1:- module(
2 cli_arguments,
3 [
4 cli_arguments/5 5 ]
6).
12:- use_module(library(apply)). 13:- use_module(library(error)). 14:- use_module(library(lists)). 15:- use_module(library(pairs)). 16
17:- use_module(library(dcg)). 18:- use_module(library(dict)). 19:- use_module(library(string_ext)).
47cli_arguments(Usages, LongSpecs, ShortSpecs, Options, PosArgs) :-
48 current_prolog_flag(argv, Atoms),
49 parse_arguments(LongSpecs, ShortSpecs, Atoms, Pairs1, PosArgs),
50 usage_arguments(Usages, PosArgs),
51 set_default_options(LongSpecs, ShortSpecs, Pairs1, Pairs2),
52 dict_pairs(Options, Pairs2).
61parse_arguments(_, _, [], [], []) :- !.
63parse_arguments(LongSpecs, ShortSpecs, [H1|T1], [H2|T2], L3) :-
64 atom_phrase(parse_flag(LongSpecs, ShortSpecs, H2), H1), !,
65 parse_arguments(LongSpecs, ShortSpecs, T1, T2, L3).
67parse_arguments(LongSpecs, ShortSpecs, [Arg|T1], L2, [Arg|T3]) :-
68 parse_arguments(LongSpecs, ShortSpecs, T1, L2, T3).
73parse_flag(LongSpecs, _, Key-false) -->
74 "--no-", !,
75 {must_be_key_type_(LongSpecs, Key, boolean)},
76 remainder_as_atom(Key).
78parse_flag(LongSpecs, _, Key-Value) -->
79 "--",
80 '...'(Codes),
81 "=", !,
82 {atom_codes(Key, Codes)},
83 {key_type_(LongSpecs, Key, Type)},
84 parse_value(Type, Value).
86parse_flag(LongSpecs, _, Key-true) -->
87 "--", !,
88 remainder_as_atom(Key),
89 {must_be_key_type_(LongSpecs, Key, boolean)}.
91parse_flag(_, ShortSpecs, Key-Value) -->
92 "-",
93 dcg_char(Key),
94 "=", !,
95 {key_type_(ShortSpecs, Key, Type)},
96 parse_value(Type, Value).
98parse_flag(_, ShortSpecs, Key-true) -->
99 "-", !,
100 dcg_char(Key),
101 {must_be_key_type_(ShortSpecs, Key, boolean)}.
102
103key_type_(Specs, Key, Type) :-
104 dict_get(Key, Specs, Spec), !,
105 dict_get(type, Spec, Type).
106key_type_(_, Key, _) :-
107 existence_error(cli_key(Key), cli_unspecified_key).
108
109must_be_key_type_(Specs, Key, SyntacticType) :-
110 key_type_(Specs, Key, SemanticType),
111 ( SemanticType = SyntacticType
112 -> true
113 ; syntax_error(cli_type_conflict(Key,SyntacticType,SemanticType))
114 ).
118parse_value(atom, Value) --> !,
119 remainder_as_atom(Value).
120parse_value(boolean, Value) --> !,
121 dcg_boolean(Value).
122parse_value(oneof(Values), Value) --> !,
123 remainder_as_atom(Value),
124 {must_be(oneof(Values), Value)}.
125parse_value(string, Value) -->
126 remainder_as_string(Value).
133set_default_options(LongSpecs, ShortSpecs, L2, L3) :-
134 maplist(dict_pairs, [LongSpecs,ShortSpecs], L0),
135 append(L0, L1),
136 set_default_options_(L1, L2, L3).
137
139set_default_options_([], _, []) :- !.
141set_default_options_([Key-_|T1], L2, [Key-Value|T3]) :-
142 memberchk(Key-Value, L2), !,
143 set_default_options_(T1, L2, T3).
145set_default_options_([Key-Spec|T1], L2, [Key-Default|T3]) :-
146 optionSpec{default: Default} :< Spec, !,
147 set_default_options_(T1, L2, T3).
149set_default_options_([_|T1], L2, L3) :-
150 set_default_options_(T1, L2, L3).
157usage_arguments(_, []) :- !.
159usage_arguments(Usages, PosArgs) :-
160 length(PosArgs, Len),
161 length(Pattern, Len),
162 memberchk(Pattern, Usages), !.
164usage_arguments(_, PosArgs) :-
165 length(PosArgs, Arity),
166 syntax_error(cli_args(Arity,PosArgs))
Command-line argument parsing
*/