1/* Part of SWI-Prolog 2 3 Author: Marcus Uneson 4 E-mail: marcus.uneson@ling.lu.se 5 WWW: http://person.sol.lu.se/MarcusUneson/ 6 Copyright (c) 2011-2015, Marcus Uneson 7 All rights reserved. 8 9 Redistribution and use in source and binary forms, with or without 10 modification, are permitted provided that the following conditions 11 are met: 12 13 1. Redistributions of source code must retain the above copyright 14 notice, this list of conditions and the following disclaimer. 15 16 2. Redistributions in binary form must reproduce the above copyright 17 notice, this list of conditions and the following disclaimer in 18 the documentation and/or other materials provided with the 19 distribution. 20 21 THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 22 "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 23 LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 24 FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 25 COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 26 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 27 BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 28 LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 29 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 30 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 31 ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 32 POSSIBILITY OF SUCH DAMAGE. 33*/ 34 35:- module(optparse, 36 [ opt_parse/5, %+OptsSpec, +CLArgs, -Opts, -PositionalArgs,-ParseOptions 37 opt_parse/4, %+OptsSpec, +CLArgs, -Opts, -PositionalArgs, 38 opt_arguments/3, %+OptsSpec, -Opts, -PositionalArgs 39 opt_help/2 %+OptsSpec, -Help 40 ]). 41 42:- use_module(library(apply)). 43:- use_module(library(lists)). 44:- use_module(library(option)). 45:- use_module(library(error)). 46:- set_prolog_flag(double_quotes, codes). 47%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% EXPORTS
337:- predicate_options(opt_parse/5, 5, 338 [ allow_empty_flag_spec(boolean), 339 duplicated_flags(oneof([keepfirst,keeplast,keepall])), 340 output_functor(atom), 341 suppress_empty_meta(boolean) 342 ]). 343 344:- multifile 345 error:has_type/2, 346 parse_type/3.
Opts is a list of parsed options in the form Key(Value). Dashed
args not in OptsSpec are not permitted and will raise error (see
tip on how to pass unknown flags in the module description).
PositionalArgs are the remaining non-dashed args after each flag
has taken its argument (filling in true
or false
for booleans).
There are no restrictions on non-dashed arguments and they may go
anywhere (although it is good practice to put them last). Any
leading arguments for the runtime (up to and including '--') are
discarded.
366opt_arguments(OptsSpec, Opts, PositionalArgs) :-
367 current_prolog_flag(argv, Argv),
368 opt_parse(OptsSpec, Argv, Opts, PositionalArgs).
opt_parse(OptsSpec, ApplArgs, Opts, PositionalArgs, [])
.
375opt_parse(OptsSpec, ApplArgs, Opts, PositionalArgs) :-
376 opt_parse(OptsSpec, ApplArgs, Opts, PositionalArgs, []).
Opts is a list of parsed options in the form Key(Value), or (with
the option functor(Func)
given) in the form Func(Key, Value).
Dashed args not in OptsSpec are not permitted and will raise error
(see tip on how to pass unknown flags in the module description).
PositionalArgs are the remaining non-dashed args after each flag
has taken its argument (filling in true
or false
for booleans).
There are no restrictions on non-dashed arguments and they may go
anywhere (although it is good practice to put them last).
ParseOptions are
keepfirst, keeplast, keepall
with the obvious meaning.
Default is keeplast
.allow_empty_flag_spec(false)
gives the more customary behaviour of
raising error on empty flags.
416opt_parse(OptsSpec, ApplArgs, Opts, PositionalArgs, ParseOptions) :-
417 opt_parse_(OptsSpec, ApplArgs, Opts, PositionalArgs, ParseOptions).
424opt_help(OptsSpec, Help) :- 425 opt_help(OptsSpec, Help, []). 426 427% semi-arbitrary default format settings go here; 428% if someone needs more control one day, opt_help/3 could be exported 429opt_help(OptsSpec, Help, HelpOptions0) :- 430 Defaults = [ line_width(80) 431 , min_help_width(40) 432 , break_long_flags(false) 433 , suppress_empty_meta(true) 434 ], 435 merge_options(HelpOptions0, Defaults, HelpOptions), 436 opt_help_(OptsSpec, Help, HelpOptions). 437 438 439%{{{ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% OPT_PARSE 440 441opt_parse_(OptsSpec0, Args0, Opts, PositionalArgs, ParseOptions) :- 442 assertion(ground(Args0)), 443 assertion(is_list_of_atoms(Args0)), 444 445 check_opts_spec(OptsSpec0, ParseOptions, OptsSpec), 446 447 maplist(atom_codes, Args0, Args1), 448 parse_options(OptsSpec, Args1, Args2, PositionalArgs), 449 add_default_opts(OptsSpec, Args2, Args3), 450 451 option(duplicated_flags(Keep), ParseOptions, keeplast), 452 remove_duplicates(Keep, Args3, Args4), 453 454 option(output_functor(Func), ParseOptions, 'OPTION'), 455 refunctor_opts(Func, Args4, Opts). %}}} 456 457 458 459%{{{ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% MAKE HELP 460opt_help_(OptsSpec0, Help, HelpOptions) :- 461 check_opts_spec(OptsSpec0, HelpOptions, OptsSpec1), 462 include_in_help(OptsSpec1, OptsSpec2), 463 format_help_fields(OptsSpec2, OptsSpec3), 464 col_widths(OptsSpec3, [shortflags, metatypedef], CWs), 465 long_flag_col_width(OptsSpec3, LongestFlagWidth), 466 maplist(format_opt(LongestFlagWidth, CWs, HelpOptions), OptsSpec3, Lines), 467 atomic_list_concat(Lines, Help). 468 469include_in_help([], []). 470include_in_help([OptSpec|OptsSpec], Result) :- 471 ( flags(OptSpec, [_|_]) 472 -> Result = [OptSpec|Rest] 473 ; Result = Rest 474 ), 475 include_in_help(OptsSpec, Rest). 476 477format_help_fields(OptsSpec0, OptsSpec) :- 478 maplist(embellish_flag(short), OptsSpec0, OptsSpec1), 479 maplist(embellish_flag(long), OptsSpec1, OptsSpec2), 480 maplist(merge_meta_type_def, OptsSpec2, OptsSpec). 481 482merge_meta_type_def(OptSpecIn, [metatypedef(MTD)|OptSpecIn]) :- 483 memberchk(meta(Meta), OptSpecIn), 484 memberchk(type(Type), OptSpecIn), 485 memberchk(default(Def), OptSpecIn), 486 atom_length(Meta, N), 487 ( N > 0 488 -> format(atom(MTD), '~w:~w=~w', [Meta, Type, Def]) 489 ; format(atom(MTD), '~w=~w', [Type, Def]) 490 ). 491embellish_flag(short, OptSpecIn, OptSpecOut) :- 492 memberchk(shortflags(FlagsIn), OptSpecIn), 493 maplist(atom_concat('-'), FlagsIn, FlagsOut0), 494 atomic_list_concat(FlagsOut0, ',', FlagsOut), 495 merge_options([shortflags(FlagsOut)], OptSpecIn, OptSpecOut). 496embellish_flag(long, OptSpecIn, OptSpecOut) :- 497 memberchk(longflags(FlagsIn), OptSpecIn), 498 maplist(atom_concat('--'), FlagsIn, FlagsOut), 499 merge_options([longflags(FlagsOut)], OptSpecIn, OptSpecOut). 500 501col_widths(OptsSpec, Functors, ColWidths) :- 502 maplist(col_width(OptsSpec), Functors, ColWidths). 503col_width(OptsSpec, Functor, ColWidth) :- 504 findall(N, 505 ( member(OptSpec, OptsSpec), 506 M =.. [Functor, Arg], 507 member(M, OptSpec), 508 format(atom(Atom), '~w', [Arg]), 509 atom_length(Atom, N0), 510 N is N0 + 2 %separate cols with two spaces 511 ), 512 Ns), 513 max_list([0|Ns], ColWidth). 514 515long_flag_col_width(OptsSpec, ColWidth) :- 516 findall(FlagLength, 517 ( member(OptSpec, OptsSpec), 518 memberchk(longflags(LFlags), OptSpec), 519 member(LFlag, LFlags), 520 atom_length(LFlag, FlagLength) 521 ), 522 FlagLengths), 523 max_list([0|FlagLengths], ColWidth). 524 525 526format_opt(LongestFlagWidth, [SFlagsCW, MTDCW], HelpOptions, Opt, Line) :- 527 memberchk(shortflags(SFlags), Opt), 528 529 memberchk(longflags(LFlags0), Opt), 530 group_length(LongestFlagWidth, LFlags0, LFlags1), 531 LFlagsCW is LongestFlagWidth + 2, %separate with comma and space 532 option(break_long_flags(BLF), HelpOptions, true), 533 ( 534 -> maplist(atomic_list_concat_(',\n'), LFlags1, LFlags2) 535 ; maplist(atomic_list_concat_(', '), LFlags1, LFlags2) 536 ), 537 atomic_list_concat(LFlags2, ',\n', LFlags), 538 539 memberchk(metatypedef(MetaTypeDef), Opt), 540 541 memberchk(help(Help), Opt), 542 HelpIndent is LFlagsCW + SFlagsCW + MTDCW + 2, 543 option(line_width(LW), HelpOptions, 80), 544 option(min_help_width(MHW), HelpOptions, 40), 545 HelpWidth is max(MHW, LW - HelpIndent), 546 ( atom(Help) 547 -> line_breaks(Help, HelpWidth, HelpIndent, BrokenHelp) 548 ; assertion(is_list_of_atoms(Help)) 549 -> indent_lines(Help, HelpIndent, BrokenHelp) 550 ), 551 format(atom(Line), '~w~t~*+~w~t~*+~w~t~*+~w~n', 552 [LFlags, LFlagsCW, SFlags, SFlagsCW, MetaTypeDef, MTDCW, BrokenHelp]). 553 554 555line_breaks(TextLine, LineLength, Indent, TextLines) :- 556 atomic_list_concat(Words, ' ', TextLine), 557 group_length(LineLength, Words, Groups0), 558 maplist(atomic_list_concat_(' '), Groups0, Groups), 559 indent_lines(Groups, Indent, TextLines). 560 561indent_lines(Lines, Indent, TextLines) :- 562 format(atom(Separator), '~n~*|', [Indent]), 563 atomic_list_concat(Lines, Separator, TextLines). 564 565atomic_list_concat_(Separator, List, Atom) :- 566 atomic_list_concat(List, Separator, Atom). 567 568%group_length(10, 569% [here, are, some, words, you, see], 570% [[here are], [some words], [you see]]) %each group >= 10F 571group_length(LineLength, Words, Groups) :- 572 group_length_(Words, LineLength, LineLength, [], [], Groups). 573 574group_length_([], _, _, ThisLine, GroupsAcc, Groups) :- 575 maplist(reverse, [ThisLine|GroupsAcc], GroupsAcc1), 576 reverse(GroupsAcc1, Groups). 577group_length_([Word|Words], LineLength, Remains, ThisLine, Groups, GroupsAcc) :- 578 atom_length(Word, K), 579 ( (Remains >= K; ThisLine = []) %Word fits on ThisLine, or too long too fit 580 -> Remains1 is Remains - K - 1, %even on a new line 581 group_length_(Words, LineLength, Remains1, [Word|ThisLine], Groups, GroupsAcc) 582 583 %Word doesn't fit on ThisLine (non-empty) 584 ; group_length_([Word|Words], LineLength, LineLength, [], [ThisLine|Groups], GroupsAcc) 585 ). 586 587 588%}}} 589 590 591%{{{ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% OPTSSPEC DEFAULTS 592 593 594add_default_defaults(OptsSpec0, OptsSpec, Options) :- 595 option(suppress_empty_meta(SEM), Options, true), 596 maplist(default_defaults(SEM), OptsSpec0, OptsSpec). 597 598default_defaults(SuppressEmptyMeta, OptSpec0, OptSpec) :- 599 ( 600 -> Meta = '' 601 ; memberchk(type(Type), OptSpec0) 602 -> meta_placeholder(Type, Meta) 603 ; Meta = 'T' 604 ), 605 606 Defaults = [ help('') 607 , type(term) 608 , shortflags([]) 609 , longflags([]) 610 , default('_') 611 , meta(Meta) 612 ], 613 merge_options(OptSpec0, Defaults, OptSpec). 614 %merge_options(+New, +Old, -Merged) 615 616 617meta_placeholder(boolean, 'B'). 618meta_placeholder(atom, 'A'). 619meta_placeholder(float, 'F'). 620meta_placeholder(integer, 'I'). 621meta_placeholder(term, 'T'). 622 623 624 625%}}} 626 627 628%{{{ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% OPTSSPEC VALIDATION 629 630%this is a bit paranoid, but OTOH efficiency is no issue 631check_opts_spec(OptsSpec0, Options, OptsSpec) :- 632 validate_opts_spec(OptsSpec0, Options), 633 add_default_defaults(OptsSpec0, OptsSpec, Options), 634 validate_opts_spec(OptsSpec, Options). 635 636validate_opts_spec(OptsSpec, ParseOptions) :- 637 \+ invalidate_opts_spec(OptsSpec, ParseOptions). 638 639invalidate_opts_spec(OptsSpec, _ParseOptions) :- 640 %invalid if not ground -- must go first for \+ to be sound 641 ( \+ ground(OptsSpec) 642 -> throw(error(instantiation_error, 643 context(validate_opts_spec/1, 'option spec must be ground'))) 644 645 %invalid if conflicting flags 646 ; ( member(O1, OptsSpec), flags(O1, Flags1), member(F, Flags1), 647 member(O2, OptsSpec), flags(O2, Flags2), member(F, Flags2), 648 O1 \= O2) 649 -> throw(error(domain_error(unique_atom, F), 650 context(validate_opts_spec/1, 'ambiguous flag'))) 651 652 %invalid if unknown opt spec 653 ; ( member(OptSpec, OptsSpec), 654 member(Spec, OptSpec), 655 functor(Spec, F, _), 656 \+ member(F, [opt, shortflags, longflags, type, help, default, meta]) ) 657 -> throw(error(domain_error(opt_spec, F), 658 context(validate_opts_spec/1, 'unknown opt spec'))) 659 660 %invalid if mandatory option spec opt(ID) is not unique in the entire Spec 661 ; ( member(O1, OptsSpec), member(opt(Name), O1), 662 member(O2, OptsSpec), member(opt(Name), O2), 663 O1 \= O2) 664 -> throw(error(domain_error(unique_atom, Name), 665 context(validate_opts_spec/1, 'ambiguous id'))) 666 ). 667 668invalidate_opts_spec(OptsSpec, _ParseOptions) :- 669 member(OptSpec, OptsSpec), 670 \+ member(opt(_Name), OptSpec), 671 %invalid if mandatory option spec opt(ID) is absent 672 throw(error(domain_error(unique_atom, OptSpec), 673 context(validate_opts_spec/1, 'opt(id) missing'))). 674 675invalidate_opts_spec(OptsSpec, ParseOptions) :- 676 member(OptSpec, OptsSpec), %if we got here, OptSpec has a single unique Name 677 member(opt(Name), OptSpec), 678 679 option(allow_empty_flag_spec(AllowEmpty), ParseOptions, true), 680 681 %invalid if allow_empty_flag_spec(false) and no flag is given 682 ( (\+ , \+ flags(OptSpec, [_|_])) 683 -> format(atom(Msg), 'no flag specified for option ''~w''', [Name]), 684 throw(error(domain_error(unique_atom, _), 685 context(validate_opts_spec/1, Msg))) 686 687 %invalid if any short flag is not actually single-letter 688 ; ( memberchk(shortflags(Flags), OptSpec), 689 member(F, Flags), 690 atom_length(F, L), 691 L > 1) 692 -> format(atom(Msg), 'option ''~w'': flag too long to be short', [Name]), 693 throw(error(domain_error(short_flag, F), 694 context(validate_opts_spec/1, Msg))) 695 696 %invalid if any option spec is given more than once 697 ; duplicate_optspec(OptSpec, 698 [type,opt,default,help,shortflags,longflags,meta]) 699 -> format(atom(Msg), 'duplicate spec in option ''~w''', [Name]), 700 throw(error(domain_error(unique_functor, _), 701 context(validate_opts_spec/1, Msg))) 702 703 %invalid if unknown type 704 ; ( memberchk(type(Type), OptSpec), 705 Type \== term, 706 \+ clause(error:has_type(Type,_), _) 707 ) 708 -> format(atom(Msg), 'unknown type ''~w'' in option ''~w''', [Type, Name]), 709 throw(error(type_error(flag_value, Type), 710 context(validate_opts_spec/1, Msg))) 711 712 %invalid if type does not match default 713 %note1: reverse logic: we are trying to _in_validate OptSpec 714 715 %note2: 'term' approves of any syntactically valid prolog term, since 716 %if syntactically invalid, OptsSpec wouldn't have parsed 717 718 %note3: the special placeholder '_' creates a new variable, so no typecheck 719 ; (memberchk(type(Type), OptSpec), 720 Type \= term, 721 memberchk(default(Default), OptSpec), 722 Default \= '_' 723 -> \+ must_be(Type, Default)) 724 725 %invalidation failed, i.e., optspec is OK 726 ; fail 727 ). 728 729duplicate_optspec(_, []) :- !, fail. 730duplicate_optspec(OptSpec, [Func|Funcs]) :- 731 functor(F, Func, 1), 732 findall(F, member(F, OptSpec), Xs), 733 (Xs = [_,_|_] 734 -> true 735 ; duplicate_optspec(OptSpec, Funcs) 736 ). 737 738 739%}}} 740 741 742%{{{ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% PARSE OPTIONS 743% NOTE: 744% -sbar could be interpreted in two ways: as short for -s bar, and 745% as short ('clustered') for -s -b -a -r. Here, the former interpretation 746% is chosen. 747% Cf http://perldoc.perl.org/Getopt/Long.html (no clustering by default) 748 749 750parse_options(OptsSpec, Args0, Options, PosArgs) :- 751 append(Args0, [""], Args1), 752 parse_args_(Args1, OptsSpec, Args2), 753 partition_args_(Args2, Options, PosArgs). 754 755%{{{ PARSE ARGS 756 757 758%if arg is boolean flag given as --no-my-arg, expand to my-arg, false, re-call 759parse_args_([Arg,Arg2|Args], OptsSpec, [opt(KID, false)|Result]) :- 760 flag_name_long_neg(Dashed, NonDashed, Arg, []), 761 flag_id_type(OptsSpec, NonDashed, KID, boolean), 762 !, 763 parse_args_([Dashed, "false", Arg2|Args], OptsSpec, Result). 764 765%if arg is ordinary boolean flag, fill in implicit true if arg absent; re-call 766parse_args_([Arg,Arg2|Args], OptsSpec, Result) :- 767 flag_name(K, Arg, []), 768 flag_id_type(OptsSpec, K, _KID, boolean), 769 \+ member(Arg2, ["true", "false"]), 770 !, 771 parse_args_([Arg, "true", Arg2 | Args], OptsSpec, Result). 772 773% separate short or long flag run together with its value and parse 774parse_args_([Arg|Args], OptsSpec, [opt(KID, Val)|Result]) :- 775 flag_name_value(Arg1, Arg2, Arg, []), 776 \+ short_flag_w_equals(Arg1, Arg2), 777 flag_name(K, Arg1, []), 778 !, 779 parse_option(OptsSpec, K, Arg2, opt(KID, Val)), 780 parse_args_(Args, OptsSpec, Result). 781 782%from here, unparsed args have form 783% PosArg1,Flag1,Val1,PosArg2,PosArg3,Flag2,Val2, PosArg4... 784%i.e., positional args may go anywhere except between FlagN and ValueN 785%(of course, good programming style says they should go last, but it is poor 786%programming style to assume that) 787 788parse_args_([Arg1,Arg2|Args], OptsSpec, [opt(KID, Val)|Result]) :- 789 flag_name(K, Arg1, []), 790 !, 791 parse_option(OptsSpec, K, Arg2, opt(KID, Val)), 792 parse_args_(Args, OptsSpec, Result). 793 794parse_args_([Arg1,Arg2|Args], OptsSpec, [pos(At)|Result]) :- 795 \+ flag_name(_, Arg1, []), 796 !, 797 atom_codes(At, Arg1), 798 parse_args_([Arg2|Args], OptsSpec, Result). 799 800parse_args_([""], _, []) :- !. %placeholder, but useful for error messages 801parse_args_([], _, []) :- !. 802 803short_flag_w_equals([0'-,_C], [0'=|_]) :- 804 throw(error(syntax_error('disallowed: <shortflag>=<value>'),_)). 805 806 807 808flag_id_type(OptsSpec, FlagCodes, ID, Type) :- 809 atom_codes(Flag, FlagCodes), 810 member(OptSpec, OptsSpec), 811 flags(OptSpec, Flags), 812 member(Flag, Flags), 813 member(type(Type), OptSpec), 814 member(opt(ID), OptSpec). 815 816%{{{ FLAG DCG 817 818%DCG non-terminals: 819% flag_name(NonDashed) %c, flag-name, x 820% flag_name_short(Dashed, NonDashed) %c, x 821% flag_name_long(Dashed, NonDashed) %flag-name 822% flag_name_long_neg(Dashed, NonDashed) %no-flag-name 823% flag_value(Val) %non-empty string 824% flag_value0(Val) %any string, also empty 825% flag_name_value(Dashed, Val) %pair of flag_name, flag_value 826 827 828flag_name(NonDashed) --> flag_name_long(_, NonDashed). 829flag_name(NonDashed) --> flag_name_short(_, NonDashed). 830flag_name(NonDashed) --> flag_name_long_neg(_, NonDashed). 831 832flag_name_long_neg([0'-,0'-|Cs], Cs) --> "--no-", name_long(Cs). 833flag_name_long([0'-,0'-|Cs], Cs) --> "--", name_long(Cs). 834flag_name_short([0'-|C], C) --> "-", name_1st(C). 835 836flag_value([C|Cs]) --> [C], flag_value0(Cs). 837flag_value0([]) --> []. 838flag_value0([C|Cs]) --> [C], flag_value0(Cs). 839flag_name_value(Dashed, Val) --> flag_name_long(Dashed, _), "=", flag_value0(Val). 840flag_name_value(Dashed, Val) --> flag_name_short(Dashed, _), flag_value(Val). 841 842name_long([C|Cs]) --> name_1st([C]), name_rest(Cs). 843name_1st([C]) --> [C], {name_1st(C)}. 844name_rest([]) --> []. 845name_rest([C|Cs]) --> [C], {name_char(C)}, name_rest(Cs). 846name_1st(C) :- char_type(C, alpha). 847name_char(C) :- char_type(C, alpha). 848name_char( 0'- ). %}}} 849 850 851%{{{ PARSE OPTION 852parse_option(OptsSpec, Arg1, Arg2, opt(KID, Val)) :- 853 ( flag_id_type(OptsSpec, Arg1, KID, Type) 854 -> parse_val(Arg1, Type, Arg2, Val) 855 ; format(atom(Msg), '~s', [Arg1]), 856 opt_help(OptsSpec, Help), %unknown flag: dump usage on stderr 857 nl(user_error), 858 write(user_error, Help), 859 throw(error(domain_error(flag_value, Msg),context(_, 'unknown flag'))) 860 ). 861 862 863parse_val(Opt, Type, Cs, Val) :- 864 catch( 865 parse_loc(Type, Cs, Val), 866 E, 867 ( format('~nERROR: flag ''~s'': expected atom parsable as ~w, found ''~s'' ~n', 868 [Opt, Type, Cs]), 869 throw(E)) 870 ). 871 872%parse_loc(+Type, +ListOfCodes, -Result). 873parse_loc(Type, _LOC, _) :- 874 var(Type), !, throw(error(instantiation_error, _)). 875parse_loc(_Type, LOC, _) :- 876 var(LOC), !, throw(error(instantiation_error, _)). 877parse_loc(boolean, Cs, true) :- atom_codes(true, Cs), !. 878parse_loc(boolean, Cs, false) :- atom_codes(false, Cs), !. 879parse_loc(atom, Cs, Result) :- atom_codes(Result, Cs), !. 880parse_loc(integer, Cs, Result) :- 881 number_codes(Result, Cs), 882 integer(Result), 883 884 !. 885parse_loc(float, Cs, Result) :- 886 number_codes(Result, Cs), 887 float(Result), 888 889 !. 890parse_loc(term, Cs, Result) :- 891 atom_codes(A, Cs), 892 term_to_atom(Result, A), 893 894 !. 895parse_loc(Type, Cs, Result) :- 896 parse_type(Type, Cs, Result), 897 !. 898parse_loc(Type, _Cs, _) :- %could not parse Cs as Type 899 throw(error(type_error(flag_value, Type), _)), 900 !. %}}} 901%}}}
907partition_args_([], [], []). 908partition_args_([opt(K,V)|Rest], [opt(K,V)|RestOpts], RestPos) :- 909 !, 910 partition_args_(Rest, RestOpts, RestPos). 911partition_args_([pos(Arg)|Rest], RestOpts, [Arg|RestPos]) :- 912 !, 913 partition_args_(Rest, RestOpts, RestPos). 914 915 916 917 918%{{{ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% ADD DEFAULTS 919 920add_default_opts([], Opts, Opts). 921add_default_opts([OptSpec|OptsSpec], OptsIn, Result) :- 922 memberchk(opt(OptName), OptSpec), 923 ( memberchk(opt(OptName, _Val), OptsIn) 924 -> Result = OptsOut %value given on cl, ignore default 925 926 ; %value not given on cl: 927 memberchk(default('_'), OptSpec) % no default in OptsSpec (or 'VAR'): 928 -> Result = [opt(OptName, _) | OptsOut] % create uninstantiated variable 929 ; 930 memberchk(default(Def), OptSpec), % default given in OptsSpec 931% memberchk(type(Type), OptSpec), % already typechecked 932% assertion(must_be(Type, Def)), 933 Result = [opt(OptName, Def) | OptsOut] 934 ), 935 add_default_opts(OptsSpec, OptsIn, OptsOut). 936 937 938 939%}}} 940 941 942%{{{ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% REMOVE DUPLICATES 943remove_duplicates(_, [], []) :- !. 944remove_duplicates(keeplast, [opt(OptName, Val) | Opts], Result) :- 945 !, 946 ( memberchk(opt(OptName, _), Opts) 947 -> Result = RestOpts 948 ; Result = [opt(OptName, Val) | RestOpts] 949 ), 950 remove_duplicates(keeplast, Opts, RestOpts). 951 952remove_duplicates(keepfirst, OptsIn, OptsOut) :- 953 !, 954 reverse(OptsIn, OptsInRev), 955 remove_duplicates(keeplast, OptsInRev, OptsOutRev), 956 reverse(OptsOutRev, OptsOut). 957 958remove_duplicates(keepall, OptsIn, OptsIn) :- !. 959remove_duplicates(K, [_|_], _) :- 960 !, 961 throw(error(domain_error(keep_flag, K), _)). %}}} 962 963 964%{{{ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% REFUNCTOR 965refunctor_opts(Fnct, OptsIn, OptsOut) :- 966 maplist(refunctor_opt(Fnct), OptsIn, OptsOut). 967 968refunctor_opt('OPTION', opt(OptName, OptVal), Result) :- 969 !, 970 Result =.. [OptName, OptVal]. 971 972refunctor_opt(F, opt(OptName, OptVal), Result) :- 973 Result =.. [F, OptName, OptVal]. %}}} 974 975 976%{{{ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% ACCESSORS 977 978flags(OptSpec, Flags) :- memberchk(shortflags(Flags), OptSpec). 979flags(OptSpec, Flags) :- memberchk(longflags(Flags), OptSpec). %}}} 980 981%{{{ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% UTILS 982is_list_of_atoms([]). 983is_list_of_atoms([X|Xs]) :- atom(X), is_list_of_atoms(Xs). 984%}}}
command line parsing
This module helps in building a command-line interface to an application. In particular, it provides functions that take an option specification and a list of atoms, probably given to the program on the command line, and return a parsed representation (a list of the customary Key(Val) by default; or optionally, a list of Func(Key, Val) terms in the style of current_prolog_flag/2). It can also synthesize a simple help text from the options specification.
The terminology in the following is partly borrowed from python, see http://docs.python.org/library/optparse.html#terminology . Very briefly, arguments is what you provide on the command line and for many prologs show up as a list of atoms
Args
incurrent_prolog_flag(argv, Args)
. For a typical prolog incantation, they can be divided intoPositional arguments are in particular used for mandatory arguments without which your program won't work and for which there are no sensible defaults (e.g,, input file names). Options, by contrast, offer flexibility by letting you change a default setting. Options are optional not only by etymology: this library has no notion of mandatory or required options (see the python docs for other rationales than laziness).
The command-line arguments enter your program as a list of atoms, but the programs perhaps expects booleans, integers, floats or even prolog terms. You tell the parser so by providing an options specification. This is just a list of individual option specifications. One of those, in turn, is a list of ground prolog terms in the customary Name(Value) format. The following terms are recognized (any others raise error).
current_prolog_flag(Key, Value)
. This term is mandatory (an error is thrown if missing).-s , -K
, etc). Uppercase letters must be quoted. Usually ListOfFlags will be a singleton list, but sometimes aliased flags may be convenient.--verbose, --no-debug
, etc). They are basically a more readable alternative to short flags, except--flag value
or--flag=value
(but not as--flagvalue
); short flags as-f val
or-fval
(but not-f=val
)--bool-flag
or--bool-flag=true
or--bool-flag true
; and they can be negated as--no-bool-flag
or--bool-flag=false
or--bool-flag false
.Except that shortflags must be single characters, the distinction between long and short is in calling convention, not in namespaces. Thus, if you have
shortflags([v])
, you can use it as-v2
or-v 2
or--v=2
or--v 2
(but not-v=2
or--v2
).Shortflags and longflags both default to
[]
. It can be useful to have flagless options -- see example below.x:integer=3
,interest:float=0.11
). It may be useful to have named variables (x
,interest
) in case you wish to mention them again in the help text. If not given theMeta:
part is suppressed -- see example below.boolean, atom, integer, float, term
. The corresponding argument will be parsed appropriately. This term is optional; if not given, defaults toterm
.Long lines are subject to basic word wrapping -- split on white space, reindent, rejoin. However, you can get more control by supplying the line breaking yourself: rather than a single line of text, you can provide a list of lines (as atoms). If you do, they will be joined with the appropriate indent but otherwise left untouched (see the option
mode
in the example below).Absence of mandatory option specs or the presence of more than one for a particular option throws an error, as do unknown or incompatible types.
As a concrete example from a fictive application, suppose we want the following options to be read from the command line (long
flag(s)
, shortflag(s)
, meta:type=default, help)We may also have some configuration parameters which we currently think not needs to be controlled from the command line, say
path('/some/file/path')
.This interface is described by the following options specification (order between the specifications of a particular option is irrelevant).
The help text above was accessed by
opt_help(ExamplesOptsSpec, HelpText)
. The options appear in the same order as in the OptsSpec.Given
ExampleOptsSpec
, a command line (somewhat syntactically inconsistent, in order to demonstrate different calling conventions) may look as followsopt_parse(ExampleOptsSpec, ExampleArgs, Opts, PositionalArgs)
would then succeed withNote that
path('/some/file/path')
showing up in Opts has a default value (of the implicit type 'term'), but no corresponding flags in OptsSpec. Thus it can't be set from the command line. The rest of your program doesn't need to know that, of course. This provides an alternative to the common practice of asserting such hard-coded parameters under a single predicate (for instancesetting(path, '/some/file/path')
), with the advantage that you may seamlessly upgrade them to command-line options, should you one day find this a good idea. Just add an appropriate flag or two and a line of help text. Similarly, suppressing an option in a cluttered interface amounts to commenting out the flags.opt_parse/5 allows more control through an additional argument list as shown in the example below.
This representation may be preferable with the empty-flag configuration parameter style above (perhaps with asserting appl_config/2).
Notes and tips
term
, which subsumesinteger, float, atom
, it may be possible to get away cheaper (e.g., by only giving booleans). However, it is recommended practice to always specify types: parsing becomes more reliable and error messages will be easier to interpret.-sbar
is taken to mean-s bar
, not-s -b -a -r
, that is, there is no clustering of flags.-s=foo
is disallowed. The rationale is that although some command-line parsers will silently interpret this as-s =foo
, this is very seldom what you want. To have an option argument start with '=' (very un-recommended), say so explicitly.depth
twice: once as-d5
and once as--iters 7
. The default when encountering duplicated flags is tokeeplast
(this behaviour can be controlled, by ParseOption duplicated_flags).