1:- module(onepointfour_basics_meta_helpers,
    2          [
    3           switch/4                 % switch(If1,Then1,If2,Then2)  (throws if 'else' condition is hit)
    4          ,switch/5                 % switch(If1,Then1,If2,Then2,Else)  
    5          ,switch/6                 % switch(If1,Then1,If2,Then2,If3,Then3)  (throws if 'else' condition is hit) 
    6          ,switch/7                 % switch(If1,Then1,If2,Then2,If3,Then3,Else) 
    7          ,switch/8                 % switch(If1,Then1,If2,Then2,If3,Then3,If4,Then4)  (throws if 'else' condition is hit)
    8          ,switch/9                 % switch(If1,Then1,If2,Then2,If3,Then3,If4,Then4,Else) 
    9          ,switch/10                % switch(If1,Then1,If2,Then2,If3,Then3,If4,Then4,If5,Then5)  (throws if 'else' condition is hit)
   10          ,switch/11                % switch(If1,Then1,If2,Then2,If3,Then3,If4,Then4,If5,Then5,Else)
   11          ,switch/12                % switch(If1,Then1,If2,Then2,If3,Then3,If4,Then4,If5,Then5,If6,Then6)  (throws if 'else' condition is hit)
   12          ,switch/13                % switch(If1,Then1,If2,Then2,If3,Then3,If4,Then4,If5,Then5,If6,Then6,Else) 
   13          ,if_then_else/3           % if_then_else(Condition,Then,Else)
   14          ,reify_outcome/4          % reify_outcome(Condition,SuccessThing,FailureThing,Out) (unifies "Out" with either "SuccessThing" or "FailureThing")
   15          ,reify/2                  % reify(Goal,Outcome) (unifies "Outcome" with either 'true' or 'false') (should properly be 'true' or 'fail')
   16          ,if_then/2                % if_then(Condition,Then) (nothing happens if the 'else' condition is hit as "Condition" fails)
   17          ,unless/2                 % unless(Condition,Else)  (nothing happens if the 'then' condition is hit as "Condition" succeeds)
   18          ,maplist_onto_open_list/4 % maplist_onto_open_list(Goal,ListIn,TipOfListOut,FinOfListOut) -- TipOfListOut-FinOfListOut is a difference list of an open list
   19         ]).   20
   21% See 
   22% https://eu.swi-prolog.org/pldoc/doc_for?object=(meta_predicate)/1 
   23% for an explanation regarding these declarations
   24
   25:- meta_predicate           
   26       switch(0,0,0,0)
   27      ,switch(0,0,0,0,0)
   28      ,switch(0,0,0,0,0,0)
   29      ,switch(0,0,0,0,0,0,0)
   30      ,switch(0,0,0,0,0,0,0,0)
   31      ,switch(0,0,0,0,0,0,0,0,0)
   32      ,switch(0,0,0,0,0,0,0,0,0,0)
   33      ,switch(0,0,0,0,0,0,0,0,0,0,0)
   34      ,switch(0,0,0,0,0,0,0,0,0,0,0,0)
   35      ,switch(0,0,0,0,0,0,0,0,0,0,0,0,0)
   36      ,if_then_else(0,0,0)
   37      ,reify_outcome(0,?,?,?)
   38      ,reify(0,?)
   39      ,if_then(0,0)
   40      ,unless(0,0)
   41      ,maplist_onto_open_list(2,?,?,?). % Goal takes 2 args more than present in the term
   42
   43/*  MIT License Follows (https://opensource.org/licenses/MIT)
   44
   45    Copyright 2021 David Tonhofer <ronerycoder@gluino.name>
   46
   47    Permission is hereby granted, free of charge, to any person obtaining
   48    a copy of this software and associated documentation files
   49    (the "Software"), to deal in the Software without restriction,
   50    including without limitation the rights to use, copy, modify, merge,
   51    publish, distribute, sublicense, and/or sell copies of the Software,
   52    and to permit persons to whom the Software is furnished to do so,
   53    subject to the following conditions:
   54
   55    The above copyright notice and this permission notice shall be
   56    included in all copies or substantial portions of the Software.
   57
   58    THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND,
   59    EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF
   60    MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT.
   61    IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY
   62    CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT,
   63    TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE
   64    SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.
   65*/
   66
   67/*
   68The homepage for this module is at
   69
   70https://github.com/dtonhofer/prolog_code/blob/main/unpacked/onepointfour_basics/README_meta_helpers.md
   71*/
   72
   73% Metapredicates that are supposed to help in programming:
   74%
   75%   switch/N       (replace an unreadable sequence of "-> ;")
   76%                  (may have a default case or not)
   77%   if_then_else/3 (replaces the difficult-to-read "-> ;")
   78%   if_then/2      (ditto, no need for the "; true" at the end)
   79%   unless/2       (à la Perl)
   80% 
   81% And also statements to reify success/failure:
   82%
   83%   reify/2
   84%   reify_outcome/4
   85%
   86% For append transformed elements onto an open list:
   87%
   88%   maplist_onto_open_list/4
   89%
   90% Examples:
   91% ---------
   92%
   93% val_string(X,S) :-
   94%    switch(
   95%       between(0,10,X),
   96%       S="between 0 and 10",
   97%       between(11,20,X),
   98%       S="between 11 and 20",
   99%       between(21,30,X),
  100%       S="between 21 and 30",
  101%       between(31,40,X),
  102%       S="between 31 and 40",
  103%       S="above 40").
  104%      
  105% ?- val_string(4,S).
  106% S = "between 0 and 10".
  107%
  108% ?- reify_outcome((random(X),X>0.5),["That went well",X],["That didn't work",X],Out).
  109% X = 0.7658474306692046,
  110% Out = ["That went well",0.7658474306692046].
  111%
  112% ?- reify_outcome((random(X),X>0.5),["That went well",X],["That didn't work",X],Out).
  113% Out = ["That didn't work",X].
  114%
  115% Note that using this instead of directly-inlined "->" may slows down a
  116% program markedly. 30% slowdown if there are lots of these calls is not 
  117% impossible. 
  118%
  119% 2021-01-19: Review
  120% 2021-02-02: Added maplist_onto_open_list/4; comment review
  121
  122% ===
  123% A better "switch" than an unreadable sequence of ->/2 and ;/2
  124% ===
  125
  126% switch/4
  127
  128switch(If1,Then1,If2,Then2) :-
  129   call(If1)
  130   ->  call(Then1)
  131   ;   call(If2)
  132   ->  call(Then2)
  133   ;   unhandled_else_error.
  134
  135% switch/5
  136
  137switch(If1,Then1,If2,Then2,Else) :-
  138   call(If1)
  139   ->  call(Then1)
  140   ;   call(If2)
  141   ->  call(Then2)
  142   ;   call(Else).
  143
  144% switch/6
  145
  146switch(If1,Then1,If2,Then2,If3,Then3) :-
  147   call(If1)
  148   ->  call(Then1)
  149   ;   call(If2)
  150   ->  call(Then2)
  151   ;   call(If3)
  152   ->  call(Then3)
  153   ;   unhandled_else_error.
  154
  155% switch/7
  156
  157switch(If1,Then1,If2,Then2,If3,Then3,Else) :-
  158   call(If1)
  159   ->  call(Then1)
  160   ;   call(If2)
  161   ->  call(Then2)
  162   ;   call(If3)
  163   ->  call(Then3)
  164   ;   call(Else).
  165
  166% switch/8
  167
  168switch(If1,Then1,If2,Then2,If3,Then3,If4,Then4) :-
  169   call(If1)
  170   ->  call(Then1)
  171   ;   call(If2)
  172   ->  call(Then2)
  173   ;   call(If3)
  174   ->  call(Then3)
  175   ;   call(If4)
  176   ->  call(Then4)
  177   ;   unhandled_else_error.
  178
  179% switch/9
  180
  181switch(If1,Then1,If2,Then2,If3,Then3,If4,Then4,Else) :-
  182   call(If1)
  183   ->  call(Then1)
  184   ;   call(If2)
  185   ->  call(Then2)
  186   ;   call(If3)
  187   ->  call(Then3)
  188   ;   call(If4)
  189   ->  call(Then4)
  190   ;   call(Else).
  191
  192% switch/10
  193
  194switch(If1,Then1,If2,Then2,If3,Then3,If4,Then4,If5,Then5) :-
  195   call(If1)
  196   ->  call(Then1)
  197   ;   call(If2)
  198   ->  call(Then2)
  199   ;   call(If3)
  200   ->  call(Then3)
  201   ;   call(If4)
  202   ->  call(Then4)
  203   ;   call(If5)
  204   ->  call(Then5)
  205   ;   unhandled_else_error.
  206
  207% switch/11
  208
  209switch(If1,Then1,If2,Then2,If3,Then3,If4,Then4,If5,Then5,Else) :-
  210   call(If1)
  211   ->  call(Then1)
  212   ;   call(If2)
  213   ->  call(Then2)
  214   ;   call(If3)
  215   ->  call(Then3)
  216   ;   call(If4)
  217   ->  call(Then4)
  218   ;   call(If5)
  219   ->  call(Then5)
  220   ;   call(Else).
  221
  222% switch/12
  223
  224switch(If1,Then1,If2,Then2,If3,Then3,If4,Then4,If5,Then5,If6,Then6) :-
  225   call(If1)
  226   ->  call(Then1)
  227   ;   call(If2)
  228   ->  call(Then2)
  229   ;   call(If3)
  230   ->  call(Then3)
  231   ;   call(If4)
  232   ->  call(Then4)
  233   ;   call(If5)
  234   ->  call(Then5)
  235   ;   call(If6)
  236   ->  call(Then6)
  237   ;   unhandled_else_error.
  238
  239% switch/13
  240
  241switch(If1,Then1,If2,Then2,If3,Then3,If4,Then4,If5,Then5,If6,Then6,Else) :-
  242   call(If1)
  243   ->  call(Then1)
  244   ;   call(If2)
  245   ->  call(Then2)
  246   ;   call(If3)
  247   ->  call(Then3)
  248   ;   call(If4)
  249   ->  call(Then4)
  250   ;   call(If5)
  251   ->  call(Then5)
  252   ;   call(If6)
  253   ->  call(Then6)
  254   ;   call(Else).
  255
  256% ===
  257% An implementation of ->/2. Pass three goals.
  258% ===
  259
  260if_then_else(Condition,Then,Else) :- 
  261   call(Condition) -> call(Then) ; call(Else).
  262
  263% ===
  264% Reification of an outcome. Pass a "Goal" and the "SuccessThing" to be unified with "Out"
  265% if the "Goal" succeeds and the "FailureThing" to be unified with "Out" if the Goal fails
  266% ===
  267
  268reify_outcome(Condition,SuccessThing,FailureThing,Out) :-
  269   call(Condition)
  270   -> (Out = SuccessThing) 
  271   ;  (Out = FailureThing).
  272
  273% ==
  274% Simpler reification to just the truth values 'true' or 'false'
  275% ===
  276
  277reify(Goal,Outcome) :-
  278   call(Goal)
  279   -> (Outcome = true)
  280   ;  (Outcome = false).
  281
  282% ===
  283% An implementation of ->/2 with an "else" that does nothing. Pass two goals.
  284% ===
  285
  286if_then(Condition,Then) :- 
  287   call(Condition) 
  288   -> call(Then) 
  289   ;  true.
  290
  291% ===
  292% An implementation of ->/2 with an "then" that does nothing. Pass two goals.
  293% ===
  294
  295unless(Condition,Else) :- 
  296   call(Condition)
  297   -> true
  298   ;  call(Else).
  299
  300% ===
  301% Throw a non-"ISO standard" exception which is used when a switch
  302% hits an "else" and there is no Goal that can be called for that
  303% eventuality. This is not an ISO standard exception because the "formal" 
  304% term 'programming_error' is not in the list of allowed terms.
  305% ---
  306
  307unhandled_else_error :-
  308   throw(
  309      error(programming_error,
  310            context(_,"hit the unhandled 'else' case of a 'switch'"))).
  311
  312% ===
  313% An amazingly simple and useful helper that seems to be missing in Prolog.
  314% It is like maplist/3, but appends to an open list and unifies the "FinalFin"
  315% argument with the final fin of this open list.
  316% ===
  317
  318maplist_onto_open_list(_,[],FinalFin,FinalFin) :- !.
  319
  320maplist_onto_open_list(Goal,[In|MoreIn],[Out|Fin],FinalFin) :-
  321   call(Goal,In,Out),
  322   maplist_onto_open_list(Goal,MoreIn,Fin,FinalFin)