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
36
37
53
54wellformed_conds_or_throw(Conditions,X) :-
55 wellformed_conds(Conditions,X) 56 ->
57 true
58 ;
59 throw_2(syntax,"conditions do not pass syntax check",Conditions).
60
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
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
84
85exists_cond(break(_Check)).
86exists_cond(smooth(_Check)).
87exists_cond(soft(_Check)).
88exists_cond(tuned(_Check)).
89exists_cond(hard(_Check)).
90
92
93wellformed_cond_or_throw(Condition,X) :-
94 atom(Condition)
95 ->
96 true
97 ;
98 (Condition =.. [_,Check], wellformed_check_or_throw(Check,X)).
99
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
112
114
115wellformed_check_2(Check,_) :-
116 atom(Check),
117 !,
118 atomoform_checks(AFCs),
119 memberchk(Check,AFCs).
120
125
126wellformed_check_2(member(_) ,_). 127wellformed_check_2(member(_,_) ,_). 128wellformed_check_2(member(_,_,_) ,_). 129wellformed_check_2(member(_,_,_,_) ,_). 130wellformed_check_2(member(_,_,_,_,_) ,_). 131wellformed_check_2(member(_,_,_,_,_,_) ,_). 132wellformed_check_2(member(_,_,_,_,_,_,_),_). 133
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
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)). 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)). 174
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
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)
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
*/