View source with raw comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        jan@swi-prolog.org
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2024, SWI-Prolog Solutions b.v.
    7    All rights reserved.
    8
    9    Redistribution and use in source and binary forms, with or without
   10    modification, are permitted provided that the following conditions
   11    are met:
   12
   13    1. Redistributions of source code must retain the above copyright
   14       notice, this list of conditions and the following disclaimer.
   15
   16    2. Redistributions in binary form must reproduce the above copyright
   17       notice, this list of conditions and the following disclaimer in
   18       the documentation and/or other materials provided with the
   19       distribution.
   20
   21    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   22    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   23    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   24    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   25    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   26    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   27    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   28    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   29    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   30    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   31    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   32    POSSIBILITY OF SUCH DAMAGE.
   33*/
   34
   35:- module(exceptions,
   36          [ catch/4,                    % :Goal, :ErrorType, ?Ball, :Recover
   37            exception/2,                % :ExceptionType, ?Ball
   38            exception_type/2            % +Type, +Term
   39          ]).   40:- use_module(library(error)).   41:- set_prolog_flag(generate_debug_info, false).   42
   43:- meta_predicate
   44    catch(0, :, ?, 0),
   45    exception(:,?).   46:- multifile
   47    error_term/2,                       % Type, Formal
   48    exception_term/2.                   % Type, Exception

Exception classification

Prolog catch/3 selects errors based on unification. This is problematic for two reasons. First, one typically wants the exception term to be more specific than the term passed to the 2nd (Ball) argument of catch/3. Second, in many situations one wishes to select multiple errors that may be raised by some operations, but let the others pass. Unification is often not suitable for this. For example, open/3 can raise an existence_error or a permission_error (and a couple more), but existence_error are also raised on, for example, undefined procedures. This is very hard to specify, Below is an attempt that still assumes nothing throws error(_,_).

    catch(open(...), error(Formal,ImplDefined),
          (   ( Formal = existence_error(source_sink,_)
              ; Formal = permission_error(open, source_sink, _)
              )
          ->  <handle>
          ;   throw(Formal, ImplDefined)
          )),
    ...

Besides being hard to specify, actual Prolog systems define a large number of additional error terms because there is no reasonable ISO exception defined. For example, SWI-Prolog open/3 may raise resource_error(max_files) if the maximum number of file handles of the OS is exceeded.

As a result, we see a lot of Prolog code in the wild that simply uses the construct below to simply fail. But, this may fail for lack of stack space, a programmer error that causes a type error, etc. This both makes it much harder to debug the code and provide meaningful feedback to the user of the application.

    catch(Goal, _, fail)

Many programing languages have their exceptions organised by a (class) hierarchy. Prolog has no hierarchy of terms. We introduce exception/2 as exception(+Type, ?Term), which can both be used as a type test for an exception term and as a constraint for the Ball of catch/3. Using a predicate we can express abstractions over concrete exception terms with more flexibility than a hierarchy. Using a multifile predicate, libraries can add their exceptions to defined types or introduce new types.

The predicate catch/4 completes the interface. */

 catch(:Goal, +ExceptionType, ?Ball, :Recover)
As catch/3, only catching exceptions for which exception(ErrorType,Ball) is true. See error/2. For example, the code below properly informs the user some file could not be processed due do some issue with File, while propagating on all other reasons while process/1 could not be executed.
    catch(process(File), file_error, Ball,
          file_not_processed(File, Ball))

file_not_processed(File, Ball) :-
    message_to_string(Ball, Msg),
    format(user_error, 'Could not process ~p: ~s', [File, Msg]).
  119:- noprofile(catch/4).  120
  121catch(Goal, ErrorType, Ball, Recover) :-
  122    exception(ErrorType, Ball),
  123    catch(Goal, Ball, Recover),
  124    del_attr(Ball, freeze).
 exception(:Type, --Ball) is det
