1:- module(onepointfour_basics_stringy_and_charylist_type,
    2          [
    3           charylist_type/2
    4          ,stringy_type/2
    5          ,stringy_type/3
    6          ,stringy_type_with_length/2
    7          ,stringy_type_with_length/3
    8          ]).    9
   10:- use_module(library('onepointfour_basics/checks.pl')).   11
   12/*  MIT License Follows (https://opensource.org/licenses/MIT)
   13
   14    Copyright 2021 David Tonhofer <ronerycoder@gluino.name>
   15
   16    Permission is hereby granted, free of charge, to any person obtaining
   17    a copy of this software and associated documentation files
   18    (the "Software"), to deal in the Software without restriction,
   19    including without limitation the rights to use, copy, modify, merge,
   20    publish, distribute, sublicense, and/or sell copies of the Software,
   21    and to permit persons to whom the Software is furnished to do so,
   22    subject to the following conditions:
   23
   24    The above copyright notice and this permission notice shall be
   25    included in all copies or substantial portions of the Software.
   26
   27    THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND,
   28    EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF
   29    MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT.
   30    IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY
   31    CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT,
   32    TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE
   33    SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.
   34*/
   35
   36/* pldoc ==================================================================== */

Analyze "chary" or "stringy" terms

This code is specific to SWI-Prolog, as that Prolog provides the traditional "atom" and the non-traditional "string" as two distinct representations of "sequences of characters".

We introduce the following additional vocabulary:

Homepage for this code

https://github.com/dtonhofer/prolog_code/blob/main/unpacked/onepointfour_basics/README_stringy_and_charylist_type.md

History

  1. 2020-07-XX: First code elements created.
  2. 2021-06-08: Re-created from existing code lying around.
  3. 2021-06-11: Back up on github.

*/

 charylist_type(@CharyList, ?Type)
