scasp

Prolog files

call_graph.pl  -- Build the call graph used for NMR check construction and indexing.Show source
a/4Arc in the call graph from Head to Goal.Source
ar/2Associate an arc ID with a list of rule IDs.Source
build_call_graph/2Build and assert the call graph.Source
destroy_call_graph/0Retract the assertions for the call graph.Source
common.pl  -- Common predicates used in multiple filesShow source
comp_duals.pl  -- Dual rule computationShow source
comp_duals/0Compute rules for the negations of positive literals (dual rules), even if there are no clauses for the positive literal (negation will be a fact).Source
comp_duals3/2Compute the dual for a single positive literal.Source
define_forall/3If BodyVars is empty, just return the original goal.Source
compile.pl  -- s(ASP) Ungrounded Stable Models SolverShow source
scasp_compile/2Create an sCASP program from Terms.Source
scasp_compile_query/3Source
scasp_load/2Load the files from Sources.Source
scasp_query/1True when Query is the (last) sCASP query that is part of the program.Source
scasp_query/3True when Query is the s(CASP) query as a list that includes the NMR check if required.Source
dyncall.pl  -- Show source
#/1Handle s(CASP) directives.Source
#</2Implementation of the s(CASP) constraints.Source
#<>/2Implementation of the s(CASP) constraints.Source
#=/2Implementation of the s(CASP) constraints.Source
#=</2Implementation of the s(CASP) constraints.Source
#>/2Implementation of the s(CASP) constraints.Source
#>=/2Implementation of the s(CASP) constraints.Source
abducible/1Declare Spec, a comma list of heads to be abducible, meaning they can both be in or outside the model.Source
scasp/2Prove query using s(CASP) semantics.Source
scasp_abolish/1Remove all facts for both PredicateIndicator and its classical negation.Source
scasp_assert/1Wrappers for assertz/1, retract/1 and retractall/1 that deal with sCASP terms which may have a head or body terms that are wrapped in -(Term), indicating classical negation.Source
scasp_dynamic/1Declare a predicates as dynamic or thread_local.Source
scasp_query_clauses/2Source
scasp_retract/1Wrappers for assertz/1, retract/1 and retractall/1 that deal with sCASP terms which may have a head or body terms that are wrapped in -(Term), indicating classical negation.Source
scasp_retractall/1Wrappers for assertz/1, retract/1 and retractall/1 that deal with sCASP terms which may have a head or body terms that are wrapped in -(Term), indicating classical negation.Source
scasp_show/2Show some aspect of the translated s(CASP) program.Source
embed.pl  -- Embed sCASP programs in Prolog sourcesShow source
gxref_called/2Hook into gxref/0 that may extend the notion of predicates being called by some infrastructure.Source
-/1sCASP classical negation.Source
begin_scasp/1Start an embedded sCASP program.Source
begin_scasp/2Start an embedded sCASP program.Source
end_scasp/0Close begin_scasp/1,2.Source
not/1sCASP NaF negation.Source
scasp_call/1Solve an sCASP goal from the interactive toplevel.Source
scasp_justification/2Justification for the current sCASP answer.Source
scasp_listing/2List the transformed program for Unit.Source
scasp_model/1True when Model represents the current set of true and false literals.Source
scasp_model/2True when Model represents the current set of true and false literals.Source
scasp_stack/1True when Stack represents the justification of the current sCASP answer.Source
html.pl  -- Render s(CASP) justification as HTMLShow source
html_text.pl  -- Switch between HTML and plain text outputShow source
human.pl  -- Print s(CASP) output in human languageShow source
human_justification_tree/2Print Tree to current_output in human representation.Source
human_model/2Source
human_predicate/2Source
human_query/2Source
human_rule/2Source
input.pl  -- Read SASP source codeShow source
load_source_files/1Given a list of source files, read, tokenize and parse them, merging their output into a single list of statements.Source
sasp_read/2Read File into a list of ASP statements.Source
scasp_load_terms/2Perform the load_source_files/1 preparation step from a list of Prolog terms.Source
listing.plShow source
scasp_code_section_title/3Source
scasp_portray_program/1Output pretty print of the program + dual rules + nmr-checks.Source
messages.plShow source
model.pl  -- sCASP model handlingShow source
canonical_model/2Source
print_model/2Print the model in aligned columns.Source
unqualify_model/3Restore the model relation to modules.Source
modules.pl  -- Encode modulesShow source
encoded_module_term/2Source
model_term_module/2Source
scasp_encoded_module_term/2Map an explicit Prolog module qualification into one that is encoded in the functor name.Source
unqualify_model_term/3Source
nmr_check.pl  -- Detect OLON rules and construct nmr_checkShow source
generate_nmr_check/1Get the rules in the program containing odd loops and compute the NMR check.Source
ops.plShow source
options.pl  -- (Command line) option handling for sCASPShow source
output.pl  -- Emit sCASP termsShow source
connector/3Get an ASCII or Unicode connector string with the claimed Semantics.Source
human_expression/3If there is a human print rule for Atom, return a list of format actions as Actions.Source
inline_constraints/2Get constraints on variables notated as Var | {Constraints} and use assigned variable names.Source
ovar_analyze_term/1Analyze variables in an output term.Source
ovar_analyze_term/2Analyze variables in an output term.Source
ovar_clean/1Delete all attributes added by ovar_analyze_term/1.Source
ovar_is_singleton/1True when Var is a singleton variable.Source
ovar_set_bindings/1Given Bindings as a list of Name=Var, set the names of the variables.Source
ovar_set_name/2Set the name of Var to Name.Source
ovar_var_name/2True when var is not a singleton and has the assigned name.Source
print_model_term/2Print a model element to the terminal.Source
pr_rules.pl  -- Output formatting and printing.Show source
clean_pr_program/1Prepare Module to receive a compiled sCASP program.Source
generate_pr_rules/2Translate the sCASP program from the defined_* predicates into pr_* predicates for sCASP.Source
process_pr_pred/5Process a #pred Spec :: Template. directive.Source
predicates.pl  -- Basic information about sCASP predicatesShow source
clp_builtin/1Success if Goal is a builtin constraint predicate.Source
clp_interval/1Success if Goal is a builtin constraint predicate to extract interval limits.Source
prolog_builtin/1Success if Goal is a builtin prolog predicate (the compiler introduced its dual).Source
scasp_compiled/1True when Head is part of the transformed representation.Source
table_predicate/1Success if Goal is defined as a tabled predicate with the directive :- table pred/n..Source
user_predicate/1Success if Goal is a user predicate.Source
program.pl  -- Input program accessShow source
assert_nmr_check/1Assert the NMR check.Source
assert_program/1Get rules, initial query and called predicates and assert them for easy access.Source
assert_rule/1Assert a program rule.Source
defined_nmr_check/1Dynamic predicate for the list of NMR sub-checks.Source
defined_predicates/1Dynamic predicate for the list of predicate symbols defined in the input program.Source
defined_query/2Dynamic predicate for query.Source
defined_rule/4Dynamic predicate for asserted rules.Source
destroy_program/0Remove all asserted predicates to allow multiple funs with different programs.Source
replace_prefix/4Source
reserved_prefix/1Define reserved prefixes for predicates and compound terms.Source
solve.pl  -- The sCASP solverShow source
solve/4Solve the list of sub-goals Goal where StackIn is the list of goals already visited and returns in StackOut the list of goals visited to prove the sub-goals and in Model the model that supports the sub-goals.Source
source_ref.pl  -- s(CASP) source referencesShow source
scasp_dynamic_clause_position/2True when Pos is the stream position is which the source code for the dynamic clause referenced by Ref was read.Source
stack.plShow source
swish.pl  -- s(CASP) adapter for SWISHShow source
post_context/1Called before the other context extraction.Source
post_context/3Bind Var with the context information that belongs to Name.Source
variables.pl  -- Variable storage and accessShow source
body_vars/3Get the body variables (variables used in the body but not in the head) for a clause.Source
is_var/1Test an entry to see if it's a variable (the first non-underscore is an upper-case letter.Source
is_var/2Test an entry to see if it's a variable (the first non-underscore is an upper-case letter.Source
revar/3If Term is a term that contains atoms using variable syntax ([A-Z].*), VarTerm is a copy of Term with all such atoms replaced by variables.Source
var_list/2Get a list of N variables, each of which is different.Source
verbose.pl  -- Print goal and stack in Ciao compatible formatShow source