1:- module(onepointfour_basics_stringy_morph,
    2          [
    3           stringy_morph/4            % stringy_morph(StringyA,StringyB,TypeA,TypeB)
    4          ,stringy_morph/5            % stringy_morph(StringyA,StringyB,TypeA,TypeB,Tuned)
    5          ,stringy_charylist_morph/4  % stringy_charylist_morph(Stringy,Charylist,StringyType,CharylistType)
    6          ,stringy_charylist_morph/5  % stringy_charylist_morph(Stringy,Charylist,StringyType,CharylistType,Tuned)
    7          ]).    8
    9:- use_module(library('onepointfour_basics/checks.pl')).   10:- use_module(library('onepointfour_basics/stringy_and_charylist_type.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 ==================================================================== */

A replacement for atom_string/2

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_morph.md

History

 stringy_morph(?StringyA, ?StringyB, ?TypeA, ?TypeB)
Behaves leniently, i.e. preferably fails instead of throwing if bad values are passed.
   77stringy_morph(StringyA,StringyB,TypeA,TypeB) :-
   78   stringy_morph(StringyA,StringyB,TypeA,TypeB,soft).
 stringy_morph(?StringyA, ?StringyB, ?TypeA, ?TypeB, @Tuned)
Establish the "morph" relationship between StringyA (an atom or a string) and StringyB (an atom or a string) whereby
   98stringy_morph(StringyA,StringyB,TypeA,TypeB,Tuned) :-
   99   check_that([StringyA,StringyB],[hard(passany(nonvar))]),
  100   check_that(StringyA,           [break(var),tuned(stringy)],Tuned),
  101   check_that(StringyB,           [break(var),tuned(stringy)],Tuned),
  102   check_that(TypeA,              [break(var),tuned(stringy_typeid)],Tuned),
  103   check_that(TypeB,              [break(var),tuned(stringy_typeid)],Tuned),
  104   stringy_type(StringyA,AsGivenTypeA),
  105   stringy_type(StringyB,AsGivenTypeB),
  106   stringy_morph_2_with_increased_determinism(AsGivenTypeA,AsGivenTypeB,StringyA,StringyB,TypeA,TypeB).
  107
  108% stringy_morph_2(AsGivenTypeA,AsGivenTypeB,StringyA,StringyB,TypeA,TypeB).
  109%
  110% The case AsGivenTypeA=var,AsGiventypeB=var is precluded by a check in
  111% stringy_morph/5
  112%
  113% Note that even if the types correspond, we must still check whether
  114% the text representations correspond.
  115
  116stringy_morph_2_with_increased_determinism(AsGivenTypeA,AsGivenTypeB,StringyA,StringyB,TypeA,TypeB) :-
  117   (
  118      (AsGivenTypeA==var,nonvar(TypeA));
  119      (AsGivenTypeB==var,nonvar(TypeB))
  120   ),
  121   !,
  122   stringy_morph_2(AsGivenTypeA,AsGivenTypeB,StringyA,StringyB,TypeA,TypeB), % we know there is only 1 solution
  123   !.
  124stringy_morph_2_with_increased_determinism(AsGivenTypeA,AsGivenTypeB,StringyA,StringyB,TypeA,TypeB) :-
  125   stringy_morph_2(AsGivenTypeA,AsGivenTypeB,StringyA,StringyB,TypeA,TypeB).
  126
  127% stringy_morph_2(AsGivenTypeA,AsGivenTypeB,StringyA,StringyB,TypeA,TypeB).
  128% ------------  | nonvar on call |           | can be var on call |
  129
  130stringy_morph_2( string, string   ,  A , B ,    string, string ) :- A=B.
  131stringy_morph_2( string, atom     ,  A , B ,    string, atom   ) :- atom_string(B,A).
  132stringy_morph_2( string, var      ,  A , B ,    string, string ) :- A=B.
  133stringy_morph_2( string, var      ,  A , B ,    string, atom   ) :- atom_string(B,A).
  134
  135stringy_morph_2( atom,   string   ,  A , B ,    atom  , string ) :- atom_string(A,B).
  136stringy_morph_2( atom,   atom     ,  A , B ,    atom  , atom   ) :- A=B.
  137stringy_morph_2( atom,   var      ,  A , B ,    atom  , string ) :- atom_string(A,B).
  138stringy_morph_2( atom,   var      ,  A , B ,    atom  , atom   ) :- A=B.
  139
  140stringy_morph_2( var,    atom     ,  A , B ,    string, atom   ) :- atom_string(B,A).
  141stringy_morph_2( var,    atom     ,  A , B ,    atom  , atom   ) :- A=B.
  142stringy_morph_2( var,    string   ,  A , B ,    string, string ) :- A=B.
  143stringy_morph_2( var,    string   ,  A , B ,    atom  , string ) :- atom_string(A,B).
 stringy_charylist_morph(Stringy, Charylist, StatedStringyType, StatedCharylistType)
  147stringy_charylist_morph(Stringy,Charylist,StatedStringyType,StatedCharylistType) :-
  148   stringy_charylist_morph(Stringy,Charylist,StatedStringyType,StatedCharylistType,soft).
 stringy_charylist_morph(Stringy, Charylist, WantStringy, WantCharylist)
Map a stringy to a charylist.
  154stringy_charylist_morph(Stringy,Charylist,StatedStringyType,StatedCharylistType,Tuned) :-
  155   check_that(Stringy,             [break(var),tuned(stringy)],Tuned),
  156   check_that(StatedStringyType,   [break(var),tuned(stringy_typeid)],Tuned),
  157   check_that(StatedCharylistType, [break(var),tuned(member(char,code,chars,codes))],Tuned),
  158   fix(StatedCharylistType,StatedCharylistType2),
  159   % Won't fail because Stringy is well-typed after check_that/2
  160   stringy_type_with_length(Stringy,ActualStringyType),
  161   % May fail as Charylist may be ill-typed
  162   (charylist_type(Charylist,ActualCharylistType)
  163    ->
  164    true
  165    ;
  166    check_that(Charylist,[fail("Charylist has unrecognized type")],Tuned)),
  167   (\+underspecified(ActualStringyType,ActualCharylistType)
  168    ->
  169    true
  170    ;
  171    check_that([Stringy,Charylist],[fail("Stringy-Charylist combination underspecifies")],Tuned)),
  172   (compatible_cross_combinations(ActualStringyType,ActualCharylistType)
  173    ->
  174    true
  175    ;
  176    check_that([ActualStringyType,ActualCharylistType],[fail("Stringy-Charylist type combination incompatible")],Tuned)),
  177   % below here it's gettign interesting; the cur is really not needed
  178   % fails on bad combination or may generate other solutions on redo
  179   enumerate_compatible_stringy_type_with_increased_determinism(ActualStringyType,StatedStringyType),
  180   % fails on bad combination or may generate other solutions on redo
  181   enumerate_compatible_charylist_type_with_increased_determinism(ActualCharylistType,StatedCharylistType2),
  182   % we make the exercise of explicitly calling the correct builtin depending on case
  183   ((ActualStringyType==var)
  184      ->
  185      % morph nonvar "Charylist" to a stringy according to "StringyType" and unify
  186      % with "Stringy", possibly yielding two solutions (atoms,strings)
  187      morph_from_charylist_with_increased_determinism(StatedCharylistType2,StatedStringyType,Charylist,Stringy)
  188      ;
  189      % morph nonvar "Stringy" to a charylist according to "StatedCharylistType2" and
  190      % unify with "Charylist", possibly yielding two solutions (codes,chars)
  191      morph_from_stringy_with_increased_determinism(StatedStringyType,StatedCharylistType2,Stringy,Charylist)).
  192
  193
  194% fix(StatedCharylistType,Fixed)
  195% The caller may have passed any of char,chars,code,codes; unify!
  196
  197fix(X,X)          :- var(X),!.
  198fix(chars,chars)  :- !.
  199fix(char,chars)   :- !.
  200fix(codes,codes)  :- !.
  201fix(code,codes).
  202
  203% enumerate_compatible_stringy_type(ActualStringyType,StatedStringyType)
  204%
  205% This is an implementation of this table, where incompatible
  206% combinations have been left out and thus fail
  207%
  208% ActualStringyType  StatedStringyType (may be var)
  209% ------------------------------
  210% 'var'              Var,'atom','string'   StringyType can be bound to 'atom' or 'string'
  211% 'atom(L)'          Var,'atom'            StringyType must be bound to 'atom'
  212% 'string(L)'        Var,'string'          StringyType must be bound to 'string'
  213%
  214
  215enumerate_compatible_stringy_type_with_increased_determinism(A,B) :-
  216   assertion(nonvar(A)),
  217   nonvar(B),
  218   !,
  219   enumerate_compatible_stringy_type(A,B),
  220   !.
  221enumerate_compatible_stringy_type_with_increased_determinism(A,B) :-
  222   enumerate_compatible_stringy_type(A,B).
  223
  224enumerate_compatible_stringy_type(string(_),string).
  225enumerate_compatible_stringy_type(atom(_),atom).
  226enumerate_compatible_stringy_type(var,atom).
  227enumerate_compatible_stringy_type(var,string).
  228
  229% enumerate_compatible_charylist_type(ActualCharylistType,StatedCharylistType)
  230
  231enumerate_compatible_charylist_type_with_increased_determinism(A,B) :-
  232   assertion(nonvar(A)),
  233   nonvar(B),
  234   !,
  235   enumerate_compatible_charylist_type(A,B),
  236   !.
  237enumerate_compatible_charylist_type_with_increased_determinism(A,B) :-
  238   enumerate_compatible_charylist_type(A,B).
  239
  240enumerate_compatible_charylist_type(chars(_),chars).
  241enumerate_compatible_charylist_type(codes(_),codes).
  242enumerate_compatible_charylist_type(chars_vars(_,_),chars).
  243enumerate_compatible_charylist_type(codes_vars(_,_),codes).
  244enumerate_compatible_charylist_type(empty,chars).
  245enumerate_compatible_charylist_type(empty,codes).
  246enumerate_compatible_charylist_type(vars(_),chars).
  247enumerate_compatible_charylist_type(vars(_),codes).
  248enumerate_compatible_charylist_type(var,chars).
  249enumerate_compatible_charylist_type(var,codes).
  250
  251% underspecified(ActualStringyType,ActualCharysType)
  252%
  253% List the type combinations which leave too much leeway for a meaningful answer.
  254
  255underspecified(var,var).
  256underspecified(var,vars(_)).
  257underspecified(var,chars_vars(_,_)).
  258underspecified(var,codes_vars(_,_)).
  259
  260% compatible_cross_combinations(ActualStringyType,ActualCharysType)
  261%
  262% List the type combinations for which Stringy<->Charys morph makes sense.
  263
  264compatible_cross_combinations(string(L),chars(L)).
  265compatible_cross_combinations(string(L),codes(L)).
  266compatible_cross_combinations(atom(L),chars(L)).
  267compatible_cross_combinations(atom(L),codes(L)).
  268compatible_cross_combinations(string(L),chars_vars(C,V)) :- L =:= C+V.
  269compatible_cross_combinations(string(L),codes_vars(C,V)) :- L =:= C+V.
  270compatible_cross_combinations(atom(L),chars_vars(C,V)) :- L =:= C+V.
  271compatible_cross_combinations(atom(L),codes_vars(C,V)) :- L =:= C+V.
  272compatible_cross_combinations(string(0),empty).
  273compatible_cross_combinations(atom(0),empty).
  274compatible_cross_combinations(string(L),vars(L)).
  275compatible_cross_combinations(atom(L),vars(L)).
  276compatible_cross_combinations(string(_),var).
  277compatible_cross_combinations(atom(_),var).
  278
  279compatible_cross_combinations(var,chars(_)).
  280compatible_cross_combinations(var,codes(_)).
  281compatible_cross_combinations(var,empty).
  282
  283% morph_from_stringy(StringyType,CharylistType,StringyIn,CharylistOut)
  284% More complex than need to get determinism on the first two arguments
  285
  286morph_from_stringy_with_increased_determinism(A,B,C,D) :-
  287   assertion(nonvar(A)),
  288   nonvar(B),
  289   !,
  290   morph_from_stringy(A,B,C,D),
  291   !.
  292morph_from_stringy_with_increased_determinism(A,B,C,D) :-
  293   morph_from_stringy(A,B,C,D).
  294
  295morph_from_stringy(string , chars , StringyIn , CharylistOut) :- string_chars(StringyIn,CharylistOut).
  296morph_from_stringy(string , codes , StringyIn , CharylistOut) :- string_codes(StringyIn,CharylistOut).
  297morph_from_stringy(atom   , chars , StringyIn , CharylistOut) :- atom_chars(StringyIn,CharylistOut).
  298morph_from_stringy(atom   , codes , StringyIn , CharylistOut) :- atom_codes(StringyIn,CharylistOut).
  299
  300% morph_from_charylist(CharylistType,StringyType,CharylistIn,StringyOut)
  301
  302morph_from_charylist_with_increased_determinism(A,B,C,D) :-
  303   assertion(nonvar(A)),
  304   nonvar(B),
  305   !,
  306   morph_from_charylist(A,B,C,D),
  307   !.
  308morph_from_charylist_with_increased_determinism(A,B,C,D) :-
  309   morph_from_charylist(A,B,C,D).
  310
  311morph_from_charylist(chars , string , CharylistIn, StringyOut) :- string_chars(StringyOut,CharylistIn).
  312morph_from_charylist(chars , atom   , CharylistIn, StringyOut) :- atom_chars(StringyOut,CharylistIn).
  313morph_from_charylist(codes , string , CharylistIn, StringyOut) :- string_codes(StringyOut,CharylistIn).
  314morph_from_charylist(codes , atom   , CharylistIn, StringyOut) :- atom_codes(StringyOut,CharylistIn).
  315morph_from_charylist(empty , string , [], "").
  316morph_from_charylist(empty , atom   , [], '')