Determine the type of a charylist. It will be one of the following atoms or compound terms or else the predicate will fail (it doesn't throw, i.e. behaves "smoothly"). Note that CharyList must be proper list, partial lists are rejected.
   86charylist_type(CharyList,var) :-
   87   var(CharyList),
   88   !.
   89
   90charylist_type(CharyList,Type) :-
   91   list_traversal(CharyList,VarCount,CodeCount,CharCount,TotalCount), % fails on malformed/non-list
   92   assertion(VarCount + CodeCount + CharCount =:= TotalCount),
   93   type_decide(VarCount,CodeCount,CharCount,Type).
   94
   95type_decide(VarCount,CodeCount,CharCount,chars_vars(CharCount,VarCount)) :-
   96   VarCount > 0,
   97   CharCount > 0,
   98   assertion(CodeCount == 0),
   99   !.
  100
  101type_decide(VarCount,CodeCount,CharCount,codes_vars(CodeCount,VarCount)) :-
  102   VarCount > 0,
  103   CodeCount > 0,
  104   assertion(CharCount == 0),
  105   !.
  106
  107type_decide(VarCount,CodeCount,CharCount,vars(VarCount)) :-
  108   VarCount > 0,
  109   CodeCount == 0,
  110   CharCount == 0,
  111   !.
  112
  113type_decide(VarCount,CodeCount,CharCount,vars(VarCount)) :-
  114   VarCount > 0,
  115   CodeCount == 0,
  116   CharCount == 0,
  117   !.
  118
  119type_decide(VarCount,CodeCount,CharCount,chars(CharCount)) :-
  120   VarCount == 0,
  121   CharCount > 0,
  122   assertion(CodeCount == 0),
  123   !.
  124
  125type_decide(VarCount,CodeCount,CharCount,codes(CodeCount)) :-
  126   VarCount == 0,
  127   CodeCount > 0,
  128   assertion(CharCount == 0),
  129   !.
  130
  131type_decide(VarCount,CodeCount,CharCount,empty) :-
  132   assertion(VarCount + CodeCount + CharCount =:= 0).
  133
  134list_traversal(List,VarCount,CodeCount,CharCount,TotalCount) :-
  135   list_traversal_2(List,0,0,0,0,VarCount,CodeCount,CharCount,TotalCount).
  136
  137% we need to beware of being handed an open list, so we
  138% can't unify solely in the head
  139
  140list_traversal_2(List,VarCount,CodeCount,CharCount,TotalCount,VarCountOut,CodeCountOut,CharCountOut,TotalCountOut) :-
  141   nonvar(List),
  142   List=[X|More],
  143   var(X),
  144   !,
  145   VarCountNext is VarCount+1,
  146   TotalCountNext is TotalCount+1,
  147   list_traversal_2(More,VarCountNext,CodeCount,CharCount,TotalCountNext,
  148                         VarCountOut,CodeCountOut,CharCountOut,TotalCountOut).
  149
  150list_traversal_2(List,VarCount,CodeCount,CharCount,TotalCount,VarCountOut,CodeCountOut,CharCountOut,TotalCountOut) :-
  151   nonvar(List),
  152   List=[X|More],
  153   check_that(X,[smooth(char)]), % is a char, fail if not
  154   !,
  155   CodeCount=:=0,
  156   CharCountNext is CharCount+1,
  157   TotalCountNext is TotalCount+1,
  158   list_traversal_2(More,VarCount,CodeCount,CharCountNext,TotalCountNext,
  159                         VarCountOut,CodeCountOut,CharCountOut,TotalCountOut).
  160
  161list_traversal_2(List,VarCount,CodeCount,CharCount,TotalCount,VarCountOut,CodeCountOut,CharCountOut,TotalCountOut) :-
  162   nonvar(List),
  163   List=[X|More],
  164   check_that(X,[smooth(code)]), % is a code, fail if not
  165   !,
  166   CharCount=:=0,
  167   CodeCountNext is CodeCount+1,
  168   TotalCountNext is TotalCount+1,
  169   list_traversal_2(More,VarCount,CodeCountNext,CharCount,TotalCountNext,
  170                         VarCountOut,CodeCountOut,CharCountOut,TotalCountOut).
  171
  172list_traversal_2(List,VarCount,CodeCount,CharCount,TotalCount,VarCount,CodeCount,CharCount,TotalCount) :-
  173   nonvar(List),
  174   List=[].
 stringy_type(@Stringy, ?Type)
Determine the type of Stringy. Type can be string or atom or var, the latter indicating that Stringy is uninstantiated. This predicates behaves softly, i.e. preferentially fails on bad input.
  182stringy_type(Stringy,Type) :-
  183   stringy_type(Stringy,Type,soft).
  184
  185% !stringy_type(@Stringy,?Type,@Tuned)
  186%
  187% As stringy_type/2, but setting Tuned to =|hard|= will make the
  188% predicate throw on bad input (contrary is =|soft|=)
  189
  190stringy_type(Stringy,Type,Tuned) :-
  191   check_that(Stringy,[break(var),tuned(stringy)],Tuned),
  192   check_that(Type,[break(var),tuned(member(var,atom,string))],Tuned),
  193   stringy_type_2(Stringy,Type).
  194
  195stringy_type_2(Stringy,var)    :- var(Stringy),!.
  196stringy_type_2(Stringy,atom)   :- atom(Stringy),!.
  197stringy_type_2(Stringy,string) :- string(Stringy),!.
 stringy_type_with_length(@Stringy, Type)
Determine an atom or compound-term representation for the actual type of Stringy. It will be one of the atom var or one of the compound terms atom(L) or string(L), where L is the length of Stringy. This predicates behaves softly, i.e. preferentially fails on bad input.
  206stringy_type_with_length(Stringy,Type) :-
  207   stringy_type_with_length(Stringy,Type,soft).
 stringy_type_with_length(@Stringy, Type, Tuned)
As stringy_type_with_length/2, but setting Tuned to either true or throw will make the predicate throw on bad input.
  214stringy_type_with_length(Stringy,Type,Tuned) :-
  215   check_that(Stringy,[break(var),tuned(stringy)],Tuned),
  216   check_that(Type,[break(var),
  217                    tuned(
  218                       forany(
  219                          [unifies(var),
  220                           unifies(atom(_)),
  221                           unifies(string(_))]
  222                       ))],Tuned),
  223   stringy_type_with_length_2(Stringy,Type).
  224
  225stringy_type_with_length_2(Stringy,var)       :- var(Stringy),!.
  226stringy_type_with_length_2(Stringy,atom(L))   :- atom(Stringy),!,atom_length(Stringy,L).
  227stringy_type_with_length_2(Stringy,string(L)) :- string(Stringy),!,string_length(Stringy,L)