View source with formatted comments or as raw
    1:- module(scasp_options,
    2          [ scasp_parse_args/3,            % +Argv, -Sources, -Options
    3            scasp_help/0,
    4            scasp_set_options/1,           % +Options
    5            scasp_set_options/2,           % +Options, -Unprocessed
    6            scasp_version/1,               % -Version
    7            scasp_opt_type/3,              % ?Flag, ?Option, ?Type
    8            scasp_opt_help/2,              % +Option, -Help
    9            scasp_opt_meta/2               % +Option, -Meta
   10          ]).   11:- use_module(library(main)).   12:- use_module(library(strings)).           % Quasi quotation
   13:- use_module(library(apply)).   14:- use_module(library(lists)).   15:- use_module(library(option)).   16
   17/** <module> (Command line) option handling for sCASP
   18
   19@author Joaquin Arias
   20*/
   21
   22% Prefer Unicode symbols over ASCII
   23:- create_prolog_flag(scasp_unicode, true, []).   24
   25%!  scasp_version(-Version)
   26%
   27%   print the current version of s(CASP)
   28
   29scasp_version('swi.0.21.11.26').
   30
   31%!  scasp_set_options(+Options) is det.
   32%!  scasp_set_options(+Options, -Unprocessed) is det.
   33%
   34%   Set Prolog flags that control the solver from Options.
   35
   36scasp_set_options(Options) :-
   37    scasp_set_options(Options, _).
   38
   39scasp_set_options(Options, Left) :-
   40    opt_process(Options, Options1),
   41    exclude(set_option, Options1, Left).
   42
   43% Solver options
   44set_option(nmr(Bool)) =>
   45    set_prolog_flag(scasp_compile_nmr, Bool).
   46set_option(olon(Bool)) =>
   47    set_prolog_flag(scasp_compile_olon, Bool).
   48set_option(forall(Algorithm)) =>
   49    set_prolog_flag(scasp_forall, Algorithm).
   50set_option(dcc(Bool)) =>
   51    set_prolog_flag(scasp_dcc, Bool).
   52% Presentation uptions
   53set_option(unicode(Bool)) =>
   54    set_prolog_flag(scasp_unicode, Bool).
   55set_option(assume(Bool)) =>
   56    set_prolog_flag(scasp_assume, Bool).
   57set_option(real(Decimals)) =>
   58    set_prolog_flag(scasp_real, Decimals).
   59% Verbosity options
   60set_option(verbose(Bool)) =>
   61    set_prolog_flag(scasp_verbose, Bool).
   62set_option(warning(Bool)) =>
   63    set_prolog_flag(scasp_warnings, Bool).
   64set_option(trace_fails(Bool)) =>
   65    set_prolog_flag(scasp_trace_failures, Bool).
   66set_option(trace_dcc(Bool)) =>
   67    set_prolog_flag(scasp_trace_dcc, Bool).
   68set_option(raw(Bool)) =>
   69    set_prolog_flag(scasp_list_raw, Bool).
   70set_option(color(Bool)) =>
   71    set_prolog_flag(color_term, Bool).
   72% Ignore other well formed options.
   73set_option(Term), compound(Term), functor(Term, _, 1) =>
   74    fail.
   75
   76		 /*******************************
   77		 *        OPTION CHECKING	*
   78		 *******************************/
   79
   80%!  opt_process(+OptionsIn, -Options) is det.
   81%
   82%   Post processs the option list. This   does a findall/3 on opt_rule/1
   83%   which may use opt/1 to access the   option list being processed. The
   84%   opt_rule/1 returns one or more actions.  Defined actions are:
   85%
   86%     - default(+Opt)
   87%       If Opt is not defined, add Opt as default.
   88%     - add(+Opt)
   89%       Add an option.  If the option is defined, remove it.
   90%     - replace(+Opts, +Opt)
   91%       Remove options for Opts (a list or a single option) and
   92%       add Opt.
   93%     - warning(Term)
   94%       call print_message(warning, Term) and continue.
   95%     - error(Term)
   96%       call print_message(error, Term) and die using halt(1).
   97
   98%   @tbd This is code that might go into the Prolog libraries at some time.
   99
  100:- det(opt_process/2).  101opt_process(Options0, Options) :-
  102    opt_step(Options0, Options1),
  103    (   Options1 == Options0
  104    ->  Options = Options1
  105    ;   opt_step(Options1, Options)
  106    ).
  107
  108opt_step(Options0, Options) :-
  109    findall(Act, opt_act(Options0, Act), Actions),
  110    foldl(apply_action, Actions, Options0, Options).
  111
  112apply_action(default(Opt), Options0, Options) =>
  113    merge_options(Options0, [Opt], Options).
  114apply_action(add(Opt), Options0, Options) =>
  115    merge_options([Opt], Options0, Options).
  116apply_action(replace(Old, New), Options0, Options) =>
  117    opt_delete(Old, Options0, Options1),
  118    merge_options([New], Options1, Options).
  119apply_action(warning(Msg), Options0, Options) =>
  120    Options = Options0,
  121    print_message(warning, Msg).
  122apply_action(error(Msg), _Options0, _Options) =>
  123    print_message(error, Msg),
  124    halt(1).
  125
  126opt_delete([], Options0, Options) =>
  127    Options = Options0.
  128opt_delete([H|T], Options0, Options), is_opt(H) =>
  129    delete(Options0, H, Options1),
  130    opt_delete(T, Options1, Options).
  131opt_delete(Opt, Options0, Options), is_opt(Opt) =>
  132    delete(Options0, Opt, Options).
  133
  134is_opt(Opt) :-
  135    compound(Opt),
  136    compound_name_arity(Opt, _, 1).
  137
  138opt_act(Options, Act) :-
  139    b_setval(options, Options),
  140    opt_rule(Act).
  141
  142opt(Opt) :-
  143    b_getval(options, Opts),
  144    option(Opt, Opts).
  145
  146%!  opt_rule(-Action) is nondet.
  147%
  148%   Option rules for s(CASP).  Processed using opt_process/2 above.
  149
  150opt_rule(Action) :-
  151    detail(print_tree, Action).
  152opt_rule(Action) :-
  153    detail(write_program, Action).
  154opt_rule(Error) :-
  155    at_most_one_of([verbose, human], Error).
  156opt_rule(Error) :-
  157    at_most_one_of([interactive, human], Error).
  158opt_rule(add(forall(prev))) :-
  159    \+ opt(forall(_)),
  160    opt_true(dcc).
  161opt_rule(error(scasp(opt_dcc_prev_forall))) :-
  162    opt(forall(Forall)),
  163    Forall \== prev,
  164    opt_true(dcc).
  165
  166detail(Opt, Action) :-
  167    True =.. [Opt,true],
  168    opt(True),
  169    (opt(short(Short)) -> true ; Short = '-'),
  170    (opt(mid(Mid))     -> true ; Mid   = '-'),
  171    (opt(long(Long))   -> true ; Long  = '-'),
  172    (   detail(Short, Mid, Long, Detail)
  173    ->  Del =.. [Opt,_],
  174        New =.. [Opt,Detail],
  175        Action = replace([Del,short(_),mid(_),long(_)],
  176                         New)
  177    ;   Action = error(scasp(at_most_one_of([short,mid,long])))
  178    ).
  179
  180detail(true, -, -, short).
  181detail(-, true, -, mid).
  182detail(-, -, true, long).
  183detail(-, -, -,    mid).
  184
  185at_most_one_of(List, Error) :-
  186    append(_, [First|Rest], List),
  187    opt_true(First),
  188    member(Second, Rest),
  189    opt_true(Second),
  190    !,
  191    Error = error(scasp(at_most_one_of(List))).
  192
  193opt_true(Name) :-
  194    Opt =.. [Name,true],
  195    opt(Opt).
  196
  197
  198		 /*******************************
  199		 *             SPEC		*
  200		 *******************************/
  201
  202%!  opt_type(?Opt, ?Destination, ?Type)
  203
  204opt_type(interactive, interactive,    boolean).
  205opt_type(i,           interactive,    boolean).
  206
  207opt_type(s,           answers,        nonneg).
  208opt_type(n,           answers,        nonneg).
  209
  210opt_type(query,       query,          term([variable_names(_)])).
  211
  212opt_type(compiled,    compiled,       boolean).
  213opt_type(c,           compiled,       boolean).
  214
  215opt_type(plaindual,   plain_dual,     boolean).
  216opt_type(d,           plain_dual,     boolean).
  217
  218opt_type(r,           real,           between(1,16)|oneof([float])).
  219
  220opt_type(code,        write_program,  boolean).
  221opt_type(human,       human,          boolean).
  222opt_type(tree,        tree,           boolean).
  223opt_type(pos,         pos,            boolean).
  224opt_type(assume,      assume,         boolean).
  225opt_type(short,       short,          boolean).
  226opt_type(mid,         pos,            boolean).
  227opt_type(long,        long,           boolean).
  228
  229opt_type(html,        html,           file(write)).
  230opt_type(css,         style,          boolean).
  231opt_type(script,      script,         boolean).
  232opt_type(collapse,    collapse_below, nonneg).
  233
  234opt_type(json,        json,           file(write)).
  235opt_type(width,       width,          nonneg).
  236
  237opt_type(unicode,     unicode,        boolean).
  238opt_type(u,           unicode,        boolean).
  239
  240opt_type(color,       color,          boolean).
  241
  242opt_type(verbose,     verbose,        boolean).
  243opt_type(v,           verbose,        boolean).
  244
  245opt_type(version,     version,        boolean).
  246
  247opt_type(forall,      forall,         oneof([all,all_c,prev,sasp])).
  248
  249opt_type(trace_fails, trace_fails,    boolean).
  250opt_type(f,           trace_fails,    boolean).
  251
  252opt_type(trace_dcc,   trace_dcc,      boolean).
  253
  254opt_type(nmr,         nmr,            boolean(false)).
  255opt_type(olon,        olon,           boolean(false)).
  256opt_type(dcc,         dcc,            boolean).
  257
  258opt_type(unknown,     unknown,        oneof([fail,warning,error])).
  259
  260opt_type(warning,     warning,        boolean).
  261opt_type(w,           warning,        boolean).
  262
  263opt_type(minimal,     minimal,        boolean).
  264opt_type(m,           minimal,        boolean).
  265
  266opt_type(raw,         raw,            boolean).
  267
  268opt_help(interactive,    "Run in interactive mode (REP loop)").
  269opt_help(answers,        "Number of answers to report (0 for all)").
  270opt_help(query,          "Query to run (overrules ?- query from program)").
  271opt_help(compiled,       "Load compiled files (e.g. extracted using --code)").
  272opt_help(write_program,  "Output the compiled program and exit").
  273opt_help(plain_dual,     "Generate dual program with single-goal clauses").
  274opt_help(real,           "Output rational numbers as decimal. \c
  275                          An integer value specifies the number of decimals \c
  276                          the value `float` simply converts to a float.").
  277opt_help(code,           "Print program with dual clauses and exit").
  278opt_help(human,          "Output code/justification tree in natural language").
  279opt_help(tree,           "Print justification tree for each answer").
  280opt_help(assume,         "Mark assumed nodes in the justification").
  281opt_help(long,           "Output long version of code or justification.").
  282opt_help(mid,            "Output mid-sized version of code or justification \c
  283			  (default)").
  284opt_help(short,          "Short version of code or justification").
  285opt_help(pos,            "Only format the selected literals in the \c
  286                          justification").
  287opt_help(html,           "Generate an HTML file (\"-\" for standard output)").
  288opt_help(style,          "Include CSS in HTML output (default)").
  289opt_help(script,         "Include JavaScript in HTML output (default)").
  290opt_help(collapse_below, "Collapse HTML tree below this level (2)").
  291opt_help(json,           "Generate a JSON file (\"-\" for standard output)").
  292opt_help(width,          "Page width.  For JSON, 0 stops formatting the output").
  293
  294opt_help(unicode,        "Use Unicode symbols in output").
  295opt_help(color,          "Use ANSI sequences to color terminal output").
  296opt_help(verbose,        "Enable verbose progress messages").
  297opt_help(trace_fails,    "Trace user-predicate failures").
  298opt_help(trace_dcc,      "Trace DCC pruning").
  299opt_help(unknown,        "Act on undefined predicates (fail,warning,error)").
  300opt_help(forall,         "Forall algorithm to use ([all], all_c, prev, sasp)").
  301opt_help(olon,           "Compile olon rules (--no-olon for debugging purposes)").
  302opt_help(nmr,            "Compile NMR rules (--no-nmr for debugging purposes)").
  303opt_help(dcc,            "Use Dynamic Consistency Checking").
  304opt_help(warning,        "Enable warning messages (failures in variant \c
  305                          loops / disequality)").
  306opt_help(version,        "Print version and exit").
  307opt_help(variant,        "Do not fail in the presence of variant loops").
  308opt_help(minimal,        "Collect only the minimal models (TABLING required)").
  309opt_help(raw,            "Sort the clauses as s(ASP) does (use with --code)").
  310
  311opt_help(help(header), [ansi(bold, '~w', [Header])]) :-
  312    scasp_version(Version),
  313    Header = {|string(Version)||
  314              | s(CASP) version {Version}
  315             |}.
  316opt_help(help(usage), Usage) :-
  317    Usage = {|string||
  318             | [options] file ...
  319             |
  320             | s(CASP) computes stable models of predicate normal logic programs
  321             | with contraints using a top-down evaluation algorihtm.
  322            |}.
  323
  324opt_meta(answers,        'COUNT').
  325opt_meta(real,           'DECIMALS').
  326opt_meta(unknown,        'MODE').
  327opt_meta(collapse_below, 'LEVELS').
  328opt_meta(forall,	 'ALGORITHM').
  329opt_meta(width,		 'WIDTH').
  330
  331%!  scasp_opt_type(?Flag, ?Option, ?Type).
  332%!  scasp_opt_help(?Option, ?Help).
  333%!  scasp_opt_meta(?Option, ?Meta).
  334%
  335%   Allow reusing scasp option processing
  336
  337scasp_opt_type(Flag, Option, Type) :-
  338    opt_type(Flag, Option, Type).
  339
  340scasp_opt_help(Option, Help) :-
  341    opt_help(Option, Help),
  342    Option \= help(_).
  343
  344scasp_opt_meta(Option, Meta) :-
  345    opt_meta(Option, Meta).
  346
  347%!  scasp_help
  348%
  349%   Print command line option help.
  350
  351scasp_help :-
  352    argv_usage(debug).
  353
  354%!  scasp_parse_args(+Args, -Sources, -Options)
  355%
  356%   Select  from  the  list  of   arguments  in   Args  which   are  the
  357%   user-options, Options and which are the program files, Sources.
  358%
  359%   This predicate calls halt/0 when called with ``--version``.
  360
  361scasp_parse_args(Argv, Sources, Options) :-
  362    argv_options(Argv, Sources, Options0),
  363    opt_process(Options0, Options),
  364    info_and_exit_option(Sources, Options).
  365
  366info_and_exit_option(_Sources, Options) :-
  367    info_option(Options),
  368    !,
  369    halt(0).
  370info_and_exit_option(_, _).
  371
  372info_option(Options) :-
  373    option(version(true), Options),
  374    scasp_version(Version),
  375    print_message(informational, scasp(version(Version)))