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-2023, 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_debug_opt_type/3,       % -Flag, -Option, -Type
   44            cli_debug_opt_help/2,       % -Option, -Message
   45            cli_debug_opt_meta/2,       % -Option, -Arg
   46	    cli_enable_development_system/0
   47          ]).   48:- use_module(library(debug), [debug/1]).   49:- autoload(library(apply), [maplist/2, 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.

When main/0 is called interactively it simply calls main/1 with the arguments. This allows for debugging scripts as follows:

$ swipl -l script.pl -- arg ...
?- gspy(suspect/1).		% setup debugging
?- main.			% run program
  112main :-
  113    current_prolog_flag(break_level, _),
  114    !,
  115    current_prolog_flag(argv, Av),
  116    context_module(M),
  117    M:main(Av).
  118main :-
  119    context_module(M),
  120    set_signals,
  121    current_prolog_flag(argv, Av),
  122    catch_with_backtrace(M:main(Av), Error, throw(Error)),
  123    (   interactive
  124    ->  cli_enable_development_system
  125    ;   true
  126    ).
  127
  128set_signals :-
  129    on_signal(int, _, interrupt).
 interrupt(+Signal)
We received an interrupt. This handler is installed using on_signal/3.
  136interrupt(_Sig) :-
  137    halt(1).
  138
  139		 /*******************************
  140		 *            OPTIONS		*
  141		 *******************************/
 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. Disjunction can be used create long options with optional values. For example, using the type nonneg|boolean, for an option http handles --http as http(true), --no-http as http(false), --http=3000 and --http 3000 as http(3000). With an optional boolean an option is considered boolean if it is the last or the next argument starts with a hyphen (-).
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.
number
Any number (integer, float, rational).
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.
directory
Convert to a file name in Prolog canonical notation using prolog_to_os_filename/2. No checking is done and thus this type is the same as file
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.
directory(Access)
As directory, and check access. Access is one of read write or create. In the latter case the parent directory must exist and have write access.
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).

  243argv_options(M:Argv, Positional, Options) :-
  244    in(M:opt_type(_,_,_)),
  245    !,
  246    argv_options(M:Argv, Positional, Options, [on_error(halt(1))]).
  247argv_options(_:Argv, Positional, Options) :-
  248    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']
  265argv_options(Argv, Positional, Options, POptions) :-
  266    option(on_error(halt(Code)), POptions),
  267    !,
  268    E = error(_,_),
  269    catch(opt_parse(Argv, Positional, Options, POptions), E,
  270	  ( print_message(error, E),
  271	    halt(Code)
  272	  )).
  273argv_options(Argv, Positional, Options, POptions) :-
  274    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.
  284argv_untyped_options([], Pos, Opts) =>
  285    Pos = [], Opts = [].
  286argv_untyped_options([--|R], Pos, Ops) =>
  287    Pos = R, Ops = [].
  288argv_untyped_options([H0|T0], R, Ops), sub_atom(H0, 0, _, _, --) =>
  289    Ops = [H|T],
  290    (   sub_atom(H0, B, _, A, =)
  291    ->  B2 is B-2,
  292	sub_atom(H0, 2, B2, _, Name),
  293	sub_string(H0, _, A,  0, Value0),
  294	convert_option(Name, Value0, Value)
  295    ;   sub_atom(H0, 2, _, 0, Name0),
  296	(   sub_atom(Name0, 0, _, _, 'no-')
  297	->  sub_atom(Name0, 3, _, 0, Name),
  298	    Value = false
  299	;   Name = Name0,
  300	    Value = true
  301	)
  302    ),
  303    canonical_name(Name, PlName),
  304    H =.. [PlName,Value],
  305    argv_untyped_options(T0, R, T).
  306argv_untyped_options([H|T0], Ops, T) =>
  307    Ops = [H|R],
  308    argv_untyped_options(T0, R, T).
  309
  310convert_option(password, String, String) :- !.
  311convert_option(_, String, Number) :-
  312    number_string(Number, String),
  313    !.
  314convert_option(_, String, Atom) :-
  315    atom_string(Atom, String).
  316
  317canonical_name(Name, PlName) :-
  318    split_string(Name, "-_", "", Parts),
  319    atomic_list_concat(Parts, '_', PlName).
 opt_parse(:Argv, -Positional, -Options, +POptions) is det
Rules follow those of Python optparse:
  331opt_parse(M:Argv, _Positional, _Options, _POptions) :-
  332    opt_needs_help(M:Argv),
  333    !,
  334    argv_usage(M:debug),
  335    halt(0).
  336opt_parse(M:Argv, Positional, Options, POptions) :-
  337    opt_parse(Argv, Positional, Options, M, POptions).
  338
  339opt_needs_help(M:[Arg]) :-
  340    in(M:opt_type(_, help, boolean)),
  341    !,
  342    in(M:opt_type(Opt, help, boolean)),
  343    (   short_opt(Opt)
  344    ->  atom_concat(-, Opt, Arg)
  345    ;   atom_concat(--, Opt, Arg)
  346    ),
  347    !.
  348opt_needs_help(_:['-h']).
  349opt_needs_help(_:['-?']).
  350opt_needs_help(_:['--help']).
  351
  352opt_parse([], Positional, Options, _, _) =>
  353    Positional = [],
  354    Options = [].
  355opt_parse([--|T], Positional, Options, _, _) =>
  356    Positional = T,
  357    Options = [].
  358opt_parse([H|T], Positional, Options, M, POptions), atom_concat(--, Long, H) =>
  359    take_long(Long, T, Positional, Options, M, POptions).
  360opt_parse([H|T], Positional, Options, M, POptions),
  361    H \== '-',
  362    string_concat(-, Opts, H) =>
  363    string_chars(Opts, Shorts),
  364    take_shorts(Shorts, T, Positional, Options, M, POptions).
  365opt_parse(Argv, Positional, Options, _M, POptions),
  366    option(options_after_arguments(false), POptions) =>
  367    Positional = Argv,
  368    Options = [].
  369opt_parse([H|T], Positional, Options, M, POptions) =>
  370    Positional = [H|PT],
  371    opt_parse(T, PT, Options, M, POptions).
  372
  373
  374take_long(Long, T, Positional, Options, M, POptions) :- % --long=Value
  375    sub_atom(Long, B, _, A, =),
  376    !,
  377    sub_atom(Long, 0, B, _, LName0),
  378    sub_atom(Long, _, A, 0, VAtom),
  379    canonical_name(LName0, LName),
  380    (   in(M:opt_type(LName, Name, Type))
  381    ->  opt_value(Type, Long, VAtom, Value),
  382	Opt =.. [Name,Value],
  383	Options = [Opt|OptionsT],
  384	opt_parse(T, Positional, OptionsT, M, POptions)
  385    ;   opt_error(unknown_option(M:LName0))
  386    ).
  387take_long(LName0, T, Positional, Options, M, POptions) :- % --long
  388    canonical_name(LName0, LName),
  389    take_long_(LName, T, Positional, Options, M, POptions).
  390
  391take_long_(Long, T, Positional, Options, M, POptions) :- % --long
  392    opt_bool_type(Long, Name, Value, M),                 % only boolean
  393    !,
  394    Opt =.. [Name,Value],
  395    Options = [Opt|OptionsT],
  396    opt_parse(T, Positional, OptionsT, M, POptions).
  397take_long_(Long, T, Positional, Options, M, POptions) :- % --no-long, --nolong
  398    (   atom_concat('no_', LName, Long)
  399    ;   atom_concat('no', LName, Long)
  400    ),
  401    in(M:opt_type(LName, Name, Type)),
  402    type_optional_bool(Type, Value0),
  403    !,
  404    negate(Value0, Value),
  405    Opt =.. [Name,Value],
  406    Options = [Opt|OptionsT],
  407    opt_parse(T, Positional, OptionsT, M, POptions).
  408take_long_(Long, T, Positional, Options, M, POptions) :- % --long [value]
  409    in(M:opt_type(Long, Name, Type)),
  410    type_optional_bool(Type, Value),
  411    (   T = [VAtom|_],
  412        sub_atom(VAtom, 0, _, _, -)
  413    ->  true
  414    ;   T == []
  415    ),
  416    Opt =.. [Name,Value],
  417    Options = [Opt|OptionsT],
  418    opt_parse(T, Positional, OptionsT, M, POptions).
  419take_long_(Long, T, Positional, Options, M, POptions) :- % --long
  420    in(M:opt_type(Long, Name, Type)),
  421    !,
  422    (   T = [VAtom|T1]
  423    ->  opt_value(Type, Long, VAtom, Value),
  424	Opt =.. [Name,Value],
  425	Options = [Opt|OptionsT],
  426	opt_parse(T1, Positional, OptionsT, M, POptions)
  427    ;   opt_error(missing_value(Long, Type))
  428    ).
  429take_long_(Long, _, _, _, M, _) :-
  430    opt_error(unknown_option(M:Long)).
  431
  432take_shorts([], T, Positional, Options, M, POptions) :-
  433    opt_parse(T, Positional, Options, M, POptions).
  434take_shorts([H|T], Argv, Positional, Options, M, POptions) :-
  435    opt_bool_type(H, Name, Value, M),
  436    !,
  437    Opt =.. [Name,Value],
  438    Options = [Opt|OptionsT],
  439    take_shorts(T, Argv, Positional, OptionsT, M, POptions).
  440take_shorts([H|T], Argv, Positional, Options, M, POptions) :-
  441    in(M:opt_type(H, Name, Type)),
  442    !,
  443    (   T == []
  444    ->  (   Argv = [VAtom|ArgvT]
  445	->  opt_value(Type, H, VAtom, Value),
  446	    Opt =.. [Name,Value],
  447	    Options = [Opt|OptionsT],
  448	    take_shorts(T, ArgvT, Positional, OptionsT, M, POptions)
  449	;   opt_error(missing_value(H, Type))
  450	)
  451    ;   atom_chars(VAtom, T),
  452	opt_value(Type, H, VAtom, Value),
  453	Opt =.. [Name,Value],
  454	Options = [Opt|OptionsT],
  455	take_shorts([], Argv, Positional, OptionsT, M, POptions)
  456    ).
  457take_shorts([H|_], _, _, _, M, _) :-
  458    opt_error(unknown_option(M:H)).
  459
  460opt_bool_type(Opt, Name, Value, M) :-
  461    in(M:opt_type(Opt, Name, Type)),
  462    type_bool(Type, Value).
  463
  464type_bool(Type, Value) :-
  465    (   Type == boolean
  466    ->  Value = true
  467    ;   Type = boolean(Value)
  468    ).
  469
  470type_optional_bool((A|B), Value) =>
  471    (   type_optional_bool(A, Value)
  472    ->  true
  473    ;   type_optional_bool(B, Value)
  474    ).
  475type_optional_bool(Type, Value) =>
  476    type_bool(Type, Value).
  477
  478negate(true, false).
  479negate(false, true).
 opt_value(+Type, +Opt, +VAtom, -Value) is det
Errors
- opt_error(Error)
  485opt_value(Type, _Opt, VAtom, Value) :-
  486    opt_convert(Type, VAtom, Value),
  487    !.
  488opt_value(Type, Opt, VAtom, _) :-
  489    opt_error(value_type(Opt, Type, VAtom)).
 opt_convert(+Type, +VAtom, -Value) is semidet
  493opt_convert(A|B, Spec, Value) :-
  494    (   opt_convert(A, Spec, Value)
  495    ->  true
  496    ;   opt_convert(B, Spec, Value)
  497    ).
  498opt_convert(boolean, Spec, Value) :-
  499    to_bool(Spec, Value).
  500opt_convert(boolean(_), Spec, Value) :-
  501    to_bool(Spec, Value).
  502opt_convert(number, Spec, Value) :-
  503    atom_number(Spec, Value).
  504opt_convert(integer, Spec, Value) :-
  505    atom_number(Spec, Value),
  506    integer(Value).
  507opt_convert(float, Spec, Value) :-
  508    atom_number(Spec, Value0),
  509    Value is float(Value0).
  510opt_convert(nonneg, Spec, Value) :-
  511    atom_number(Spec, Value),
  512    integer(Value),
  513    Value >= 0.
  514opt_convert(natural, Spec, Value) :-
  515    atom_number(Spec, Value),
  516    integer(Value),
  517    Value >= 1.
  518opt_convert(between(Low, High), Spec, Value) :-
  519    atom_number(Spec, Value0),
  520    (   ( float(Low) ; float(High) )
  521    ->  Value is float(Value0)
  522    ;   integer(Value0),
  523	Value = Value0
  524    ),
  525    Value >= Low, Value =< High.
  526opt_convert(atom, Value, Value).
  527opt_convert(oneof(List), Value, Value) :-
  528    memberchk(Value, List).
  529opt_convert(string, Value0, Value) :-
  530    atom_string(Value0, Value).
  531opt_convert(file, Spec, Value) :-
  532    prolog_to_os_filename(Value, Spec).
  533opt_convert(file(Access), Spec, Value) :-
  534    (   Spec == '-'
  535    ->  Value = '-'
  536    ;   prolog_to_os_filename(Value, Spec),
  537	(   access_file(Value, Access)
  538	->  true
  539	;   opt_error(access_file(Spec, Access))
  540	)
  541    ).
  542opt_convert(directory, Spec, Value) :-
  543    prolog_to_os_filename(Value, Spec).
  544opt_convert(directory(Access), Spec, Value) :-
  545    prolog_to_os_filename(Value, Spec),
  546    access_directory(Value, Access).
  547opt_convert(term, Spec, Value) :-
  548    term_string(Value, Spec, []).
  549opt_convert(term(Options), Spec, Value) :-
  550    term_string(Term, Spec, Options),
  551    (   option(variable_names(Bindings), Options)
  552    ->  Value = Term-Bindings
  553    ;   Value = Term
  554    ).
  555
  556access_directory(Dir, read) =>
  557    exists_directory(Dir),
  558    access_file(Dir, read).
  559access_directory(Dir, write) =>
  560    exists_directory(Dir),
  561    access_file(Dir, write).
  562access_directory(Dir, create) =>
  563    (   exists_directory(Dir)
  564    ->  access_file(Dir, write)
  565    ;   \+ exists_file(Dir),
  566        file_directory_name(Dir, Parent),
  567        exists_directory(Parent),
  568        access_file(Parent, write)
  569    ).
  570
  571to_bool(true,    true).
  572to_bool('True',  true).
  573to_bool('TRUE',  true).
  574to_bool(on,      true).
  575to_bool('On',    true).
  576to_bool(yes,     true).
  577to_bool('Yes',   true).
  578to_bool('1',     true).
  579to_bool(false,   false).
  580to_bool('False', false).
  581to_bool('FALSE', false).
  582to_bool(off,     false).
  583to_bool('Off',   false).
  584to_bool(no,      false).
  585to_bool('No',    false).
  586to_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'])]).
  615argv_usage(M:Level) :-
  616    print_message(Level, opt_usage(M)).
  617
  618:- multifile
  619    prolog:message//1.  620
  621prolog:message(opt_usage(M)) -->
  622    usage(M).
  623
  624usage(M) -->
  625    usage_text(M:header),
  626    usage_line(M),
  627    usage_options(M),
  628    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.
  635usage_text(M:Which) -->
  636    { in(M:opt_help(help(Which), Help))
  637    },
  638    !,
  639    (   {Which == header}
  640    ->  user_text(M:Help), [nl]
  641    ;   [nl], user_text(M:Help)
  642    ).
  643usage_text(_) -->
  644    [].
  645
  646user_text(M:Entries) -->
  647    { is_list(Entries) },
  648    sequence(help_elem(M), Entries).
  649user_text(_:Help) -->
  650    [ '~w'-[Help] ].
  651
  652help_elem(M, \Callable) -->
  653    { callable(Callable) },
  654    call(M:Callable),
  655    !.
  656help_elem(_M, Elem) -->
  657    [ Elem ].
  658
  659usage_line(M) -->
  660    [ ansi(comment, 'Usage: ', []) ],
  661    cmdline(M),
  662    (   {in(M:opt_help(help(usage), Help))}
  663    ->  user_text(M:Help)
  664    ;   [ ' [options]'-[] ]
  665    ),
  666    [ nl, nl ].
  667
  668
  669cmdline(_M) -->
  670    { current_prolog_flag(app_name, App),
  671      !,
  672      current_prolog_flag(os_argv, [Argv0|_])
  673    },
  674    cmdarg(Argv0), [' '-[], ansi(bold, '~w', [App])].
  675cmdline(_M) -->
  676    { current_prolog_flag(associated_file, AbsFile),
  677      file_base_name(AbsFile, Base),
  678      current_prolog_flag(os_argv, Argv),
  679      append(Pre, [File|_], Argv),
  680      file_base_name(File, Base),
  681      append(Pre, [File], Cmd),
  682      !
  683    },
  684    sequence(cmdarg, [' '-[]], Cmd).
  685cmdline(_M) -->
  686    { current_prolog_flag(saved_program, true),
  687      current_prolog_flag(os_argv, OsArgv),
  688      append(_, ['-x', State|_], OsArgv),
  689      !
  690    },
  691    cmdarg(State).
  692cmdline(_M) -->
  693    { current_prolog_flag(os_argv, [Argv0|_])
  694    },
  695    cmdarg(Argv0).
  696
  697cmdarg(A) -->
  698    [ '~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.
  706usage_options(M) -->
  707    { findall(Opt, get_option(M, Opt), Opts),
  708      maplist(options_width, Opts, OptWidths),
  709      max_list(OptWidths, MaxOptWidth),
  710      tty_width(Width),
  711      OptColW is min(MaxOptWidth, 30),
  712      HelpColW is Width-4-OptColW
  713    },
  714    [ ansi(comment, 'Options:', []), nl ],
  715    sequence(opt_usage(OptColW, HelpColW), [nl], Opts).
  716
  717% Just  catch/3  is   enough,   but    dependency   tracking   in  e.g.,
  718% list_undefined/0 still considers this a missing dependency.
  719:- if(current_predicate(tty_size/2)).  720tty_width(Width) :-
  721     catch(tty_size(_, Width), _, Width = 80).
  722:- else.  723tty_width(80).
  724:- endif.  725
  726opt_usage(OptColW, HelpColW, opt(_Name, Type, Short, Long, Help, Meta)) -->
  727    options(Type, Short, Long, Meta),
  728    [ '~t~*:| '-[OptColW] ],
  729    help_text(Help, OptColW, HelpColW).
  730
  731help_text([First|Lines], Indent, _Width) -->
  732    !,
  733    [ '~w'-[First], nl ],
  734    sequence(rest_line(Indent), [nl], Lines).
  735help_text(Text, _Indent, Width) -->
  736    { string_length(Text, Len),
  737      Len =< Width
  738    },
  739    !,
  740    [ '~w'-[Text] ].
  741help_text(Text, Indent, Width) -->
  742    { wrap_text(Width, Text, [First|Lines])
  743    },
  744    [ '~w'-[First], nl ],
  745    sequence(rest_line(Indent), [nl], Lines).
  746
  747rest_line(Indent, Line) -->
  748    [ '~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.
  756wrap_text(Width, Text, Wrapped) :-
  757    split_string(Text, " \t\n", " \t\n", Words),
  758    wrap_lines(Words, Width, Wrapped).
  759
  760wrap_lines([], _, []).
  761wrap_lines([H|T0], Width, [Line|Lines]) :-
  762    !,
  763    string_length(H, Len),
  764    take_line(T0, T1, Width, Len, LineWords),
  765    atomics_to_string([H|LineWords], " ", Line),
  766    wrap_lines(T1, Width, Lines).
  767
  768take_line([H|T0], T, Width, Here, [H|Line]) :-
  769    string_length(H, Len),
  770    NewHere is Here+Len+1,
  771    NewHere =< Width,
  772    !,
  773    take_line(T0, T, Width, NewHere, Line).
  774take_line(T, T, _, _, []).
 options(+Type, +ShortOpt, +LongOpts, +Meta)//
Emit a line with options.
  780options(Type, ShortOpt, LongOpts, Meta) -->
  781    { append(ShortOpt, LongOpts, Opts) },
  782    sequence(option(Type, Meta), [', '-[]], Opts).
  783
  784option(boolean, _, Opt) -->
  785    opt(Opt).
  786option(_Type, [Meta], Opt) -->
  787    \+ { short_opt(Opt) },
  788    !,
  789    opt(Opt),
  790    [ '[='-[], ansi(var, '~w', [Meta]), ']'-[] ].
  791option(_Type, Meta, Opt) -->
  792    opt(Opt),
  793    (   { short_opt(Opt) }
  794    ->  [ ' '-[] ]
  795    ;   [ '='-[] ]
  796    ),
  797    [ ansi(var, '~w', [Meta]) ].
 options_width(+Opt, -Width) is det
Compute the width of the column we need for the options.
  803options_width(opt(_Name, boolean, Short, Long, _Help, _Meta), W) =>
  804    length(Short, SCount),
  805    length(Long, LCount),
  806    maplist(atom_length, Long, LLens),
  807    sum_list(LLens, LLen),
  808    W is ((SCount+LCount)-1)*2 +               % ', ' seps
  809	 SCount*2 +
  810	 LCount*2 + LLen.
  811options_width(opt(_Name, _Type, Short, Long, _Help, Meta), W) =>
  812    length(Short, SCount),
  813    length(Long, LCount),
  814    (   Meta = [MName]
  815    ->  atom_length(MName, MLen0),
  816        MLen is MLen0+2
  817    ;   atom_length(Meta, MLen)
  818    ),
  819    maplist(atom_length, Long, LLens),
  820    sum_list(LLens, LLen),
  821    W is ((SCount+LCount)-1)*2 +               % ', ' seps
  822	 SCount*3 + SCount*MLen +
  823	 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).
  831get_option(M, opt(help, boolean, [h,?], [help],
  832		  Help, -)) :-
  833    \+ in(M:opt_type(_, help, boolean)),       % user defined help
  834    (   in(M:opt_help(help, Help))
  835    ->  true
  836    ;   Help = "Show this help message and exit"
  837    ).
  838get_option(M, opt(Name, TypeName, Short, Long, Help, Meta)) :-
  839    findall(Name, in(M:opt_type(_, Name, _)), Names),
  840    list_to_set(Names, UNames),
  841    member(Name, UNames),
  842    findall(Opt-Type,
  843	    in(M:opt_type(Opt, Name, Type)),
  844	    Pairs),
  845    option_type(Name, Pairs, TypeT),
  846    functor(TypeT, TypeName, _),
  847    pairs_keys(Pairs, Opts),
  848    partition(short_opt, Opts, Short, Long),
  849    (   in(M:opt_help(Name, Help))
  850    ->  true
  851    ;   Help = ''
  852    ),
  853    (   in(M:opt_meta(Name, Meta0))
  854    ->  true
  855    ;   upcase_atom(TypeName, Meta0)
  856    ),
  857    (   \+ type_bool(TypeT, _),
  858        type_optional_bool(TypeT, _)
  859    ->  Meta = [Meta0]
  860    ;   Meta = Meta0
  861    ).
  862
  863option_type(Name, Pairs, Type) :-
  864    pairs_values(Pairs, Types),
  865    sort(Types, [Type|UTypes]),
  866    (   UTypes = []
  867    ->  true
  868    ;   print_message(warning,
  869		      error(opt_error(multiple_types(Name, [Type|UTypes])),_))
  870    ).
 in(:Goal)
As call/1, but fails silently if there is no predicate that implements Goal.
  877in(Goal) :-
  878    pi_head(PI, Goal),
  879    current_predicate(PI),
  880    call(Goal).
  881
  882short_opt(Opt) :-
  883    atom_length(Opt, 1).
  884
  885		 /*******************************
  886		 *      OPT ERROR HANDLING	*
  887		 *******************************/
 opt_error(+Error)
Errors
- opt_error(Term)
  893opt_error(Error) :-
  894    throw(error(opt_error(Error), _)).
  895
  896:- multifile
  897    prolog:error_message//1.  898
  899prolog:error_message(opt_error(Error)) -->
  900    opt_error(Error).
  901
  902opt_error(unknown_option(M:Opt)) -->
  903    [ 'Unknown option: '-[] ],
  904    opt(Opt),
  905    hint_help(M).
  906opt_error(missing_value(Opt, Type)) -->
  907    [ 'Option '-[] ],
  908    opt(Opt),
  909    [ ' requires an argument (of type ~p)'-[Type] ].
  910opt_error(value_type(Opt, Type, Found)) -->
  911    [ 'Option '-[] ],
  912    opt(Opt), [' requires'],
  913    type(Type),
  914    [ ' (found '-[], ansi(code, '~w', [Found]), ')'-[] ].
  915opt_error(access_file(File, exist)) -->
  916    [ 'File '-[], ansi(code, '~w', [File]),
  917      ' does not exist'-[]
  918    ].
  919opt_error(access_file(File, Access)) -->
  920    { access_verb(Access, Verb) },
  921    [ 'Cannot access file '-[], ansi(code, '~w', [File]),
  922      ' for '-[], ansi(code, '~w', [Verb])
  923    ].
  924
  925access_verb(read,    reading).
  926access_verb(write,   writing).
  927access_verb(append,  writing).
  928access_verb(execute, executing).
  929
  930hint_help(M) -->
  931    { in(M:opt_type(Opt, help, boolean)) },
  932    !,
  933    [ ' (' ], opt(Opt), [' for help)'].
  934hint_help(_) -->
  935    [ ' (-h for help)'-[] ].
  936
  937opt(Opt) -->
  938    { short_opt(Opt) },
  939    !,
  940    [ ansi(bold, '-~w', [Opt]) ].
  941opt(Opt) -->
  942    [ ansi(bold, '--~w', [Opt]) ].
  943
  944type(A|B) -->
  945    type(A), [' or'],
  946    type(B).
  947type(oneof([One])) -->
  948    !,
  949    [ ' ' ],
  950    atom(One).
  951type(oneof(List)) -->
  952    !,
  953    [ ' one of '-[] ],
  954    sequence(atom, [', '], List).
  955type(between(Low, High)) -->
  956    !,
  957    [ ' a number '-[],
  958      ansi(code, '~w', [Low]), '..', ansi(code, '~w', [High])
  959    ].
  960type(nonneg) -->
  961    [ ' a non-negative integer'-[] ].
  962type(natural) -->
  963    [ ' a positive integer (>= 1)'-[] ].
  964type(file(Access)) -->
  965    [ ' a file with ~w access'-[Access] ].
  966type(Type) -->
  967    [ ' an argument of type '-[], ansi(code, '~w', [Type]) ].
  968
  969atom(A) -->
  970    [ ansi(code, '~w', [A]) ].
  971
  972
  973		 /*******************************
  974		 *         DEBUG SUPPORT	*
  975		 *******************************/
 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.
  993cli_parse_debug_options([], []).
  994cli_parse_debug_options([H|T0], Opts) :-
  995    debug_option(H),
  996    !,
  997    cli_parse_debug_options(T0, Opts).
  998cli_parse_debug_options([H|T0], [H|T]) :-
  999    cli_parse_debug_options(T0, T).
 cli_debug_opt_type(-Flag, -Option, -Type)
 cli_debug_opt_help(-Option, -Message)
 cli_debug_opt_meta(-Option, -Arg)
Implements opt_type/3, opt_help/2 and opt_meta/2 for debug arguments. Applications that wish to use these features can call these predicates from their own hook. Fot example:
opt_type(..., ..., ...).	% application types
opt_type(Flag, Opt, Type) :-
    cli_debug_opt_type(Flag, Opt, Type).
% similar for opt_help/2 and opt_meta/2

main(Argv) :-
    argv_options(Argv, Positional, Options0),
    cli_parse_debug_options(Options0, Options),
    ...
 1021cli_debug_opt_type(debug,       debug,       string).
 1022cli_debug_opt_type(spy,         spy,         string).
 1023cli_debug_opt_type(gspy,        gspy,        string).
 1024cli_debug_opt_type(interactive, interactive, boolean).
 1025
 1026cli_debug_opt_help(debug,
 1027                   "Call debug(Topic).  See debug/1 and debug/3. \c
 1028                    Multiple topics may be separated by : or ;").
 1029cli_debug_opt_help(spy,
 1030                   "Place a spy-point on Predicate. \c
 1031                    Multiple topics may be separated by : or ;").
 1032cli_debug_opt_help(gspy,
 1033                   "As --spy using the graphical debugger.  See tspy/1 \c
 1034                    Multiple topics may be separated by `;`").
 1035cli_debug_opt_help(interactive,
 1036                   "Start the Prolog toplevel after main/1 completes.").
 1037
 1038cli_debug_opt_meta(debug, 'TOPICS').
 1039cli_debug_opt_meta(spy,   'PREDICATES').
 1040cli_debug_opt_meta(gspy,  'PREDICATES').
 1041
 1042:- meta_predicate
 1043    spy_from_string(1, +). 1044
 1045debug_option(interactive(true)) :-
 1046    asserta(interactive).
 1047debug_option(debug(Spec)) :-
 1048    split_string(Spec, ";", "", Specs),
 1049    maplist(debug_from_string, Specs).
 1050debug_option(spy(Spec)) :-
 1051    split_string(Spec, ";", "", Specs),
 1052    maplist(spy_from_string(spy), Specs).
 1053debug_option(gspy(Spec)) :-
 1054    split_string(Spec, ";", "", Specs),
 1055    maplist(spy_from_string(cli_gspy), Specs).
 1056
 1057debug_from_string(TopicS) :-
 1058    term_string(Topic, TopicS),
 1059    debug(Topic).
 1060
 1061spy_from_string(Pred, Spec) :-
 1062    atom_pi(Spec, PI),
 1063    call(Pred, PI).
 1064
 1065cli_gspy(PI) :-
 1066    (   exists_source(library(threadutil))
 1067    ->  use_module(library(threadutil), [tspy/1]),
 1068	Goal = tspy(PI)
 1069    ;   exists_source(library(gui_tracer))
 1070    ->  use_module(library(gui_tracer), [gspy/1]),
 1071	Goal = gspy(PI)
 1072    ;   Goal = spy(PI)
 1073    ),
 1074    call(Goal).
 1075
 1076atom_pi(Atom, Module:PI) :-
 1077    split(Atom, :, Module, PiAtom),
 1078    !,
 1079    atom_pi(PiAtom, PI).
 1080atom_pi(Atom, Name//Arity) :-
 1081    split(Atom, //, Name, Arity),
 1082    !.
 1083atom_pi(Atom, Name/Arity) :-
 1084    split(Atom, /, Name, Arity),
 1085    !.
 1086atom_pi(Atom, _) :-
 1087    format(user_error, 'Invalid predicate indicator: "~w"~n', [Atom]),
 1088    halt(1).
 1089
 1090split(Atom, Sep, Before, After) :-
 1091    sub_atom(Atom, BL, _, AL, Sep),
 1092    !,
 1093    sub_atom(Atom, 0, BL, _, Before),
 1094    sub_atom(Atom, _, AL, 0, AfterAtom),
 1095    (   atom_number(AfterAtom, After)
 1096    ->  true
 1097    ;   After = AfterAtom
 1098    ).
 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.

 1111cli_enable_development_system :-
 1112    on_signal(int, _, debug),
 1113    set_prolog_flag(xpce_threaded, true),
 1114    set_prolog_flag(message_ide, true),
 1115    (   current_prolog_flag(xpce_version, _)
 1116    ->  use_module(library(pce_dispatch)),
 1117	memberchk(Goal, [pce_dispatch([])]),
 1118	call(Goal)
 1119    ;   true
 1120    ),
 1121    set_prolog_flag(toplevel_goal, prolog).
 1122
 1123
 1124		 /*******************************
 1125		 *          IDE SUPPORT		*
 1126		 *******************************/
 1127
 1128:- multifile
 1129    prolog:called_by/2. 1130
 1131prolog:called_by(main, [main(_)]).
 1132prolog:called_by(argv_options(_,_,_),
 1133		 [ opt_type(_,_,_),
 1134		   opt_help(_,_),
 1135		   opt_meta(_,_)
 1136		 ])