Towards an extension of `library(error)`

In the context of a little code cleanup of JPL consisting (mainly) in grouping all the calls to throw/1, Jan Wielemaker & myself wanted to kick off a discussion of an extension to library(eror). So I will post first.

Naming

In the ISO Standard chapter 7.12.1, pp. 62 (“The effect of an error”), it is stated that throw/1 shall throw a term Exception as in:

throw(Exception)

where the carried term is

Exception=error(Error_term, Imp_def)

In the description of throw/1, the SWI Prolog manual uses:

error(Formal, ImplementationDefined)

Let’s set the vocabulary as follows:

  • error(Error_term, Imp_def)the exception term
  • Error_termthe error term, a subterm of the exception term
  • Imp_defthe implementation-defined term, a subterm of the exception term
  • The subterms of the error term are variously named Cuplrit, ValidTerm etc.

Current predicates from library(error)

library(error) provides predicates for throwing ISO Standard errors. The following “throwing predicates” are exported, and they look exactly like the corresponding Error term that is carried by the Exception term:

  • type_error(+Type, +Term)
  • domain_error(+Type, +Term)
  • existence_error(+Type, +Term)
  • existence_error(+Type, +Term, +Set)
  • permission_error(+Action, +Type, +Term)
  • instantiation_error(+Term)
  • uninstantiation_error(+Term)
  • representation_error(+Reason)
  • syntax_error(+Culprit)
  • resource_error(+Culprit)

(It is my personal opinion that the action word throw_ is missing in the name of all of the above. I do think seeing throw_type_error(what,where) is more descriptive than seeing type_error(what,where)).

(Also, the ISO error term is disturbingly nonuniform: atoms and variously named compound terms of arity 1,2 or 3 . The “error term” should probably have been a list: [isoerror,domain,Type,Term])

The above predicates are both more liberal and more restrictive than what the ISO standard demands and provides:

  • More liberal: In the standard, the terms Type, Action, Term, Reason, Culprit are meant to be atoms and even selected from sets of pre-listed atoms. That’s unnecessarily restrictive. However, library(error) allows one to pass any term. On the other hand, assumptions are made at catchers about what these terms are. For example, the toplevel expects something like domain_error(integer,5). If that’s not the case, what it prints is confusing.
  • More restrictive: The ISO standard allows an “implementation-specific subterm” in the thrown exception term in all cases. This is very useful. For example, in JPL, the “implementation-specific subterm” is set to a cleartext error message but the calls to throw/1 are explicit and do not go through library(error). None of the predicates of library(error) allows to set an “implementation-specific subterm” right now.

Thus, the following extension is proposed:

  • Add predicates that allow passing the “implementation-specific subterm” for each case.
  • Possibly rename the predicates (not gonna happen!)
  • Cleanup the names of the parameter terms to make them comform to the ISO Standard (that’s just syntax, see below)

Additionally, there are missing exception types. Evidently the list of “ISO Standard Exceptions” cannot be exhaustive, as the set of programs is not closed. There are two cases where no ISO Standard Exception seems to fit:

  • Exception thrown when an assertion has failed. This would be the counterpart of Java’s AssertionError: “Thrown to indicate that an assertion has failed.”
  • Exception thrown when the program finds that it is in a computational state that shouldn’t be entered. The counterpart of Java’s IllegalStateException: “Signals that a method has been invoked at an illegal or inappropriate time. In other words, the Java environment or Java application is not in an appropriate state for the requested operation.” One might think that the ISO Standard system error might be appropriate but that error should only be throw by the Prolog Processor and moreover carries no information.

Thus I propose the following additional predicates:

throw_illegal_state_error(+About, +ImplDefined)
throw_assertion_error(+About, +ImplDefined)

The complete list:

% ===
% Existing predicates with an additional ImplDefined term.
% ===

% instantiation_error's "Culprit" is not ISO (yet), so it's not set in a ISO thrown term!
throw_instantiation_error(+Culprit, +ImplDefined) 
throw_uninstantiation_error(+Culprit, +ImplDefined)
throw_type_error(+ValidType, +Cuplrit, +ImplDefined)
throw_domain_error(+ValidDomain, +Cuplrit, +ImplDefined)
throw_existence_error(+ObjectType, +Culprit, +ImplDefined)
% Is "Set" of existence_error still needed in this configuration?
throw_existence_error(+ObjectType, +Cuplrit, +Set, +ImplDefined)  
throw_permission_error(+Operation, +PermissionType, +Culprit)
throw_representation_error(+Flag, +ImplDefined)
throw_resource_error(+Resource, +ImplDefined)
throw_syntax_error(+Culprit, +ImplDefined)

