% This LaTeX document was generated using the LaTeX backend of PlDoc, % The SWI-Prolog documentation system \section{library(error): Error generating support} \label{sec:error} \begin{tags} \mtag{author}- Jan Wielemaker \\- Richard O'Keefe \\- Ulrich Neumerkel\mtag{See also}- \file{library(debug)} and \file{library(prolog_stack)}. \\- \predref{print_message}{2} is used to print (uncaught) error terms. \end{tags} 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 \predref{must_be}{2} provides simple run-time type validation. The *_error predicates are simple wrappers around \predref{throw}{1} to simplify throwing the most common ISO error terms.\vspace{0.7cm} \begin{description} \predicate{type_error}{2}{+ValidType, +Culprit} Tell the user that \arg{Culprit} is not of the expected \arg{ValidType}. This error is closely related to \predref{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 \textit{type_error}. If it is a negative integer, it is a \textit{domain_error}. Typical borderline cases are predicates accepting a compound term, e.g., \verb$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 \verb$point(_,_)$ a \textit{type_error}. \predicate{domain_error}{2}{+ValidDomain, +Culprit} The argument is of the proper type, but has a value that is outside the supported values. See \predref{type_error}{2} for a more elaborate discussion of the distinction between type- and domain-errors. \predicate{existence_error}{2}{+ObjectType, +Culprit} \arg{Culprit} is of the correct type and correct domain, but there is no existing (external) resource of type \arg{ObjectType} that is represented by it. \predicate{existence_error}{3}{+ObjectType, +Culprit, +Set} \arg{Culprit} is of the correct type and correct domain, but there is no existing (external) resource of type \arg{ObjectType} that is represented by it in the provided set. The thrown exception term carries a formal term structured as follows: \verb$existence_error(ObjectType, Culprit, Set)$ \begin{tags} \tag{Compatibility} This error is outside the ISO Standard. \end{tags} \predicate{permission_error}{3}{+Operation, +PermissionType, +Culprit} It is not allowed to perform \arg{Operation} on (whatever is represented by) \arg{Culprit} that is of the given \arg{PermissionType} (in fact, the ISO Standard is confusing and vague about these terms' meaning). \predicate{instantiation_error}{1}{+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. \begin{arguments} \arg{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. \\ \end{arguments} \predicate{uninstantiation_error}{1}{+Culprit} An argument is over-instantiated. This error is used for output arguments whose value cannot be known upfront. For example, the goal \verb$open(File, read, input)$ cannot succeed because the system will allocate a new unique stream handle that will never unify with \const{input}. \predicate{representation_error}{1}{+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. \predicate{syntax_error}{1}{+Culprit} A text has invalid syntax. The error is described by \arg{Culprit}. According to the ISO Standard, \arg{Culprit} should be an implementation-dependent atom. \begin{tags} \tag{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. \verb$syntax_error(number('1a'))$ means that \verb$1a$ is not a valid number. \end{tags} \predicate{resource_error}{1}{+Resource} A goal cannot be completed due to lack of resources. According to the ISO Standard, \arg{Resource} should be an implementation-dependent atom. \predicate[det]{must_be}{2}{+Type, @Term} True if \arg{Term} satisfies the type constraints for \arg{Type}. Defined types are \const{atom}, \const{atomic}, \const{between}, \const{boolean}, \const{callable}, \const{chars}, \const{codes}, \const{text}, \const{compound}, \const{constant}, \const{float}, \const{integer}, \const{nonneg}, \verb$positive_integer$, \verb$negative_integer$, \const{nonvar}, \const{number}, \const{oneof}, \const{list}, \verb$list_or_partial_list$, \const{symbol}, \const{var}, \const{rational}, \const{encoding}, \const{dict} and \const{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. \begin{quote} \begin{tabulary}{0.9\textwidth}{|l|L|} \hline acyclic & Acyclic term (tree); see \predref{acyclic_term}{1} \\ any & any term \\ \verb$between(FloatL,FloatU)$ & Number [FloatL..FloatU] \\ \verb$between(IntL,IntU)$ & Integer [IntL..IntU] \\ boolean & One of \const{true} or \const{false} \\ char & Atom of length 1 \\ chars & Proper list of 1-character atoms \\ code & Representation Unicode code point \\ codes & Proper list of Unicode character codes \\ constant & Same as \const{atomic} \\ cyclic & Cyclic term (rational tree); see \predref{cyclic_term}{1} \\ dict & A dictionary term; see \predref{is_dict}{1} \\ encoding & Valid name for a character encoding; see \predref{current_encoding}{1} \\ list & A (non-open) list; see \predref{is_list}{1} \\ negative_integer & Integer $<$ 0 \\ nonneg & Integer \Sge{} 0 \\ \verb$oneof(L)$ & Ground term that is member of L \\ pair & Key-Value pair \\ positive_integer & Integer $>$ 0 \\ proper_list & Same as list \\ \verb$list(Type)$ & Proper list with elements of \arg{Type} \\ list_or_partial_list & A list or an open list (ending in a variable); see \predref{is_list_or_partial_list}{1} \\ stream & A stream name or valid stream handle; see \predref{is_stream}{1} \\ symbol & Same as \const{atom} \\ text & One of \const{atom}, \const{string}, \const{chars} or \const{codes} \\ type & \arg{Term} is a valid type specification \\ \hline \end{tabulary} \end{quote} Note: The Windows version can only represent Unicode code points up to 2\Shat{}16-1. Higher values cause a representation error on most text handling predicates. \begin{tags} \tag{throws} instantiation_error if \arg{Term} is insufficiently instantiated and \verb$type_error(Type, Term)$ if \arg{Term} is not of \arg{Type}. \end{tags} \predicate[semidet]{is_of_type}{2}{+Type, @Term} True if \arg{Term} satisfies \arg{Type}. \predicate[semidet,multifile]{has_type}{2}{+Type, @Term} True if \arg{Term} satisfies \arg{Type}. \predicate[nondet]{current_encoding}{1}{?Name} True if \arg{Name} is the name of a supported encoding. See encoding option of e.g., \predref{open}{4}. \predicate[nondet]{current_type}{3}{?Type, @Var, -Body} True when \arg{Type} is a currently defined type and \arg{Var} satisfies \arg{Type} of the body term \arg{Body} succeeds. \end{description}