All predicatesShow sourceprogram.pl -- Input program access

Allow access to input program rules and query by asserting them and exporting the resulting dynamic predicates.

author
- Kyle Marple
version
- 20170628
license
- BSD-3
Source defined_rule(+Name:atom, +FullHead:compound, -Body:list, -Origin:compound) is nondet
Dynamic predicate for asserted rules.
Arguments:
Head- Head predicate has head/arity (no args).
FullHead- A predicate struct containing the head predicate with args.
Body- list of body goals.
Origin- A term describing the origin of this rule. For rules that are derived from loaded clauses, Origin is set to clause(ClauseRef); for compiler generated rules, Origin is set to generated(Why) where Why is one of neg for classical negation, nmr for NMR checks, and dual for dual rules; for rules read directly as s(CASP) with e.g. load_source_files/1, Origin is set to source(Path, Pos) where Path is the path of the source file, and Pos is a term describing the postition and layout of the rule in the file.
Source defined_query(-Goals:list, -SolCount:int) is det
Dynamic predicate for query.
Arguments:
Goals- List of goals in the query.
SolCount- The number of answer sets to compute.
Source defined_predicates(-Predicates:list) is det
Dynamic predicate for the list of predicate symbols defined in the input program.
Arguments:
Predicates- List of predicate structs.
Source defined_nmr_check(+Subchecks:list) is det
Dynamic predicate for the list of NMR sub-checks.
Arguments:
Subchecks- The list of subcheck goals.
Source program(?ProgramStruct:compound, ?Rules:list, ?Directives:list, ?Query:compound) is det[private]
Convert a program structure into its components, or vice-versa.
Arguments:
ProgramStruct- Program structure.
Rules- List of rules.
Directives- List of directives.
Query- Query structure.
Source query(?QueryStruct:compound, ?Query:list, ?NMR_Check:list, ?SolutionCount:int) is det[private]
Convert a query structure to its components, or vice-versa. NMR_Check will be unbound until after generate_nmr_check/0 has finished.
Arguments:
QueryStruct- Query structure.
Query- List of query goals.
NMR_Check- List of NMR check goals (heads of NMR sub-checks).
SolutionCount- Hard-coded solution count.
Source reserved_prefix(+Prefix:ground) is det
Define reserved prefixes for predicates and compound terms. These take the form of a single letter followed by an underscore. This predicate just tests the letter. The dummy prefix (o_) is appended to predicates and compound terms that either begin with an underscore (legal in ASP but not Prolog) or with a reserved prefix. It will be removed last before printing, and at most one copy will be removed, ensuring that user-defined predicates starting with a reserved prefix won't be processed the same as internally created ones.
Arguments:
Prefix- The letter portion of the prefix.
Source replace_prefix(+FunctorIn, +OldPrefix, +NewPrefix, -Functor)
Source assert_program(+Statements:list) is det
Get rules, initial query and called predicates and assert them for easy access. This fills the dynamic predicates
Arguments:
Statements- List of rules and compute statements produced by DCG.
Source format_program(+Statements:list, -Program:compound) is det[private]
Convert the list of statements to a program structure containing a list of rules and a single query. Queries are generated from compute statements. Use the last compute statement encountered, or a default one if no other is found. The default will always succeed during execution, so the answer set returned will rely on the NMR check.
Arguments:
Statements- List of rules and compute statements produced by DCG.
Program- Program data struct.
Source sort_by_type(+Statements:list, -Rules:list, -Directives:list, +ComputeIn:compound, -ComputeOut:compound) is det[private]
Take a list of statements, return a list of rules and the last compute statement encountered. Compute statement will be formatted as a query.
Arguments:
Statements- List of rules and compute statements produced by DCG.
Rules- extracted from Statements. Each rule is a term Head-Body.
Directives- is a list of plain directive terms (without # or :-)
ComputeIn- compute statement. @arg ComputeOut compute statement. Only the final compute statement is kept.
Source get_predicates(+Program:compound, -Predicates:list) is det[private]
Get a list of the predicate symbols used in the rules or query of the program. This includes predicates that are called but not defined. The internal-use predicate _false_0 should be included explictly, in case a hard-coded query overrode the default one. We add _false_0 as head of the query for that purpose. This both gets the query in the shape of a rule and ensures _false_0 is included.
Arguments:
Program- A program struct.
Predicates- A list of predicate symbols defined in the program.
Source handle_classical_negation(+Predicate:atom) is det[private]
If Predicate is classically negated (in the source starts with '-'). Assign the required number of variables, then create a rule of the form
:- -x, x.
Arguments:
Predicate- is the name (atom) of a predicate
Source assert_program_struct(+Program:compound) is det[private]
Assert rules and query from program struct.
Arguments:
Program- A program struct.
Source assert_rule(+Rule:compound) is det
Assert a program rule.
Arguments:
Rule- A rule struct.
Source assert_directive(+Directive) is det[private]
Assert a directive
Arguments:
Directive- is a term table(Pred), show(Pred) or pred(Pred)
Source assert_query(+Query:compound) is det[private]
Assert the initial query.
Arguments:
Query- A query struct.
Source assert_nmr_check(+NMR:list) is det
Assert the NMR check.
Arguments:
NMR- The list of goals in the NMR check.
Source assert_predicates(+Predicates:list) is det[private]
Assert the list of defined predicate symbols.
Arguments:
Predicates- A list of predicates.
Source destroy_program
Remove all asserted predicates to allow multiple funs with different programs.

Re-exported predicates

The following predicates are exported from this file while their implementation is defined in imported modules or non-module files loaded by this module.

Source has_prefix(+Functor:atom, -Prefix:atom) is semidet
Succeed if Functor begins with a reserved prefix, returning the character part of the (first) prefix.
Arguments:
Functor- The functor to test.
Prefix- The character of the (first) reserved prefix of the functor.
Source non_printable(+Name) is semidet
True if Name should not be printed. This is true if it starts with an underscore or has a normal prefix and then an underscore.

Undocumented predicates

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

Source defined_directive(Arg1)