% ===
% Extra predicates that not ISO, so should probably throw an error term different from error/2.
% ===

throw_illegal_state_error(+About, +ImplDefined)
throw_assertion_error(+About, +ImplDefined)

ISO Errors Recapitulation

In chapter 7.12.2, pp. 62-63 (“Error classification”) the ISO Standard lists the Error terms below.

  • I shall add the corresponding predicate from library(error).
  • I also add some grumpycat notes.

Instantiation Error

ISO

Error=instantiation_error

(no parameters, just 1 atom)

An argument or one of its components is a variable, and an instantiated argument or component is required instead.

Note

There is no parameter to indicate which argument is the one of interest (making this error a bit deficient in usefulness). This means one has to use the ImplDefined term instead to carry that information.

Call from library(error)

instantiation_error(+Term)

The SWI Prolog documentation says: “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

ISO

Error=uninstantiation_error(Culprit)

An argument or one of its components is not a variable, and a variable or a component as variable is required. Culprit is the argument or one of its components which caused the error. Appears in Corrigendum 2 of the ISO Standard.

Call from library(error)

uninstantiation_error(+Term)

Type Error

ISO

Error=type_error(ValidType,Culprit)

An argument or one of its components is incorrect, but not a variable (“A Type Error occurs when a value does not belong to one of the types defined in this part of ISO/IEC 13211”).

ISO-compatible values for ValidType are listed in the standard.

Call from library(error)

type_error(+Type, +Term)

Notes

Actually stipulating - instead of recommending - values for ValidType as the standard is overly restrictive. list is one of the ValidType values, and it’s not even a “type” - but difflist or conjunction are not. Neither are dict or blob of course. Compare with the approach taken for syntax_error(ImplDepAtom) below.

Domain Error

ISO

Error=domain_error(ValidDomain, Culprit)

An argument’s type is correct but the value is outside the domain for which the procedure is defined. (“Domain Error occurs when the value is not a a member of an implementation defined or implementation-dependent set.”)

ISO-compatible values for ValidDomain are defined in the standard.

Call from library(error)

domain_error(+Type, +Term)

Notes

As above, stipulating - instead of recommending - the values for ValidDomain as the standard is overly restrictive. This exception also misses the far more interesting case of a being outside the allowed subdomain in a domain spanned by several arguments instead of just one.

Existence Error

ISO

Error=existence_error(ObjectType, Culprit)

An object on which an operation is to be performed does not exist. ObjectType is one of procedure, source_sink, stream.

Call from library(error)

existence_error(+Type, +Term)
existence_error(+Type, +Term, +Set) “This error is not in ISO.”

The second predicate is meant to carry more information, but which?

(And is it needed if ImplDefined can be used?)

Permission Error

ISO

Error=permission_error(Operation, PermissionType, Culprit)

The runtime system (or the thread) is lacking permission to perform a specific operation.

Operation is one of: access, create, input, modify, open, output, reposition

PermissionType is one of: binary_stream, flag, operator, past_end_of_stream, private_procedure, static_procedure, source_sink, stream, text_stream

Call from library(error)

permission_error(+Action, +Type, +Term)

Representation Error

ISO

Error=representation_error(Flag)

An implementation-defined limit has been breached.

Flag is one of: character, character_code, in_character_code, max_arity, max_integer, min_integer.

Call from library(error)

representation_error(+Reason)

Evaluation Error

ISO

Formal=evaluation_error(Error)

The operands of an evaluable functor are such that the operation has an exceptional value.

Error is one of: float_overflow, int_overflow, undefined, underflow, zero_divisor

Call from library(error)

There is no corresponding call. That is probably because that exception is thrown only by built-ins?

Notes

This seems to apply only to arithmetic functions. And it does not even seems to cover the IEEE 754 exceptions. May need extension.

Resource Error

ISO

Error=resource_error(Resource)

The runtime system has insufficient resources to complete execution. “A Resource Error may happen for example when a calculation on unbounded integers has a value which is too large.”

Resource is an implementation-dependent atom.

Call from library(error)

resource_error(+Culprit)

Syntax Error

ISO

Error=syntax_error(ImplDepAtom)

A sequence of characters which are being input as a read-term do not conform to the syntax.

ImplDepAtom denotes an implementation-dependent atom.

Call from library(error)

