1:- module( upsh, [upsh_make/0,upsh_make/1,upsh_version/1,upsh_version/2] ).    2
    3:- ensure_loaded( '../src/upsh_version' ).    4
    5upsh_make_defaults( Defs ) :- 
    6    current_prolog_flag( home, SwiHome ),
    7    % 1st place to look: ../../bin/swipl relative to flag home
    8    file_directory_name( SwiHome, SwiLib ),
    9    file_directory_name( SwiLib, BaseD ),
   10    directory_file_path( BaseD, bin, BinD ),
   11    Exec = upsh,
   12    ( exists_directory(BinD) ->
   13        Defs = [exec(Exec),bin_dir(BinD)]
   14        ;
   15        write( unable_to_locate_bin_dir_for_upsh__use_option(bin_dir) ), nl,
   16        Defs = [exec(Exec)]
   17    ).

Unix to Prolog shell.

Upsh 2.6

Upsh stands for Unix to Prolog shell. It is a Prolog program which can be used to run Prolog programs from the command line or as scripts.
It origianlly ran on three prolog engines without changes to the source code. Current versions are only tested on SWI-Prolog.

With version 2.*, Upsh has all the features I had envisaged and many which I just thought of on the way. It is also fairly stable.
The development has now been switched to SWI and upsh is also provided as an easy to install SWI pack.<br>

It is unlikely there will be any major releases in the future. I will of course get fixes on reported bugs or add features that are interesting.
For reporting a bug or feature requests contact me:

http://stoics.org.uk/~nicos/sware/contact.html

If you use Upsh for a while I would appreciate an email with the kind of scripts you using it with.

The pack has a single main predicate which creates an executable state that provides a convenient way of executing prolog scripts for the command line.
The state can be invoked by calling the created executable (upsh) on command line.
By default the upsh binary is placed in same directory as the swipl executable. Only tested on linux.

Install:
?- pack_install(upsh).

Load:
?- use_module(library(upsh)).

Create the executable.
?- upsh_make.

test.

?- halt.

-- ask your shell to re-read its executables with something like: rehash

upsh say naku

%  /home/nicos/.rcpl compiled 0.00 sec, 8 clauses
% /home/nicos/bin/cline_upsh/say.pl compiled 0.00 sec, 5 clauses
naku

lykos;upsh/scripts% upsh v
upsh_exec(upsh(2:2:1),swi(7:7:13),built_on(2018/5/2,14:42:49))

The executable will look into three places for scripts.

Upsh will also convert os friendly arguments to Prolog terms:

upsh say a=b
%  /home/nicos/.rcpl compiled 0.00 sec, 8 clauses
% /home/nicos/bin/cline_upsh/say.pl compiled 0.00 sec, 5 clauses
a(b)

The executable takes a number of one letter flags:

upsh say p a=b
%  /home/nicos/.rcpl compiled 0.00 sec, 8 clauses
a(b)

upsh say f p a=b
a(b)

By default the executable looks into script say.pl for main/0, main/1, main/n, say/0, say/1, say/n and calls it with the appropriate number of arguments.

See more examples with

upsh h
author
- nicos angelopoulos
version
- 2.3 2018/5/2
- 2.4 2018/12/10 simplified upsh_make/1 (no more shell call to build the executable).
- 2.5 2019/12/23 work around new SWI configs

*/

 upsh_make
 upsh_make(Opts)
Create an upsh executable for running Prolog scripts from command line.

Opts

bin_dir(BinDir=SwiBin)
directory for putting the executable in, defaults to the one holding swipl constructed from current_prolog_flag( home, Home ).
exec(Exec=upsh)
name of executable
author
- Nicos Angelopoulos
version
- 0.1 2017/06/03
- 0.2 2018/12/10

*/

  127upsh_make :-
  128    upsh_make( [] ).
  129
  130upsh_make( ArgS ) :-
  131    debug( upsh(make), 'making new upsh executable', [] ),  % we don't expect this to show
  132    debug( upsh(make) ),
  133    \+ var(ArgS),
  134    ( is_list(ArgS) -> Args = ArgS; Args = [ArgS] ),
  135    upsh_make_defaults( Defs ),
  136    append( Args, Defs, Opts ),
  137    multifile( upsh_built_call/1 ),
  138    dynamic( upsh_built_call/1 ),
  139    asserta( upsh_built_call(true) ),
  140    load_files( pack('upsh/src/upsh') ), 
  141    memberchk( exec(Exec), Opts ),
  142    memberchk( bin_dir(BinD), Opts ),
  143    directory_file_path( BinD, Exec, AbsExec ),
  144    qsave_program( AbsExec, [init_file(none_what_noever),goal(upsh_exec:upsh)] ),
  145    nodebug( upsh(make) ),
  146    abolish( upsh_built_call/1 ).
  147
  148/* pre 18.12.10:
  149upsh_make( ArgS ) :-
  150    \+ var(ArgS),
  151    ( is_list(ArgS) -> Args = ArgS; Args = [ArgS] ),
  152    upsh_make_defaults( Defs ),
  153    append( Args, Defs, Opts ),
  154    % delete_local_exec,
  155    once( absolute_file_name( pack(upsh), UpshD ) ),
  156    % working_directory( Old, UpshD ),
  157    % Shell ='swipl -f upsh_create.pl -g upsh_create',
  158    debug( upsh, 'Shelling: ~w', Shell ),
  159    shell( Shell ),
  160    memberchk( exec(Exec), Opts ),
  161    memberchk( bin_dir(BinD), Opts ),
  162    directory_file_path( BinD, Exec, PathTo ),
  163    % rename_file( 'bin/upsh', PathTo ),
  164    atom_concat( 'mv bin/upsh ', PathTo, MvTo ),
  165    shell( MvTo ),
  166    debug( upsh, 'Moved to: ~p', PathTo ),
  167    working_directory( _, Old ),
  168    debug( upsh, 'Done', true ).
  169    */
  170
  171delete_local_exec :-
  172    Loc = 'bin/upsh',
  173    exists_file( Loc ),
  174    !,
  175    delete_file( Loc ).
  176delete_local_exec