1:- module(
2 type_ext,
3 [
4 boolean/1, 5 positive_integer/1 6 ]
7).
20:- use_module(library(error)). 21:- use_module(library(lists)). 22
23:- use_module(library(dict)). 24
25:- multifile
26 error:has_type/2. 27
28error:has_type(maybe(Type), Term) :-
29 ( error:has_type(Type, Term)
30 ; error:has_type(var, Term)
31 ).
32error:has_type(options, Term) :-
33 error:has_type(dict, Term),
34 dict_key(Term, options).
35error:has_type(or(Types), Term) :-
36 member(Type, Types),
37 error:has_type(Type, Term), !.
43boolean(false).
44boolean(true).
50positive_integer(Term) :-
51 error:has_type(positive_integer, Term)
Extended support for types
Extends support for types in the SWI-Prolog standard library.
This module introduces the following types:
options
: A dictionary with tagoptions
that is used to represent options passed to predicates.*/