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

Generate and accept strings consisting only of char 0x20, "SPACE"

This is specific to SWI-Prolog, which distinguishes "string" and "atom" as two distinct representations of "sequences of characters".

Homepage for this code

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

History

  1. 2020-07-XX: First version.
  2. 2021-05-27: Full review.
  3. 2021-06-10: Further review.
  4. 2021-06-11: Back up on github.
  5. 2021-06-17: Rewritten to take "StringyType" arg and generally be clearer code

*/

 space_stringy(?N, ?Stringy, +StringyType)
Succeeds iff Stringy is a string of N SPACE characters having type StringyType (either 'atom' or 'string').

If both arguments N and Stringy are unbound, generates pairs (N,Stringy) with N monotonically increasing.

   66space_stringy(N,Stringy,StringyType) :-
   67   space_stringy(N,Stringy,StringyType,soft).
 space_stringy_smooth(?N, ?Stringy, ?StringyType)
As space_stringy/3 that only fails, never throws even if it is given out-of-type or out-of-domain arguments.
   74space_stringy_smooth(N,Stringy,StringyType) :-
   75   check_that(Stringy,[break(var),soft(stringy)]),
   76   check_that(N,[break(var),soft(int),soft(pos0int)]),
   77   check_that(StringyType,[break(var),soft(stringy_typeid)]),
   78   space_stringy_2(N,Stringy,StringyType).
 space_stringy_lax(?N, ?Stringy, ?StringyType)
A space_stringy/3 that accepts negative N, and just unifies Stringy with an empty "" or '' in that case.
   85space_stringy_lax(N,Stringy,StringyType) :-
   86   check_that(Stringy,[break(var),hard(stringy)]),
   87   check_that(N,[break(var),hard(int)]),
   88   check_that(StringyType,[break(var),hard(stringy_typeid)]),
   89   ((nonvar(N))
   90    ->
   91    (M is max(N,0))
   92    ;
   93    M=N),
   94   space_stringy_2(M,Stringy,StringyType).
 space_stringy(?N, ?Stringy, ?StringyType, @Throw)
As space_stringy/3 but one can request that:
  102space_stringy(N,Stringy,StringyType,Tuned) :-
  103   check_that(Stringy,[break(var),hard(stringy)]),
  104   check_that(N,[break(var),hard(int),tuned(pos0int)],Tuned),
  105   check_that(StringyType,[break(var),hard(stringy_typeid)]),
  106   space_stringy_2(N,Stringy,StringyType).
  107
  108% --- what lies beneath ---
  109
  110space_stringy_2(N,Stringy,StringyType) :-
  111   var_tag(N,TaggedN),
  112   var_tag(Stringy,TaggedStringy),
  113   var_tag(StringyType,TaggedStringyType),
  114   instantiate_stringy_type(TaggedStringy,TaggedStringyType), % fails if Stringy and StringyType are incompatible
  115   space_stringy_3(TaggedN,TaggedStringy,StringyType). % StringyType may or may not have been further instantiate by previous call
  116
  117% this code is also used in stringy_concat.pl
  118
  119instantiate_stringy_type(var(_Stringy),nonvar(_StringyType)) :- !.                   % Do nothing, decision on type to generate has been provided
  120instantiate_stringy_type(var(_Stringy),var(_StringyType))    :- !.                   % Do nothing, leaving indeterminism on StringyType
  121instantiate_stringy_type(nonvar(Stringy),var(atom))          :- atom(Stringy),!.     % Instantiate type inside var/1 tag to 'atom'
  122instantiate_stringy_type(nonvar(Stringy),var(string))        :- string(Stringy),!.   % Instantiate type inside var/1 tag to 'string'
  123instantiate_stringy_type(nonvar(Stringy),nonvar(atom))       :- atom(Stringy),!.     % Accept only if type is 'atom'
  124instantiate_stringy_type(nonvar(Stringy),nonvar(string))     :- string(Stringy).     % Accept only if type is 'string'
  125
  126var_tag(X,var(X))    :- var(X),!.
  127var_tag(X,nonvar(X)).
  128
  129space_stringy_3(var(N),nonvar(Stringy),_) :-
  130   !,
  131   atom_string(Stringy,StringyAsStr),                         % makes sure we have a *string representation*
  132   string_length(StringyAsStr,N),
  133   gen_string_of_spaces(N,StringyAsStr).                      % given N, regenerate N-space string for unification
  134
  135space_stringy_3(nonvar(N),nonvar(Stringy),_) :-
  136   !,
  137   atom_string(Stringy,StringyAsStr),                         % makes sure we have a *string representation*
  138   gen_string_of_spaces(N,StringyAsStr).                      % given N, regenerate N-space string for unification with Stringy2
  139
  140space_stringy_3(nonvar(N),var(Stringy),StringyType) :-        % argument 3, StringyType, may or may not have been instantiated on call
  141   !,
  142   (var(StringyType)                                          % SWI-Prolog 8.3. cannot determine that space_string_4/3 has just one answer with first arg bound
  143    ->                                                        % so we introduce determinism manually (this is annoying)
  144     space_stringy_4(StringyType,nonvar(N),var(Stringy))      % call another predicate for easyness-to-read; that predicate is nondeterministic on StringType.
  145    ;
  146     (space_stringy_4(StringyType,nonvar(N),var(Stringy)),!)).
  147
  148space_stringy_3(var(N),var(Stringy),StringyType) :-           % argument 3, StringyType, may or may not have been instantiated on call
  149   between(0,inf,N),                                          % infinite backtracking on top of
  150   space_stringy_4(StringyType,nonvar(N),var(Stringy)).       % two possible types if (StringyType is still unbound at this point)
  151
  152
  153space_stringy_4(atom,nonvar(N),var(Stringy)) :-
  154   gen_string_of_spaces(N,StringyAsStr),                      % this may fail for bad N but does not throw
  155   atom_string(Stringy,StringyAsStr).                         % we want an atom, so convert
  156
  157space_stringy_4(string,nonvar(N),var(Stringy)) :-
  158   gen_string_of_spaces(N,Stringy).                           % this may fail for bad N but does not throw
  159
  160% Generate (possibly long) strings quickly by recursively applying
  161% string_concat/3 on two strings of half the desired length.
  162% Add specific cases besides length 0 and 1 for fast generation for
  163% short strings.
  164
  165gen_string_of_spaces( 0 ,"")           :- !.
  166gen_string_of_spaces( 1 ," ")          :- !.
  167gen_string_of_spaces( 2 ,"  ")         :- !.
  168gen_string_of_spaces( 3 ,"   ")        :- !.
  169gen_string_of_spaces( 4 ,"    ")       :- !.
  170gen_string_of_spaces( 5 ,"     ")      :- !.
  171gen_string_of_spaces( 6 ,"      ")     :- !.
  172gen_string_of_spaces( 7 ,"       ")    :- !.
  173gen_string_of_spaces( 8 ,"        ")   :- !.
  174gen_string_of_spaces( 9 ,"         ")  :- !.
  175gen_string_of_spaces(10 ,"          ") :- !.
  176gen_string_of_spaces(N  ,String) :-
  177   N >= 0,                                     % fail if N < 0
  178   integer(N),                                 % divmod throws on non-integer; preclude that
  179   divmod(N,2,Times,Remainder),
  180   gen_string_of_spaces(Times,S1),
  181   string_concat(S1,S1,S2),                    % S2 := 2*S1
  182   (
  183      Remainder>0
  184      ->
  185      gen_string_of_spaces(Remainder,SR),
  186      string_concat(S2,SR,String)
  187      ;
  188      String = S2
  189   )