Did you know ... | Search Documentation: |
Pack pack_errors -- prolog/pack_errors.pl |
This is a stoics.infrastructure pack that
Version 0.3 introduced type errors via type/3 on top of must_be/2.
Version 2.0 has been re-written to be Options centric, fully decoupled and introduced of_same_length/3.
The pack manage mid-level error handling in a uniform way so other packs can use SWI's infracture in a simple way. The user only needs to define the print messages (if the pre-canned ones are not suitable) and then throw the appropriate terms during execution.
Two simple ways to identifying originating caller are provided by allowing options in either the message, or via using an new version of throw, throw/2.
In addition the library includes a number or pre-canned messages and has evolved to provide some error related predicates.
Any term recognised as the first argument of the defined message/3 can be made to spit
a token identifying the originating pack/module and predicate. The main intuition is that this is the
the predicate responsible for the error. You can do this by either wrapping the message or by using
pack_error's own version of throw, throw/2.
Wrapping is via pack_error/2 where the first argument is the message and second is a list of options.
?- throw( pack_error(lengths_mismatch(a,b,1,2),[]) ). ERROR: Lists for a and b have mismatching lengths: 1 and 2 respectively ?- throw( pack_error(lengths_mismatch(a,b,1,2),[foo:bar/1]) ). ERROR: foo:bar/1: Lists for a and b have mismatching lengths: 1 and 2 respectively
You can also use throw/2, which is defined in the pack, without wrapping the Message,
?- throw( lengths_mismatch(a,b,1,2), [foo:bar/1] ). ERROR: foo:bar/1: Lists for a and b have mismatching lengths: 1 and 2 respectively
In both cases, you can drop the list if it contains a single element, thus
?- throw( lengths_mismatch(a,b,1,2), foo:bar/1 ). ERROR: foo:bar/1: Lists for a and b have mismatching lengths: 1 and 2 respectively
Note that in the latter case (throw/2) the options can also contain terms controling the execution of throw/2.
Options in both cases provide the context:
The library is loosely designed around the principle that most packs will define a homonym module. If both Pack and Mod are given and are the same only one is printed, however if they differ, they will both be shown. The order of identification is that of going throough the list above from top to bottom. The first one matching will identify the predicate and stop looking, so alternatives will be ignored.
Argument errors.
Poss is a list of (argument) positions and Args a list of arguments.
arg_enumerate(Pos,Vals,Arg)
see also type/3arg_ground(Pos,Arg)
,
ground argument(s)
were expected at Posarg_ground_in_one_of(Poss,Args)
at least one ground argument was expected in a list of arguments (Args)arg_ground_pattern(Poss,Args)
Printing of Arg(s) itself can be surpressed with prolog_flag(pack_errors_arg,false)
- useful for long data.
Other errors
cast(Term,From,To)
)lengths_mismatch(Tkn1,Tkn2,Len1,Len2)
lengths_mismatch(Tkn1,Tkn2,Op,Len1,Len2)
type_error(Type,Term)
type_error(Pos,Type,Term)
wrong_token(Tkn,Cat)
?- throw( pack_error(arg_ground(3,name), os:os_ext/3) ). ERROR: os:os_ext/3: Ground argument expected at position: 3, (found: name) ?- throw( pack_error(arg_ground(3,name(_)), os:os_ext/3) ). ERROR: os:os_ext/3: Ground argument expected at position: 3, (found: name(_4210)) ?- set_prolog_flag(pack_errors_arg,true). % this is the default, so no change in behaviour: ?- throw( pack_error(arg_ground(3,name(_)), os:os_ext/3) ). ERROR: os:os_ext/3: Ground argument expected at position: 3, (found: name(_4210)) ?- set_prolog_flag(pack_errors_arg,false). ?- throw( pack_error(arg_ground(3,name(_)), os:os_ext/3) ). ERROR: os:os_ext/3: Ground argument expected at position: 3 ?- set_prolog_flag(pack_errors_arg,true). ?- throw( pack_error(arg_enumerate(3,[a,b,c],d), [pack(os),pred(os_pred/3)]) ). ERROR: os:os_pred/3: Term at position: 3, is not one of: [a,b,c], (found: d) % use throw/2 as it makes code clearer: ?- throw( arg_enumerate(3,[a,b,c],d), os:os_pred/3 ). ERROR: os:os_pred/3: Term at position: 3, is not one of: [a,b,c], (found: d) ?- throw( arg_enumerate(3,[a,b,c],d), [pack(os),os_pred/3] ). ERROR: os:os_pred/3: Term at position: 3, is not one of: [a,b,c], (found: d) ?- throw( lengths_mismatch(a,b,1,2), [pack(foo)] ). ERROR: foo:_Unk: Lists for a and b have mismatching lengths: 1 and 2 respectively ?- throw( lengths_mismatch(a,b,1,2), pred(bar/1) ). ERROR: _Unk:bar/1: Lists for a and b have mismatching lengths: 1 and 2 respectively ?- throw( cast(abc('file.csv'),atom), os:os_term/2 ). ERROR: os:os_term/2: Cannot cast: abc(file.csv), to type: atom
Examples from other packs:
?- map_list_options( plus_one, In, [2,3,4,5], [add_options(maybe),on_fail(skip)] ). ERROR: false:map_list_options/4 @ option(add_options): Object of type: boolean, expected but found term: maybe
Example file (available at pack('pack_errors/examples/fold_data_errors.pl')
):
:- multifile( pack_errors:message/3 ). pack_errors:message( fold_data_insufficient(Dlen,N) ) --> ['Insufficient length of data (~d) as ~d folds are required'-[Dlen,N]]. pack_errors:message( fold_data_residual(Dlen) ) --> ['Residual data of length: ~d while splitting folds'-[Dlen]].
Load and try with
?- [pack('pack_errors/examples/fold_data_errors')]. ?- throw( pack_error(fold_data_insufficient(10,20),true) ). ERROR: Insufficient length of data (10) as 20 folds are required ?- throw( fold_data_insufficient(10,20), mlu:ten_fold/3 ). ERROR: mlu:ten_fold/3: Insufficient length of data (10) as 20 folds are required
The library reacts to debug(pack_errors)
spitting informational message along the execution of library predicates.
Pack predicates:
+Error, +Opts
+Goal, +Error, +Opts
+Type, +Term
+Term, -Groundness
+Pid, +From, +Opts
+Lists
+List1, +List2, +Opts
+Version, +Date
Pack defined errors selection: (see pack('pack_errors/prolog/pack_errors.pl')
for a full list)
arg_ground(Pos,Arg)
arg_ground_in_one_of(Poss,Args)
lengths_mismatch(Tkn1,Tkn2,Len1,Len2)
cast(Term,To)
Opts
?- caught( fail, my_exception(on_data), true ). ERROR: Unhandled exception: pack_error(my_exception(on_data),[on_exit(error),message(error)]) ?- caught( fail, my_exception(on_data), on_exit(true) ). false % it fails because the message writing fails, which is probably best ?- caught( false, os_exists_not(abc), [] ). ERROR: OS entity: abc, does not exist ?- caught( false, os_exists_not(abc), on_exit(error) ). ERROR: OS entity: abc, does not exist ?- caught( false, os_exists_not(abc), on_exit(fail) ). ERROR: OS entity: abc, does not exist false. ?- caught( false, os_exists_not(abc), on_exit(true) ). ERROR: OS entity: abc, does not exist true.
partial
and false
are collapsed to false
.
Groundness
?- ground( abc, Abc ), ground( de(F), Def ), ground( GHI, Ghi ). Abc = true, Def = partial, Ghi = false. ?- ground_binary( abc, Abc ), ground_binary( de(F), Def ), ground_binary( GHI, Ghi ). Abc = true, Def = Ghi, Ghi = false.
throw()
decouples type of message printing and execution behaviour.<br>
As of version 0.3 this should be the adviced entry point for message writing and ball throwing for stoics packs.
Opts
Level = error
and OnExit = error
Level=quiet
and OnExit = false
Level=warning
and OnExit = false
[true,false,error]
. if not given the default depends on Err,
foo:bar/1
or bar/2
)?- throw( cast(abc('file.csv'),atom) ). ERROR: Unhandled exception: cast(abc(file.csv),atom) ?- throw( pack_error(cast(abc('file.csv'),atom),true) ). ERROR: Cannot cast: abc(file.csv), to type: atom ?- Opt = os:os_exists/2, throw(pack_error(cast(abc('file.csv'),atom),Opt)), writeln(later). ERROR: os:os_exists/2: Cannot cast: abc(file.csv), to type: atom ?- throw(cast(abc('file.csv'),atom), os:os_exists/2), writeln(later). ERROR: os:os_exists/2: Cannot cast: abc(file.csv), to type: atom ?- throw(cast(abc('file.csv'),atom), err(test)), writeln(later). false. ?- _Opts = [message(quiet),on_exit(true)], throw(cast(abc('file.csv'),atom), _Opts), writeln(later). later true. ?- _Opts = [message(warning),on_exit(true)], throw(cast(abc('file.csv'),atom), _Opts), writeln(later). Warning: Cannot cast: abc(file.csv), to type: atom later true. ?- _Opts = [message(informational),on_exit(true)], throw(cast(abc('file.csv'),atom), _Opts), writeln(later). % Cannot cast: abc(file.csv), to type: atom later true. ?- _Opts = [message(warning),on_exit(false)], throw(cast(abc('file.csv'),atom), _Opts), writeln(later). Warning: Cannot cast: abc(file.csv), to type: atom false. ?- throw(cast(abc('file.csv'),atom), err(exists)), writeln(later). Warning: Cannot cast: abc(file.csv), to type: atom false. ?- throw(cast(abc('file.csv'),atom), on_exit(true)), writeln(later). ERROR: Cannot cast: abc(file.csv), to type: atom later true. ?- throw(cast(abc('file.csv'),atom), on_exit(false)), writeln(later). ERROR: Cannot cast: abc(file.csv), to type: atom false. ?- throw(cast(abc('file.csv'),atom), on_exit(error)), writeln(later). ERROR: Cannot cast: abc(file.csv), to type: atom ?- throw(cast(abc('file.csv'),atom), message(warning)), writeln(later). Warning: Cannot cast: abc(file.csv), to type: atom ?- throw(cast(abc('file.csv'),atom), message(informational)), writeln(later). % Cannot cast: abc(file.csv), to type: atom later true. ?- _Opts = [message(informational),on_exit(false)], throw(cast(abc('file.csv'),atom), _Opts), writeln(later). % Cannot cast: abc(file.csv), to type: atom false. ?- _Opts = [message(informational),on_exit(error)], throw(cast(abc('file.csv'),atom), _Opts), writeln(later). % Cannot cast: abc(file.csv), to type: atom
call(Callable)
), which will succeed iff
call( Callable, Term )
succeeds. It also enhances must_be/2 by adding options.
In the case of a call-wrapped type, the call to type/3 will succeed iff
call(Callable,Term)
succeeds.
Opts (unlisted is ok)
?- type( boolean, maybe ). ERROR: Object of type: boolean, expected but found term: maybe ?- type( boolean, maybe, error(false) ). false. ?- type( boolean, maybe, pack(sure) ). ERROR: pack(sure): Object of type: boolean, expected but found term: maybe ?- type( boolean, maybe, [pack(sure),pred(lost/2)] ). ERROR: sure:lost/2: Object of type: boolean, expected but found term: maybe ?- type( boolean, maybe, [pack(sure),pred(lost/2+3)] ). ERROR: sure:lost/2+3: Object of type: boolean, expected but found term: maybe ?- type( boolean, maybe, [pack(sure),pred(1+lost/2)] ). ERROR: sure:1+lost/2: Object of type: boolean, expected but found term: maybe ?- type( boolean, maybe, [pack(sure),pred(lost(arg1)/2)] ). ERROR: sure:lost(arg1)/2: Object of type: boolean, expected but found term: maybe
load(true)
)pack(lib)
's lib(suggests(Pack))
to, on-demand,
Note that pack(lib)
also provides
lib(suggests(Pid,Load))
which is an alternative and more automatic way to achieve demand driven loading via hot-swapping.
:- lib(suggests(Pack))
silently fails if Pack is not present. This is intendent for dependendencies that do not impact major parts for the importing pack. Thus allow common use without grabbing all dependencies that may not be needed for a particular user.
Opts are passed to throw/2, except for:
load(Load=false)
?- defined( abc/0, pack(b_real) ). ERROR: Predicate: abc/0 is not defined (source apparently available at: pack(b_real); not asked to load) ?- defined( abc/0, false ). ERROR: Predicate: abc/0 is not defined ?- defined( abc/0, false, pack(sourcey) ). ERROR: sourcey:$unknown/0: Predicate: abc/0 is not defined ?- defined( abc/0, pack(b_real), [pack(sourcey),pred(foo/1;2)] ). ERROR: sourcey:foo/1;2: Predicate: abc/0 is not defined (source apparently available at: pack(b_real); not asked to load) ?- defined( b_real/0, pack(b_real), [as_pack_err(true),load(library(b_real))] ). true.
The above only succeeds if b_real is an install library and defines b_real/0.
From or Load can have the special form: lib(CodeLib)
. This assumes pack(lib)
is installed and lib/1
will be used to load the requested CodeLib.
?- defined( b_real/0, lib(b_real), load(true) ).
Will again, only succeed if b_real is installed and defines b_real/0. In this occasion library(lib)
should be also installed.
In order to disambiguate between the two versions of the arity 2,
in that scenario options should be a term of the form opts(OptsL)
.
Opts are passed to throw/2, the only local one is:
action(Act)
of_same_length(Lng1,Lng2,Tkn1,Tkn2)
token1(Tkn1=1)
name of List1
(used in error throwing to id the list)token2(Tkn2=n)
name of List2 (used in error throwing)
when first argument is Lists, Tkn2 will be the index position of the first list length-mismatch the head list?- of_same_length( [a,b,c], [1,2,3] ). true. ?- of_same_length( [[a,b,c],[1,2,3]] ). true. ?- of_same_length( [1,2,3], [a,b], token1(first) ). ERROR: Lists for first and 2 have mismatching lengths: 3 and 2 respectively
V = 2:2:0, D = date(2022, 12, 29).
The following predicates are exported, but not or incorrectly documented.