Did you know ... Search Documentation:
Pack nan_common -- prolog/nan_validation.pl
PublicShow source

Nan.Validation 1.2: Validation Operations (nan_validation)

This module is part of Nan.Common 1.2: Common Operations (nan_common) http://julio.diegidio.name/Projects/Prolog/Nan.Common

This module provides common operations for testing and validation of term types, domains and custom conditions, and for the construction of exception and error terms.

This module abstracts and extends the type testing and validation system provided by library(error). In particular, this module extends to the types that are documented in test_type/2.

NOTE: The type testing and validation system is extensible: specifically, error:has_type/2 is a multifile (and dynamic) predicate. See library(error) for details.

author
- J.P. Di Egidio
version
- 1.2
license
- GPL3 + SWI-Exception
To be done
- Extend the type system beyond error:has_type/2 (for type spec).
 test_type(+Type:type, @Term:any) is semidet
Succeeds if Term satisfies Type, otherwise fails.

Supports all types documented in error:must_be/2 plus those listed here:

predicateatom/nonneg
formattedtext-list or text
formal_errorcallable
term_orderoneof([=, <, >])
pair(KeyType-ValueType)KeyType-ValueType
or([Type1, ..., TypeN])Type1 or ... or TypeN
var(SubType)var or SubType
m_var(SubType)atom:var or atom:SubType
m_predicateatom:predicate or predicate
m_callableatom:callable or callable
s_callable(Struct:struct)callable and has_struct(Struct, Term) (*)
structcallable with "_terminals_" atom or var:SubType (*)
typecallable and clause(error:has_type(Term, _))

(*) The implicit predicate has_struct/2 tests functor equality of non-"terminal" sub-terms of Struct to the corresponding sub-terms of Term. For "terminal" sub-terms of Struct, specifically meaning any encountered (sub-)terms of Struct that are of type var:SubType, has_struct/2 tests that the corresponding (sub-)term of Term satisfies SubType. (Variable names in "terminals" of Struct are ignored but useful for self-documentation.)

Arguments:
Type- The type that Term must satisfy.
Term- The term to test.
Errors
- type_error: invalid argument(s).
To be done
- Extend type formal_error (to ISO?).
- Extend type type to a proper type specification (e.g. type_spec(?Type, ?Struct, ?Test, ?Validate)) (?).
 test_domain(+Type:type, :Constraint:m_callable, @Term:any) is semidet
Succeeds if Term satisfies Type and Constraint, otherwise fails.

Supports the types documented in test_type/2.

Arguments:
Type- The type that Term must satisfy.
Constraint- The constraint that Term must satisfy.
Term- The term to test.
Errors
- type_error: invalid argument(s).
 validate_type(+Type:type, @Term:any, +Message:var(formatted)) is det
 validate_type(+Type:type, @Term:any, :Caller:m_var(predicate), +Message:var(formatted)) is det
Succeeds if Term satisfies Type, otherwise throws error(type_error(Type, Term), context(Caller, Message)).

Supports the types documented in test_type/2.

NOTE: The variant validate_type/3 is translated to validate_type/4 via term rewriting, with Caller set to the (qualified) predicate indicator of the predicate containing the call.

Arguments:
Type- The type that Term must satisfy.
Term- The term to test.
Caller- (Optional) A predicate indicator representing the caller.
Message- (Optional) An error message.
Errors
- type_error: invalid argument(s).
- type_error(Type, Term)
 validate_domain(+Type:type, :Constraint:m_callable, @Term:any, +Message:var(formatted)) is det
 validate_domain(+Type:type, :Constraint:m_callable, @Term:any, :Caller:m_var(predicate), +Message:var(formatted)) is det
Succeeds if Term satisfies Type and Constraint, otherwise throws error(Error, context(Caller, Message)), where Error is type_error(Type, Term) or domain_error(constr(Type, Constraint), Term), depending on the case.

Supports the types documented in test_type/2.

NOTE: The variant validate_domain/4 is translated to validate_domain/5 via term rewriting, with Caller set to the (qualified) predicate indicator of the predicate containing the call.

Arguments:
Type- The type that Term must satisfy.
Constraint- The constraint that Term must satisfy.
Term- The term to test.
Caller- (Optional) A predicate indicator representing the caller.
Message- (Optional) An error message.
Errors
- type_error: invalid argument(s).
- type_error(Type, Term)
- domain_error(constr(Type, Constraint), Term)
 validate_condition(:Condition:m_callable, +Error:formal_error, +Message:var(formatted)) is det
 validate_condition(:Condition:m_callable, +Error:formal_error, :Caller:m_var(predicate), +Message:var(formatted)) is det
