Types and properties related to assertions
Author(s): Manuel Hermenegildo.
This module is part of the assertions library. It provides the formal definition of the syntax of several forms of assertions and describes their meaning. It does so by defining types and properties related to the assertions themselves. The text describes, for example, the overall fields which are admissible in the bodies of assertions, where properties can be used inside these bodies, how to combine properties for a given predicate argument (e.g., conjunctions) , etc. and provides some examples.
Usage and interface
- Library usage:
:- use_module(library(assertions_props)). - Exports:
- Imports:
- Internal (engine) modules:
term_basic, arithmetic, atomic_basic, basic_props, basiccontrol, data_facts, exceptions, io_aux, io_basic, prolog_flags, streams_basic, system_info, term_compare, term_typing, hiord_rt, debugger_support. - Packages:
prelude, nonpure, dcg, assertions, regtypes.
- Internal (engine) modules:
Documentation on exports
Pr [:: DP] [: CP] [=> AP] [+ GP] [# CO]
where (fields between [...] are optional):
- Pr is a head pattern (head_pattern/1) which describes the predicate or property and possibly gives some implicit call/answer information.
- DP is a (possibly empty) complex argument property (complex_arg_property/1) which expresses properties which are compatible with the predicate, i.e., instantiations made by the predicate are compatible with the properties in the sense that applying the property at any point would not make it fail.
- CP is a (possibly empty) complex argument property (complex_arg_property/1) which applies to the calls to the predicate.
- AP is a (possibly empty) complex argument property (complex_arg_property/1) which applies to the answers to the predicate (if the predicate succeeds). These only apply if the (possibly empty) properties given for calls in the assertion hold.
- GP is a (possibly empty) complex goal property (complex_goal_property/1) which applies to the whole execution of a call to the predicate. These only apply if the (possibly empty) properties given for calls in the assertion hold.
- CO is a comment string (docstring/1). This comment only applies if the (possibly empty) properties given for calls in the assertion hold. The usual formatting commands that are applicable in comment strings can be used (see stringcommand/1).
See the lpdoc manual for documentation on assertion comments.
Usage:assrt_body(X)
X is an assertion body.
- A variable. This is useful in order to be able to refer to the corresponding argument positions by name within properties and in comments. Thus, p(Input,Parameter,Output) is a valid head pattern.
- A variable, as above, but preceded by a “mode.” This mode determines in a compact way certain call or answer properties. For example, the head pattern p(Input,+Parameter,Output) is valid, as long as +/1 is declared as a mode.
Acceptable modes are documented in library(basicmodes) and library(isomodes). User defined modes are documented in modedef/1.
- Any term. In this case this term determines the instantiation state of the corresponding argument position of the predicate calls to which the assertion applies.
- A ground term preceded by a “mode.” The ground term determines a property of the corresponding argument. The mode determines if it applies to the calls and/or the successes. The actual property referred to is that given by the term but with one more argument added at the beginning, which is a new variable which, in a rewriting of the head pattern, appears at the argument position occupied by the term. For example, the head pattern p(Input,+list(int),Output) is valid for mode +/1 defined in library(isomodes), and equivalent in this case to having the head pattern p(Input,A,Output) and stating that the property list(A,int) holds for the calls of the predicate.
- Any term preceded by a “mode.” In this case, only one variable is admitted, it has to be the first argument of the mode, and it represents the argument position. I.e., it plays the role of the new variable mentioned above. Thus, no rewriting of the head pattern is performed in this case. For example, the head pattern p(Input,+(Parameter,list(int)),Output) is valid for mode +/2 defined in library(isomodes), and equivalent in this case to having the head pattern p(Input,Parameter,Output) and stating that the property list(Parameter,int) holds for the calls of the predicate.
Usage:head_pattern(Pr)
Pr is a head pattern.
Props is a (possibly empty) complex argument property. Such properties can appear in two formats, which are defined by property_conjunction/1 and property_starterm/1 respectively. The two formats can be mixed provided they are not in the same field of an assertion. I.e., the following is a valid assertion:
:- pred foo(X,Y) : nonvar * var => (ground(X),ground(Y)).
Usage:complex_arg_property(Props)
Props is a (possibly empty) complex argument property
- (integer(X),list(Y,integer)): X has the property integer/1 and Y has the property list/2, with second argument integer.
Usage:property_conjunction(Props)
Props is either a term or a conjunction of terms. The main functor and arity of each of those terms corresponds to the definition of a property. The first argument of each such term is a variable which appears as a head argument.
- integer * list(integer): the first argument of the procedure (or function, or ...) has the property integer/1 and the second one has the property list/2, with second argument integer.
- {integer,var} * list(integer): the first argument of the procedure (or function, or ...) has the properties integer/1 and var/1 and the second one has the property list/2, with second argument integer.
Usage:property_starterm(Props)
Props is either a term or several terms separated by */2. The main functor of each of those terms corresponds to that of the definition of a property, and the arity should be one less than in the definition of such property. All arguments of each such term are ground.
Props is a (possibly empty) complex goal property. Such properties can be either a term or a conjunction of terms. The main functor and arity of each of those terms corresponds to the definition of a property. Such properties apply to all executions of all goals of the predicate which comply with the assertion in which the Props appear.
The arguments of the terms in Props are implicitely augmented with a first argument which corresponds to a goal of the predicate of the assertion in which the Props appear. For example, the assertion
:- comp var(A) + not_further_inst(A).has property not_further_inst/1 as goal property, and establishes that in all executions of var(A) it should hold that not_further_inst(var(A),A).
Usage:complex_goal_property(Props)
Props is either a term or a conjunction of terms. The main functor and arity of each of those terms corresponds to the definition of a property. A first implicit argument in such terms identifies goals to which the properties apply.
This predicate defines the different types of syntax admissible in the bodies of call/1, entry/1, etc. assertions. The following are admissible:
Pr : CP [# CO]
where (fields between [...] are optional):
- CP is a (possibly empty) complex argument property (complex_arg_property/1) which applies to the calls to the predicate.
- CO is a comment string (docstring/1). This comment only applies if the (possibly empty) properties given for calls in the assertion hold. The usual formatting commands that are applicable in comment strings can be used (see stringcommand/1).
The format of the different parts of the assertion body are given by n_assrt_body/5 and its auxiliary types.
Usage:c_assrt_body(X)
X is a call assertion body.
This predicate defines the different types of syntax admissible in the bodies of pred/1, func/1, etc. assertions. The following are admissible:
Pr : CP => AP # CO Pr : CP => AP Pr => AP # CO Pr => AP
where:
- Pr is a head pattern (head_pattern/1) which describes the predicate or property and possibly gives some implicit call/answer information.
- CP is a (possibly empty) complex argument property (complex_arg_property/1) which applies to the calls to the predicate.
- AP is a (possibly empty) complex argument property (complex_arg_property/1) which applies to the answers to the predicate (if the predicate succeeds). These only apply if the (possibly empty) properties given for calls in the assertion hold.
- CO is a comment string (docstring/1). This comment only applies if the (possibly empty) properties given for calls in the assertion hold. The usual formatting commands that are applicable in comment strings can be used (see stringcommand/1).
The format of the different parts of the assertion body are given by n_assrt_body/5 and its auxiliary types.
Usage:s_assrt_body(X)
X is a predicate assertion body.
This predicate defines the different types of syntax admissible in the bodies of comp/1 assertions. The following are admissible:
Pr : CP + GP # CO Pr : CP + GP Pr + GP # CO Pr + GP
where:
- Pr is a head pattern (head_pattern/1) which describes the predicate or property and possibly gives some implicit call/answer information.
- CP is a (possibly empty) complex argument property (complex_arg_property/1) which applies to the calls to the predicate.
- GP contains (possibly empty) complex goal property (complex_goal_property/1) which applies to the whole execution of a call to the predicate. These only apply if the (possibly empty) properties given for calls in the assertion hold.
- CO is a comment string (docstring/1). This comment only applies if the (possibly empty) properties given for calls in the assertion hold. The usual formatting commands that are applicable in comment strings can be used (see stringcommand/1).
The format of the different parts of the assertion body are given by n_assrt_body/5 and its auxiliary types.
Usage:g_assrt_body(X)
X is a comp assertion body.
assrt_status(true). assrt_status(false). assrt_status(check). assrt_status(checked). assrt_status(trust).
Usage:assrt_status(X)
X is an acceptable status for an assertion.
assrt_type(pred). assrt_type(prop). assrt_type(decl). assrt_type(func). assrt_type(calls). assrt_type(success). assrt_type(comp). assrt_type(entry). assrt_type(exit). assrt_type(test). assrt_type(texec). assrt_type(modedef).
Usage:assrt_type(X)
X is an admissible kind of assertion.
Usage:docstring(String)
String is a text comment with admissible documentation commands. The usual formatting commands that are applicable in comment strings are defined by stringcommand/1. See the lpdoc manual for documentation on comments.