View source with raw comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2002-2021, University of Amsterdam
    7                              VU University Amsterdam
    8                              SWI-Prolog Solutions b.v.
    9    All rights reserved.
   10
   11    Redistribution and use in source and binary forms, with or without
   12    modification, are permitted provided that the following conditions
   13    are met:
   14
   15    1. Redistributions of source code must retain the above copyright
   16       notice, this list of conditions and the following disclaimer.
   17
   18    2. Redistributions in binary form must reproduce the above copyright
   19       notice, this list of conditions and the following disclaimer in
   20       the documentation and/or other materials provided with the
   21       distribution.
   22
   23    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   24    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   25    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   26    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   27    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   28    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   29    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   30    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   31    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   32    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   33    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   34    POSSIBILITY OF SUCH DAMAGE.
   35*/
   36
   37:- module(prolog_main,
   38          [ main/0,
   39            argv_options/3,             % +Argv, -RestArgv, -Options
   40            argv_options/4,             % +Argv, -RestArgv, -Options, +ParseOpts
   41            argv_usage/1,               % +Level
   42            cli_parse_debug_options/2,  % +OptionsIn, -Options
   43            cli_enable_development_system/0
   44          ]).   45% use autoload/1 to avoid checking these files at load time.
   46:- autoload(library(debug)).   47:- autoload(library(threadutil)).   48% These are fine to be checked and loaded
   49:- autoload(library(apply), [maplist/3, partition/4]).   50:- autoload(library(lists), [append/3]).   51:- autoload(library(pairs), [pairs_keys/2, pairs_values/2]).   52:- autoload(library(prolog_code), [pi_head/2]).   53:- autoload(library(prolog_debug), [spy/1]).   54:- autoload(library(dcg/high_order), [sequence//3, sequence//2]).   55:- autoload(library(option), [option/2]).   56
   57:- meta_predicate
   58    argv_options(:, -, -),
   59    argv_options(:, -, -, +),
   60    argv_usage(:).   61
   62:- dynamic
   63    interactive/0.

Provide entry point for scripts

This library is intended for supporting PrologScript on Unix using the #! magic sequence for scripts using commandline options. The entry point main/0 calls the user-supplied predicate main/1 passing a list of commandline options. Below is a simle echo implementation in Prolog.

#!/usr/bin/env swipl

:- initialization(main, main).

main(Argv) :-
    echo(Argv).

echo([]) :- nl.
echo([Last]) :- !,
    write(Last), nl.
echo([H|T]) :-
    write(H), write(' '),
    echo(T).
See also
- library(prolog_stack) to force backtraces in case of an uncaught exception.
- XPCE users should have a look at library(pce_main), which starts the GUI and processes events until all windows have gone. */
   94:- module_transparent
   95    main/0.
 main
Call main/1 using the passed command-line arguments. Before calling main/1 this predicate installs a signal handler for SIGINT (Control-C) that terminates the process with status 1.
  103main :-
  104    context_module(M),
  105    set_signals,
  106    current_prolog_flag(argv, Av),
  107    catch_with_backtrace(M:main(Av), Error, throw(Error)),
  108    (   interactive
  109    ->  cli_enable_development_system
  110    ;   true
  111    ).
  112
  113set_signals :-
  114    on_signal(int, _, interrupt).
 interrupt(+Signal)
We received an interrupt. This handler is installed using on_signal/3.
  121interrupt(_Sig) :-
  122    halt(1).
  123
  124		 /*******************************
  125		 *            OPTIONS		*
  126		 *******************************/
 argv_options(:Argv, -Positional, -Options) is det
Parse command line arguments. This predicate acts in one of two modes.

When guided, three predicates are called in the calling module. opt_type/3 must be defined, the others need not. Note that these three predicates may be defined as multifile to allow multiple modules contributing to the provided commandline options. Defining them as discontiguous allows for creating blocks that describe a group of related options.

opt_type(Opt, Name, Type)
Defines Opt to add an option Name(Value), where Value statisfies Type. Opt does not include the leading -. A single character implies a short option, multiple a long option. Long options use _ as word separator, user options may use either _ or -. Type is one of:
A | B
Disjunctive type.
boolean(Default)
boolean
Boolean options are special. They do not take a value except for when using the long --opt=value notation. This explicit value specification converts true, True, TRUE, on, On, ON, 1 and the obvious false equivalents to Prolog true or false. If the option is specified, Default is used. If --no-opt or --noopt is used, the inverse of Default is used.
integer
Argument is converted to an integer
float
Argument is converted to a float. User may specify an integer
nonneg
As integer. Requires value >= 0.
natural
As integer. Requires value >= 1.
between(Low, High)
If both one of Low and High is a float, convert as float, else convert as integer. Then check the range.
atom
No conversion
oneof(List)
As atom, but requires the value to be a member of List (enum type).
string
Convert to a SWI-Prolog string
file
Convert to a file name in Prolog canonical notation using prolog_to_os_filename/2.
file(Access)
As file, and check access using access_file/2. A value - is not checked for access, assuming the application handles this as standard input or output.
term
Parse option value to a Prolog term.
term(+Options)
As term, but passes Options to term_string/3. If the option variable_names(Bindings) is given the option value is set to the pair Term-Bindings.
opt_help(Name, HelpString)
Help string used by argv_usage/1.
opt_meta(Name, Meta)
If a typed argument is required this defines the placeholder in the help message. The default is the uppercase version of the type functor name. This produces the FILE in e.g. -f FILE.

By default, -h, -? and --help are bound to help. If opt_type(Opt, help, boolean) is true for some Opt, the default help binding and help message are disabled and the normal user rules apply. In particular, the user should also provide a rule for opt_help(help, String).

  212argv_options(M:Argv, Positional, Options) :-
  213    in(M:opt_type(_,_,_)),
  214    !,
  215    argv_options(M:Argv, Positional, Options, [on_error(halt(1))]).
  216argv_options(_:Argv, Positional, Options) :-
  217    argv_untyped_options(Argv, Positional, Options).
 argv_options(:Argv, -Positional, -Options, +ParseOptions) is det
As argv_options/3 in guided mode, Currently this version allows parsing argument options throwing an exception rather than calling halt/1 by passing an empty list to ParseOptions. ParseOptions:
on_error(+Goal)
If Goal is halt(Code), exit with Code. Other goals are currently not supported.
options_after_arguments(+Boolean)
If false (default true), stop parsing after the first positional argument, returning options that follow this argument as positional arguments. E.g, -x file -y results in positional arguments [file, '-y']
  234argv_options(Argv, Positional, Options, POptions) :-
  235    option(on_error(halt(Code)), POptions),
  236    !,
  237    E = error(_,_),
  238    catch(opt_parse(Argv, Positional, Options, POptions), E,
  239          ( print_message(error, E),
  240            halt(Code)
  241          )).
  242argv_options(Argv, Positional, Options, POptions) :-
  243    opt_parse(Argv, Positional, Options, POptions).
 argv_untyped_options(+Argv, -RestArgv, -Options) is det
Generic transformation of long commandline arguments to options. Each --Name=Value is mapped to Name(Value). Each plain name is mapped to Name(true), unless Name starts with no-, in which case the option is mapped to Name(false). Numeric option values are mapped to Prolog numbers.
  253argv_untyped_options([], Pos, Opts) =>
  254    Pos = [], Opts = [].
  255argv_untyped_options([--|R], Pos, Ops) =>
  256    Pos = R, Ops = [].
  257argv_untyped_options([H0|T0], R, Ops), sub_atom(H0, 0, _, _, --) =>
  258    Ops = [H|T],
  259    (   sub_atom(H0, B, _, A, =)
  260    ->  B2 is B-2,
  261        sub_atom(H0, 2, B2, _, Name),
  262        sub_string(H0, _, A,  0, Value0),
  263        convert_option(Name, Value0, Value)
  264    ;   sub_atom(H0, 2, _, 0, Name0),
  265        (   sub_atom(Name0, 0, _, _, 'no-')
  266        ->  sub_atom(Name0, 3, _, 0, Name),
  267            Value = false
  268        ;   Name = Name0,
  269            Value = true
  270        )
  271    ),
  272    canonical_name(Name, PlName),
  273    H =.. [PlName,Value],
  274    argv_untyped_options(T0, R, T).
  275argv_untyped_options([H|T0], Ops, T) =>
  276    Ops = [H|R],
  277    argv_untyped_options(T0, R, T).
  278
  279convert_option(password, String, String) :- !.
  280convert_option(_, String, Number) :-
  281    number_string(Number, String),
  282    !.
  283convert_option(_, String, Atom) :-
  284    atom_string(Atom, String).
  285
  286canonical_name(Name, PlName) :-
  287    split_string(Name, "-_", "", Parts),
  288    atomic_list_concat(Parts, '_', PlName).
 opt_parse(:Argv, -Positional, -Options, +POptions) is det
Rules follow those of Python optparse:
  300opt_parse(M:Argv, _Positional, _Options, _POptions) :-
  301    opt_needs_help(M:Argv),
  302    !,
  303    argv_usage(M:debug),
  304    halt(0).
  305opt_parse(M:Argv, Positional, Options, POptions) :-
  306    opt_parse(Argv, Positional, Options, M, POptions).
  307
  308opt_needs_help(M:[Arg]) :-
  309    in(M:opt_type(_, help, boolean)),
  310    !,
  311    in(M:opt_type(Opt, help, boolean)),
  312    (   short_opt(Opt)
  313    ->  atom_concat(-, Opt, Arg)
  314    ;   atom_concat(--, Opt, Arg)
  315    ),
  316    !.
  317opt_needs_help(_:['-h']).
  318opt_needs_help(_:['-?']).
  319opt_needs_help(_:['--help']).
  320
  321opt_parse([], Positional, Options, _, _) =>
  322    Positional = [],
  323    Options = [].
  324opt_parse([--|T], Positional, Options, _, _) =>
  325    Positional = T,
  326    Options = [].
  327opt_parse([H|T], Positional, Options, M, POptions), atom_concat(--, Long, H) =>
  328    take_long(Long, T, Positional, Options, M, POptions).
  329opt_parse([H|T], Positional, Options, M, POptions),
  330    H \== '-',
  331    string_concat(-, Opts, H) =>
  332    string_chars(Opts, Shorts),
  333    take_shorts(Shorts, T, Positional, Options, M, POptions).
  334opt_parse(Argv, Positional, Options, _M, POptions),
  335    option(options_after_arguments(false), POptions) =>
  336    Positional = Argv,
  337    Options = [].
  338opt_parse([H|T], Positional, Options, M, POptions) =>
  339    Positional = [H|PT],
  340    opt_parse(T, PT, Options, M, POptions).
  341
  342
  343take_long(Long, T, Positional, Options, M, POptions) :- % --long=Value
  344    sub_atom(Long, B, _, A, =),
  345    !,
  346    sub_atom(Long, 0, B, _, LName0),
  347    sub_atom(Long, _, A, 0, VAtom),
  348    canonical_name(LName0, LName),
  349    (   in(M:opt_type(LName, Name, Type))
  350    ->  opt_value(Type, Long, VAtom, Value),
  351        Opt =.. [Name,Value],
  352        Options = [Opt|OptionsT],
  353        opt_parse(T, Positional, OptionsT, M, POptions)
  354    ;   opt_error(unknown_option(M:LName0))
  355    ).
  356take_long(LName0, T, Positional, Options, M, POptions) :- % --long
  357    canonical_name(LName0, LName),
  358    take_long_(LName, T, Positional, Options, M, POptions).
  359
  360take_long_(Long, T, Positional, Options, M, POptions) :- % --long
  361    opt_bool_type(Long, Name, Value, M),
  362    !,
  363    Opt =.. [Name,Value],
  364    Options = [Opt|OptionsT],
  365    opt_parse(T, Positional, OptionsT, M, POptions).
  366take_long_(Long, T, Positional, Options, M, POptions) :- % --no-long, --nolong
  367    (   atom_concat('no_', LName, Long)
  368    ;   atom_concat('no', LName, Long)
  369    ),
  370    opt_bool_type(LName, Name, Value0, M),
  371    !,
  372    negate(Value0, Value),
  373    Opt =.. [Name,Value],
  374    Options = [Opt|OptionsT],
  375    opt_parse(T, Positional, OptionsT, M, POptions).
  376take_long_(Long, T, Positional, Options, M, POptions) :- % --long
  377    in(M:opt_type(Long, Name, Type)),
  378    !,
  379    (   T = [VAtom|T1]
  380    ->  opt_value(Type, Long, VAtom, Value),
  381        Opt =.. [Name,Value],
  382        Options = [Opt|OptionsT],
  383        opt_parse(T1, Positional, OptionsT, M, POptions)
  384    ;   opt_error(missing_value(Long, Type))
  385    ).
  386take_long_(Long, _, _, _, M, _) :-
  387    opt_error(unknown_option(M:Long)).
  388
  389take_shorts([], T, Positional, Options, M, POptions) :-
  390    opt_parse(T, Positional, Options, M, POptions).
  391take_shorts([H|T], Argv, Positional, Options, M, POptions) :-
  392    opt_bool_type(H, Name, Value, M),
  393    !,
  394    Opt =.. [Name,Value],
  395    Options = [Opt|OptionsT],
  396    take_shorts(T, Argv, Positional, OptionsT, M, POptions).
  397take_shorts([H|T], Argv, Positional, Options, M, POptions) :-
  398    in(M:opt_type(H, Name, Type)),
  399    !,
  400    (   T == []
  401    ->  (   Argv = [VAtom|ArgvT]
  402        ->  opt_value(Type, H, VAtom, Value),
  403            Opt =.. [Name,Value],
  404            Options = [Opt|OptionsT],
  405            take_shorts(T, ArgvT, Positional, OptionsT, M, POptions)
  406        ;   opt_error(missing_value(H, Type))
  407        )
  408    ;   atom_chars(VAtom, T),
  409        opt_value(Type, H, VAtom, Value),
  410        Opt =.. [Name,Value],
  411        Options = [Opt|OptionsT],
  412        take_shorts([], Argv, Positional, OptionsT, M, POptions)
  413    ).
  414take_shorts([H|_], _, _, _, M, _) :-
  415    opt_error(unknown_option(M:H)).
  416
  417opt_bool_type(Opt, Name, Value, M) :-
  418    in(M:opt_type(Opt, Name, Type)),
  419    (   Type == boolean
  420    ->  Value = true
  421    ;   Type = boolean(Value)
  422    ).
  423
  424negate(true, false).
  425negate(false, true).
 opt_value(+Type, +Opt, +VAtom, -Value) is det
Errors
- opt_error(Error)
  431opt_value(Type, _Opt, VAtom, Value) :-
  432    opt_convert(Type, VAtom, Value),
  433    !.
  434opt_value(Type, Opt, VAtom, _) :-
  435    opt_error(value_type(Opt, Type, VAtom)).
 opt_convert(+Type, +VAtom, -Value) is semidet
  439opt_convert(A|B, Spec, Value) :-
  440    (   opt_convert(A, Spec, Value)
  441    ->  true
  442    ;   opt_convert(B, Spec, Value)
  443    ).
  444opt_convert(boolean, Spec, Value) :-
  445    to_bool(Spec, Value).
  446opt_convert(boolean(_), Spec, Value) :-
  447    to_bool(Spec, Value).
  448opt_convert(integer, Spec, Value) :-
  449    atom_number(Spec, Value),
  450    integer(Value).
  451opt_convert(float, Spec, Value) :-
  452    atom_number(Spec, Value0),
  453    Value is float(Value0).
  454opt_convert(nonneg, Spec, Value) :-
  455    atom_number(Spec, Value),
  456    integer(Value),
  457    Value >= 0.
  458opt_convert(natural, Spec, Value) :-
  459    atom_number(Spec, Value),
  460    integer(Value),
  461    Value >= 1.
  462opt_convert(between(Low, High), Spec, Value) :-
  463    atom_number(Spec, Value0),
  464    (   ( float(Low) ; float(High) )
  465    ->  Value is float(Value0)
  466    ;   integer(Value0),
  467        Value = Value0
  468    ),
  469    Value >= Low, Value =< High.
  470opt_convert(atom, Value, Value).
  471opt_convert(oneof(List), Value, Value) :-
  472    memberchk(Value, List).
  473opt_convert(string, Value0, Value) :-
  474    atom_string(Value0, Value).
  475opt_convert(file, Spec, Value) :-
  476    prolog_to_os_filename(Value, Spec).
  477opt_convert(file(Access), Spec, Value) :-
  478    (   Spec == '-'
  479    ->  Value = '-'
  480    ;   prolog_to_os_filename(Value, Spec),
  481        (   access_file(Value, Access)
  482        ->  true
  483        ;   opt_error(access_file(Spec, Access))
  484        )
  485    ).
  486opt_convert(term, Spec, Value) :-
  487    term_string(Value, Spec, []).
  488opt_convert(term(Options), Spec, Value) :-
  489    term_string(Term, Spec, Options),
  490    (   option(variable_names(Bindings), Options)
  491    ->  Value = Term-Bindings
  492    ;   Value = Term
  493    ).
  494
  495to_bool(true,    true).
  496to_bool('True',  true).
  497to_bool('TRUE',  true).
  498to_bool(on,      true).
  499to_bool('On',    true).
  500to_bool('1',     true).
  501to_bool(false,   false).
  502to_bool('False', false).
  503to_bool('FALSE', false).
  504to_bool(off,     false).
  505to_bool('Off',   false).
  506to_bool('0',     false).
 argv_usage(:Level) is det
Use print_message/2 to print a usage message at Level. To print the message as plain text indefault color, use debug. Other meaningful options are informational or warning. The help page consists of four sections, two of which are optional:
  1. The header is created from opt_help(help(header), String). It is optional.
  2. The usage is added by default. The part behind Usage: <command> is by default [options] and can be overruled using opt_help(help(usage), String).
  3. The actual option descriptions. The options are presented in the order they are defined in opt_type/3. Subsequent options for the same destination (option name) are joined with the first.
  4. The footer_ is created from opt_help(help(footer), String). It is optional.

The help provided by help(header), help(usage) and help(footer) are either a simple string or a list of elements as defined by print_message_lines/3. In the latter case, the construct \Callable can be used to call a DCG rule in the module from which the user calls argv_options/3. For example, we can add a bold title using

opt_help(help(header), [ansi(bold, '~w', ['My title'])]).
  535argv_usage(M:Level) :-
  536    print_message(Level, opt_usage(M)).
  537
  538:- multifile
  539    prolog:message//1.  540
  541prolog:message(opt_usage(M)) -->
  542    usage(M).
  543
  544usage(M) -->
  545    usage_text(M:header),
  546    usage_line(M),
  547    usage_options(M),
  548    usage_text(M:footer).
 usage_text(:Which)// is det
Emit a user element. This may use elements as defined by print_message_lines/3 or can be a simple string.
  555usage_text(M:Which) -->
  556    { in(M:opt_help(help(Which), Help))
  557    },
  558    !,
  559    (   {Which == header}
  560    ->  user_text(M:Help), [nl]
  561    ;   [nl], user_text(M:Help)
  562    ).
  563usage_text(_) -->
  564    [].
  565
  566user_text(M:Entries) -->
  567    { is_list(Entries) },
  568    sequence(help_elem(M), Entries).
  569user_text(_:Help) -->
  570    [ '~w'-[Help] ].
  571
  572help_elem(M, \Callable) -->
  573    { callable(Callable) },
  574    call(M:Callable),
  575    !.
  576help_elem(_M, Elem) -->
  577    [ Elem ].
  578
  579usage_line(M) -->
  580    [ ansi(comment, 'Usage: ', []) ],
  581    cmdline(M),
  582    (   {in(M:opt_help(help(usage), Help))}
  583    ->  user_text(M:Help)
  584    ;   [ ' [options]'-[] ]
  585    ),
  586    [ nl, nl ].
  587
  588cmdline(_M) -->
  589    { current_prolog_flag(associated_file, AbsFile),
  590      file_base_name(AbsFile, Base),
  591      current_prolog_flag(os_argv, Argv),
  592      append(Pre, [File|_], Argv),
  593      file_base_name(File, Base),
  594      append(Pre, [File], Cmd),
  595      !
  596    },
  597    sequence(cmdarg, [' '-[]], Cmd).
  598cmdline(_M) -->
  599    { current_prolog_flag(saved_program, true),
  600      current_prolog_flag(os_argv, OsArgv),
  601      append(_, ['-x', State|_], OsArgv),
  602      !
  603    },
  604    cmdarg(State).
  605cmdline(_M) -->
  606    { current_prolog_flag(os_argv, [Argv0|_])
  607    },
  608    cmdarg(Argv0).
  609
  610cmdarg(A) -->
  611    [ '~w'-[A] ].
 usage_options(+Module)//
Find the defined options and display help on them. Uses opt_type/3 to find the options and their type, opt_help/2 to find the option help comment and opt_meta/2 for meta types.
  619usage_options(M) -->
  620    { findall(Opt, get_option(M, Opt), Opts),
  621      maplist(options_width, Opts, OptWidths),
  622      max_list(OptWidths, MaxOptWidth),
  623      catch(tty_size(_, Width), _, Width = 80),
  624      OptColW is min(MaxOptWidth, 30),
  625      HelpColW is Width-4-OptColW
  626    },
  627    [ ansi(comment, 'Options:', []), nl ],
  628    sequence(opt_usage(OptColW, HelpColW), [nl], Opts).
  629
  630opt_usage(OptColW, HelpColW, opt(_Name, Type, Short, Long, Help, Meta)) -->
  631    options(Type, Short, Long, Meta),
  632    [ '~t~*:| '-[OptColW] ],
  633    help_text(Help, OptColW, HelpColW).
  634
  635help_text([First|Lines], Indent, _Width) -->
  636    !,
  637    [ '~w'-[First], nl ],
  638    sequence(rest_line(Indent), [nl], Lines).
  639help_text(Text, _Indent, Width) -->
  640    { string_length(Text, Len),
  641      Len =< Width
  642    },
  643    !,
  644    [ '~w'-[Text] ].
  645help_text(Text, Indent, Width) -->
  646    { wrap_text(Width, Text, [First|Lines])
  647    },
  648    [ '~w'-[First], nl ],
  649    sequence(rest_line(Indent), [nl], Lines).
  650
  651rest_line(Indent, Line) -->
  652    [ '~t~*| ~w'-[Indent, Line] ].
 wrap_text(+Width, +Text, -Wrapped)
Simple text wrapper. Breaks Text into words and creates lines with minimally one word and as many additional words as fit in Width. Wrapped is a list of strings.
  660wrap_text(Width, Text, Wrapped) :-
  661    split_string(Text, " \t\n", " \t\n", Words),
  662    wrap_lines(Words, Width, Wrapped).
  663
  664wrap_lines([], _, []).
  665wrap_lines([H|T0], Width, [Line|Lines]) :-
  666    !,
  667    string_length(H, Len),
  668    take_line(T0, T1, Width, Len, LineWords),
  669    atomics_to_string([H|LineWords], " ", Line),
  670    wrap_lines(T1, Width, Lines).
  671
  672take_line([H|T0], T, Width, Here, [H|Line]) :-
  673    string_length(H, Len),
  674    NewHere is Here+Len+1,
  675    NewHere =< Width,
  676    !,
  677    take_line(T0, T, Width, NewHere, Line).
  678take_line(T, T, _, _, []).
 options(+Type, +ShortOpt, +LongOpts, +Meta)//
Emit a line with options.
  684options(Type, ShortOpt, LongOpts, Meta) -->
  685    { append(ShortOpt, LongOpts, Opts) },
  686    sequence(option(Type, Meta), [', '-[]], Opts).
  687
  688option(boolean, _, Opt) -->
  689    opt(Opt).
  690option(_, Meta, Opt) -->
  691    opt(Opt),
  692    (   { short_opt(Opt) }
  693    ->  [ ' '-[] ]
  694    ;   [ '='-[] ]
  695    ),
  696    [ ansi(var, '~w', [Meta]) ].
 options_width(+Opt, -Width) is det
Compute the width of the column we need for the options.
  702options_width(opt(_Name, boolean, Short, Long, _Help, _Meta), W) =>
  703    length(Short, SCount),
  704    length(Long, LCount),
  705    maplist(atom_length, Long, LLens),
  706    sum_list(LLens, LLen),
  707    W is ((SCount+LCount)-1)*2 +               % ', ' seps
  708         SCount*2 +
  709         LCount*2 + LLen.
  710options_width(opt(_Name, _Type, Short, Long, _Help, Meta), W) =>
  711    length(Short, SCount),
  712    length(Long, LCount),
  713    atom_length(Meta, MLen),
  714    maplist(atom_length, Long, LLens),
  715    sum_list(LLens, LLen),
  716    W is ((SCount+LCount)-1)*2 +               % ', ' seps
  717         SCount*3 + SCount*MLen +
  718         LCount*3 + LLen + LCount*MLen.
 get_option(+Module, -Opt) is multi
Get a description for a single option. Opt is a term
opt(Name, Type, ShortFlags, Longflags, Help, Meta).
  726get_option(M, opt(help, boolean, [h,?], [help],
  727                  Help, -)) :-
  728    \+ in(M:opt_type(_, help, boolean)),       % user defined help
  729    (   in(M:opt_help(help, Help))
  730    ->  true
  731    ;   Help = "Show this help message and exit"
  732    ).
  733get_option(M, opt(Name, Type, Short, Long, Help, Meta)) :-
  734    findall(Name, in(M:opt_type(_, Name, _)), Names),
  735    list_to_set(Names, UNames),
  736    member(Name, UNames),
  737    findall(Opt-Type,
  738            in(M:opt_type(Opt, Name, Type)),
  739            Pairs),
  740    option_type(Name, Pairs, TypeT),
  741    functor(TypeT, Type, _),
  742    pairs_keys(Pairs, Opts),
  743    partition(short_opt, Opts, Short, Long),
  744    (   in(M:opt_help(Name, Help))
  745    ->  true
  746    ;   Help = ''
  747    ),
  748    (   in(M:opt_meta(Name, Meta))
  749    ->  true
  750    ;   upcase_atom(Type, Meta)
  751    ).
  752
  753option_type(Name, Pairs, Type) :-
  754    pairs_values(Pairs, Types),
  755    sort(Types, [Type|UTypes]),
  756    (   UTypes = []
  757    ->  true
  758    ;   print_message(warning,
  759                      error(opt_error(multiple_types(Name, [Type|UTypes])),_))
  760    ).
 in(:Goal)
As call/1, but fails silently if there is no predicate that implements Goal.
  767in(Goal) :-
  768    pi_head(PI, Goal),
  769    current_predicate(PI),
  770    call(Goal).
  771
  772short_opt(Opt) :-
  773    atom_length(Opt, 1).
  774
  775		 /*******************************
  776		 *      OPT ERROR HANDLING	*
  777		 *******************************/
 opt_error(+Error)
Errors
- opt_error(Term)
  783opt_error(Error) :-
  784    throw(error(opt_error(Error), _)).
  785
  786:- multifile
  787    prolog:error_message//1.  788
  789prolog:error_message(opt_error(Error)) -->
  790    opt_error(Error).
  791
  792opt_error(unknown_option(M:Opt)) -->
  793    [ 'Unknown option: '-[] ],
  794    opt(Opt),
  795    hint_help(M).
  796opt_error(missing_value(Opt, Type)) -->
  797    [ 'Option '-[] ],
  798    opt(Opt),
  799    [ ' requires an argument (of type ~p)'-[Type] ].
  800opt_error(value_type(Opt, Type, Found)) -->
  801    [ 'Option '-[] ],
  802    opt(Opt), [' requires'],
  803    type(Type),
  804    [ ' (found '-[], ansi(code, '~w', [Found]), ')'-[] ].
  805opt_error(access_file(File, exist)) -->
  806    [ 'File '-[], ansi(code, '~w', [File]),
  807      ' does not exist'-[]
  808    ].
  809opt_error(access_file(File, Access)) -->
  810    { access_verb(Access, Verb) },
  811    [ 'Cannot access file '-[], ansi(code, '~w', [File]),
  812      ' for '-[], ansi(code, '~w', [Verb])
  813    ].
  814
  815access_verb(read,    reading).
  816access_verb(write,   writing).
  817access_verb(append,  writing).
  818access_verb(execute, executing).
  819
  820hint_help(M) -->
  821    { in(M:opt_type(Opt, help, boolean)) },
  822    !,
  823    [ ' (' ], opt(Opt), [' for help)'].
  824hint_help(_) -->
  825    [ ' (-h for help)'-[] ].
  826
  827opt(Opt) -->
  828    { short_opt(Opt) },
  829    !,
  830    [ ansi(bold, '-~w', [Opt]) ].
  831opt(Opt) -->
  832    [ ansi(bold, '--~w', [Opt]) ].
  833
  834type(A|B) -->
  835    type(A), [' or'],
  836    type(B).
  837type(oneof([One])) -->
  838    !,
  839    [ ' ' ],
  840    atom(One).
  841type(oneof(List)) -->
  842    !,
  843    [ ' one of '-[] ],
  844    sequence(atom, [', '], List).
  845type(between(Low, High)) -->
  846    !,
  847    [ ' a number '-[],
  848      ansi(code, '~w', [Low]), '..', ansi(code, '~w', [High])
  849    ].
  850type(nonneg) -->
  851    [ ' a non-negative integer'-[] ].
  852type(natural) -->
  853    [ ' a positive integer (>= 1)'-[] ].
  854type(file(Access)) -->
  855    [ ' a file with ~w access'-[Access] ].
  856type(Type) -->
  857    [ ' an argument of type '-[], ansi(code, '~w', [Type]) ].
  858
  859atom(A) -->
  860    [ ansi(code, '~w', [A]) ].
  861
  862
  863		 /*******************************
  864		 *         DEBUG SUPPORT	*
  865		 *******************************/
 cli_parse_debug_options(+OptionsIn, -Options) is det
Parse certain commandline options for debugging and development purposes. Options processed are below. Note that the option argument is an atom such that these options may be activated as e.g., --debug='http(_)'.
debug(Topic)
Call debug(Topic). See debug/1 and debug/3.
spy(Predicate)
Place a spy-point on Predicate.
gspy(Predicate)
As spy using the graphical debugger. See tspy/1.
interactive(true)
Start the Prolog toplevel after main/1 completes.
  883cli_parse_debug_options([], []).
  884cli_parse_debug_options([H|T0], Opts) :-
  885    debug_option(H),
  886    !,
  887    cli_parse_debug_options(T0, Opts).
  888cli_parse_debug_options([H|T0], [H|T]) :-
  889    cli_parse_debug_options(T0, T).
  890
  891debug_option(interactive(true)) :-
  892    asserta(interactive).
  893debug_option(debug(TopicS)) :-
  894    term_string(Topic, TopicS),
  895    debug(Topic).
  896debug_option(spy(Atom)) :-
  897    atom_pi(Atom, PI),
  898    spy(PI).
  899debug_option(gspy(Atom)) :-
  900    atom_pi(Atom, PI),
  901    tspy(PI).
  902
  903atom_pi(Atom, Module:PI) :-
  904    split(Atom, :, Module, PiAtom),
  905    !,
  906    atom_pi(PiAtom, PI).
  907atom_pi(Atom, Name//Arity) :-
  908    split(Atom, //, Name, Arity),
  909    !.
  910atom_pi(Atom, Name/Arity) :-
  911    split(Atom, /, Name, Arity),
  912    !.
  913atom_pi(Atom, _) :-
  914    format(user_error, 'Invalid predicate indicator: "~w"~n', [Atom]),
  915    halt(1).
  916
  917split(Atom, Sep, Before, After) :-
  918    sub_atom(Atom, BL, _, AL, Sep),
  919    !,
  920    sub_atom(Atom, 0, BL, _, Before),
  921    sub_atom(Atom, _, AL, 0, AfterAtom),
  922    (   atom_number(AfterAtom, After)
  923    ->  true
  924    ;   After = AfterAtom
  925    ).
 cli_enable_development_system
Re-enable the development environment. Currently re-enables xpce if this was loaded, but not initialised and causes the interactive toplevel to be re-enabled.

This predicate may be called from main/1 to enter the Prolog toplevel rather than terminating the application after main/1 completes.

  938cli_enable_development_system :-
  939    on_signal(int, _, debug),
  940    set_prolog_flag(xpce_threaded, true),
  941    set_prolog_flag(message_ide, true),
  942    (   current_prolog_flag(xpce_version, _)
  943    ->  use_module(library(pce_dispatch)),
  944        memberchk(Goal, [pce_dispatch([])]),
  945        call(Goal)
  946    ;   true
  947    ),
  948    set_prolog_flag(toplevel_goal, prolog).
  949
  950
  951		 /*******************************
  952		 *          IDE SUPPORT		*
  953		 *******************************/
  954
  955:- multifile
  956    prolog:called_by/2.  957
  958prolog:called_by(main, [main(_)]).
  959prolog:called_by(argv_options(_,_,_),
  960                 [ opt_type(_,_,_),
  961                   opt_help(_,_),
  962                   opt_meta(_,_)
  963                 ])