Practical happy CLI arg parsing with Scryer #2862
Replies: 6 comments 12 replies
-
Thank you a lot for sharing this! I find such examples extremely helpful for learning Prolog. The code looks very elegant. Personally, I would do 2 things a bit differently: Instead of using Second, I would most likely write functors_pairs([Functor|Functors], [Pair then I already know that functors_pairs([Functor|Functors], [Hs-Arg And then I would try to use an analogous name for the tail of the list, a name that is somehow suggestive of and connected with functors_pairs([Functor|Functors], [Hs-Arg|HAs]) :- And now could be a good time to say: One moment, what about first describing this for a single functor and pair? functor_pair(Functor, Hs-Arg) :- Functor =.. [Head,Arg], atom_chars(Head, Hs). In an ideal implementation, In fact, the first argument is not even a functor? So, a better name would also be appropriate. And then we can write functors_pairs(Functors, Pairs) :- maplist(functor_pair, Functors, Pairs). or alternatively use |
Beta Was this translation helpful? Give feedback.
-
Regarding term_expansion(option(Name,Long,Short), ( param(Option) --> ( [[-,-|Long]] | [[-|Short]] ), [Value] )) :- Option =.. [Name,Value]. option(username, "username", "u"). option(port, "port", "p"). option(host, "host", "h"). We get: ?- phrase(param(P), ["--username","test"]). P = username("test") ; false. |
Beta Was this translation helpful? Give feedback.
-
Version 2 of the script: :- use_module(library(dcgs)).
:- use_module(library(pio)).
:- use_module(library(lists)).
:- use_module(library(os)).
/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
Intended to be used with the following style of bash script:
local parsed=$(scryer-prolog -f ./path/to/this.pl -g main -- $@)
declare -A params
while IFS='=' read -r key value; do
params[$key]=$value;
done <<< $parsed
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
%% v2: per https://github.com/mthom/scryer-prolog/discussions/2862#discussioncomment-12663273
term_expansion(option(Name,Long,Short),
( param(Option) -->
( [[-,-|Long]] | [[-|Short]] ),
[Value] )) :-
Option =.. [Name,Value].
option(username, "username", "u").
option(port, "port", "p").
option(host, "host", "h").
option(dbusername, "dbusername", "du").
option(dbpassword, "dbpassword", "dp").
%% v2: add param "spellcheck"
param(_) -->
[Param],
[Value],
!,
{ error(unknown_values, [param(Param), value(Value)])}.
inputs_params([]) --> [].
inputs_params([Param|Params]) -->
param(Param),
inputs_params(Params).
inputs_params(Inputs, Params) :-
phrase(inputs_params(Params), Inputs).
% v2: per https://github.com/mthom/scryer-prolog/discussions/2862#discussioncomment-12660682
functor_pair(Functor, Hs-Arg) :-
Functor =.. [Head,Arg],
atom_chars(Head, Hs).
functors_pairs(Functors, Pairs) :-
maplist(functor_pair, Functors, Pairs).
% v2: per https://github.com/mthom/scryer-prolog/discussions/2862#discussioncomment-12668080
list_newlinephrase([]) --> [].
list_newlinephrase([X|Xs]) -->
X,
"\n",
list_newlinephrase(Xs).
printkvs(KVs) :-
phrase_to_stream(list_newlinephrase(KVs), user_output).
main :-
argv(As),
inputs_params(As, Params),
functors_pairs(Params, Pairs),
printkvs(Pairs),
halt(0). |
Beta Was this translation helpful? Give feedback.
-
Version 3 of the script: % CLI parsing example, version 3
:- use_module(library(dcgs)).
:- use_module(library(debug)).
:- use_module(library(pio)).
:- use_module(library(lists)).
:- use_module(library(os)).
/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
Intended to be used with the following style of bash script:
local parsed=$(scryer-prolog -f ./path/to/this.pl -g main -- $@)
declare -A params
while IFS='=' read -r key value; do
params[$key]=$value;
done <<< $parsed
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
%% v2: per https://github.com/mthom/scryer-prolog/discussions/2862#discussioncomment-12663273
term_expansion(option(Name,Long,Short),
( param(Option) -->
( [[-,-|Long]] | [[-|Short]] ),
[Value] )) :-
Option =.. [Name,Value].
option(username, "username", "u").
option(port, "port", "p").
option(host, "host", "h").
option(dbusername, "dbusername", "du").
option(dbpassword, "dbpassword", "dp").
% v2: add param "spellcheck"
param(_) -->
[Param],
[Value],
!,
{ error(unknown_values, [param(Param), value(Value)])}.
inputs_params([]) --> [].
inputs_params([Param|Params]) -->
param(Param),
inputs_params(Params).
inputs_params(Inputs, Params) :-
phrase(inputs_params(Params), Inputs).
% v2: per https://github.com/mthom/scryer-prolog/discussions/2862#discussioncomment-12660682
functor_pair(Functor, Hs-Arg) :-
Functor =.. [Head,Arg],
atom_chars(Head, Hs).
functors_pairs(Functors, Pairs) :-
maplist(functor_pair, Functors, Pairs).
% v2: per https://github.com/mthom/scryer-prolog/discussions/2862#discussioncomment-12668080
% v3: per https://github.com/mthom/scryer-prolog/discussions/2862#discussioncomment-12669324
list_newlinephrase([]) --> [].
list_newlinephrase([K-V|Xs]) -->
format_("~s=~s~n", [K,V]),
list_newlinephrase(Xs).
printkvs(KVs) :-
phrase_to_stream(list_newlinephrase(KVs), user_output).
main :-
argv(As),
inputs_params(As, Params),
functors_pairs(Params, Pairs),
printkvs(Pairs),
halt(0). |
Beta Was this translation helpful? Give feedback.
-
So I realized that I'll need to reuse the script multiple times with different options. Rather than copy/paste the script, I thought I would try to dynamically load the options. Honestly, I'm not crazy about this approach, but it works. If anyone has any more elegant thoughts, please let me know: main :-
getenv("PARSE_OPTS_FILE", ParseOptsFile),
open(ParseOptsFile, read, Stream),
load(Stream),
argv(As),
inputs_params(As, Params),
functors_pairs(Params, Pairs),
printkvs(Pairs),
halt(0). Idea being to invoke with something like: $ PARSE_OPTS_FILE=./scripts/admin/create_user_options.pl scryer-prolog -f ./scripts/admin/create_user.pl -g main -- --username username -du admin -dp 4567 -h localhost where option(username, "username", "u").
option(port, "port", "p").
option(host, "host", "h").
option(dbusername, "dbusername", "du").
option(dbpassword, "dbpassword", "dp"). I would definetly prefer a metainterpreter based approach, but my creativity is failing me here. |
Beta Was this translation helpful? Give feedback.
-
Imho interesting idea would be to parse CLI arguments (or any other sort of configuration), populate environment variables from those values and then |
Beta Was this translation helpful? Give feedback.
Uh oh!
There was an error while loading. Please reload this page.
Uh oh!
There was an error while loading. Please reload this page.
-
Got very annoyed writing bash scripts like this because I can never remember the syntax. I stared writing some code like below only to realize
getopts
only handles short args like-u
and-p
and not long params like--host
... then I'd have to write some stupidshift 2
parser and look up even more syntax. Which is fine I guess BUT thank God I remembered Prolog exists!Then I remembered -- Scryer Prolog!!
Voila!
Earth shattering? No. But great example of a place where it's legitimately faster and more maintainable to write Scryer code than some other production code for a practical industry task.
(comments improving the script welcome!)
Beta Was this translation helpful? Give feedback.
All reactions