A The SWI-Prolog library
All Application Manual Name SummaryHelp

  • 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
        • library(exceptions): Exception classification
          • catch/4
          • exception/2
          • error_term/2
          • exception_term/2
          • exception_type/2
        • 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(macros): Macro expansion
        • 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_coverage): Coverage analysis tool
        • library(prolog_debug): User level debugging tools
        • library(prolog_jiti): Just In Time Indexing (JITI) utilities
        • library(prolog_trace): Print access to predicates
        • library(prolog_versions): Demand specific (Prolog) versions
        • 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(rwlocks): Read/write locks
        • 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.17 library(exceptions): 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]).
[det]exception(:Type, --Ball)
[semidet]exception(:Type, +Ball)
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.

[nondet,multifile]error_term(?Type, ?Term)
Describe the formal part of error(Formal,ImplDefined) exceptions.
[nondet,multifile]exception_term(?Type, ?Term)
Describe exceptions that are not error(Formal, _) terms.
exception_type(+Type, +Term)
Declare all exceptions subsumed by Term to be an exception of Type. This declaration is module specific.