Succeeds if calling Condition succeeds, otherwise throws error(Error, context(Caller, Message)).

NOTE: The variant validate_condition/3 is translated to validate_condition/4 via term rewriting, with Caller set to the (qualified) predicate indicator of the predicate containing the call.

Arguments:
Condition- The goal representing the validation condition.
Error- The formal error to throw if Condition fails.
Caller- (Optional) A predicate indicator representing the caller.
Message- (Optional) An error message.
Errors
- type_error: invalid argument(s).
- Error
 type_exception(+Type:type, @Term:any, +Message:var(formatted), -Exception:exception) is det
 type_exception(+Type:type, @Term:any, :Caller:m_var(predicate), +Message:var(formatted), -Exception:exception) is det
Constructs an exception of the form error(type_error(Type, Term), context(Caller, Message)).

Supports the types documented in test_type/2.

NOTE: The variant type_exception/4 is translated to type_exception/5 via term rewriting, with Caller set to the (qualified) predicate indicator of the predicate containing the call.

Arguments:
Type- The type that Term must satisfy.
Term- The term to test.
Caller- (Optional) A predicate indicator representing the caller.
Message- (Optional) An error message.
Exception- The resulting exception term.
Errors
- type_error: invalid argument(s).
 domain_exception(+Type:type, :Constraint:m_callable, @Term:any, +Message:var(formatted), -Exception:exception) is det
 domain_exception(+Type:type, :Constraint:m_callable, @Term:any, :Caller:m_var(predicate), +Message:var(formatted), -Exception:exception) is det
Constructs an exception of the form error(Error, context(Caller, Message)), where Error is domain_error(constr(Type, Constraint), Term).

Supports the types documented in test_type/2.

NOTE: The variant domain_exception/5 is translated to domain_exception/6 via term rewriting, with Caller set to the (qualified) predicate indicator of the predicate containing the call.

Arguments:
Type- The type that Term must satisfy.
Constraint- The constraint that Term must satisfy.
Term- The term to test.
Caller- (Optional) A predicate indicator representing the caller.
Message- (Optional) An error message.
Exception- The resulting exception term.
Errors
- type_error: invalid argument(s).
 custom_exception(+Error:formal_error, +Message:var(formatted), -Exception:exception) is det
 custom_exception(+Error:formal_error, :Caller:m_var(predicate), +Message:var(formatted), -Exception:exception) is det
Constructs an exception of the form error(Error, context(Caller, Message)).

NOTE: The variant custom_exception/3 is translated to custom_exception/4 via term rewriting, with Caller set to the (qualified) predicate indicator of the predicate containing the call.

Arguments:
Error- The formal error.
Caller- (Optional) A predicate indicator representing the caller.
Message- (Optional) An error message.
Exception- The resulting exception term.
Errors
- type_error: invalid argument(s).
 type_error(+Type:type, @Term:any, -Error:formal_error) is det
Constructs a formal error of the form type_error(Type, Term).

Supports the types documented in test_type/2.

Arguments:
Type- The type that Term must satisfy.
Term- The term to test.
Error- The resulting error term.
Errors
- type_error: invalid argument(s).
 domain_error(+Type:type, :Constraint:m_callable, @Term:any, -Error:formal_error) is det
Constructs a formal error of the form domain_error(constr(Type, Constraint), Term).

Supports the types documented in test_type/2.

Arguments:
Type- The type that Term must satisfy.
Constraint- The constraint that Term must satisfy.
Term- The term to test.
Error- The resulting error term.
Errors
- type_error: invalid argument(s).
 current_caller(-Caller:m_callable) is det
Returns in Caller the (qualified) predicate indicator of the predicate containing the call.

NOTE: An invocation to this predicate is translated via term rewriting as shown in the following example:

For a predicate =my_mod:my_pred/1= such as:

==
my_pred(X) :- ..., current_caller(Caller), ...
==

The translation would be:

==
my_pred(X) :- ..., Caller = my_mod:my_pred/1, ...
==
Arguments:
Caller- The qualified predicate indicator for the caller.

Undocumented predicates

The following predicates are exported, but not or incorrectly documented.

 validate_type(Arg1, Arg2, Arg3, Arg4)
 validate_domain(Arg1, Arg2, Arg3, Arg4, Arg5)
 validate_condition(Arg1, Arg2, Arg3, Arg4)
 type_exception(Arg1, Arg2, Arg3, Arg4, Arg5)
 domain_exception(Arg1, Arg2, Arg3, Arg4, Arg5, Arg6)
 custom_exception(Arg1, Arg2, Arg3, Arg4)