A The SWI-Prolog library
AllApplicationManualNameSummaryHelp

  • Documentation
    • Reference manual
      • The SWI-Prolog library
        • library(aggregate): Aggregation operators on backtrackable predicates
        • library(ansi_term): Print decorated text to ANSI consoles
        • library(apply): Apply predicates on a list
        • library(assoc): Association lists
        • library(broadcast): Broadcast and receive event notifications
        • library(charsio): I/O on Lists of Character Codes
        • library(check): Consistency checking
        • library(clpb): CLP(B): Constraint Logic Programming over Boolean Variables
        • library(clpfd): CLP(FD): Constraint Logic Programming over Finite Domains
        • library(clpqr): Constraint Logic Programming over Rationals and Reals
        • library(csv): Process CSV (Comma-Separated Values) data
        • library(dcg/basics): Various general DCG utilities
        • library(dcg/high_order): High order grammar operations
        • library(debug): Print debug messages and test assertions
        • library(dicts): Dict utilities
        • library(error): Error generating support
          • type_error/2
          • domain_error/2
          • existence_error/2
          • existence_error/3
          • permission_error/3
          • instantiation_error/1
          • uninstantiation_error/1
          • representation_error/1
          • syntax_error/1
          • resource_error/1
          • must_be/2
          • is_of_type/2
          • has_type/2
          • current_encoding/1
          • current_type/3
        • library(fastrw): Fast reading and writing of terms
        • library(gensym): Generate unique symbols
        • library(heaps): heaps/priority queues
        • library(increval): Incremental dynamic predicate modification
        • library(intercept): Intercept and signal interface
        • library(iostream): Utilities to deal with streams
        • library(listing): List programs and pretty print clauses
        • library(lists): List Manipulation
        • library(main): Provide entry point for scripts
        • library(nb_set): Non-backtrackable set
        • library(www_browser): Open a URL in the users browser
        • library(occurs): Finding and counting sub-terms
        • library(option): Option list processing
        • library(optparse): command line parsing
        • library(ordsets): Ordered set manipulation
        • library(pairs): Operations on key-value lists
        • library(persistency): Provide persistent dynamic predicates
        • library(pio): Pure I/O
        • library(portray_text): Portray text
        • library(predicate_options): Declare option-processing of predicates
        • library(prolog_debug): User level debugging tools
        • library(prolog_jiti): Just In Time Indexing (JITI) utilities
        • library(prolog_pack): A package manager for Prolog
        • library(prolog_xref): Prolog cross-referencer data collection
        • library(quasi_quotations): Define Quasi Quotation syntax
        • library(random): Random numbers
        • library(rbtrees): Red black trees
        • library(readutil): Read utilities
        • library(record): Access named fields in a term
        • library(registry): Manipulating the Windows registry
        • library(settings): Setting management
        • library(statistics): Get information about resource usage
        • library(strings): String utilities
        • library(simplex): Solve linear programming problems
        • library(solution_sequences): Modify solution sequences
        • library(tables): XSB interface to tables
        • library(terms): Term manipulation
        • library(thread): High level thread primitives
        • library(thread_pool): Resource bounded thread management
        • library(ugraphs): Graph manipulation library
        • library(url): Analysing and constructing URL
        • library(varnumbers): Utilities for numbered terms
        • library(yall): Lambda expressions
    • Packages

A.16 library(error): Error generating support

author
- Jan Wielemaker
- Richard O'Keefe
- Ulrich Neumerkel
See also
- library(debug) and library(prolog_stack).
- print_message/2 is used to print (uncaught) error terms.

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.

type_error(+ValidType, +Culprit)
Tell the user that Culprit is not of the expected ValidType. This error is closely related to domain_error/2 because the notion of types is not really set in stone in Prolog. We introduce the difference using a simple example.

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.