syntax_error(+Culprit)

The description says:

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.

System Error

ISO

Error=system_error (completely parameterless!)

Can happen at any point of computation. The conditions for a System Error and the actions taken by a Prolog runtime after occurrence are implementation-dependent. A System Error may happen for example (a) in interactions with the operating system (for example, a disc crash or interrupt), or (b) when a goal throw(T) has been executed and there is no active goal catch/3.

Call from library(error)

There is no corresponding call. “System Error” should not be thrown from user code.

Note

As a programmer, you would not throw System Error, the more so as it doesn’t take any parameter. It sounds like the counterpart of a Java Error)

Reference

At Exception Handling in ISO Prolog a recapitulation of the ISO Standard can be found (12 April 1999). The uninstantiation_error is not listed as it was added only later.

1 Like

Also there is something strange that JPL doesn’t extend term_message//1. It has all the text directly inside the throw. But I guess the idea is that there is a message infrastructure that translates formal errors to text.

Maybe JPL could extend prolog:error_message//1. Don’t know what the official hook is. prolog:error_message//1 is probed by term_message//1, but prolog:error_message//1 is not further documented.

It would be nice if there were some more documentation about ImplementationDefined … from looking at library(error), it seems that error(Formal, _) is often used, but the documentation of the default handler seems to imply that error(Formal) is essentially equivalent. Is this the case?

Instantiating the ImplementationDefined part gives a different message (no traceback). I couldn’t find where this was implemented, nor where the behavior is documented.

?- throw(error(type_error(integer,a),foo)).
ERROR: Type error: `integer' expected, found `a' (an atom)

To give a few data points:

  • The entire translation is in boot/messages.pl, translate_message//1. It is not well documented. It does have a couple of hooks to change the translation of the whole thing or parts thereof. I’m afraid you have to live with the brief comment or look in the source to see when in the translation phase each of these hooks is called.
:- multifile
    prolog:message//1,              % entire message
    prolog:error_message//1,        % 1-st argument of error term
    prolog:message_context//1,      % Context of error messages
    prolog:deprecated//1,	    % Deprecated features
    prolog:message_location//1,     % (File) location of error messages
    prolog:message_line_element/2.  % Extend printing
  • ImplDefined for error(Format, ImplDefined) is normally a term context(Location,Comment) for SWI-Prolog. Typically the code raising the exception leaves this unbound. prolog_exception_hook/4, defined in library(prolog_stack) adds a backtrace if (a) the exception is not caught or (b) the exception is caught using catch_with_backtrace/3. This turns the 2nd argument into context(Backtrace, Comment). So, if you want to add a comment and keep the backtrace, use e.g., context(_, "Nice comment").

See library(prolog_stack), user:prolog_exception_hook/4.

So far, so good. Now, how is this used? These are the rough guidelines

  • Use ISO error terms when applicable. SWI-Prolog defines a few extra that I try to reuse through libraries and applications. @dtonhofer pointed out some. I use the type and domain as partly interchangeable and if there is an applicable ISO constant I use it, but otherwise I just invent my own.

Following the above, I think this should have been (as @j4n_bur53 claims) something like type_error(jpl_class_or_descriptor, Culprit), optionally with a rule for prolog:error_message//1. Now we lost the “1st arg”. We have no way to deal with this except for something like this:

 throw(error(type_error(...), context(_, 'in 1st argument'))

That is a bit too much work for me. Often it is not really a problem as most error terms carry the culprit and as the stack is printed it is fairly obvious what is the problem. Some (as @dtonhofer notes) lack this and sometimes the culprit is somewhere deeply nested in a big term and hard to find. I guess there some directions to think about:

  • Can we further improve the default error message (for example by locating the culprit in the call and highlighting it, either in color or using an additional comment)?
  • Can we somehow pass additional information through the type_error/2, etc. predicates. Ideally that should also deal with e.g. must_be/2, so we can tell the cause must_be/2 to say this is a problem with the second argument. That hints at some meta goal around these error generating predicates.
  • Shall we also use (prefer) a term for the 2nd of context/2 and have that translated by a hook, e.g., have context(_, arg(2)) to say we have a problem with the 2nd argument.
  • Shall we allow the first argument of context/2 to trim the stack. For example, if we claim jpl_new/3, the stack will not contain frames deeper than jpl_new/3. This would allow a helper of jpl_new/3 to throw an exception that is reported as coming from jpl_new/3.

That is it for now. How should we proceed? The aim should (I think) be good error messages with as little as possible work.