View source with raw comments or as raw
    1:- module(scasp,
    2          [ scasp/2,                    % :Goal, +Options
    3            (?)/1,                      % :Query
    4            (??)/1,                     % :Query
    5            (?--)/1,                    % :Query
    6            (?+-)/1,                    % :Query
    7            (?-+)/1,                    % :Query
    8            (?++)/1,                    % :Query
    9            (??+-)/1,                   % :Query
   10            (??-+)/1,                   % :Query
   11            (??++)/1,                   % :Query
   12
   13            scasp_show/2,               % :Query,+What
   14
   15            (scasp_dynamic)/1,          % :Spec
   16            scasp_assert/1,             % :Clause
   17            scasp_assert/2,             % :Clause, +Pos
   18            scasp_retract/1,            % :Clause
   19            scasp_retractall/1,         % :Head
   20            scasp_abolish/1,            % :Name/Arity
   21            (#)/1,                      % :Directive
   22            (#)/2,                      % :Directive, +Pos
   23            (pred)/1,                   % :Templates
   24            (show)/1,                   % :Atoms
   25            (abducible)/1,              % :Heads
   26            (abducible)/2,              % :Heads, +Pos
   27
   28            begin_scasp/1,              % +Unit
   29            begin_scasp/2,              % +Unit, +Exports
   30            end_scasp/0,
   31            scasp_listing/2,            % +Unit, +Options
   32            scasp_model/1,              % :Model
   33            scasp_stack/1,              % -Stack
   34            scasp_justification/2,      % -Tree, +Options
   35            (not)/1,                    % :Query
   36            (-)/1,                      % :Query
   37
   38            (#=)/2,
   39            (#<>)/2,
   40            (#<)/2,
   41            (#>)/2,
   42            (#=<)/2,
   43            (#>=)/2,
   44
   45            op(900,  fy, not),
   46            op(700, xfx, '\u2209'),     % not element of
   47            op(1150, fx, ??),           % same as ?++
   48            op(1150, fx, ?),            % same as ?+-
   49            op(1150, fx, ?--),          % bindings only
   50            op(1150, fx, ?+-),          % bindings + model
   51            op(1150, fx, ?-+),          % bindings + tree
   52            op(1150, fx, ?++),          % bindings + model + tree
   53            op(1150, fx, ??+-),         % Human versions of the above
   54            op(1150, fx, ??-+),
   55            op(1150, fx, ??++),
   56            op(950, xfx, ::),           % pred not x :: "...".
   57            op(1200, fx, #),
   58            op(1150, fx, pred),
   59            op(1150, fx, show),
   60            op(1150, fx, abducible),
   61            op(1150, fx, scasp_dynamic),
   62            op(700, xfx, #=),
   63            op(700, xfx, #<>),
   64            op(700, xfx, #<),
   65            op(700, xfx, #>),
   66            op(700, xfx, #=<),
   67            op(700, xfx, #>=)
   68          ]).

Using s(CASP) from Prolog

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. */

   77%:- set_prolog_flag(optimise, true).
   78
   79:- use_module(scasp/embed).   80:- use_module(scasp/dyncall).   81:- use_module(scasp/messages).   82
   83:- meta_predicate
   84    ?(:),
   85    ??(:),
   86    ?--(:),
   87    ?+-(:),
   88    ?-+(:),
   89    ?++(:),
   90    ??+-(:),
   91    ??-+(:),
   92    ??++(:).
 ?--(:Query)
 ?+-(:Query)
 ?-+(:Query)
 ?++(:Query)
 ??+-(:Query)
 ??-+(:Query)
 ??++(:Query)
Shortcuts for scasp/1 that control printing the model and/or tree and the format. The +/- control whether the model and/or tree are printed (in that order). The ?? versions print the human version.
  106?   Q :- scasp_and_show(Q, unicode, false).
  107??  Q :- scasp_and_show(Q, unicode, unicode).
  108
  109?--  Q :- scasp_and_show(Q, false, false).
  110?-+  Q :- scasp_and_show(Q, false, unicode).
  111?+-  Q :- scasp_and_show(Q, unicode, false).
  112?++  Q :- scasp_and_show(Q, unicode, unicode).
  113??-+ Q :- scasp_and_show(Q, false, human).
  114??+- Q :- scasp_and_show(Q, human, false).
  115??++ Q :- scasp_and_show(Q, human, human).
  116
  117scasp_and_show(Q, Model, Tree) :-
  118    scasp_mode(M0, T0),
  119    setup_call_cleanup(
  120        set_scasp_mode(Model, Tree),
  121        (   scasp(Q, [])
  122        ;   false                       % make always nondet.
  123        ),
  124        set_scasp_mode(M0, T0)).
  125
  126scasp_mode(M, T) :-
  127    current_prolog_flag(scasp_show_model, M),
  128    current_prolog_flag(scasp_show_justification, T).
  129
  130set_scasp_mode(M, T) :-
  131    set_prolog_flag(scasp_show_model, M),
  132    set_prolog_flag(scasp_show_justification, T).
  133
  134
  135
  136		 /*******************************
  137		 *            SANDBOX		*
  138		 *******************************/
  139
  140:- multifile
  141    sandbox:safe_meta_predicate/1,
  142    sandbox:safe_prolog_flag/2.  143
  144sandbox:safe_meta(scasp:(? _), []).
  145sandbox:safe_meta(scasp:(?? _), []).
  146sandbox:safe_meta(scasp:(?-- _), []).
  147sandbox:safe_meta(scasp:(?+- _), []).
  148sandbox:safe_meta(scasp:(?-+ _), []).
  149sandbox:safe_meta(scasp:(?++ _), []).
  150sandbox:safe_meta(scasp:(??+- _), []).
  151sandbox:safe_meta(scasp:(??-+ _), []).
  152sandbox:safe_meta(scasp:(??++ _), []).
  153
  154sandbox:safe_prolog_flag(scasp_lang, _).
  155sandbox:safe_prolog_flag(scasp_unknown, _).
  156sandbox:safe_prolog_flag(scasp_plain_dual, _).
  157sandbox:safe_prolog_flag(scasp_compile_olon, _).
  158sandbox:safe_prolog_flag(scasp_compile_nmr, _).
  159sandbox:safe_prolog_flag(scasp_dcc, _)