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( , , , ), 45 exception( , ). 46:- multifile 47 error_term/2, % Type, Formal 48 exception_term/2. % Type, Exception 49 50/** <module> Exception classification 51 52Prolog catch/3 selects errors based on unification. This is problematic 53for two reasons. First, one typically wants the exception term to be 54more specific than the term passed to the 2nd (`Ball`) argument of 55catch/3. Second, in many situations one wishes to select multiple errors 56that may be raised by some operations, but let the others pass. 57Unification is often not suitable for this. For example, open/3 can 58raise an _existence_error_ or a _permission_error_ (and a couple more), 59but _existence_error_ are also raised on, for example, undefined 60procedures. This is very hard to specify, Below is an attempt that 61still assumes nothing throws error(_,_). 62 63``` 64 catch(open(...), error(Formal,ImplDefined), 65 ( ( Formal = existence_error(source_sink,_) 66 ; Formal = permission_error(open, source_sink, _) 67 ) 68 -> <handle> 69 ; throw(Formal, ImplDefined) 70 )), 71 ... 72``` 73 74Besides being hard to specify, actual Prolog systems define a large 75number of additional error terms because there is no reasonable ISO 76exception defined. For example, SWI-Prolog open/3 may raise 77resource_error(max_files) if the maximum number of file handles of the 78OS is exceeded. 79 80As a result, we see a lot of Prolog code in the wild that simply uses 81the construct below to simply fail. But, this may fail for lack of stack 82space, a programmer error that causes a type error, etc. This both makes 83it much harder to debug the code and provide meaningful feedback to the 84user of the application. 85 86``` 87 catch(Goal, _, fail) 88``` 89 90Many programing languages have their exceptions organised by a (class) 91hierarchy. Prolog has no hierarchy of terms. We introduce exception/2 as 92exception(+Type, ?Term), which can both be used as a type test for an 93exception term and as a _constraint_ for the `Ball` of catch/3. Using a 94predicate we can express abstractions over concrete exception terms with 95more flexibility than a hierarchy. Using a _multifile_ predicate, 96libraries can add their exceptions to defined types or introduce new 97types. 98 99The predicate catch/4 completes the interface. 100*/ 101 102%! catch(:Goal, +ExceptionType, ?Ball, :Recover) 103% 104% As catch/3, only catching exceptions for which 105% exception(ErrorType,Ball) is true. See error/2. For example, the 106% code below properly informs the user some file could not be 107% processed due do some issue with `File`, while propagating on all 108% other reasons while process/1 could not be executed. 109% 110% ``` 111% catch(process(File), file_error, Ball, 112% file_not_processed(File, Ball)) 113% 114% file_not_processed(File, Ball) :- 115% message_to_string(Ball, Msg), 116% format(user_error, 'Could not process ~p: ~s', [File, Msg]). 117% ``` 118 119:- noprofile(catch/4). 120 121catch(Goal, ErrorType, Ball, Recover) :- 122 exception(ErrorType, Ball), 123 catch(Goal, Ball, Recover), 124 del_attr(Ball, freeze). 125 126%! exception(:Type, --Ball) is det. 127%! exception(:Type, +Ball) is semidet. 128% 129% If Ball is unbound, adds a delayed goal that tests the error belongs 130% to Type when Ball is instantiated (by catch/3). Else succeed is 131% error is of the specified Type. 132% 133% Note that the delayed goal is added using freeze/2 and therefore the 134% stepwise instantiation of Ball does not work, e.g. 135% exception(file_error, error(Formal,_)) immediately fails. 136% 137% Error types may be defined or extended (e.g., by libraries) by 138% adding clauses to the multifile predicates error_term/2 and 139% exception_term/2. _Modules_ may (re-)define local error types using 140% the exception_type/2 directive. 141 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 ). 161 162%! ex_term(+Type, +Module, -Term) is nondet. 163 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 ). 176 177%! error_term(?Type, ?Term) is nondet. 178% 179% Describe the formal part of error(Formal,ImplDefined) exceptions. 180 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(_)). 194 195%! exception_term(?Type, ?Term) is nondet. 196% 197% Describe exceptions that are not error(Formal, _) terms. 198 199exception_term(timeout, time_limit_exceeded). 200exception_term(timeout, time_limit_exceeded(_TimeLimit)). 201 202%! exception_type(+Type, +Term) 203% 204% Declare all exceptions subsumed by Term to be an exception of Type. 205% This declaration is module specific. 206 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 227systemterm_expansion((:-exception_type(Type, Term)), Clauses) :- 228 exception_type_clause(Type, Term, Clause), 229 add_decl(Clause, Clauses)