YAP 7.1.0
error.yap
Go to the documentation of this file.
1/**
2 @file pl/error.yap
4 @author Jan Wielemaker
5 @author Richard O'Keefe
6 @author adapted to YAP by Vitor Santos Costa
7*/
8
9/*
10:- module(system(error,
11 [ must_be_of_type/2, % +Type, +Term
12 must_be_of_type/3, % +Type, +Term, +Comment
13 must_be/2, % +Type, +Term
14 must_be/3, % +Type, +Term, +Comment
15 type_error/2, % +Type, +Term
16% must_be_in_domain/2, % +Domain, +Term
17% must_be_in_domain/3, % +Domain, +Term, +Comment
18 domain_error/3, % +Domain, +Values, +Term
19 existence_error/2, % +Type, +Term
20 permission_error/3, % +Action, +Type, +Term
21 must_be_instantiated/1, % +Term
22 must_bind_to_type/2, % +Type, ?Term
23 instantiation_error/1, % +Term
24 representation_error/1, % +Reason
25 is_of_type/2 % +Type, +Term
26 ]), []) .
27 */
28
29/**
30 @defgroup ErrorBuiltins Error generating type-checking
31@ingroup Builtins
32
33This code is based oon the SWI predicates to simplify error generation and
34checking. Adapted to use YAP built-ins.
35
36Its implementation is based on a discussion on the SWI-Prolog
37mailinglist on best practices in error handling. The utility predicate
38must_be/2 provides simple run-time type validation. The *_error
39predicates are simple wrappers around throw/1 to simplify throwing the
40most common ISO error terms.
41
42YAP reuses the code with some extensions, and supports interfacing to some C-builtins.
43
44@{
45
46*/
47
48:- multifile
49 has_type/2.
50
51%% @pred type_error(+Type, +Term).
52%% @pred domain_error(+Type, +Value, +Term).
53%% @pred existence_error(+Type, +Term).
54%% @pred permission_error(+Action, +Type, +Term).
55%% @pred instantiation_error(+Term).
56%% @pred representation_error(+Reason).
57%
58% Throw ISO compliant error messages.
59
60type_error(Type, Term) :-
61 throw(error(type_error(Type, Term), _)).
62domain_error(Type, Term) :-
63 throw(error(domain_error(Type, Term), _)).
64existence_error(Type, Term) :-
65 throw(error(existence_error(Type, Term), _)).
66permission_error(Action, Type, Term) :-
67 throw(error(permission_error(Action, Type, Term), _)).
68instantiation_error(_Term) :-
69 throw(error(instantiation_error, _)).
70representation_error(Reason) :-
71 throw(error(representation_error(Reason), _)).
72
73%% must_be_of_type(+Type, ?Term) is det.
74%
75% True if Term satisfies the type constraints for Type. Defined
76% types are =atom=, =atomic=, =between=, =boolean=, =callable=,
77% =chars=, =codes=, =text=, =compound=, =constant=, =float=,
78% =integer=, =nonneg=, =positive_integer=, =negative_integer=,
79% =nonvar=, =number=, =oneof=, =list=, =list_or_partial_list=,
80% =symbol=, =var=, =rational= and =string=.
81%
82% Most of these types are defined by an arity-1 built-in predicate
83% of the same name. Below is a brief definition of the other
84% types.
85%
86% | boolean | one of =true= or =false= |
87% | chars | Proper list of 1-character atoms |
88% | codes | Proper list of Unicode character codes |
89% | text | One of =atom=, =string=, =chars= or =codes= |
90% | between(L,U) | Number between L and U (including L and U) |
91% | nonneg | Integer >= 0 |
92% | positive_integer | Integer > 0 |
93% | negative_integer | Integer < 0 |
94% | oneof(L) | Ground term that is member of L |
95% | list(Type) | Proper list with elements of Type |
96% | list_or_partial_list | A list or an open list (ending in a variable) |
97% | predicate_indicator | a predicate indicator of the form M:N/A or M:N//A |
98%
99% @throws instantiation_error if Term is insufficiently
100% instantiated and type_error(Type, Term) if Term is not of Type.
101
102must_be(Type, X) :-
103 must_be_of_type(Type, X).
104
105must_be(Type, X, Comment) :-
106 must_be_of_type(Type, X, Comment).
107
108must_be_of_type(callable, X) :-
109 must_be_of_type,
111must_be_of_type(atom, X) :-
112 must_be_of_type,
113 is_atom(X).
114must_be_of_type(module, X) :-
115 must_be_of_type,
116 is_atom(X).
117must_be_of_type(predicate_indicator, X) :-
118 must_be_of_type,
119 is_predicate_indicator(X).
120must_be_of_type(Type, X) :-
121 ( has_type(Type, X)
122 -> has_type
123 ; is_not(Type, X)
124 ).
125
126inline(must_be_of_type( atom, X ), is_atom(X, _) ).
127inline(must_be_of_type( module, X ), is_module(X, _) ).
128inline(must_be_of_type( callable, X ), must_be_callable(X) ).
129inline(must_be_atom( X ), is_atom(X, _) ).
130inline(must_be_module( X ), is_atom(X, _) ).
131
132must_be_of_type(predicate_indicator, X, Comment) :-
133 must_be_of_type,
134 is_predicate_indicator(X, Comment).
135must_be_of_type(callable, X, _Comment) :-
136 must_be_of_type,
138must_be_of_type(Type, X, _Comment) :-
139 ( has_type(Type, X)
140 -> has_type
141 ; is_not(Type, X)
142 ).
143
144must_bind_to_type(Type, X) :-
145 ( may_bind_to_type(Type, X)
146 -> may_bind_to_type
147 ; is_not(Type, X)
148 ).
149
150%% @predicate is_not(+Type, @Term)
151%
152% Throws appropriate error. It is _known_ that Term is not of type
153% Type.
154%
155% @throws type_error(Type, Term)
156% @throws instantiation_error
157
158is_not(list, X) :- is_not,
159 not_a_list(list, X).
160is_not(list(_), X) :- _not,
161 not_a_list(list, X).
162is_not(list_or_partial_list, X) :- _not,
163 type_error(list, X).
164is_not(chars, X) :- _not,
165 not_a_list(chars, X).
166is_not(codes, X) :- _not,
167 not_a_list(codes, X).
168is_not(var,_X) :- _not,
169 representation_error(variable).
170is_not(rational, X) :- _not,
171 not_a_rational(X).
172is_not(Type, X) :-
173 ( var(X)
175 ; ground_type(Type), \+ ground(X)
177 ; type_error(Type, X)
178 ).
179
180ground_type(ground).
181ground_type(oneof(_)).
182ground_type(stream).
183ground_type(text).
184ground_type(string).
185
186not_a_list(Type, X) :-
187 '$skip_list'(_, X, Rest),
188 ( var(Rest)
190 ; type_error(Type, X)
191 ).
192
193not_a_rational(X) :-
194 ( var(X)
196 ; X = rdiv(N,D)
197 -> must_be(integer, N), must_be(integer, D),
198 type_error(rational,X)
199 ; type_error(rational,X)
200 ).
201
202%% is_of_type(+Type, @Term) is semidet.
203%
204% True if Term satisfies Type.
205
206is_of_type(Type, Term) :-
207 has_type(Type, Term).
208
209
210%% has_type(+Type, @Term) is semidet.
211%
212% True if Term satisfies Type.
213
214has_type(impossible, _) :- instantiation_error(_).
215has_type(any, _).
216has_type(atom, X) :- atom(X).
217has_type(atomic, X) :- atomic(X).
218has_type(between(L,U), X) :- ( integer(L)
219 -> integer(X), between(L,U,X)
220 ; number(X), X >= L, X =< U
221 ).
222has_type(boolean, X) :- (X==true;X==false), .
223has_type(callable, X) :- callable(X).
224has_type(chars, X) :- chars(X).
225has_type(codes, X) :- codes(X).
226has_type(text, X) :- text(X).
227has_type(compound, X) :- compound(X).
228has_type(constant, X) :- atomic(X).
229has_type(float, X) :- float(X).
230has_type(ground, X) :- ground(X).
231has_type(integer, X) :- integer(X).
232has_type(nonneg, X) :- integer(X), X >= 0.
233has_type(positive_integer, X) :- integer(X), X > 0.
234has_type(negative_integer, X) :- integer(X), X < 0.
235has_type(nonvar, X) :- nonvar(X).
236has_type(number, X) :- number(X).
237has_type(oneof(L), X) :- ground(X), ground:memberchk(X, L).
238has_type(proper_list, X) :- is_list(X).
239has_type(list, X) :- is_list(X).
240has_type(list_or_partial_list, X) :- is_list_or_partial_list(X).
241has_type(symbol, X) :- atom(X).
242has_type(var, X) :- var(X).
243has_type(rational, X) :- rational(X).
244has_type(string, X) :- string(X).
245has_type(stream, X) :- is_stream(X).
246has_type(list(Type), X) :- is_list(X), element_types(X, Type).
247
248%% may_bind_to_type(+Type, @Term) is semidet.
249%
250% True if _Term_ or term _Term\theta_ satisfies _Type_.
251
252may_bind_to_type(_, X ) :- var(X), var.
253may_bind_to_type(impossible, _) :- instantiation_error(_).
254may_bind_to_type(any, _).
255may_bind_to_type(atom, X) :- atom(X).
256may_bind_to_type(atomic, X) :- atomic(X).
257may_bind_to_type(between(L,U), X) :- ( integer(L)
258 -> integer(X), between(L,U,X)
259 ; number(X), X >= L, X =< U
260 ).
261may_bind_to_type(boolean, X) :- (X==true;X==false), .
262may_bind_to_type(callable, X) :- callable(X).
263may_bind_to_type(chars, X) :- chars(X).
264may_bind_to_type(codes, X) :- codes(X).
265may_bind_to_type(text, X) :- text(X).
266may_bind_to_type(compound, X) :- compound(X).
267may_bind_to_type(constant, X) :- atomic(X).
268may_bind_to_type(float, X) :- float(X).
269may_bind_to_type(ground, X) :- ground(X).
270may_bind_to_type(integer, X) :- integer(X).
271may_bind_to_type(nonneg, X) :- integer(X), X >= 0.
272may_bind_to_type(positive_integer, X) :- integer(X), X > 0.
273may_bind_to_type(negative_integer, X) :- integer(X), X < 0.
274may_bind_to_type(predicate_indicator, X) :-
275 (
276 X = M:PI
277 ->
278 may_bind_to_type( atom, M),
279 may_bind_to_type(predicate_indicator, PI)
280 ;
281 X = N/A
282 ->
283 may_bind_to_type( atom, N),
284 may_bind_to_type(integer, A)
285 ;
286 X = N//A
287 ->
288 may_bind_to_type( atom, N),
289 may_bind_to_type(integer, A)
290 ).
291
292
293may_bind_to_type(nonvar, _X).
294may_bind_to_type(number, X) :- number(X).
295may_bind_to_type(oneof(L), X) :- ground(X), ground:memberchk(X, L).
296may_bind_to_type(proper_list, X) :- is_list(X).
297may_bind_to_type(list, X) :- is_list(X).
298may_bind_to_type(list_or_partial_list, X) :- is_list_or_partial_list(X).
299may_bind_to_type(symbol, X) :- atom(X).
300may_bind_to_type(var, X) :- var(X).
301may_bind_to_type(rational, X) :- rational(X).
302may_bind_to_type(string, X) :- string(X).
303may_bind_to_type(stream, X) :- is_stream(X).
304may_bind_to_type(list(Type), X) :- is_list(X), element_types(X, Type).
305
306chars(0) :- chars, chars.
307chars([]).
308chars([H|T]) :-
309 atom(H), atom_length(H, 1),
310 chars(T).
311
312codes(x) :- codes, codes.
313codes([]).
314codes([H|T]) :-
315 integer(H), between(1, 0x10ffff, H),
316 codes(T).
317
318text(X) :-
319 ( atom(X)
320 ; string(X)
321 ; chars(X)
322 ; codes(X)
323 ), !.
324
325element_types([], _).
326element_types([H|T], Type) :-
327 must_be(Type, H),
328 element_types(T, Type).
329
330is_list_or_partial_list(L0) :-
331 '$skip_list'(_, L0,L),
332 ( var(L) -> var ; L == [] ).
333
334must_be_instantiated(X) :-
335 ( var(X) -> instantiation_error(X) ; instantiation_error).
336
337must_be_instantiated(X, Comment) :-
338 ( var(X) -> instantiation_error(X, Comment) ; instantiation_error).
339
340%% @}
341
callable( ?_Goal_ )
is_list( ?_List_ )
must_be_callable( ?_Goal_ )
throw(+ Ball)
existence_error(+Type, +Term)
instantiation_error(+Term)
is_not(+Type, @Term)
permission_error(+Action, +Type, +Term)
representation_error(+Reason)
type_error(+Type, +Term)
atom_length(+ A,? I)
ground( T)
atom( T)
atomic(T)
compound( T)
float( T)
integer( T)
nonvar( T)
number( T)
var( T)
between(+ Low:int, + High:int, ? Value:int)
memberchk(+ Element, + Set)