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

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

   80%:- set_prolog_flag(optimise, true).
   81
   82:- use_module(scasp/embed).   83:- use_module(scasp/dyncall).   84:- use_module(scasp/messages).   85
   86:- meta_predicate
   87    ?(:),
   88    ??(:),
   89    ?--(:),
   90    ?+-(:),
   91    ?-+(:),
   92    ?++(:),
   93    ?+++(:),
   94    ??+-(:),
   95    ??-+(:),
   96    ??++(:).
 ?--(:Query)
 ?+-(: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.
  111?   Q :- scasp_and_show(Q, unicode, false, []).
  112??  Q :- scasp_and_show(Q, unicode, unicode, []).
  113
  114?--  Q :- scasp_and_show(Q, false, false, []).
  115?-+  Q :- scasp_and_show(Q, false, unicode, []).
  116?+-  Q :- scasp_and_show(Q, unicode, false, []).
  117?++  Q :- scasp_and_show(Q, unicode, unicode, []).
  118?+++ Q :- scasp_and_show(Q, unicode, [unicode(true), long(true)], []).
  119??-+ Q :- scasp_and_show(Q, false, human, []).
  120??+- Q :- scasp_and_show(Q, human, false, []).
  121??++ Q :- scasp_and_show(Q, human, human, []).
  122
  123scasp_and_show(Q, Model, Tree, Options) :-
  124    scasp_mode(M0, T0),
  125    setup_call_cleanup(
  126        set_scasp_mode(Model, Tree),
  127        (   scasp(Q, Options)
  128        ;   false                       % make always nondet.
  129        ),
  130        set_scasp_mode(M0, T0)).
  131
  132scasp_mode(M, T) :-
  133    current_prolog_flag(scasp_show_model, M),
  134    current_prolog_flag(scasp_show_justification, T).
  135
  136set_scasp_mode(M, T) :-
  137    set_prolog_flag(scasp_show_model, M),
  138    set_prolog_flag(scasp_show_justification, T).
  139
  140
  141
  142		 /*******************************
  143		 *            SANDBOX		*
  144		 *******************************/
  145
  146:- multifile
  147    sandbox:safe_meta_predicate/1,
  148    sandbox:safe_prolog_flag/2.  149
  150sandbox:safe_meta(scasp:(? _), []).
  151sandbox:safe_meta(scasp:(?? _), []).
  152sandbox:safe_meta(scasp:(?-- _), []).
  153sandbox:safe_meta(scasp:(?+- _), []).
  154sandbox:safe_meta(scasp:(?-+ _), []).
  155sandbox:safe_meta(scasp:(?++ _), []).
  156sandbox:safe_meta(scasp:(??+- _), []).
  157sandbox:safe_meta(scasp:(??-+ _), []).
  158sandbox:safe_meta(scasp:(??++ _), []).
  159sandbox:safe_meta(scasp_dyncall:(scasp_show(_,_)), []).
  160
  161sandbox:safe_prolog_flag(scasp_lang, _).
  162sandbox:safe_prolog_flag(scasp_unknown, _).
  163sandbox:safe_prolog_flag(scasp_plain_dual, _).
  164sandbox:safe_prolog_flag(scasp_compile_olon, _).
  165sandbox:safe_prolog_flag(scasp_compile_nmr, _).
  166sandbox:safe_prolog_flag(scasp_forall, _).
  167sandbox:safe_prolog_flag(scasp_dcc, _)