While library(scasp/main) is used to build the scasp
executable,
this library (library(scasp)) is used to embed or dynamically create
s(CASP)
programs in Prolog and query them from Prolog.
The following predicates are re-exported from other modules
Otherwise the read clauses are asserted verbatim. Directives are terms #(Directive). Prolog directives (:- Directive) are interpreted as sCASP global constraints. The matching end_scasp/0 compiles the sCASP program and creates wrappers in the enclosing module that call the sCASP solver.
The sCASP code must be closed using end_scasp/0. Both begin_scasp/1,2 and end_scasp/0 must be used as directives.
s(CASP)
constraints. This implementation is
normally not used and mostly makes the program analysis work.Otherwise the read clauses are asserted verbatim. Directives are terms #(Directive). Prolog directives (:- Directive) are interpreted as sCASP global constraints. The matching end_scasp/0 compiles the sCASP program and creates wrappers in the enclosing module that call the sCASP solver.
The sCASP code must be closed using end_scasp/0. Both begin_scasp/1,2 and end_scasp/0 must be used as directives.
-(Term)
, indicating classical negation. Also deals with global
constraints written in any of these formats:
false :- Constraint
.:- Constraint
.s(CASP)
semantics. This performs the following
steps:
s(CASP)
representation in a temporary
modules(CASP)
solverOptions are passed to scasp_compile/2. Other options processed:
s(CASP)
model, a list of model terms.
See scasp_model/1.s(CASP)
justification tree. See
scasp_justification/2 for details.false
, do not include source origin terms into the
final tree.s(CASP)
constraints. This implementation is
normally not used and mostly makes the program analysis work.s(CASP)
constraints. This implementation is
normally not used and mostly makes the program analysis work.-(Term)
, indicating classical negation. Also deals with global
constraints written in any of these formats:
false :- Constraint
.:- Constraint
.:- scasp_dynamic p/1. :- scasp_dynamic p/1 as shared.
s(CASP)
constraints. This implementation is
normally not used and mostly makes the program analysis work.s(CASP)
constraints. This implementation is
normally not used and mostly makes the program analysis work.-(Term)
, indicating classical negation. Also deals with global
constraints written in any of these formats:
false :- Constraint
.:- Constraint
.s(CASP)
program. Currently
What is one of:
?- scasp_show(Query, code(user(false), constraints(true))).
s(CASP)
directives. Same as :- Directive.
. Provides
compatibility with sCASP sources as normally found.s(CASP)
constraints. This implementation is
normally not used and mostly makes the program analysis work.The following predicates are exported, but not or incorrectly documented.