1/* Part of SWI-Prolog 2 3 Author: Jan Wielemaker 4 E-mail: J.Wielemaker@vu.nl 5 WWW: http://www.swi-prolog.org 6 Copyright (c) 2006-2024, University of Amsterdam 7 VU University Amsterdam 8 SWI-Prolog Solutions b.v. 9 All rights reserved. 10 11 Redistribution and use in source and binary forms, with or without 12 modification, are permitted provided that the following conditions 13 are met: 14 15 1. Redistributions of source code must retain the above copyright 16 notice, this list of conditions and the following disclaimer. 17 18 2. Redistributions in binary form must reproduce the above copyright 19 notice, this list of conditions and the following disclaimer in 20 the documentation and/or other materials provided with the 21 distribution. 22 23 THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 24 "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 25 LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 26 FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 27 COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 28 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 29 BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 30 LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 31 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 32 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 33 ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 34 POSSIBILITY OF SUCH DAMAGE. 35*/ 36 37:- module(error, 38 [ instantiation_error/1, % +FormalSubTerm 39 uninstantiation_error/1, % +Culprit 40 type_error/2, % +ValidType, +Culprit 41 domain_error/2, % +ValidDomain, +Culprit 42 existence_error/2, % +ObjectType, +Culprit 43 existence_error/3, % +ObjectType, +Culprit, +Set 44 permission_error/3, % +Operation, +PermissionType, +Culprit 45 representation_error/1, % +Flag 46 resource_error/1, % +Resource 47 syntax_error/1, % +ImplDepAtom 48 49 must_be/2, % +Type, +Term 50 is_of_type/2, % +Type, +Term 51 current_type/3 % ?Type, @Var, -Body 52 ]). 53:- set_prolog_flag(generate_debug_info, false). 54:- use_module(library(debug), [assertion/1]).
72:- multifile 73 has_type/2. 74 75 /******************************* 76 * ISO ERRORS * 77 *******************************/
Suppose an argument must be a non-negative integer. If the actual argument is not an integer, this is a type_error. If it is a negative integer, it is a domain_error.
Typical borderline cases are predicates accepting a compound term,
e.g., point(X,Y)
. One could argue that the basic type is a
compound-term and any other compound term is a domain error. Most
Prolog programmers consider each compound as a type and would
consider a compound that is not point(_,_)
a type_error.
96type_error(ValidType, Culprit) :-
97 throw(error(type_error(ValidType, Culprit), _)).
105domain_error(ValidDomain, Culprit) :-
106 throw(error(domain_error(ValidDomain, Culprit), _)).
114existence_error(ObjectType, Culprit) :-
115 throw(error(existence_error(ObjectType, Culprit), _)).
existence_error(ObjectType,
Culprit, Set)
127existence_error(ObjectType, Culprit, Set) :-
128 throw(error(existence_error(ObjectType, Culprit, Set), _)).
136permission_error(Operation, PermissionType, Culprit) :-
137 throw(error(permission_error(Operation, PermissionType, Culprit), _)).
151instantiation_error(_FormalSubTerm) :-
152 throw(error(instantiation_error, _)).
open(File, read, input)
cannot succeed because the system will
allocate a new unique stream handle that will never unify with
input
.
162uninstantiation_error(Culprit) :-
163 throw(error(uninstantiation_error(Culprit), _)).
173representation_error(Flag) :-
174 throw(error(representation_error(Flag), _)).
187syntax_error(Culprit) :-
188 throw(error(syntax_error(Culprit), _)).
196resource_error(Resource) :- 197 throw(error(resource_error(Resource), _)). 198 199 200 /******************************* 201 * MUST-BE * 202 *******************************/
atom
, atomic
, between
, boolean
, callable
,
chars
, codes
, text
, compound
, constant
, float
,
integer
, nonneg
, positive_integer
, negative_integer
,
nonvar
, number
, oneof
, list
, list_or_partial_list
,
symbol
, var
, rational
, encoding
, dict
and string
.
Most of these types are defined by an arity-1 built-in predicate of the same name. Below is a brief definition of the other types.
acyclic | Acyclic term (tree); see acyclic_term/1 |
any | any term |
between(FloatL,FloatU) | Number [FloatL..FloatU] |
between(IntL,IntU) | Integer [IntL..IntU] |
boolean | One of true or false |
callable | Atom or compound term |
char | Atom of length 1 |
chars | Proper list of 1-character atoms |
code | Representation Unicode code point (0..0x10ffff) |
codes | Proper list of Unicode character codes |
compound | compound term |
compound(Term) | Compound with same name/arity as term; checks arguments |
constant | Same as atomic |
cyclic | Cyclic term (rational tree); see cyclic_term/1 |
dict | A dictionary term; see is_dict/1 |
encoding | Valid name for a character encoding; see current_encoding/1 |
list | A (non-open) list; see is_list/1 |
list(Type) | Proper list with elements of Type |
list_or_partial_list | A list or an open list (ending in a variable); see is_list_or_partial_list/1 |
negative_integer | Integer < 0 |
nonneg | Integer >= 0 |
oneof(L) | Ground term that is member of L |
pair | Key-Value pair. Same as compound(any-any) |
positive_integer | Integer > 0 |
proper_list | Same as list |
stream | A stream name or valid stream handle; see is_stream/1 |
symbol | Same as atom |
text | One of atom , string , chars or codes |
type | Term is a valid type specification |
In addition, types may be composed using TypeA,TypeB
,
TypeA;TypeB
and negated using \Type
.
253must_be(Type, X) :-
254 ( nonvar(Type),
255 has_type(Type, X)
256 -> true
257 ; nonvar(Type)
258 -> is_not(Type, X)
259 ; instantiation_error(Type)
260 ).
270is_not(list, X) :- 271 !, 272 not_a_list(list, X). 273is_not(list(Of), X) :- 274 !, 275 not_a_list(list(Of), X). 276is_not(list_or_partial_list, X) :- 277 !, 278 type_error(list, X). 279is_not(chars, X) :- 280 !, 281 not_a_list(list(char), X). 282is_not(codes, X) :- 283 !, 284 not_a_list(list(code), X). 285is_not(var,X) :- 286 !, 287 uninstantiation_error(X). 288is_not(cyclic, X) :- 289 domain_error(cyclic_term, X). 290is_not(acyclic, X) :- 291 domain_error(acyclic_term, X). 292is_not(Type, X) :- 293 current_type(Type, _Var, _Body), 294 !, 295 ( var(X) 296 -> instantiation_error(X) 297 ; ground_type(Type), \+ ground(X) 298 -> instantiation_error(X) 299 ; type_error(Type, X) 300 ). 301is_not(Type, _) :- 302 existence_error(type, Type). 303 304ground_type(ground). 305ground_type(oneof(_)). 306ground_type(stream). 307ground_type(text). 308ground_type(string). 309ground_type(rational). 310 311not_a_list(Type, X) :- 312 '$skip_list'(_, X, Rest), 313 ( var(Rest) 314 -> instantiation_error(X) 315 ; Rest == [] 316 -> Type = list(Of), 317 ( nonvar(Of) 318 -> element_is_not(X, Of) 319 ; instantiation_error(Of) 320 ) 321 ; type_error(Type, X) 322 ). 323 324 325element_is_not([H|T], Of) :- 326 has_type(Of, H), 327 !, 328 element_is_not(T, Of). 329element_is_not([H|_], Of) :- 330 !, 331 is_not(Of, H). 332element_is_not(_List, _Of) :- 333 assertion(fail).
339is_of_type(Type, Term) :- 340 nonvar(Type), 341 !, 342 has_type(Type, Term), 343 !. 344is_of_type(Type, _) :- 345 instantiation_error(Type).
351:- '$clausable'(has_type/2). % always allow clause/2 352:- public % May be called through current_type/3 353 is_list_or_partial_list/1, 354 current_encoding/1, 355 element_types/2. 356 357has_type(any, _). 358has_type(atom, X) :- atom(X). 359has_type(atomic, X) :- atomic(X). 360has_type(between(L,U), X) :- 361 ( integer(L) 362 -> integer(X), between(L,U,X) 363 ; number(X), X >= L, X =< U 364 ). 365has_type(boolean, X) :- (X==true;X==false), !. 366has_type(callable, X) :- callable(X). 367has_type(char, X) :- '$is_char'(X). 368has_type(code, X) :- '$is_char_code'(X). 369has_type(chars, X) :- '$is_char_list'(X, _Len). 370has_type(codes, X) :- '$is_code_list'(X, _Len). 371has_type(text, X) :- text(X). 372has_type(compound, X) :- compound(X). 373has_type(compound(Term),X):- compound(X), is_term_of_type(Term,X). 374has_type(constant, X) :- atomic(X). 375has_type(float, X) :- float(X). 376has_type(ground, X) :- ground(X). 377has_type(cyclic, X) :- cyclic_term(X). 378has_type(acyclic, X) :- acyclic_term(X). 379has_type(integer, X) :- integer(X). 380has_type(nonneg, X) :- integer(X), X >= 0. 381has_type(positive_integer, X) :- integer(X), X > 0. 382has_type(negative_integer, X) :- integer(X), X < 0. 383has_type(nonvar, X) :- nonvar(X). 384has_type(number, X) :- number(X). 385has_type(oneof(L), X) :- ground(X), \+ \+ memberchk(X, L). 386has_type(pair, X) :- nonvar(X), X = _-_. 387has_type(proper_list, X) :- is_list(X). 388has_type(list, X) :- is_list(X). 389has_type(list_or_partial_list, X) :- is_list_or_partial_list(X). 390has_type(symbol, X) :- atom(X). 391has_type(var, X) :- var(X). 392has_type(rational, X) :- rational(X). 393has_type(string, X) :- string(X). 394has_type(stream, X) :- is_stream(X). 395has_type(encoding, X) :- current_encoding(X). 396has_type(dict, X) :- is_dict(X). 397has_type(list(Type), X) :- is_list(X), element_types(X, Type). 398has_type(list_or_partial_list(Type), X) :- is_list_or_partial_list(X), element_types(X, Type). 399has_type(type, Type) :- ground(Type), current_type(Type,_,_). 400has_type((A,B), X) :- (is_of_type(A,X)->is_of_type(B,X)). 401has_type((A;B), X) :- (is_of_type(A,X)->true;is_of_type(B,X)). 402has_type(\A, X) :- \+ is_of_type(A,X). 403 404text(X) :- 405 ( atom(X) 406 ; string(X) 407 ; '$is_char_list'(X, _) 408 ; '$is_code_list'(X, _) 409 ), 410 !. 411 412element_types(List, Type) :- 413 nonvar(Type), 414 !, 415 element_types_(List, Type). 416element_types(_List, Type) :- 417 instantiation_error(Type). 418 419element_types_(Var, _) :- 420 var(Var), 421 !. 422element_types_([], _). 423element_types_([H|T], Type) :- 424 has_type(Type, H), 425 !, 426 element_types_(T, Type). 427 428is_list_or_partial_list(L0) :- 429 '$skip_list'(_, L0,L), 430 ( var(L) -> true ; L == [] ).
437current_encoding(octet). 438current_encoding(ascii). 439current_encoding(iso_latin_1). 440current_encoding(text). 441current_encoding(utf8). 442current_encoding(unicode_be). 443current_encoding(unicode_le). 444current_encoding(wchar_t).
452current_type(Type, Var, Body) :- 453 clause(has_type(Type, Var), Body0), 454 qualify(Body0, Body). 455 456qualify(Var, VarQ) :- 457 var(Var), 458 !, 459 VarQ = Var. 460qualify((A0,B0), (A,B)) :- 461 qualify(A0, A), 462 qualify(B0, B). 463qualify(G0, G) :- 464 predicate_property(system:G0, built_in), 465 !, 466 G = G0. 467qualify(G, error:G).
compound(oneof(list(atom)))
.473is_term_of_type(Term, X) :- 474 compound_name_arity(Term, N, A), 475 compound_name_arity(X, N, A), 476 term_arg_types(1, A, Term, X). 477 478term_arg_types(I, A, Type, X) :- 479 I =< A, 480 !, 481 arg(I, Type, AType), 482 arg(I, X, XArg), 483 has_type(AType, XArg), 484 I2 is I+1, 485 term_arg_types(I2, A, Type, X). 486term_arg_types(_, _, _, _). 487 488 489 /******************************* 490 * SANDBOX * 491 *******************************/ 492 493:- multifile sandbox:safe_primitive/1. 494 495sandbox:safe_primitive(error:current_type(_,_,_))
Error generating support
This module provides predicates to simplify error generation and checking. It's implementation is based on a discussion on the SWI-Prolog mailinglist on best practices in error handling. The utility predicate must_be/2 provides simple run-time type validation. The *_error predicates are simple wrappers around throw/1 to simplify throwing the most common ISO error terms.