exception(:Type, +Ball) is semidet
If Ball is unbound, adds a delayed goal that tests the error belongs to Type when Ball is instantiated (by catch/3). Else succeed is error is of the specified Type.

Note that the delayed goal is added using freeze/2 and therefore the stepwise instantiation of Ball does not work, e.g. exception(file_error, error(Formal,_)) immediately fails.

Error types may be defined or extended (e.g., by libraries) by adding clauses to the multifile predicates error_term/2 and exception_term/2. Modules may (re-)define local error types using the exception_type/2 directive.

  142exception(Type, Ball) :-
  143    freeze(Ball, is_exception(Type, Ball)).
  144
  145is_exception(M:Type, Ball) :-
  146    is_exception(Type, M, Ball).
  147
  148is_exception((A;B), M, Ball) =>
  149    (   is_exception(A, M, Ball)
  150    ->  true
  151    ;   is_exception(B, M, Ball)
  152    ).
  153is_exception(\+A, M, Ball) =>
  154    \+ is_exception(A, M, Ball).
  155is_exception(Type, M, Ball) =>
  156    (   ex_term(Type, M, Pattern)
  157    *-> subsumes_term(Pattern, Ball),
  158        !
  159    ;   existence_error(exception_type, Type)
  160    ).
 ex_term(+Type, +Module, -Term) is nondet
  164ex_term(Type, Module, error(Term,_)) :-
  165    (   current_predicate(Module:'$error_term'/2),
  166        Module:'$error_term'(Type, Term)
  167    *-> true
  168    ;   error_term(Type, Term)
  169    ).
  170ex_term(Type, Module, Term) :-
  171    (   current_predicate(Module:'$exception_term'/2),
  172        Module:'$exception_term'(Type, Term)
  173    *-> true
  174    ;   exception_term(Type, Term)
  175    ).
 error_term(?Type, ?Term) is nondet
Describe the formal part of error(Formal,ImplDefined) exceptions.
  181error_term(file_error, existence_error(source_sink, _Culprit)).
  182error_term(file_error, permission_error(open, source_sink, _Culprit)).
  183error_term(file_error, resource_error(max_files)).
  184error_term(file_error, representation_error(max_symbolic_links)).
  185error_term(file_error, representation_error(max_path_length)).
  186
  187error_term(network_error, socket_error(_Code, _Message)).
  188error_term(network_error, timeout_error(_Operation, _Culprit)).
  189error_term(network_error, io_error(_Operation, _Culprit)).
  190
  191error_term(timeout, timeout_error(_Operation, _Culprit)).
  192
  193error_term(evaluation_error, evaluation_error(_)).
 exception_term(?Type, ?Term) is nondet
Describe exceptions that are not error(Formal, _) terms.
  199exception_term(timeout, time_limit_exceeded).
  200exception_term(timeout, time_limit_exceeded(_TimeLimit)).
 exception_type(+Type, +Term)
Declare all exceptions subsumed by Term to be an exception of Type. This declaration is module specific.
  207exception_type(Type, Term) :-
  208    throw(error(context_error(nodirective, exception_type(Type, Term)), _)).
  209
  210exception_type_clause(Type, error(Formal, Var), Clause),
  211    ground(Type), var(Var) =>
  212    Clause = '$error_term'(Type, Formal).
  213exception_type_clause(Type, Exception, Clause),
  214    ground(Type) =>
  215    Clause = '$exception_term'(Type, Exception).
  216
  217add_decl(Clause, Clauses) :-
  218    prolog_load_context(module, Module),
  219    pi_head(PI, Clause),
  220    (   current_predicate(Module:PI)
  221    ->  Clauses = Clause
  222    ;   Module == user
  223    ->  Clauses = [(:- multifile(PI)), Clause]
  224    ;   Clauses = [(:- discontiguous(PI)), Clause]
  225    ).
  226
  227system:term_expansion((:-exception_type(Type, Term)), Clauses) :-
  228    exception_type_clause(Type, Term, Clause),
  229    add_decl(Clause, Clauses)