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

A replacement for must/2

check_that/3 and friends: a replacement for the must_be/2 predicate of Prolog. must_be/2 is used to check preconditions on predicate entry, but is not very flexible. Can we improve on that?

The homepage for this module is at

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

*/

   52% called from the main predicates to verify a list of conditions.
   53
   54wellformed_conds_or_throw(Conditions,X) :-
   55   wellformed_conds(Conditions,X) % may also throw
   56   ->
   57   true
   58   ;
   59   throw_2(syntax,"conditions do not pass syntax check",Conditions).
   60
   61% wellformed_conds(Conditions,X)
   62%
   63% Verify the conds of Conditions for syntactic correctness. This is done
   64% outside of actual check-evaluation eval/4, to have clean code and to be able to
   65% disable the verification for well-formedness by (currently) commenting out
   66% the call to wellformed/2.
   67
   68wellformed_conds([Condition|More],X) :-
   69   exists_cond_or_throw(Condition),
   70   wellformed_cond_or_throw(Condition,X),
   71   wellformed_conds(More,X).
   72wellformed_conds([],_).
   73
   74% ---
   75
   76exists_cond_or_throw(Condition) :-
   77   exists_cond(Condition)
   78   ->
   79   true
   80   ;
   81   throw_2(unknown_condition,"unknown condition found during syntax check",Condition).
   82
   83% Verify the form of a single condition.
   84
   85exists_cond(break(_Check)).
   86exists_cond(smooth(_Check)).
   87exists_cond(soft(_Check)).
   88exists_cond(tuned(_Check)).
   89exists_cond(hard(_Check)).
   90
   91% ---
   92
   93wellformed_cond_or_throw(Condition,X) :-
   94   atom(Condition)
   95   ->
   96   true
   97   ;
   98   (Condition =.. [_,Check], wellformed_check_or_throw(Check,X)).
   99
  100% ---
  101
  102wellformed_check_or_throw(Check,X) :-
  103   wellformed_check_2(Check,X)
  104   ->
  105   true
  106   ;
  107   throw_2(unknown_or_problematic_check,"unknown or problematic check found during syntax check",Check).
  108
  109% ---
  110% Check whether a single 'check' (which has been removed from its 'condition') is well-formed
  111% ---
  112
  113% If the 'check' is an atom, we just need to see whether it's one of the allowed atoms
  114
  115wellformed_check_2(Check,_) :- 
  116   atom(Check),
  117   !,
  118   atomoform_checks(AFCs),
  119   memberchk(Check,AFCs).
  120
  121% If it's a compound term with functor 'member', then we allow either a single (possibly 
  122% empty) list as argument to member/1 or >= 1 arguments that are packed into a list.
  123% The latter makes it unnecessary to add brackets, which increases legibility. But 
  124% we can't check anything about the arguments of member.
  125
  126wellformed_check_2(member(_)            ,_).  % argument  can be anything, maybe even a list
  127wellformed_check_2(member(_,_)          ,_).  % arguments can be anything
  128wellformed_check_2(member(_,_,_)        ,_).  % arguments can be anything
  129wellformed_check_2(member(_,_,_,_)      ,_).  % arguments can be anything
  130wellformed_check_2(member(_,_,_,_,_)    ,_).  % arguments can be anything
  131wellformed_check_2(member(_,_,_,_,_,_)  ,_).  % arguments can be anything
  132wellformed_check_2(member(_,_,_,_,_,_,_),_).  % arguments can be anything
  133
  134% Various other compound term.
  135% Sometimes we just verify the form. For example, for dict_has_key/2 we leave the testing
  136% of Key and Dict type to the actual check call.
  137
  138wellformed_check_2(dict_has_key(_),_).
  139wellformed_check_2(type(ListOfTypes),_) :- 
  140   is_proper_list(ListOfTypes),
  141   atomoform_checks(AFCs),
  142   maplist({AFCs}/[T]>>memberchk(T,AFCs),ListOfTypes).
  143wellformed_check_2(random(Probability),_) :-
  144   number(Probability),
  145   0=<Probability,
  146   Probability=<1.
  147wellformed_check_2(unifies(_),_).
  148wellformed_check_2(forall(ListOfChecks),X) :-
  149   wellformed_list_of_checks(ListOfChecks,X).
  150wellformed_check_2(forany(ListOfChecks),X) :-
  151   wellformed_list_of_checks(ListOfChecks,X).
  152wellformed_check_2(fornone(ListOfChecks),X) :-
  153   wellformed_list_of_checks(ListOfChecks,X).
  154wellformed_check_2(passall(Check),ListOfX) :-
  155   wellformed_check_over_list(Check,ListOfX).
  156wellformed_check_2(passany(Check),ListOfX) :-
  157   wellformed_check_over_list(Check,ListOfX).
  158wellformed_check_2(passnone(Check),ListOfX) :-
  159   wellformed_check_over_list(Check,ListOfX).
  160
  161% Specialized verification
  162
  163wellformed_list_of_checks(ListOfChecks,X) :-
  164   is_proper_list(ListOfChecks),
  165   forall(
  166      member(Check,ListOfChecks),
  167      wellformed_check_or_throw(Check,X)). % ** recursive **
  168
  169wellformed_check_over_list(Check,ListOfX) :-
  170   is_proper_list_or_throw(Check,ListOfX),
  171   forall(
  172      member(M,ListOfX),
  173      wellformed_check_or_throw(Check,M)). % ** recursive **
  174
  175% The list of atoms for "elementary checks", i.e. those that are not a compound term, are listed here.
  176
  177atomoform_checks(
  178   [
  179   var,nonvar,
  180   nonground,ground,
  181   atom,symbol,
  182   atomic,constant,
  183   compound,
  184   boolean,
  185   pair,
  186   string,stringy,
  187   char,code,chary,
  188   char_list,chars,
  189   code_list,codes,
  190   chary_list,charys,
  191   nonempty_stringy,
  192   stringy_typeid,
  193   chary_typeid,
  194   number,float,integer,int,rational,nonint_rational,proper_rational,
  195   negnum,negnumber,
  196   posnum,posnumber,
  197   neg0num,neg0number,
  198   pos0num,pos0number,
  199   non0num,non0number,
  200   float_not_nan,
  201   float_not_inf,
  202   float_not_neginf,
  203   float_not_posinf,
  204   negint,negative_integer,
  205   posint,positive_integer,
  206   neg0int,pos0int,nonneg,
  207   negfloat,posfloat,
  208   neg0float,pos0float,
  209   inty,
  210   neginty,posinty,
  211   neg0inty,pos0inty,
  212   list,proper_list,
  213   nonempty_list,
  214   dict,
  215   cyclic,cyclic_now,acyclic_now,acyclic_forever,
  216   stream
  217   ]
  218).
  219
  220% Helpers
  221
  222is_proper_list_or_throw(Check,ListOfX) :-
  223   is_proper_list(ListOfX)
  224   ->
  225   true
  226   ;
  227   throw_2(type,"check needs a list as argument",[check(Check),arg(ListOfX)]).
  228
  229
  230is_proper_list(L) :- is_list(L)