All predicatesShow sourceinput.pl -- Read SASP source code

This module defines reading sCASP input based on the Prolog parser.

Source load_source_files(+Files:list) is det
Given a list of source files, read, tokenize and parse them, merging their output into a single list of statements. Next, call assert_program/1 to process the statements.
Arguments:
Files- The list of files to load.
Source scasp_load_terms(+Terms, +Options)
Perform the load_source_files/1 preparation step from a list of Prolog terms.
Source sasp_read(+File, -Statements) is det
Read File into a list of ASP statements. To facilitate using a file both as dynamic and stand-alone file, statements (:- use_module(_)) are ignored.
Source prep_read(-Undo)[private]
Setup the Prolog syntax for reading sCASP. This currently sets the allow_variable_name_as_functor flag, such that e.g. _female(jane) is valid syntax.
 sasp_read_stream(+In, -Statements, +Options) is det[private]
Read the content of the stream In into a list of sCASP statements.
Source sasp_statement(+Term, +VarNames, -SASP, +Pos, +Options) is det[private]
Convert a raw Prolog term into its sCASP equivalent. Currently does these transformations:

This also processes directives, terms of the shape #Directive.

Arguments:
VarNames- is a list Name=Var as produced by read_term/3. Remaining variables are bound to _V<N>.
Source sasp_statement(+Term, -SASPTerm, +TermPos, +Options) is det[private]
Translate a single term.
Source sasp_predicate(+Pred, -ASPPred, +Pos, +Options) is det[private]
Source sasp_predicate_m(+Options, +Pred, -ASPPred, +Pos) is det[private]
Handle an ASP atom. Renames the functor when needed. Knows about -Pred (classical negation) and not(Pred).
Source handle_prefixes(+FunctorIn:atom, -FunctorOut:atom)[private]
If the predicate begins with a reserved prefix, add the dummy prefix to ensure that it won't be treated the same as predicates where the prefix is added internally. If no prefix, just return the original.
Source builtin(+Pred:pi) is semidet[private]
Predicates that will be executed by Prolog
Source directive(+Directive, -Statements, +Pos, +Options) is det[private]
Process a directive.
Source sasp_syntax_error(+Error, +Pos, +Options)[private]
To be done
- : properly translate the error location
Source comma_list(+BodyTerm, +Pos, -BodyList, -PosList) is det[private]
Translate a conjunction into a list, also translating possible position information.