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:- if(exists_source(library(doc_markdown))). 57:- autoload(library(doc_markdown), [print_markdown/2]). 58:- endif. 59 60:- meta_predicate 61 argv_options( , , ), 62 argv_options( , , , ), 63 argv_usage( ). 64 65:- dynamic 66 interactive/0.
97:- module_transparent
98 main/0.
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
115main :- 116 current_prolog_flag(break_level, _), 117 !, 118 current_prolog_flag(argv, Av), 119 context_module(M), 120 M:main(Av). 121main :- 122 context_module(M), 123 set_signals, 124 current_prolog_flag(argv, Av), 125 catch_with_backtrace(M:main(Av), Error, throw(Error)), 126 ( interactive 127 -> cli_enable_development_system 128 ; true 129 ). 130 131set_signals :- 132 on_signal(int, _, interrupt).
139interrupt(_Sig) :- 140 halt(1). 141 142 /******************************* 143 * OPTIONS * 144 *******************************/
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.
-
. 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:
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 (-
).--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
. Requires value >= 0.integer
. Requires value >= 1.float
,
else convert as integer
. Then check the range.atom
, but requires the value to be a member of List
(enum type).file
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
, 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
, 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
.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)
.
246argv_options(M:Argv, Positional, Options) :- 247 in(M:opt_type(_,_,_)), 248 !, 249 argv_options(M:Argv, Positional, Options, [on_error(halt(1))]). 250argv_options(_:Argv, Positional, Options) :- 251 argv_untyped_options(Argv, Positional, Options).
halt(Code)
, exit with Code. Other goals are
currently not supported.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']
268argv_options(Argv, Positional, Options, POptions) :- 269 option(on_error(halt(Code)), POptions), 270 !, 271 E = error(_,_), 272 catch(opt_parse(Argv, Positional, Options, POptions), E, 273 ( print_message(error, E), 274 halt(Code) 275 )). 276argv_options(Argv, Positional, Options, POptions) :- 277 opt_parse(Argv, Positional, Options, POptions).
--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.287argv_untyped_options([], Pos, Opts) => 288 Pos = [], Opts = []. 289argv_untyped_options([--|R], Pos, Ops) => 290 Pos = R, Ops = []. 291argv_untyped_options([H0|T0], R, Ops), sub_atom(H0, 0, _, _, --) => 292 Ops = [H|T], 293 ( sub_atom(H0, B, _, A, =) 294 -> B2 is B-2, 295 sub_atom(H0, 2, B2, _, Name), 296 sub_string(H0, _, A, 0, Value0), 297 convert_option(Name, Value0, Value) 298 ; sub_atom(H0, 2, _, 0, Name0), 299 ( sub_atom(Name0, 0, _, _, 'no-') 300 -> sub_atom(Name0, 3, _, 0, Name), 301 Value = false 302 ; Name = Name0, 303 Value = true 304 ) 305 ), 306 canonical_name(Name, PlName), 307 H =.. [PlName,Value], 308 argv_untyped_options(T0, R, T). 309argv_untyped_options([H|T0], Ops, T) => 310 Ops = [H|R], 311 argv_untyped_options(T0, R, T). 312 313convert_option(password, String, String) :- !. 314convert_option(_, String, Number) :- 315 number_string(Number, String), 316 !. 317convert_option(_, String, Atom) :- 318 atom_string(Atom, String). 319 320canonical_name(Name, PlName) :- 321 split_string(Name, "-_", "", Parts), 322 atomic_list_concat(Parts, '_', PlName).
334opt_parse(M:Argv, _Positional, _Options, _POptions) :- 335 opt_needs_help(M:Argv), 336 !, 337 argv_usage(M:debug), 338 halt(0). 339opt_parse(M:Argv, Positional, Options, POptions) :- 340 opt_parse(Argv, Positional, Options, M, POptions). 341 342opt_needs_help(M:[Arg]) :- 343 in(M:opt_type(_, help, boolean)), 344 !, 345 in(M:opt_type(Opt, help, boolean)), 346 ( short_opt(Opt) 347 -> atom_concat(-, Opt, Arg) 348 ; atom_concat(--, Opt, Arg) 349 ), 350 !. 351opt_needs_help(_:['-h']). 352opt_needs_help(_:['-?']). 353opt_needs_help(_:['--help']). 354 355opt_parse([], Positional, Options, _, _) => 356 Positional = [], 357 Options = []. 358opt_parse([--|T], Positional, Options, _, _) => 359 Positional = T, 360 Options = []. 361opt_parse([H|T], Positional, Options, M, POptions), atom_concat(--, Long, H) => 362 take_long(Long, T, Positional, Options, M, POptions). 363opt_parse([H|T], Positional, Options, M, POptions), 364 H \== '-', 365 string_concat(-, Opts, H) => 366 string_chars(Opts, Shorts), 367 take_shorts(Shorts, T, Positional, Options, M, POptions). 368opt_parse(Argv, Positional, Options, _M, POptions), 369 option(options_after_arguments(false), POptions) => 370 Positional = Argv, 371 Options = []. 372opt_parse([H|T], Positional, Options, M, POptions) => 373 Positional = [H|PT], 374 opt_parse(T, PT, Options, M, POptions). 375 376 377take_long(Long, T, Positional, Options, M, POptions) :- % --long=Value 378 sub_atom(Long, B, _, A, =), 379 !, 380 sub_atom(Long, 0, B, _, LName0), 381 sub_atom(Long, _, A, 0, VAtom), 382 canonical_name(LName0, LName), 383 ( in(M:opt_type(LName, Name, Type)) 384 -> opt_value(Type, Long, VAtom, Value), 385 Opt =.. [Name,Value], 386 Options = [Opt|OptionsT], 387 opt_parse(T, Positional, OptionsT, M, POptions) 388 ; opt_error(unknown_option(M:LName0)) 389 ). 390take_long(LName0, T, Positional, Options, M, POptions) :- % --long 391 canonical_name(LName0, LName), 392 take_long_(LName, T, Positional, Options, M, POptions). 393 394take_long_(Long, T, Positional, Options, M, POptions) :- % --long 395 opt_bool_type(Long, Name, Value, M), % only boolean 396 !, 397 Opt =.. [Name,Value], 398 Options = [Opt|OptionsT], 399 opt_parse(T, Positional, OptionsT, M, POptions). 400take_long_(Long, T, Positional, Options, M, POptions) :- % --no-long, --nolong 401 ( atom_concat('no_', LName, Long) 402 ; atom_concat('no', LName, Long) 403 ), 404 in(M:opt_type(LName, Name, Type)), 405 type_optional_bool(Type, Value0), 406 !, 407 negate(Value0, Value), 408 Opt =.. [Name,Value], 409 Options = [Opt|OptionsT], 410 opt_parse(T, Positional, OptionsT, M, POptions). 411take_long_(Long, T, Positional, Options, M, POptions) :- % --long [value] 412 in(M:opt_type(Long, Name, Type)), 413 type_optional_bool(Type, Value), 414 ( T = [VAtom|_], 415 sub_atom(VAtom, 0, _, _, -) 416 -> true 417 ; T == [] 418 ), 419 Opt =.. [Name,Value], 420 Options = [Opt|OptionsT], 421 opt_parse(T, Positional, OptionsT, M, POptions). 422take_long_(Long, T, Positional, Options, M, POptions) :- % --long 423 in(M:opt_type(Long, Name, Type)), 424 !, 425 ( T = [VAtom|T1] 426 -> opt_value(Type, Long, VAtom, Value), 427 Opt =.. [Name,Value], 428 Options = [Opt|OptionsT], 429 opt_parse(T1, Positional, OptionsT, M, POptions) 430 ; opt_error(missing_value(Long, Type)) 431 ). 432take_long_(Long, _, _, _, M, _) :- 433 opt_error(unknown_option(M:Long)). 434 435take_shorts([], T, Positional, Options, M, POptions) :- 436 opt_parse(T, Positional, Options, M, POptions). 437take_shorts([H|T], Argv, Positional, Options, M, POptions) :- 438 opt_bool_type(H, Name, Value, M), 439 !, 440 Opt =.. [Name,Value], 441 Options = [Opt|OptionsT], 442 take_shorts(T, Argv, Positional, OptionsT, M, POptions). 443take_shorts([H|T], Argv, Positional, Options, M, POptions) :- 444 in(M:opt_type(H, Name, Type)), 445 !, 446 ( T == [] 447 -> ( Argv = [VAtom|ArgvT] 448 -> opt_value(Type, H, VAtom, Value), 449 Opt =.. [Name,Value], 450 Options = [Opt|OptionsT], 451 take_shorts(T, ArgvT, Positional, OptionsT, M, POptions) 452 ; opt_error(missing_value(H, Type)) 453 ) 454 ; atom_chars(VAtom, T), 455 opt_value(Type, H, VAtom, Value), 456 Opt =.. [Name,Value], 457 Options = [Opt|OptionsT], 458 take_shorts([], Argv, Positional, OptionsT, M, POptions) 459 ). 460take_shorts([H|_], _, _, _, M, _) :- 461 opt_error(unknown_option(M:H)). 462 463opt_bool_type(Opt, Name, Value, M) :- 464 in(M:opt_type(Opt, Name, Type)), 465 type_bool(Type, Value). 466 467type_bool(Type, Value) :- 468 ( Type == boolean 469 -> Value = true 470 ; Type = boolean(Value) 471 ). 472 473type_optional_bool((A|B), Value) => 474 ( type_optional_bool(A, Value) 475 -> true 476 ; type_optional_bool(B, Value) 477 ). 478type_optional_bool(Type, Value) => 479 type_bool(Type, Value). 480 481negate(true, false). 482negate(false, true).
488opt_value(Type, _Opt, VAtom, Value) :- 489 opt_convert(Type, VAtom, Value), 490 !. 491opt_value(Type, Opt, VAtom, _) :- 492 opt_error(value_type(Opt, Type, VAtom)).
496opt_convert(A|B, Spec, Value) :- 497 ( opt_convert(A, Spec, Value) 498 -> true 499 ; opt_convert(B, Spec, Value) 500 ). 501opt_convert(boolean, Spec, Value) :- 502 to_bool(Spec, Value). 503opt_convert(boolean(_), Spec, Value) :- 504 to_bool(Spec, Value). 505opt_convert(number, Spec, Value) :- 506 atom_number(Spec, Value). 507opt_convert(integer, Spec, Value) :- 508 atom_number(Spec, Value), 509 integer(Value). 510opt_convert(float, Spec, Value) :- 511 atom_number(Spec, Value0), 512 Value is float(Value0). 513opt_convert(nonneg, Spec, Value) :- 514 atom_number(Spec, Value), 515 integer(Value), 516 Value >= 0. 517opt_convert(natural, Spec, Value) :- 518 atom_number(Spec, Value), 519 integer(Value), 520 Value >= 1. 521opt_convert(between(Low, High), Spec, Value) :- 522 atom_number(Spec, Value0), 523 ( ( float(Low) ; float(High) ) 524 -> Value is float(Value0) 525 ; integer(Value0), 526 Value = Value0 527 ), 528 Value >= Low, Value =< High. 529opt_convert(atom, Value, Value). 530opt_convert(oneof(List), Value, Value) :- 531 memberchk(Value, List). 532opt_convert(string, Value0, Value) :- 533 atom_string(Value0, Value). 534opt_convert(file, Spec, Value) :- 535 prolog_to_os_filename(Value, Spec). 536opt_convert(file(Access), Spec, Value) :- 537 ( Spec == '-' 538 -> Value = '-' 539 ; prolog_to_os_filename(Value, Spec), 540 ( access_file(Value, Access) 541 -> true 542 ; opt_error(access_file(Spec, Access)) 543 ) 544 ). 545opt_convert(directory, Spec, Value) :- 546 prolog_to_os_filename(Value, Spec). 547opt_convert(directory(Access), Spec, Value) :- 548 prolog_to_os_filename(Value, Spec), 549 access_directory(Value, Access). 550opt_convert(term, Spec, Value) :- 551 term_string(Value, Spec, []). 552opt_convert(term(Options), Spec, Value) :- 553 term_string(Term, Spec, Options), 554 ( option(variable_names(Bindings), Options) 555 -> Value = Term-Bindings 556 ; Value = Term 557 ). 558 559access_directory(Dir, read) => 560 exists_directory(Dir), 561 access_file(Dir, read). 562access_directory(Dir, write) => 563 exists_directory(Dir), 564 access_file(Dir, write). 565access_directory(Dir, create) => 566 ( exists_directory(Dir) 567 -> access_file(Dir, write) 568 ; \+ exists_file(Dir), 569 file_directory_name(Dir, Parent), 570 exists_directory(Parent), 571 access_file(Parent, write) 572 ). 573 574to_bool(true, true). 575to_bool('True', true). 576to_bool('TRUE', true). 577to_bool(on, true). 578to_bool('On', true). 579to_bool(yes, true). 580to_bool('Yes', true). 581to_bool('1', true). 582to_bool(false, false). 583to_bool('False', false). 584to_bool('FALSE', false). 585to_bool(off, false). 586to_bool('Off', false). 587to_bool(no, false). 588to_bool('No', false). 589to_bool('0', false).
debug
. Other meaningful
options are informational
or warning
. The help page consists of
four sections, two of which are optional:
opt_help(help(header), String)
.
It is optional.Usage: <command>
is by default [options]
and can be
overruled using opt_help(help(usage), String)
.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'])]).
618argv_usage(M:Level) :- 619 print_message(Level, opt_usage(M)). 620 621:- multifile 622 prolog:message//1. 623 624prologmessage(opt_usage(M)) --> 625 usage(M). 626 627usage(M) --> 628 usage_text(M:header), 629 usage_line(M), 630 usage_text(M:description), 631 usage_options(M), 632 usage_text(M:footer).
639usage_text(M:Which) --> 640 { in(M:opt_help(help(Which), Help)) 641 }, 642 !, 643 ( {Which == header ; Which == description} 644 -> user_text(M:Help), [nl, nl] 645 ; [nl], user_text(M:Help) 646 ). 647usage_text(_) --> 648 []. 649 650user_text(M:Entries) --> 651 { is_list(Entries) }, 652 !, 653 sequence(help_elem(M), Entries). 654:- if(current_predicate(print_markdown/2)). 655user_text(_:md(Help)) --> 656 !, 657 { with_output_to(string(String), 658 ( current_output(S), 659 set_stream(S, tty(true)), 660 print_markdown(Help, []))) }, 661 [ '~s'-[String] ]. 662:- else. 663user_text(_:md(Help)) --> 664 !, 665 [ '~w'-[Help] ]. 666:- endif. 667user_text(_:Help) --> 668 [ '~w'-[Help] ]. 669 670help_elem(M, \Callable) --> 671 { callable(Callable) }, 672 call(M:Callable), 673 !. 674help_elem(_M, Elem) --> 675 [ Elem ]. 676 677usage_line(M) --> 678 { findall(Help, in(M:opt_help(help(usage), Help)), HelpLines) 679 }, 680 [ ansi(comment, 'Usage: ', []) ], 681 ( {HelpLines == []} 682 -> cmdline(M), [ ' [options]'-[] ] 683 ; sequence(usage_line(M), [nl], HelpLines) 684 ), 685 [ nl, nl ]. 686 687usage_line(M, Help) --> 688 [ '~t~8|'-[] ], 689 cmdline(M), 690 user_text(M:Help). 691 692cmdline(_M) --> 693 { current_prolog_flag(app_name, App), 694 !, 695 current_prolog_flag(os_argv, [Argv0|_]) 696 }, 697 cmdarg(Argv0), [' '-[], ansi(bold, '~w', [App])]. 698cmdline(_M) --> 699 { current_prolog_flag(associated_file, AbsFile), 700 file_base_name(AbsFile, Base), 701 current_prolog_flag(os_argv, Argv), 702 append(Pre, [File|_], Argv), 703 file_base_name(File, Base), 704 append(Pre, [File], Cmd), 705 ! 706 }, 707 sequence(cmdarg, [' '-[]], Cmd). 708cmdline(_M) --> 709 { current_prolog_flag(saved_program, true), 710 current_prolog_flag(os_argv, OsArgv), 711 append(_, ['-x', State|_], OsArgv), 712 ! 713 }, 714 cmdarg(State). 715cmdline(_M) --> 716 { current_prolog_flag(os_argv, [Argv0|_]) 717 }, 718 cmdarg(Argv0). 719 720cmdarg(A) --> 721 [ '~w'-[A] ].
729usage_options(M) --> 730 { findall(Opt, get_option(M, Opt), Opts), 731 maplist(options_width, Opts, OptWidths), 732 max_list(OptWidths, MaxOptWidth), 733 tty_width(Width), 734 OptColW is min(MaxOptWidth, 30), 735 HelpColW is Width-4-OptColW 736 }, 737 [ ansi(comment, 'Options:', []), nl ], 738 sequence(opt_usage(OptColW, HelpColW), [nl], Opts). 739 740% Just catch/3 is enough, but dependency tracking in e.g., 741% list_undefined/0 still considers this a missing dependency. 742:- if(current_predicate(tty_size/2)). 743tty_width(Width) :- 744 catch(tty_size(_, Width), _, Width = 80). 745:- else. 746tty_width(80). 747:- endif. 748 749opt_usage(OptColW, HelpColW, opt(_Name, Type, Short, Long, Help, Meta)) --> 750 options(Type, Short, Long, Meta), 751 [ '~t~*:| '-[OptColW] ], 752 help_text(Help, OptColW, HelpColW). 753 754help_text([First|Lines], Indent, _Width) --> 755 !, 756 [ '~w'-[First], nl ], 757 sequence(rest_line(Indent), [nl], Lines). 758help_text(Text, _Indent, Width) --> 759 { string_length(Text, Len), 760 Len =< Width 761 }, 762 !, 763 [ '~w'-[Text] ]. 764help_text(Text, Indent, Width) --> 765 { wrap_text(Width, Text, [First|Lines]) 766 }, 767 [ '~w'-[First], nl ], 768 sequence(rest_line(Indent), [nl], Lines). 769 770rest_line(Indent, Line) --> 771 [ '~t~*| ~w'-[Indent, Line] ].
779wrap_text(Width, Text, Wrapped) :- 780 split_string(Text, " \t\n", " \t\n", Words), 781 wrap_lines(Words, Width, Wrapped). 782 783wrap_lines([], _, []). 784wrap_lines([H|T0], Width, [Line|Lines]) :- 785 !, 786 string_length(H, Len), 787 take_line(T0, T1, Width, Len, LineWords), 788 atomics_to_string([H|LineWords], " ", Line), 789 wrap_lines(T1, Width, Lines). 790 791take_line([H|T0], T, Width, Here, [H|Line]) :- 792 string_length(H, Len), 793 NewHere is Here+Len+1, 794 NewHere =< Width, 795 !, 796 take_line(T0, T, Width, NewHere, Line). 797take_line(T, T, _, _, []).
803options(Type, ShortOpt, LongOpts, Meta) --> 804 { append(ShortOpt, LongOpts, Opts) }, 805 sequence(option(Type, Meta), [', '-[]], Opts). 806 807option(boolean, _, Opt) --> 808 opt(Opt). 809option(_Type, [Meta], Opt) --> 810 \+ { short_opt(Opt) }, 811 !, 812 opt(Opt), 813 [ '[='-[], ansi(var, '~w', [Meta]), ']'-[] ]. 814option(_Type, Meta, Opt) --> 815 opt(Opt), 816 ( { short_opt(Opt) } 817 -> [ ' '-[] ] 818 ; [ '='-[] ] 819 ), 820 [ ansi(var, '~w', [Meta]) ].
826options_width(opt(_Name, boolean, Short, Long, _Help, _Meta), W) => 827 length(Short, SCount), 828 length(Long, LCount), 829 maplist(atom_length, Long, LLens), 830 sum_list(LLens, LLen), 831 W is ((SCount+LCount)-1)*2 + % ', ' seps 832 SCount*2 + 833 LCount*2 + LLen. 834options_width(opt(_Name, _Type, Short, Long, _Help, Meta), W) => 835 length(Short, SCount), 836 length(Long, LCount), 837 ( Meta = [MName] 838 -> atom_length(MName, MLen0), 839 MLen is MLen0+2 840 ; atom_length(Meta, MLen) 841 ), 842 maplist(atom_length, Long, LLens), 843 sum_list(LLens, LLen), 844 W is ((SCount+LCount)-1)*2 + % ', ' seps 845 SCount*3 + SCount*MLen + 846 LCount*3 + LLen + LCount*MLen.
opt(Name, Type, ShortFlags, Longflags, Help, Meta).
854get_option(M, opt(help, boolean, [h,?], [help], 855 Help, -)) :- 856 \+ in(M:opt_type(_, help, boolean)), % user defined help 857 ( in(M:opt_help(help, Help)) 858 -> true 859 ; Help = "Show this help message and exit" 860 ). 861get_option(M, opt(Name, TypeName, Short, Long, Help, Meta)) :- 862 findall(Name, in(M:opt_type(_, Name, _)), Names), 863 list_to_set(Names, UNames), 864 member(Name, UNames), 865 findall(Opt-Type, 866 in(M:opt_type(Opt, Name, Type)), 867 Pairs), 868 option_type(Name, Pairs, TypeT), 869 functor(TypeT, TypeName, _), 870 pairs_keys(Pairs, Opts), 871 partition(short_opt, Opts, Short, Long), 872 ( in(M:opt_help(Name, Help)) 873 -> true 874 ; Help = '' 875 ), 876 ( in(M:opt_meta(Name, Meta0)) 877 -> true 878 ; upcase_atom(TypeName, Meta0) 879 ), 880 ( \+ type_bool(TypeT, _), 881 type_optional_bool(TypeT, _) 882 -> Meta = [Meta0] 883 ; Meta = Meta0 884 ). 885 886option_type(Name, Pairs, Type) :- 887 pairs_values(Pairs, Types), 888 sort(Types, [Type|UTypes]), 889 ( UTypes = [] 890 -> true 891 ; print_message(warning, 892 error(opt_error(multiple_types(Name, [Type|UTypes])),_)) 893 ).
900in(Goal) :- 901 pi_head(PI, Goal), 902 current_predicate(PI), 903 call(Goal). 904 905short_opt(Opt) :- 906 atom_length(Opt, 1). 907 908 /******************************* 909 * OPT ERROR HANDLING * 910 *******************************/
916opt_error(Error) :- 917 throw(error(opt_error(Error), _)). 918 919:- multifile 920 prolog:error_message//1. 921 922prologerror_message(opt_error(Error)) --> 923 opt_error(Error). 924 925opt_error(unknown_option(M:Opt)) --> 926 [ 'Unknown option: '-[] ], 927 opt(Opt), 928 hint_help(M). 929opt_error(missing_value(Opt, Type)) --> 930 [ 'Option '-[] ], 931 opt(Opt), 932 [ ' requires an argument (of type ~p)'-[Type] ]. 933opt_error(value_type(Opt, Type, Found)) --> 934 [ 'Option '-[] ], 935 opt(Opt), [' requires'], 936 type(Type), 937 [ ' (found '-[], ansi(code, '~w', [Found]), ')'-[] ]. 938opt_error(access_file(File, exist)) --> 939 [ 'File '-[], ansi(code, '~w', [File]), 940 ' does not exist'-[] 941 ]. 942opt_error(access_file(File, Access)) --> 943 { access_verb(Access, Verb) }, 944 [ 'Cannot access file '-[], ansi(code, '~w', [File]), 945 ' for '-[], ansi(code, '~w', [Verb]) 946 ]. 947 948access_verb(read, reading). 949access_verb(write, writing). 950access_verb(append, writing). 951access_verb(execute, executing). 952 953hint_help(M) --> 954 { in(M:opt_type(Opt, help, boolean)) }, 955 !, 956 [ ' (' ], opt(Opt), [' for help)']. 957hint_help(_) --> 958 [ ' (-h for help)'-[] ]. 959 960opt(Opt) --> 961 { short_opt(Opt) }, 962 !, 963 [ ansi(bold, '-~w', [Opt]) ]. 964opt(Opt) --> 965 [ ansi(bold, '--~w', [Opt]) ]. 966 967type(A|B) --> 968 type(A), [' or'], 969 type(B). 970type(oneof([One])) --> 971 !, 972 [ ' ' ], 973 atom(One). 974type(oneof(List)) --> 975 !, 976 [ ' one of '-[] ], 977 sequence(atom, [', '], List). 978type(between(Low, High)) --> 979 !, 980 [ ' a number '-[], 981 ansi(code, '~w', [Low]), '..', ansi(code, '~w', [High]) 982 ]. 983type(nonneg) --> 984 [ ' a non-negative integer'-[] ]. 985type(natural) --> 986 [ ' a positive integer (>= 1)'-[] ]. 987type(file(Access)) --> 988 [ ' a file with ~w access'-[Access] ]. 989type(Type) --> 990 [ ' an argument of type '-[], ansi(code, '~w', [Type]) ]. 991 992atom(A) --> 993 [ ansi(code, '~w', [A]) ]. 994 995 996 /******************************* 997 * DEBUG SUPPORT * 998 *******************************/
--debug='http(_)'
.
debug(Topic)
. See debug/1 and debug/3.1016cli_parse_debug_options([], []). 1017cli_parse_debug_options([H|T0], Opts) :- 1018 debug_option(H), 1019 !, 1020 cli_parse_debug_options(T0, Opts). 1021cli_parse_debug_options([H|T0], [H|T]) :- 1022 cli_parse_debug_options(T0, T).
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), ...
1044cli_debug_opt_type(debug, debug, string). 1045cli_debug_opt_type(spy, spy, string). 1046cli_debug_opt_type(gspy, gspy, string). 1047cli_debug_opt_type(interactive, interactive, boolean). 1048 1049cli_debug_opt_help(debug, 1050 "Call debug(Topic). See debug/1 and debug/3. \c 1051 Multiple topics may be separated by : or ;"). 1052cli_debug_opt_help(spy, 1053 "Place a spy-point on Predicate. \c 1054 Multiple topics may be separated by : or ;"). 1055cli_debug_opt_help(gspy, 1056 "As --spy using the graphical debugger. See tspy/1 \c 1057 Multiple topics may be separated by `;`"). 1058cli_debug_opt_help(interactive, 1059 "Start the Prolog toplevel after main/1 completes."). 1060 1061cli_debug_opt_meta(debug, 'TOPICS'). 1062cli_debug_opt_meta(spy, 'PREDICATES'). 1063cli_debug_opt_meta(gspy, 'PREDICATES'). 1064 1065:- meta_predicate 1066 spy_from_string( , ). 1067 1068debug_option(interactive(true)) :- 1069 asserta(interactive). 1070debug_option(debug(Spec)) :- 1071 split_string(Spec, ";", "", Specs), 1072 maplist(debug_from_string, Specs). 1073debug_option(spy(Spec)) :- 1074 split_string(Spec, ";", "", Specs), 1075 maplist(spy_from_string(spy), Specs). 1076debug_option(gspy(Spec)) :- 1077 split_string(Spec, ";", "", Specs), 1078 maplist(spy_from_string(cli_gspy), Specs). 1079 1080debug_from_string(TopicS) :- 1081 term_string(Topic, TopicS), 1082 debug(Topic). 1083 1084spy_from_string(Pred, Spec) :- 1085 atom_pi(Spec, PI), 1086 call(Pred, PI). 1087 1088cli_gspy(PI) :- 1089 ( exists_source(library(threadutil)) 1090 -> use_module(library(threadutil), [tspy/1]), 1091 Goal = tspy(PI) 1092 ; exists_source(library(gui_tracer)) 1093 -> use_module(library(gui_tracer), [gspy/1]), 1094 Goal = gspy(PI) 1095 ; Goal = spy(PI) 1096 ), 1097 call(Goal). 1098 1099atom_pi(Atom, Module:PI) :- 1100 split(Atom, :, Module, PiAtom), 1101 !, 1102 atom_pi(PiAtom, PI). 1103atom_pi(Atom, Name//Arity) :- 1104 split(Atom, //, Name, Arity), 1105 !. 1106atom_pi(Atom, Name/Arity) :- 1107 split(Atom, /, Name, Arity), 1108 !. 1109atom_pi(Atom, _) :- 1110 format(user_error, 'Invalid predicate indicator: "~w"~n', [Atom]), 1111 halt(1). 1112 1113split(Atom, Sep, Before, After) :- 1114 sub_atom(Atom, BL, _, AL, Sep), 1115 !, 1116 sub_atom(Atom, 0, BL, _, Before), 1117 sub_atom(Atom, _, AL, 0, AfterAtom), 1118 ( atom_number(AfterAtom, After) 1119 -> true 1120 ; After = AfterAtom 1121 ).
This predicate may be called from main/1 to enter the Prolog toplevel rather than terminating the application after main/1 completes.
1134cli_enable_development_system :- 1135 on_signal(int, _, debug), 1136 set_prolog_flag(xpce_threaded, true), 1137 set_prolog_flag(message_ide, true), 1138 ( current_prolog_flag(xpce_version, _) 1139 -> use_module(library(pce_dispatch)), 1140 memberchk(Goal, [pce_dispatch([])]), 1141 call(Goal) 1142 ; true 1143 ), 1144 set_prolog_flag(toplevel_goal, prolog). 1145 1146 1147 /******************************* 1148 * IDE SUPPORT * 1149 *******************************/ 1150 1151:- multifile 1152 prolog:called_by/2. 1153 1154prologcalled_by(main, [main(_)]). 1155prologcalled_by(argv_options(_,_,_), 1156 [ opt_type(_,_,_), 1157 opt_help(_,_), 1158 opt_meta(_,_) 1159 ])
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 simleecho
implementation in Prolog.