Skip to content

Commit

Permalink
Layout, PlDoc comment [no ci]
Browse files Browse the repository at this point in the history
  • Loading branch information
JanWielemaker committed Oct 7, 2024
1 parent 1beb59e commit 7562672
Showing 1 changed file with 16 additions and 15 deletions.
31 changes: 16 additions & 15 deletions library/error.pl
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@
Author: Jan Wielemaker
E-mail: [email protected]
WWW: http://www.swi-prolog.org
Copyright (c) 2006-2023, University of Amsterdam
Copyright (c) 2006-2024, University of Amsterdam
VU University Amsterdam
SWI-Prolog Solutions b.v.
All rights reserved.
Expand Down Expand Up @@ -142,11 +142,11 @@
% is, but if some variables are bound to appropriate values it would
% be acceptable.
%
% @param FormalSubTerm is the term that needs (further)
% instantiation. Unfortunately, the ISO error does not allow
% for passing this term along with the error, but we pass it
% to this predicate for documentation purposes and to allow
% for future enhancement.
% @arg FormalSubTerm is the term that needs (further)
% instantiation. Unfortunately, the ISO error does not allow
% for passing this term along with the error, but we pass it
% to this predicate for documentation purposes and to allow
% for future enhancement.

instantiation_error(_FormalSubTerm) :-
throw(error(instantiation_error, _)).
Expand Down Expand Up @@ -204,11 +204,11 @@
%! must_be(+Type, @Term) is det.
%
% True if Term satisfies the type constraints for Type. Defined
% types are =atom=, =atomic=, =between=, =boolean=, =callable=,
% =chars=, =codes=, =text=, =compound=, =constant=, =float=,
% =integer=, =nonneg=, =positive_integer=, =negative_integer=,
% =nonvar=, =number=, =oneof=, =list=, =list_or_partial_list=,
% =symbol=, =var=, =rational=, =encoding=, =dict= and =string=.
% types are `atom`, `atomic`, `between`, `boolean`, `callable`,
% `chars`, `codes`, `text`, `compound`, `constant`, `float`,
% `integer`, `nonneg`, `positive_integer`, `negative_integer`,
% `nonvar`, `number`, `oneof`, `list`, `list_or_partial_list`,
% `symbol`, `var`, `rational`, `encoding`, `dict` and `string`.
%
% Most of these types are defined by an arity-1 built-in predicate
% of the same name. Below is a brief definition of the other
Expand All @@ -218,7 +218,7 @@
% | any | any term |
% | between(FloatL,FloatU) | Number [FloatL..FloatU] |
% | between(IntL,IntU) | Integer [IntL..IntU] |
% | boolean | One of =true= or =false= |
% | boolean | One of `true` or `false` |
% | callable | Atom or compound term |
% | char | Atom of length 1 |
% | chars | Proper list of 1-character atoms |
Expand All @@ -241,13 +241,13 @@
% | proper_list | Same as list |
% | stream | A stream name or valid stream handle; see is_stream/1 |
% | symbol | Same as `atom` |
% | text | One of =atom=, =string=, =chars= or =codes= |
% | text | One of `atom`, `string`, `chars` or `codes` |
% | type | Term is a valid type specification |
%
% In addition, types may be composed using `TypeA,TypeB`,
% `TypeA;TypeB` and negated using `\Type`.
%
% @throws instantiation_error if Term is insufficiently
% @error instantiation_error if Term is insufficiently
% instantiated and type_error(Type, Term) if Term is not of Type.

must_be(Type, X) :-
Expand Down Expand Up @@ -357,7 +357,8 @@
has_type(any, _).
has_type(atom, X) :- atom(X).
has_type(atomic, X) :- atomic(X).
has_type(between(L,U), X) :- ( integer(L)
has_type(between(L,U), X) :-
( integer(L)
-> integer(X), between(L,U,X)
; number(X), X >= L, X =< U
).
Expand Down

0 comments on commit 7562672

Please sign in to comment.