Skip to content

Commit

Permalink
DOC: PrologScript and shell script usage
Browse files Browse the repository at this point in the history
  • Loading branch information
JanWielemaker committed Oct 31, 2023
1 parent 2b5bb70 commit 3d24113
Showing 1 changed file with 14 additions and 13 deletions.
27 changes: 14 additions & 13 deletions man/overview.doc
Original file line number Diff line number Diff line change
Expand Up @@ -910,10 +910,10 @@ disabling signal handling.
:- initialization(main, main).

main(Argv) :-
concat_atom(Argv, ' ', SingleArg),
term_to_atom(Term, SingleArg),
Val is Term,
format('~w~n', [Val]).
atomic_list_concat(Argv, ' ', SingleArg),
term_to_atom(Term, SingleArg),
Val is Term,
format('~w~n', [Val]).
\end{code}

And here are two example runs:
Expand Down Expand Up @@ -967,26 +967,27 @@ Especially on Unix systems and not-too-large applications, writing
a shell script that simply loads your application and calls the
entry point is often a good choice. A skeleton for the script is
given below, followed by the Prolog code to obtain the program
arguments.
arguments. See library \pllib{main} and argv_options/3 for details.

\begin{code}
#!/bin/sh

base=<absolute-path-to-source>
PL=swipl
SWIPL=swipl

exec $PL -q -f "$base/load" --
exec $SWIPL "$base/load.pl" -- "$@"
\end{code}

\begin{code}
:- initialization go.
:- use_module(library(main)).
:- initialization(main,main).

go :-
current_prolog_flag(argv, Arguments),
go(Arguments).
main(Argv) :-
argv_options(Argv, Positional, Options),
go(Positional, Options).

go(Args) :-
...
go(Positional, Options) :-
...
\end{code}

On Windows systems, similar behaviour can be achieved by creating a
Expand Down

0 comments on commit 3d24113

Please sign in to comment.