domain_error(+ValidDomain, +Culprit)
The argument is of the proper type, but has a value that is outside the supported values. See type_error/2 for a more elaborate discussion of the distinction between type- and domain-errors.
existence_error(+ObjectType, +Culprit)
Culprit is of the correct type and correct domain, but there is no existing (external) resource of type ObjectType that is represented by it.
existence_error(+ObjectType, +Culprit, +Set)
Culprit is of the correct type and correct domain, but there is no existing (external) resource of type ObjectType that is represented by it in the provided set. The thrown exception term carries a formal term structured as follows: existence_error(ObjectType, Culprit, Set)
Compatibility
This error is outside the ISO Standard.
permission_error(+Operation, +PermissionType, +Culprit)
It is not allowed to perform Operation on (whatever is represented by) Culprit that is of the given PermissionType (in fact, the ISO Standard is confusing and vague about these terms' meaning).
instantiation_error(+FormalSubTerm)
An argument is under-instantiated. I.e. it is not acceptable as it is, but if some variables are bound to appropriate values it would be acceptable.
FormalSubTerm is the term that needs (further) instantiation. Unfortunately, the ISO error does not allow for passing this term along with the error, but we pass it to this predicate for documentation purposes and to allow for future enhancement.
uninstantiation_error(+Culprit)
An argument is over-instantiated. This error is used for output arguments whose value cannot be known upfront. For example, the goal open(File, read, input) cannot succeed because the system will allocate a new unique stream handle that will never unify with input.
representation_error(+Flag)
A representation error indicates a limitation of the implementation. SWI-Prolog has no such limits that are not covered by other errors, but an example of a representation error in another Prolog implementation could be an attempt to create a term with an arity higher than supported by the system.
syntax_error(+Culprit)
A text has invalid syntax. The error is described by Culprit. According to the ISO Standard, Culprit should be an implementation-dependent atom.
To be done
Deal with proper description of the location of the error. For short texts, we allow for Type(Text), meaning Text is not a valid Type. E.g. syntax_error(number('1a')) means that 1a is not a valid number.
resource_error(+Resource)
A goal cannot be completed due to lack of resources. According to the ISO Standard, Resource should be an implementation-dependent atom.
[det]must_be(+Type, @Term)
True if Term satisfies the type constraints for Type. Defined types are 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.

acyclicAcyclic term (tree); see acyclic_term/1
anyany term
between(FloatL,FloatU) Number [FloatL..FloatU]
between(IntL,IntU) Integer [IntL..IntU]
booleanOne of true or false
charAtom of length 1
charsProper list of 1-character atoms
codeRepresentation Unicode code point
codesProper list of Unicode character codes
constantSame as atomic
cyclicCyclic term (rational tree); see cyclic_term/1
dictA dictionary term; see is_dict/1
encodingValid name for a character encoding; see current_encoding/1
listA (non-open) list; see is_list/1
negative_integerInteger < 0
nonnegInteger >= 0
oneof(L) Ground term that is member of L
pairKey-Value pair
positive_integerInteger > 0
proper_listSame as list
list(Type) Proper list with elements of Type
list_or_partial_listA list or an open list (ending in a variable); see is_list_or_partial_list/1
streamA stream name or valid stream handle; see is_stream/1
symbolSame as atom
textOne of atom, string, chars or codes
typeTerm is a valid type specification

Note: The Windows version can only represent Unicode code points up to 2^16-1. Higher values cause a representation error on most text handling predicates.

throws
instantiation_error if Term is insufficiently instantiated and type_error(Type, Term) if Term is not of Type.
[semidet]is_of_type(+Type, @Term)
True if Term satisfies Type.
[semidet,multifile]has_type(+Type, @Term)
True if Term satisfies Type.
[nondet]current_encoding(?Name)
True if Name is the name of a supported encoding. See encoding option of e.g., open/4.
[nondet]current_type(?Type, @Var, -Body)
True when Type is a currently defined type and Var satisfies Type of the body term Body succeeds.