stoics_lib.pl -- A medley of library predicates for stoics packs.

This library collects a medley of library predicates used in more than one stoics projects and which are not yet matured enough to be published as sub-packs. pack(lib) looks into the LibIndex.pl of this pack in order to locate source files for pack predicates.

Highlights

Installation

To install

?- pack_install( stoics_lib ).

to load the whole library


?- use_module( library(stoics_lib) ).

or

?- use_module( library(lib) ).
?- lib(stoics_lib).

To only load specific predicates

?- lib( stoics_lib:kv_compose/3 ).
?- kv_compose( [a,b,c], [1,2,3], KVs ).
KVs = [a-1, b-2, c-3].
?- kv_decompose( [a-1,b-2,c-3], Ls, Ns ).
ERROR: Undefined procedure: kv_decompose/3 (DWIM could not correct goal)
?- lib( stoics_lib:kv_decompose/3 ).
?- kv_decompose( [a-1,b-2,c-3], Ls, Ns ).
Ls = [a, b, c],
Ns = [1, 2, 3].

Pack info

author
- nicos angelopoulos
version
- 0.1 2017/2/20
- 0.2 2017/3/7
- 0.3 2017/3/9
- 0.4 2017/8/8
- 0.5 2017/8/15
- 0.6 2017/10/13
- 1.0 2018/3/18
- 1.1 2019/4/22
- 1.2 2020/9/18
- 1.3 2020/9/18
- 1.4 2020/9/18
- 1.5 2022/12/29
- 1.6 2023/1/2
- 1.7 2023/1/2
See also
- http://www.stoics.org.uk/~nicos/sware/stoics_lib
 stoics_lib
This pack does not only provide its predicates via the module definition, but it can also be used to load them on demand. The two methods are transparent and its possible to intermingle:
?- lib( stoics_lib:kv_compose/3 ).

The main idea is to serve a number of diverse predicates that are not ready to be released on their own pack can be used without including them in each individual pack that requires them.

If you want to use any of the predicates in your own pack, simply use make your pack dependendant to pack(lib) and pack(stoics_lib) by adding the following line to pack.pl

requires(stoics_lib).

Altough

requires(lib).

will also work as library(lib) will also install stoics_lib the first time it is referenced.

Note that as stoics_lib depends on pack(lib) that pack will also be installed by the package manager. You can then include code for (example) predicate io_lines/2 by adding the following to your source code.

:- use_module( library(lib) ).
:- lib( stoics_lib:io_lines/2 ).

or

:- use_module( library(lib) ).
:- lib( stoics_lib:io_lines/2 ).

Alternatively, you can make your pack only dependendant on pack(lib) and the first time

?- lib(stoics_lib).

is queried, pack(lib) will interactively install stoics_lib.

To load stoics_lib predicates without reference to the pack name, first load the index with lib_load_pack_index/2

?- lib_load_pack_index( stoics_lib ).
?- lib( kv_decompose/3 ).
?- kv_decompose([a-1,b-2,c-3], Ls, Ns ).
Ls = [a, b, c],
Ns = [1, 2, 3].
 stoics_lib_version(Version, Date)
Version, term of the from Mj:Mn:Fx and Date is date(Year,Month,Day).
?- stoics_lib_version( -V, -D ).
D = 1:6:0,
V = date(2023,1,2).
author
- nicos angelopoulos
version
- 1:5:0, 2022/12/29
- 1:6:0, 2023/01/02, improvements to arg_arg/4, list_frequency/4, new: latex_colour/4, colour_hex/2
- 1:7:0, 2023/01/02, known/2 optionised
 at_con(?List, Atom)
 at_con(?List, +Sep, ?Atom)
Mostly a nickname for atomic_list_concat/3 because this is a well used predicate and the system name is too long, but also
?- at_con( [a,b,c], _, Abc ).
Abc = a_b_c.
?- at_con( [a,b,'',c], -, Abc ).
Abc = 'a-b-c'.
?- at_con( Parts, '', abc ).
Parts = [a, b, c].

?- at_con( [A,orf,C], '', 'C14orf38' ).
A = 'C14',
C = '38' ;
false.

?- at_con( [A,B,C], '', abc ), write( A:B:C ), nl, fail.
: : abc
:a:bc
:ab:c
:abc:
a: : bc
a:b:c
a:bc:
ab: : c
ab:c:
abc: :
author
- nicos angelopoulos
version
- 0.2 2014/7/15 added avoidance of ''
- 0.3 2014/7/15 now allows non-ground List with Sep = ''
 atom_sub(+Part, ?Full)
An argument reduction and swap of sub_atom/5.

As of version v0.2, Part can be a term:

pfx(Pfx)
requires Pfx to be a prefix of Full (makes predicate deterministic)
psf(Psf)
requires Psf to be a postfix of Full (makes predicate deterministic)

 ? atom_sub( abc, xabcd ).
 true ;
 false.
 ? atom_sub( pfx(x), xabcd ).
 true.
author
- nicos angelopoulos
version
- 0.2 2019/12/29
- 0.1 2013/12/19
See also
- sub_atom/2 sub_atom/5
 prefix_atom(?Pfx, ?Atom)
Version suitable for apply calls, such as in include/3.
?-  directory_files( '.', All ),
    exclude( prefix_atom('.'), All, Adots ).
    All = ['.claws_cache', '.', '.mh_sequences', '541', .., '.claws_mark'],
    Adots = ['541'].
   
author
- Nicos Angelopoulos
version
- 0.1 2012/05/05.
 prefix_atom(?Pfx, ?Atom, -Postfix)
Pfx is a prefix of Atom with Postfix being the remainder of Atom. This is a resuffle of atom_concat/3 arguments, with this version being suitable for apply calls, such as in map_succ_list/3.
?-  directory_files( '.', All ),
    map_succ_list( prefix_atom('.'), All, DotPsfxs ).
   
author
- Nicos Angelopoulos
version
- 0.1 2013/04/17.
 sub_atom(+Full, ?Part)
Short for sub_atom( Full, _, _, _, Sub ).

As per sub_atom/5, it can succeed multiple times, so leaves backtrack points.

As of v0.2 +,+ modality calls atom_sub/2 which allows Part to be non atomic.

 ?- sub_atom( abcde, bc ).
 true ;
 false.

 ?- findall( Sub, sub_atom(abc,Sub), Subs ), length( Subs, Len ).
 Subs = ['', a, ab, abc, '', b, bc, '', c|...],
 Len = 10.

 ?- sub_atom( full, psf(ul) ).
 false.
 
 ?- sub_atom( full, psf(ll) ).
 true.
 
author
- nicos angelopoulos
version
- 0:2
See also
- sub_atom/5, atom_sub/2
 sub_atom(+Full, ?Pre, ?Post, ?Part)
As sub_atom/5 but without the Length, 3rd, argument.
 ?- sub_atom( full, Pre, Post, ul ).
 Pre = f,
 Post = l ;
 false.
 
 ?- sub_atom( full, f, l, MidBit ).
 MidBit = ul ;
 false.

 ?- sub_atom( ab, Pre, Post, Mid ), write(Pre:Mid:Post), nl, fail.
 : : ab
 :a:b
 :ab:
 a: : b
 a:b:
 ab: :
 
To be done
- sub_atom/3 with options: begins(t/f), ends(t/f), left(Left), right(Right)
 n_digits_integer_codes(+N, +Numb, -Codes)
Codes is of length N and contains either the last N digits of Numb or all digits of Numb left-padded by 0s to make its codes representation up to N.
?- n_digits_integer_codes( 2, 120, Codes ), atom_codes( Atom, Codes ).
Codes = [50, 48],
Atom = '20'.

?- n_digits_integer_codes( 2, 2, Codes ), atom_codes( Atom, Codes ).
Codes = [48, 50],
Atom = '02'.
 datime_readable(-Ratom)
 datime_readable(+Datime, -Ratom)
Ratom is a human readable representation of Datime. When Datime is missing the current datime is used.
?- datime_readable( Readable ).
Readable = 'At 15:13:36 on 2nd of Jul 2014'.
author
- nicos angelopoulos
version
- 0.2 2014/7/2 Changed to date/9 and atom representation. Be ware if you are using 0.1
See also
- debug_goal/3
To be done
- add precision for seconds.
 date_two_digit_dotted(-Dotted)
 date_two_digit_dotted(+Date, -Dotted)
Generate a YY.MM.DD atom from date/n term structures. Implied Date is the current date. Current version assumes 1st, 2nd and 3rd terms of Date are Year, Month and date. So it works with both date/1 and date_time/1.
?- get_date_time( Curr ), date_two_digit_dotted( Curr, Dotted ).
Curr = date(2013, 5, 22, 17, 21, 12.714296102523804, -7200, 'CEST', true),
Dotted = '13.05.22'.

?- date_two_digit_dotted( Dotted ).
Dotted = '13.11.12'.
author
- nicos angelopoulos
version
- 0.2 2014/3/31 % original date_two_digit_dotted should have benn date_time_...
 get_date(-Date)
Get the current date in date/1 format. Tested on Swi, not in Yap.
author
- nicos angelopoulos
version
- 0.1
See also
- get_date_time/1
 get_date_time(-CurrDatime)
Just a wrapper to SWI's get_time(Stamp), stamp_date_time(Dtime). CurrDatime should be a date_time/1 term. SWI specific. Check YAP.
author
- nicos angelopoulos
version
- 0.1 2014/03/31
 get_datetime(Dtime)
Get current datime as a datetime/6 term structure.
?- get_datetime( Dime ).
Dime = datetime(2016, 12, 2, 10, 42, 26).
author
- nicos angelopoulos
version
- 0.1 2016/12/02 (some time well before).
 three_letter_month(?IntIdx, -Month)
Indexes numeric month to 3 letter atom.
author
- nicos angelopoulos
version
- 0.1 2010/10/7
 three_letter_months(-Months)
Gets all three letter month names. *nix compatible.
author
- nicos angelopoulos
version
- 0.1 2010/10/7
 message_report(+Format, +Args, +Kind)
An Swi shortcut for printing messages. The predicate first phrases onto a list the Format message filled by Args, as it would do for debug( _, Format, Args ), then prints these lines as of Kind (error,warning,debug(_)).
 ?- Mess = 'Destination:~w already pointed to:~w, repointing to:~w',
 |    F1 = 'file1', F2 = file2, F3 = file3,
 |    message_report( Mess, [F1,F2,F3], warning ).

 Warning: Destination:file1 already pointed to:file2, repointing to:file3
 
author
- nicos angelopoulos
version
- 0.1 2014/02/28
 expand_spec(+FileSpec, -Expanded)
Expand the file specification FileSpec to an atomic File name.

Similar to expand_file_name/2 for Atomic FileSpec, but it also works on termed and aliased args (abc/def.pl and abc(def.pl) respectively). Leaves backtrack points.

?- expand_spec( '$HOME', Home ).
Home = '/home/na11'

?- expand_spec( src/kv, L  ).
L = 'src/kv'.

?- expand_spec( pack(real), Exp ).
Exp = '/home/nicos/.local/share/swi-prolog/./pack/real' ;
false.

?- lib(mtx).
?- expand_spec( data('mtcars.csv'), ExpF ).
ExpF = '/usr/local/users/nicos/data/mtcars.csv' ;
ExpF = 'data/mtcars.csv' ;
ExpF = '/home/nicos/.local/share/swi-prolog/pack/mtx/data/mtcars.csv' ;
ExpF = '/home/nicos/.local/share/swi-prolog/pack/sanger/data/mtcars.csv' ;
ExpF = '/home/nicos/.local/share/swi-prolog/pack/bio_db_repo/data/mtcars.csv' ;
ExpF = '/home/nicos/.local/share/swi-prolog/pack/gbn/data/mtcars.csv'.
author
- nicos angelopoulos
version
- 0.1 2017/3/8 (split from other sources)
 io_line(+Stream, ?Line)
Either get (if Line is a variable), or put a line, (if Line is a list of codes) on Stream.
author
- nicos angelopoulos
version
- 0.1 2017/3/13 created the common interface for put and get.
 io_get_line(+Stream, -Line)
Gets next line from Stream. Line is a list of Codes. The new line is not returned in Line. Returns end_of_file at end of file.
?- atom_codes(abc,Abc), open(abc.txt,write,Out), io_put_line(Abc,Out),close(Out).
?- open(abc.txt,read,In), io_get_line(In,Line), atom_codes(Atom,Line),close(In).
Atom = abc.
author
- nicos angelopoulos
version
- 0.1 2016/12/9
See also
- fget_line/2
 io_put_line(+Codes, +Stream)
Output a line of Codes onto Stream.
author
- nicos angelopoulos
version
- 0.1 2016/12/9
See also
- fput_line/2.
 io_lines(+FileOrStream, -Lines)
io_lines(+FileOrStream, +Lines)
Read/write a list of lines from/to a file or stream. Each line is a list of codes. When Lines is ground, writing to file/stream is assumed. If FileOrStream corresponds to a current stream, this is used for I/O. Else FileOrStream is taken to be a file which is opened in correct mode. In the latter case the stream is closing at the end of operation, whereas streams are left open.
?- maplist( atom_codes, [abc,edf,xyz], Lines ), io_lines( test_out.txt, Lines ).
author
- nicos angelopoulos
version
- 1.0 2016/12/09
See also
- file_to_list_lines/2 and list_of_lines_to_file/2
- io_open/3, io_close/2.
 io_close(+FileR, -Stream)
If FileR is a stream (should be identical to Stream) then do nothing. Else, close Stream.
 io_open(+FileR, +Mode, -Stream)
If FileR is a stream, just unify it to Stream, else assume is a file, and open for access in Mode.
 kv_compose(+Ks, +Vs, -KVs)
 kv_compose(+Ks, +Vs, -KVsCont, -Tkvs)
Ks and Vs are lists and KVs and KVsCont are made of -pairs of their values. Tkvs is the tail of difference list KVsCont.
?- kv_compose( [a,b,c], [1,2,3], Kvs ).
author
- nicos angelopoulos
version
- 0.2 2017/2/24 added /4 version.
 kv_decompose(+Pairs, -Ks, -Vs)
Split -pair list, Pairs, to its K and V lists.
?- kv_decompose( [a-1,b-2,c-3], Ks, Vs ).
Ks = [a, b, c],
Vs = [1, 2, 3].
author
- nicos angelopoulos
 kv_ks(+KVs, -Ks)
Ks are all keys in the key values KVs. 0.2 supports any /n terms as KVs by means of using arg/3.
?- kv_ks( [a-1,b-2,c-3], Ks ).
Ks = [a, b, c].

?- kv_ks( [t(1,a,'A'),t(2,b,'B'),t(3,c,'C')], Ks ).
Ks = [1, 2, 3].
author
- nicos angelopoulos
version
- 0.2 use arg/3 rather than argument unification
- 0.3 2017/3/12, docs
 kv_vs(+KVs, -Vs)
Vs are all values in the key values, -pairs, KVs. 0.2 supports any /n terms as KVs by means of using arg/3.
?- kv_vs( [a-1,b-2,c-3], Vs ).
Vs = [1, 2, 3].

?- kv_vs( [t(1,a,'A'),t(2,b,'B'),t(3,c,'C')], Vs ).
Vs = [a, b, c].
author
- nicos angelopoulos
version
- 0.2 2017/3/12, use arg/3 rather than argument unification
 kvo_k_memberchk(+Key, +KVord, -Val)
Select each Val corresponding to a single Key in a ordered (but not uniquely sorted) pairs list KVord.
KVord can be a list of any N-ary terms, Key is taken to be the first arg/3 and Val the second.

In contrast to kvs_k_memberchk/3, this assumes non-unique keys.
In both cases KVset is assumed ordered.

 kvo_k_memberchk( b, [a-1,b-2,c-3], V ).      % compare to kvs_k_memberchk/3
 V = 2;
 false.
 
 kvo_k_memberchk( b, [a-1,b-2,b-4,c-3], V ).
 V = 2;
 V = 4;
 false.

 kvo_k_memberchk( d, [a-1,b-2,c-3], V ).
 false.

 kvo_k_memberchk( c, [a+1,b+2,c+3], V ).
 V = 3;
 false.
author
- nicos angelopoulos
version
- 0.1 2014/5/23
- 0.2 2018/1/8, generalised via arg(1,,) & arg(2,,) to non - terms
 kvs_k_memberchk(+K, +KVset, -V)
Select the unique V corresponding to Should this be covered by a unification version of Swi's ord_memberchk/2 ? It seems counter intuitive that they are using ==.

Should there be a kvo version? This assumes unique keys in addition to sorted.

 kvs_k_memberchk( b, [a-1,b-2,c-3], V ).
 V = 2.

 kvs_k_memberchk( d, [a-1,b-2,c-3], V ).
 false.

 kvs_k_memberchk( c, [a+1,b+2,c+3], V ).
 V = 3.

 kvs_k_memberchk( b, [a-1,b-2,b-4,c-3], V ).
 V = 2.
author
- nicos angelopoulos
version
- 0.1 2014/5/23
- 0.2 2018/1/8, generalised via arg(1,,) & arg(2,,) to non - terms
 break_on_list(+List, +Partial, -Left, -Right)
Breaks a List at the sublist Partial, producing the Left and Right parts.
?- break_on_list( [a,b,c,d], [b,c], L, R ).
L = [a],
R = [d].
author
- nicos angelopoulos
version
- 0.2 2016/12/13, added to stoics_lib
 break_nth(?Nth, +List, -Left, -Right)
List is split on Nth Position, into Left, and Right Parts First element position is number 1. Nth element is last element in Left.

 ?- break_nth( 0, [a,b,c], L, R ).  L=[], R=[a,b,c]
 ?- break_nth( 1, [a,b,c], L, R ).  L=[a], R=[b,c]
 ?- break_nth( 3, [a,b,c], L, R ).  L=[a,b,c], R=[].
 ?- break_nth( 4, [a,b,c], L, R ).  error

 ?- break_nth( N, [a,b,c], L, R ).
   N = 1,
   L = [a],
   R = [b, c] ;
   N = 2,
   L = [a, b],
   R = [c] ;
   N = 3,
   L = [a, b, c],
   R = [] ;
   false.
 has_at_least(+N, +X, +List)
Succeeds iff List contains at least N Xs.
?- has_at_least( 2, a, [a,b,c,a] ).
true.

?- has_at_least( 2, b, [a,b,c,a] ).
false.
author
- nicos angelopoulos
version
- 0.1 2017/1/11
 has_at_most(+N, +X, +List)
Succeeds iff List contains at most N Xs.
?- has_at_most( 1, a, [a,b,c,a] ).
false.

?- has_at_most( 1, b, [a,b,c,a] ).
true.
author
- nicos angelopoulos
version
- 0.1 2017/1/11
 has_length(+Term, +Lengthy)
 has_length(+Term, +Lengthy, +CompOp)
 has_length(+Term, +Lengthy, +CompOp, +Err)
Succeeds iff Term has length that is op_compare/3 succesful with Lengthy. If the predicate does not succeed, it either fails (Err=fail) or throws an error. Lengthy is either an integer or a term, of which the length is found via term_length/2. When CompOp is missing is set to =:=. If Err is anything else than fail it will be transformed to a pack_error/N ball. If Err is error, then it is ignored and ball is a vanila lengths_mismatch/4, pack_error/1 ball. Else name and first argument of Err are taken to be the pack and preciate callers and if 3rd and fourth exist are taken to be token1 and token2 of the length_mismatch/5. If pack(pack_errror) is instaled the balls are pretty printed.
?- has_length( [a,b,c], 3 ).
true.

?- has_length( [a,b,c], X ).
false.
% because variables (X) have length 1

?- has_length( X, Y ).
true.

?- has_length( [a,b,c], 2 ).
false.

?- has_length( [a,b,c], a(d,e,f) ).
true.

?- has_length( [a,b,c], [d,e,f] ).
true.

?- has_length( [a,b,c], 2, =< ).
false.

?- has_length( [a,b,c], 2, > ).
true.

?- has_length( [a,b,c], 2, =<, err(os,os_list/4,art1,art2) ).
ERROR: os:os_list/4: Terms idied by: art1 and art2, have mismatching lengths: 3 and 2 respectively (=< expected)
author
- nicos angelopoulos
version
- 0.1 2017/8/22
- 0.2 2017/11/21, lengths for strings and vars, 3 new examples,
 list_frequency(+List, -Frequencies)
 list_frequency(+List, -Frequencies, +Opts)
Frequencies is a list of Term-Freq -pairs with Freq being the number of times each term (and its variants) appear in the List.

Opts

bins(Bins=false)
if a list of values, List elements are placed in (=<) bins, if non false atom,\br it should be predicate name that produces a bin name for the element.
Can also be a pairlist of label-break.value elements, in which case,
the last bin should also be given with something like Bin-inf.
order(Ord=false)
order of results: true sorts by element, freq sorts by frequency, and false for no sorting
transpose(T=false)
when true returns the elements of Frequencies as Freq-Term
variant(Var=true)
when false compare elements with ==
zero(Zero=false)
whether to include zero counter elements (Zero should be the list of expected elements)
?- list_frequency( [c,a,b,a,b,c], Freqs ).
Freqs = [c-2, a-2, b-2].

?- list_frequency( [c,a,b,a,b,c], Freqs, order(true) ).
Freqs = [a-2, b-2, c-2].

?- list_frequency( [c,a,b,a,b,c], Freqs, transpose(true) ).
Freqs = [2-c, 2-a, 2-b].

?- list_frequency( [c,a,b,a,b,c], Freqs, zero([b,a,c,d]) ).
Freqs = [b-2, a-2, c-2, d-0].

?- list_frequency( [a(X),b(Y),a(Z)], Freqs ).
Freqs = [a(X)-2, b(Y)-1].

?- list_frequency( [a(X),b(Y),a(Z)], Freqs, variant(false) ).
Freqs = [a(X)-1, b(Y)-1, a(Z)-1].

?- list_frequency( [a(X),b(Y),a(Z),a(X)], Freqs, variant(false) ).
Freqs = [a(X)-2, b(Y)-1, a(Z)-1].

?- list_frequency( [1,2,10,11,12,21,22], Freqs, bins([10,20]) ).
Freqs = [1-3, 2-2, 3-2].

?- list_frequency( [1,2,10,11,12,21,22], Freqs, bins([bin_1-10,bin_2-20,bin_3-inf]) ).
Freqs = [bin_1-3, bin_2-2, bin_3-2].

?- assert( (let_num(Let,Num) :- atom_codes(Let,[Code]),Num is Code-96) ).

?- list_frequency( [a,b,c,c,b,a,d], Freqs, bins(let_num) ).
Freqs = [1-2, 2-2, 3-2, 4-1].

?- list_frequency( [1,2,10,11,12,21,22], Freqs, bins(0-5) ).
Freqs = ['(0-5]'-2, '(5-10]'-1, '(10-15]'-2, '(20-25]'-2].

NOTE: arguments changed between 0.2 and 0.3.

author
- nicos angelopoulos
version
- 0.2 2015/11/25, added /3 version where wnd is Expected and examples
- 0.3 2016/12/16, changed /3 version to 3rd being the options. added options
- 0.4 2022/12/10, option bins(Bins)
 list_proportions(+List, -Propos, +Opts)
Create the proportions of each element within List.
Where the proportion of an element it is 0-1 location within the range<br>

Opts

min_max(MinMax=false)
else give a range (r(Min,Max)) that are assumed to be the min and values of list
so the code doesn't have to calculate them
to_range(ToR=false)
else give a range (r(ToMin,ToMax)) to which to cast the proportions
?- list_proportions( [1,2,3,4], Props ).
Props = [0, 0.3333333333333333, 0.6666666666666666, 1].

?- list_proportions( [1,2,3,4], Props, to_range(r(2,8)) ).
Props = [2, 4.0, 6.0, 8].
author
- nicos angelopoulos
version
- 0.1 2018/2/16
 list_transpose(+List, -Transpose)
Transpose a list of lists.
?- list_transpose( [[a,1,2,3],[b,4,5,6],[c,7,8,9]], Trans ).
Trans = [[a, b, c], [1, 4, 7], [2, 5, 8], [3, 6, 9]].
author
- nicos angelopoulos
version
- 0.1 2017/1/11
 select_all(+List, +Elem, -Select, -Rem)
Select all elements of List that are term subsumed (subsumes_term/2) by Elem. Rem is the non selected elements of List

works on Swi have n't tested Yap...

select_all( [a(b),b(c),a(b),d(a),a(c)], a(A), Sel, Rem ).
Sel = [a(b), a(b), a(c)],
Rem = [b(c), d(a)].

select_all( [a(b),b(c),a(b),d(a),a(c)], a(b), Sel, Rem ).
Sel = [a(b), a(b)],
Rem = [b(c), d(a), a(c)].
author
- nicos angelopoulos
version
- 0.2 2014/4/7
 select_first(+List, +Elem, -Rem)
An idiom of select_all/4 which unfolds to select_all( List, Elem, [H|_], Rem ), H = Elem.
 ?- select_first( [dbg(t),dbg(f),etc(x)], dbg(W), Rem ).
 W = t,
 Rem = [etc(x)].
author
- nicos angelopoulos
version
- 0.1 2014/4/7
 skim(+Nested, -Scum, -Remains)
Skim the first elements (Scum) from a Nested list with the tails being the Remains.
Fails if Nested has no more elements to skim at all positions (typically a list of empty lists).
?- Nest = [[a,b,c],[1,2,3]], skim( Nest, Sc, Rest ).
Nest = [[a, b, c], [1, 2, 3]],
Sc = [a, 1],
Rest = [[b, c], [2, 3]].

?- Nest = [[a,b,c],[1,2,3]], skim(Nest,Sc1,Rest1), skim(Rest1,Sc2,Rest2), skim(Rest2,Sc3,Rest3).
Nest = [[a, b, c], [1, 2, 3]],
Sc1 = [a, 1],
Rest1 = [[b, c], [2, 3]],
Sc2 = [b, 2],
Rest2 = [[c], [3]],
Sc3 = [c, 3],
Rest3 = [[], []].

?- Nest = [[a,b,c],[1,2,3]], skim(Nest,Sc1,Rest1), skim(Rest1,Sc2,Rest2), skim(Rest2,Sc3,Rest3), skim(Rest3,Sc4,Rest4).
false.
 current_call(+Goal)
 current_call(+Goal, +Else)
If Goal's predicate indicator is defined, call Goal. Otherwise, call Else, if in current_call/2, or fail if we are in current_call/1.
?- current_call( irrelevant(x) ).
false.
?- current_call( irrelevant(x), true ).
true.

% be cautious of auto_loading
?- current_call( member(X,[a,b,c]) ).
false.

?- member(X,[a,b,c]).
X = a ;
X = b ;
X = c.

?- current_call( member(X,[a,b,c]) ).
X = a ;
X = b ;
X = c.
author
- nicos angelopoulos
version
- 0.1 2014/9/14
- 0.2 2017/9/25
To be done
- interact with autoloading
 goal(+Partial, +ArgS, +Mod, -Goal)
Construct Goal from a partial or predicate name, either of which can be (column) :-prepended, and some arguments.
If Partial is not moduled, then Mod is :-prepended.
?- goal( p, x, u, G ).
G = u:p(x).

?- goal( a:p(t), x, u, G ).
G = a:p(t, x).

?- goal( a:b:p, x, u, G ).
false.
author
- nicos angelopoulos
version
- 0.1 2015/3/30
 goal_spec(+ModG, -ModSpec)
goal_spec(-ModG, +ModSpec)
Use functor/3 on possibly module prepended Goals and Specs.
 ?- goal_spec( data:data_file(x), Spec ).
 Spec = data:data_file/1.
 ?- goal_spec( data_file(y), Spec ).
 Spec = data_file/1.
 ?- goal_spec( G, data:data_file/1 ).
 G = data:data_file(_G1259).
author
- nicos angelopoulos
version
- 0.1 2014/9/14
 holds(+Goal, -Holds)
Goal is called deterministically with Holds = true iff Goal succeeds. Else, Holds = false.

Note that if Holds is instantiated, Goal will still be called, with holds/2 succeeding iff Holds corresponds to the right outcome from Goal.

?- holds( X=3, Holds ).
X = 3,
Holds = true.

?- holds( 4=3, Holds ).
Holds = false.

?- holds( member(X,[a,b]), Holds ).
X = a,
Holds = true.


?- holds( member(X,[a,b]), non_true ).
false.

?- holds( (write(x),nl), non_true ).
x
false.

?- holds( member(X,[a,b]), false ).
false.
author
- nicos angelopoulos
version
- 0.1 2015/12/9
- 0.2 2017/9/25, added mod_goal/2
 imported_from(+Clauser, +Mod)
Holds if Goal corresponding to Clauser (a goal or predicate identifier) and predicate_property/2 defines property imported_from(Mod).

Up to v0.2 this used to succeeed with =Moduser== if Clauser was not imported from anywhere.

author
- nicos angelopoulos
version
- 0.1 2017/02/22
- 0.2 2022/02/05, try user:Goal if failed on G
- 0.3 2022/11/19, remove success to user when not imported
 known(+Goal)
 known(+Goal, +Opts)
If call(Goal) fails, then an error is thrown (via pack_errors) saying that Tkn (usually the first arg of Goal) is not recognised as belonging to category Cat.

The main idea is to uniformly deal with failure when calling predicates for which the clause definitions expect a ground 1st argument.

This meta-predicate

  1. provides a uniform way of dealing with failure on ground 1st argument clauses
  2. avoids the creation of an intermediate predicate

Opts

category(Cat=values()
Cat should be of the form
values(Cat)
error shows Cat as the name, and the values of the first arg of Goal as the accepted values
'values()'
values of the first Tkn arg of Goal are
arbitrary_term
in which case is taken to be the category name
solutions(first)
set to all for backtracking
token(Tkn)
defaults to the first argument of Goal

Goal used to be called deterministically, version 0.3 made this non-det and 0.4 added an option to control this.

?- [user].
theme_background(colour, blue).
theme_background(monochrome, grey).
^D
?- known(theme_background(colour,Clr)).
Clr = blue.

?- known(theme_background(wrong,Clr)).
ERROR: user:theme_background/2: Token: wrong, is not a recognisable: value in [colour,monochromoe]

?- known(theme_background(wrong,Clr), colour_theme).
ERROR: user:theme_background/2: Token: wrong, is not a recognisable: colour_theme

?- known(theme_background(wrong,Clr), category(values(colour_theme))).
ERROR: user:theme_background/2: Token: wrong, is not a recognisable: colour_theme (values: [colour,monochrome])

?- known(theme_background(wrong,Clr), token(ex_token) ).
ERROR: user:theme_background/2: Token: ex_token, is not a recognisable: value in [colour,monochrome]
author
- nicos angelopoulos
version
- 0.1 2017/2/22
- 0.2 2019/7/25, Goal is now passed through mod_goal/2
- 0.3 2022/2/13, Allow module prepended Goal. Allow multi solution Goals (see os_file examples).
- 0.4 2023/1/02, interface change to /2 with options and solutions controlled via solutions(Sol)
 map_list_options(+Goal, ?InList, ?OutList, +Opts)
 map_list_options(+Goal, ?InList, +Opts)
An implementation of maplist/2,3 with Options. It addition to allowing Options to be passed to the map_list Goal, it also presents a common interface for maplist/2,3 and map_succ_list/3,4.

The predicate introduces the concept of direction. Are we generating InList from OutList or OutList from InList ? Currently this is done automatically and only affects Failed (see options). The direction might become more explicit with a new option (auto, left and right). Currently direction is right (generating InList from OutList) if Outlist is ground and InList is not, and left otherwise.

Opts

add_options(AddOpts=true)
false if do not wish to add Copts to call to Goal (AddOpts is passed through en_list/2)
call_options(Copts=[])
Options to pass to Goal (as last argument)
failed(Failed)
returns the list of failed elements (direction dependent)
on_fail(OnFail=skip)
If OnFail is fail, the whole predicate fails if Goal fails, error throws a ball
?- assert( (ex_mlo(No,Out,Opts) :- Out is No + 1, write( opts(Opts) ), nl) ).
?- map_list_options( ex_mlo, [1,2,3], Outs, call_options([a(b),b(c)]) ).
opts([a(b),b(c)])
opts([a(b),b(c)])
opts([a(b),b(c)])
Outs = [2, 3, 4]

?- assert( (plus_one(A,B) :- (var(A) -> B < 5, A is B - 1; A < 5, B is A + 1)) ).
true.

?- map_list_options( plus_one, [1,2,3], Out, [] ).
ERROR: Undefined procedure: plus_one/3
ERROR:   However, there are definitions for:
ERROR:         plus_one/2
...

?- map_list_options( plus_one, In, [2,3,4], add_options(false) ).
In = [1, 2, 3].

?- map_list_options( plus_one, In, [2,3,4,5], [add_options(false),on_fail(error)] ).
ERROR: Unhandled exception: failure_on_map_list_options_call(user:plus_one,_15236,5)

Emulate maplist/2,3

?- map_list_options( plus_one, [1,2,3,4,5], Out, [add_options(false),on_fail(fail)] ).
false.

?- map_list_options( plus_one, [1,2,3,4], Out, [add_options(false),on_fail(fail)] ).
Out = [2, 3, 4, 5].

Emulate map_succ_list/3,4

?- map_list_options( plus_one, [1,2,3,4,5], Out, [add_options(false),failed(Failures)] ).
Out = [2, 3, 4, 5],
Failures = [5].

?- map_list_options( plus_one, In, [1,2,3,4,6], [add_options(false),failed(Failures)] ).

?- map_succ_list( plus_one, In, [1,2,3,4,6], Rej ).
In = [0, 1, 2, 3],
Rej = [6].
author
- nicos angelopoulos
version
- 0.1 2016/5/23
- 0.2 2017/9/20, moved to stoics_lib, added example, pass Goal through mod_goal/4
- 0.3 2019/2/25, added error on failure, add_options(AddOpts), on_fail(OnFail), and moved call options to option call_options(Copts).
To be done
- pretty print the error message.
 map_succ_list(+Goal, ?InList, ?OutList)
 map_succ_list(+Goal, ?InList, ?OutList, -Rejects)
Apply Goal(In,Out) to InList, keeping in OutList all Out elements for calls that were successful. Also works for - InList, + OutList

Goal will be called in module user if it is not module-prepended.

?- map_succ_list( arg(2), [a(b),a(b,c),a(d,f)], Args ).
version
- 0:0:3, 2013/03/13
See also
- mod_goal/4
 mod_goal(+Mod, +Goal, -Moal, +Opts)
 mod_goal(+Mod, +Goal, -Moal)
mod_goal(-Mod, -Goal, +Moal)
 mod_goal(+Goal, -Moal)
Construct and deconstruct a goal and its module prepended form. When Mod is missing imported_from/2 is used to locate the module. If the latter fails, the module is set to user. Opts are passed to errors so real source can be reported.

Opts

override(OverR=false)
what to do when constructing over a Goal that already has a module prepention
false
ignores the new Mod
true
replaces Goal's prepention with Mod
error
reports the conflict

When de-constructing, Goal will be a goal with no module prepent. When constructing, Moal will be a module prepented goal

Incompatibility: 0.3 removed the mod_goal/4 version that had OverR as 3rd argument.

As of 0.4 imported_from/2 is used to find default module.

?- mod_goal( mod1, g1, MG ).
MG = mod1:g1.


?- mod_goal( M, G, mod2:g2(a,b,c) ).
M = mod2,
G = g2(a, b, c).

?- mod_goal( M, G, MG ).
ERROR: auxil:mod_goal/3: Ground argument expected either at: [1,2], or at: 3

?- mod_goal( m, k:g(a), MG ).
MG = k:g(a).

?- mod_goal( m, k:g(a), true, MG ).
MG = m:g(a).

?- mod_goal( g(a), MG ).
MG = user:g(a).

?- mod_goal( user, foo:bar(x), Moal, [override(false)] ).
Moal = foo:bar(x).

?- mod_goal( user, foo:bar(x), Moal, [override(true)] ).
Moal = user:bar(x).

?- mod_goal( user, foo:bar(x), Moal, [override(error)] ).
ERROR: stoics_lib:mod_goal/3: Module to fix-on: user differs from module attached in: foo:bar(x)
?- mod_goal( user, foo:bar(x), Moal, [override(error),caller:id/3] ).
ERROR: stoics_lib:mod_goal/3: Module to fix-on: user differs from module attached in: foo:bar(x)
ERROR: Trail: [caller:id/3]
author
- nicos angelopoulos
version
- 0.1 2014
- 0.2 2017/9/25, default value for Override changed to false, added mod_goal/2
- 0.3 2018/10/11, update error + options version, pushes trails to errorrs
- 0.4 2022/02/05, use imported_from/2 for locating default Mod
- 0.5 2022/11/19, when imported_from/2 fails, try predicate_property/2, currently with visible
 which(+Goal, +Term, -Indices)
Indices are those indexing Term elements which suceed when called on Goal. Works on lists and compound Terms.
 lib( odd/1 ).
 numlist( 1, 10, OneTen ),
 which( odd, OneTen, Indices ).

 OneTen = [1, 2, 3, 4, 5, 6, 7, 8, 9|...],
 Indices = [1, 3, 5, 7, 9].

 ?- numlist( 1, 11, Eleven ), Term =.. [t|Eleven], which( odd, Term, Is ).
 Eleven = [1, 2, 3, 4, 5, 6, 7, 8, 9|...],
 Term = t(1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11),
 Is = [1, 3, 5, 7, 9, 11].
 
author
- nicos angelopoulos
version
- 0.1 2014/7/2
- 0.2 2014/10/8 now uses position/3
See also
- R's which()
To be done
- implement ala library(apply)
 int_trailer(+Int, -Trailer)
Get the writen trailer for a positive integer.
?- int_trailer( 1, R ).
R = st.

?- int_trailer( 11, R ).
R = th.

?- int_trailer( 21, R ).
R = st.
author
- nicos angelopoulos
version
- 0.2 2016/12/11
 letter_strings(+Start, -N, -Letts)
Generate N letter strings, starting from Start. Start is polymorphic: string, code (integer) or atom.
?- letter_strings( a, 3, Letts ).
Letts = ["a", "b", "c"].

?- letter_strings( "C", 3, Letts ).
Letts = ["C", "D", "E"].
author
- nicos angelopoulos
version
- 0.1 2017/2/15
To be done
- check we do not over-run
 arity(?Term, ?Name, ?Arity)
 arity(?Term, ?Arity)
This is the permissive version, if we detect atomic we use functor/3 (the old stuff), otherwise we call compound_name_arity/3.
author
- nicos angelopoulos
version
- 0.1 2014/1/10
 functor_term(+Functor, -Term)
functor_term(-Functor, +Term)
Convert between a term and a Pname/Arity functor representation.
Can be used to make sure a list of terms is of certain (top) functor.
This predicate uses arity/3 rather than functor/3.
  ?- maplist( functor_term((-)/2), [a-b,c-d] ).
  true.
 ?- maplist( functor_term((-)/2), [a-b,c+d] ).
 false.

  ?- maplist( functor_term(term/0), [term,term()] ).
 true.
author
- nicos angelopoulos
version
- 0.1 2014/7/28
- 0.2 2018/1/8, tidy-up doc and added to lib(stoics_lib)
 compound(+Term, -Name, -Args)
Tries to deal with syntax changes that allow a() as a legal term.

Examples run on Swi.7

  compound( abc, Name, Args ).
  false.
  
  compound( abc(a,b,c), Name, Args ).
 Name = abc,
 Args = [a, b, c].
 
 compound( Term, abc, [a,b,c] ).
 Term = abc(a, b, c).
 
 compound( Term, abc, [] ).
 Term = abc().
author
- nicos angelopoulos
version
- 0.1 2014/1/10 (round about)
 en_list(+Term, -Listed)
en_list( +Term, -Listed, +Opts ).

Ensure that Term is either a list of things or a non-var term that is wrapped to a singleton list. If In is a variable a ball is thrown.

Opts are passed to error handlers.

 ?- en_list( x(y), Opts ).
 Opts = [x(y)].

 ?- en_list( [x,y], Opts ).
 Opts = [x, y].

 % assuming you have pack(pack_errors) installed:
 ?- en_list( X, L ).
 ERROR: stoics_lib:en_list/3: Ground argument expected at position: 1,  (found: _778)
 ?- en_list( X, L, bar/1 ).
 ERROR: stoics_lib:en_list/3: Ground argument expected at position: 1,  (found: _88)
 ERROR: Trail: [bar/1]
author
- nicos angelopoulos
version
- 0.2 2016/12/10
- 0.3 2018/10/12, added Opts and proper error via pack_errors
 op_compare(?Op, +Term1, +Term2)
Extends compare/3 on ground operators with all known operators. Also recognizes Op = (>:<) (ground only), which always succeeds.
?- op_compare( =<, 2, 3 ).
true.

?- op_compare( Op, 2, 3 ).
Op =  (<).

?- op_compare( >:<, 2, 3 ).
 portray_clauses(+List, +OptS)
Record a bunch of clauses to either a stream or a file. Supports append and write modes.

OptS can be a list or single option term from the following:

Opts

mode(Mode=append)
prepend, append or write; prepending (for now) reads old terms to memory
stream(Stream)
default is user_output
file(File)
if present, overwrites Stream.
write_opts(WOpts=[])
options to pass to portray_clause/3. when [] is given, portray_clause/2 is used.
?- portray_clauses( [a(b,c),b(d,e),c(f,g.t)], [] ).
a(b, c).
b(d, e).
c(f, g.t).
true.

?- File = 'test_prep.pl',
    portray_clauses( [b(3,4),c(5,6)], file(File) ),
    portray_clauses( [a(1,2)], [file(File),mode(prepend)] ),
    atom_concat( 'cat ', File, Cat ),
    shell( Cat ).

a(1, 2).
b(3, 4).
c(5, 6).
author
- nicos angelopoulos
version
- 0.1 2016/12/10
- 0.2 2018/12/10, removed some private code reference and added WOpts
- 0.3 2020/04/05, added mode(prepend)
 positions(+Data, -Dtype, -NofPositions)
 positions(+Data, -NofPositions)
Number of positions and data type for list/compound Data. If Data is a list NofPositions is the length. If Data is atomic the length is 1, and otherwise the number of positions is its arity. Dtype is correspondingly, list and compound.
   positions( [1,2,3,4], P ).
author
- nicos angelopoulos
version
- 0.1 2014/02/09
To be done
- allow for data() (see my compound preds).
 position(?N, +Data, ?Nth)
 position(+Type, ?N, +Data, ?Nth)
 position(+Type, ?N, +Data, ?Nth, -NxN, -Cont)
An experimental polymorphic predicate that works on Data that is one of, list, compound, number or atom. When atomic only position 1 is valid. Cont is the most efficient structure for continuing enumerating Data. In the case of lists, this is the list minus the Nth element and for everything else, Cont is unified to Data. NxN is the next counter for Cont, when Type is list, that is 1 until at the end of the list when it 0, else is N + 1. The main idea behind NxN and Cont is to provide support for iterators. The loop can end when NxN is equal to either 0 or to arity(Data).
 position( 2, [1,2,3], W ).
 position( 2, c(1,2,3), W ).
 position( compound, 2, c(1,2,3), W ).
 position( list, 2, c(1,2,3), W ).
 position( list, 2, c(1,2,3), W ).

?- position( list, 1, [1,2,3,4], Nth, NxN, Cont ).
author
- nicos angelopoulos
version
- 0.1 2014/02/09
- 0.2 2014/06/30 switch to term_type/2.
 position_nth(+N, +Data, -Nth)
 position_nth(+N, +Data, -Nth, -Rem)
 position_nth(+N, +Data, -Nth, -Rem, -Nxt)
 position_nth(+Dtype, +N, +Data, -Nth, -Rem, -Nxt)
Get Data's N position datum into Nth, with Rem being what is left of data and Nxt is the N identifier for the next to the right of Nth. Predicate expects that bounds are respected, else fails. Dtype is the datatype of Data, either list or compound which is determined by the predicate if missing.
   Data = [1,2,3,4,5],
   position_nth( list, 2, Data, Nth, Rem, Nxt ).
   position_nth( compound, 2, Data, Nth, Rem, Nxt ).
   position_nth( list, 1, Data, Nth, Rem, Nxt ).

?- maplist( position_nth(3), [c(1,2,3),c(4,5,6)], Thirds, Rem ).
Thirds = [3, 6],
Rem = [c(1, 2), c(4, 5)].
author
- nicos angelopoulos
version
- 0.2, 2014/02/27 changed from position_next
See also
- position/4 for an iterator assistant
 position_type(+Data, -Dtype)
Dtype is the determined datatype for Data. If atomic(Data) succeeds, Dtype is atomic. If Dtype is not a variable and it unifies [_|_], then Dtype unifies list, Otherwise, Dtype is compound.
 termplate(+Term, ?Arity, -Termplate)
 termplate(+Term, -Termplate)
Termplate has the same Arity and functor as Term, but all its arguments are unbound variables. Version 0.2 works for lists and atoms too.
 ?- termplate( t(a,b,c), Arity, Template ).
 Arity = 3,
 Template = t(_G6305, _G6306, _G6307).

 ?- termplate( [a,b,c], Arity, Template ).
 Arity = 3,
 Template = [_8920, _8926, _8932].
 
 ?- termplate( a, Arity, Template ).
 Arity = 0,
 Template = a.
 
 ?- termplate( A, Arity, Template ).
 ERROR: Arguments are not sufficiently instantiated
 ...
author
- nicos angelopoulos
version
- 0.1 2016/12/11
- 0.2 2017/10/04, allow Term to be a list or an atom, error handling for var Term
 locate(+File, +Exts, -Locations)
Find the exact Location of File that may have a number of extensions. This should become the standard way to interface locating of reading in files. Exts = any/*, is a special case where any file with matching extension is returned. This case is slower than the rest.

As of 0.2 only existing files are located. Predicate throws error if file does not exist.

  locate( xyw, abc, Loc ).
  ERROR: Unhandled exception: Cannot locate file with specification: xyw and extensions: abc
  
  
author
- nicos angelopoulos
version
- 0.2 2014/4/24
 compare(+Type, ?Op, +Term1, +Term2)
Common interface for compare/3 and compare_arithmetic/3, which also allows for meta calls. In this case Op is = iff call on call( Term2, Term1 ) succeeds, else it is <>. Type should be one of meta, term or arithmetic respectively.

>:< is a special Op, that is always true (under all interfaces)

 ?- compare( term, Op, 3, 3.0 ).
 ?- compare( arithmetic, Op, 3, 3.0 ).
 ?- compare( meta, Op, 3, =(3.0) ).
 Op = <> .
 ?- compare( meta, Op, 3, =:=(3.0)).
 Op =  (=).
 ?- compare( term, >:<, 3, 2 ).
 ?- compare( arithmetic, >:<, 3, 2 ).
author
- nicos angelopoulos
version
- 0.1 2014/2/16
- 0.2 2016/2/17, added special operator >:<
 compare_arithmetic(-Op, +X, +Y)
As compare, but using arithmetic operations.
 ?- compare( Op, 3, 3.0 ).
 Op = (>).
 
 ?- compare_arithmetic( Op, 3, 3.0 ).
 Op = (=).
author
- nicos angelopoulos
version
- 0.1 2014/2/16
 n_digits_min(+N, +Number, -Padded)
Padded is the atom coresponding to Number with the possible addition of leading 0s to pad the length to a minimum of legth = N.
 ?- n_digits_min( 2, 2, Atom ).
 Atom = '02'.
See also
- n_digits/3 for a procrustean version
 n_breaks(+Vector, +N, -Breaks, -Opts)
For a vector of values, create N break points.

The number of Breaks is always odd when Centre is true. This interprets odd N as the number of break points, even if N it is taken to be the number of intervals.

?- n_breaks( [1,3,4,4,5,5,6,8], 4, Bs, [] ).
Bs = [1.0, 2.75, 4.5, 6.25, 8.0].

?- n_breaks( [0.21,3,4,4,5,5,6,8], 4, Bs, [centre(1)] ).
Bs = [0.21, 0.4075, 0.605, 0.8025, 1.0, 2.75, 4.5, 6.25, 8.0].

?- n_breaks( [0.21,3,4,4,5,5,6,8], 4, Bs, [centre(1),fixed_width(true)] ).
Bs = [-6.0, -4.25, -2.5, -0.75, 1.0, 2.75, 4.5, 6.25, 8.0].

Opts

centre(Centre=false)
when an arithmetic value is given, the breaks are symmetrically split left and right of Centre
fixed_width(Sym=false)
if true and Centre arithmetic, the shorter of the left or right is extended to keep the breaks of fixed width
author
- nicos angelopoulos
version
- 0.1 2015/5/27
To be done
- add some polymorphism for Vector
 min_max(+List, -Min, -Max)
Find the minimum and the maximum elements of a list of numbers in one pass.
?- numlist(1,4,ToFour), min_max(ToFour,Min,Max).
Min = 1,
Max = 4.
author
- nicos angelopoulos
version
- 0.1 2014/5/7
- 0.2 2018/2/16, was max_min_list/3 (with switched outputs)
 nth1(?N, +List, ?With, ?Nth, +NewList)
Find and replace the N-th element of a List. The list with the element replaced is in NewList. Nth is the old value and With is the new one.
?- nth1( 3, [a,b,c,d], 3, What, New ).
What = c,
New = [a, b, 3, d].
author
- Nicos Angelopoulos
version
- 0.2 2011/?/?, 2005/02/23.
- 0.3 2017/3/13 renamed from nth_replace/5
 arg_add(?N, +Term, +ArgS, -New)
Add an Arg to the Nth position of Term, resulting in New.

N is an arithmetic expression (v.2). N can be a variable (v.3) in which case the length + 1 is returned and ArgS are appended at end.

ArgS can be a list of args (v.3).

?- arg_add( 2, x(4,3,1), 2, X ).
X = x(4, 2, 3, 1).

?- arg_add( L, x(1,2,3), [4,5], Five ).
Five = x(1, 2, 3, 4, 5).
author
- nicos angelopoulos
version
- 0.1 2016/10/28
- 0.2 2018/12/4, add expressions for N, added to stoics_lib
- 0.3 2022/12/21, Arg can be a list now and Nin a var. examples.
 arg(?N, +TermIn, +NewNth, ?Nth, -TermOut)
Find and replace nth arg in a term.
 ?- arg( 3, row(a,b,c), x, OldArg, Out ).
 OldArg = c,
 Out = row(a, b, x).

 ?- arg( N, row(a,b,c), x, c, Out ).
 N = 3,
 Out = row(a, b, x) ;
 false.
author
- Nicos Angelopoulos
version
- 0.1 2012/6/6
- 0.2 2019/1/8, use compound/3
See also
- nth1/5
 arg(+N, +TermIn, -Nth, -TermOut)
Extends arg/3 to an extra argument that returns TermIn without the N position argument.

As of version 0.2 N can also be a list of Ns. The list will first be sorted, and got rid off duplicates, before applied to finding the positions.

As of version 0.3 compound/3 instead of =.. is used.

?- arg( 3, a(1,2,3,4), Three, Term ).
Three = 3,
Term = a(1, 2, 4).

?- maplist( arg(2), [t(1,2,3),t(4,5,6),t(7,8,9)], Args, Terms ).
Args = [2, 5, 8],
Terms = [t(1, 3), t(4, 6), t(7, 9)].

?- arg( [1,3], a(x,y,z,w), Nths, Rem ).
Nths = [x, z],
Rem = a(y, w).

?- arg( [1,3,2,1], a(x,y,z,w), Nths, Rem ).
Nths = [x, z, y, x],
Rem = a(w).
author
- nicos angelopoulos
version
- 0.1 2016/6/15
- 0.2 2018/4/27, first argument can now be a list.
See also
- nth1/4
 maparg(+Pname, ?Term1)
 maparg(+Pname, ?Term1, ?Term2)
 maparg(+Pname, +Npos, ?Term1, ?Term2)
Call Pname on all paired Term1 and Term2 arguments. When Npos is present it should be an integer I: [-1,0,1,2]. -1 stands for not inclusions of the argument (default). Npos is the position at which the index of the argument can be added to the call/3.
?- maparg( number, row(1,2,3) ).
true.

?- assert( times(X,Y,Product) :- Product is X * Y).
?- maparg( times(2), c(1,2,3), Term ).
Term = c(2, 4, 6).

?- assert( times3(X,Y,Z,Product) :- Product is X * Y * Z).
?- maparg( times3(2), 1, c(1,2,3), Term ).
Term = c(2, 8, 18).

?- maparg( times(2), -1, c(1,2,3), Term ).
Term = c(2, 4, 6).

The last example adds indices: 1, 2 and 3 to the 3 calls to times3, thus the call can be informed of the positional context of the element.

author
- nicos angelopoulos
version
- 0.2 2014/3/5, added Npos
- 0.3 2014/4/3, added maparg/2
- 0.4 2017/9/25, pass meta-goals through mod_goal/2
 atom_replace(+Atom, +What, +With, -New)
Replace all occurances of What in Atom with With to produce New.
 io_sections(+File, -Sections, +Opts)
Read a file to a list of Sections. In vanilla operation, each section is a list of the codes read-in. Each section is delimited by a marker line.

Opts

include_separator(Inc=false)
whether to include to the separating line. (Terminator, is never retruned.) See example 2.
process(Pgoal=(=))
Goal to process the Sections before storing.
process_opts(Popts=false)
else pass Sopts to processor Pgoal (as last arg)
separator_call(SepCall)
if given it is used to separate sections, called with 1 argument: the current line. If the call succeeds, the line is considered to be a separator line. See example 3.
separator_id(Sid=false)
if true SepCall is called with an extra argument which is used to create SectionId-Section pairlists of sections
separator(Sep=[92])
section separating line, used if SepCall is not present (back compatibility, this is now define as sep_call(==(Line))
terminating_separator(Tmn=true)
whether a terminating separator is required at end of file
 ?- write('example 1'), nl.
 ?- io_sections( pack('stoics_lib/examples/sectioned.txt'), Sects, separator(`[term]`) ).
 Sects = [[[97], [98]], [[99], [100]]].

 ?- write('example 2'), nl.
 ?- o_sections( pack('stoics_lib/examples/sectioned.txt'), Sects, [separator(`[term]`),include_separator(true)] ).
    Sects = [[[91, 116, 101, 114, 109, 93], [97], [98]], [[91, 116, 101, 114, 109, 93], [99], [100]]].


 ?- write('example 3'), nl.
 ?- assert(

 ?- write('private example'), nl.
 ?- cd( '/usr/local/users/nicos/work/2015/15.10.05-lmtk3_substrates' ).
 ?- io_sections( 'uniprot_sprot.dat', Sects, process(length) ).
author
- nicos angelopoulos
version
- 0.1 2015/10/05
- 0.2 2016/02/04
- 0.3 2021/02/04, added include_separator(Inc), examples, pass file through absolute_file_name/2
 on_fail(+Goal, +Call)
 on_fail(+Goal, +Call, +Opts)
If Goal fails or exceptions (where exception is catched by Catcher, see Opts), then Call is called. The predicate in these cases might report the incident on the std output depending on the value of option rep(Rep).

Currently the predicate does not protect the call to Call. This is likely to change.

Opts

catch(Catcher)
free var by default (catches everything) user can pass something more specific
mtype(Mtype=informational)
type of message, also: warning or error (see message_report/3)
rep(Rep=exception)
alternatively: failure, true/both/all or none/false
rethrow(Rethrow=true)
whether to rethrow the exception (after calling Call).
?- on_fail( none, true ).
% While calling: none/0, caught exception: error(existence_error(procedure,stoics_lib:none/0),context(system:catch/3,_1530)), now calling: true/0
ERROR ...
...

?- on_fail( none, true, rethrow(false) ).
% While calling: none/0, caught exception: error(existence_error(procedure,stoics_lib:none/0),context(system:catch/3,_4114)), now calling: true/0
true.

?- on_fail( none, true, [rep(false),rethrow(false)] ).
true

?- on_fail( none, true, [rep(exception),rethrow(false)] ).
% While calling: none/0, caught exception: error(existence_error(procedure,stoics_lib:none/0),context(system:catch/3,_9454)), now calling: true/0
true.

?- on_fail( fail, true, [rep(exception),rethrow(false)] ).
true.

?- on_fail( fail, true, rep(both)  ).
% Call to fail/0, failed, calling: true/0
true.
author
- nicos angelopoulos
version
- 0.1 2017/08/11, lil'B
 on_call(+OnB, +Call, +ArgIn, -ArgOut)
A generic caller of Call iff OnB is true.
The call incorporates as its two last args ArgIn and ArgOut.
The predicate provides a simple way to control via an option (pack(options)) the call of a predicate on partial results.
typically that is on the elements of an output list.
?- assert( to_integer(Num,Int) :- Int is integer(Num) ).
?- on_call( true, to_integer, 3.0, Three ).
Three = 3.
author
- nicos angelopoulos
version
- 0.1
To be done
- add a on_call(Args,Body) option to options_append/4 that asserts temp preds (and means to clean them afterwards).
 term_length(+Term, -Length)
Return the length of the term.
For atoms and numbers, the length is the length of the codes list that
comprise the atomic term.
Variables and dicts (for now) are of length 0.
?- term_length( [a,b,c], L ).
?- term_length( x(a,b,c), L ).
?- St = "abc", string( St ), term_length( St, L ).
?- term_length( abc, L ).
?- term_length( 123, L ).
L = 3.

?- term_length( X, L ).
L = 0.
author
- nicos angelopoulos
version
- 0.1 2017/11/21
See also
- lib(term_type).
 curtail(+Term, +Max, -Curtailed)
Chop Term to a possible maximum of Max (>0) length.
If Term is shorter, Curtail is unified to Term and the call succeeds.
?- curtail( [a,b,c], 2, L ).
L = [a, b].
?- curtail( x(a,b,c), 2, C ).
C = x(a, b).
?- curtail( X, 2, V ).
X = V.
?- curtail( abc, 0, V ).
false.
?- curtail( abc, 2, V ).
V = ab.
author
- nicos angelopous
version
- 0.1 2017/11/21
 term_type(+Term, -Type)
Type is the type of Term. One of: var, list, compound, string, dict, number(_integer_), number(_float_), number(rational) and atom.

Top: document the order

 ?- term_type( [a,b,c], Type ).
 Type = list.
  
 ?- term_type( a(b), Type ).
 Type = compound.
author
- nicos angelopoulos
version
- 0.1 2017/11/21, copy from pack(term_type) % which is currently private
To be done
- implement in C ? (if it is faster...)
 en_append(+ListOr1, +ListOr2, -List)
Enlists (en_list/2) ListOr1 and 2 before appending them.
άμπελος;src/term% lib stoics_lib
%  /home/na11/.rcpl compiled 0.00 sec, 8 clauses
?- en_append( a, b, C ).
C = [a, b].

?- en_append( a, [b], C ).
C = [a, b].
author
- nicos angelopoulos
version
- 0.1 2017/01/03
 url_file(+Url, ?File)
 url_file(+Url, ?File, +Opts)
Get the remote file pointed to by Url to local File.
When File is an unbound variable, place the download into downloads(Base), if downloads is a known file alias,
or as Base in local directory, and return the used file in File. Base is taken as the file_base_name/2 of Url.

The predicate's progress can be be looked into, by ?- debug(url_file).

The main download code is a copy-paste from SWI's library(prolog_pack) file.

Opts

dnt(Dnt=false)
if true, create a File.dnt with the start and end datime/6 stamps.
iface(Iface=prolog)
or wget
overwrite(Ow=error)
default throws an error if file exists, fail or false for failure and anything else for business as usual (overwrite local)
 ?- file_search_path( downloads, Dnloads ).
 Dnloads = '/usr/local/users/nicos/local/dnloads'.

 ?- url_file( 'http://stoics.org.uk/~nicos/index.html', File ).
 File = '/usr/local/users/na11/local/dnloads/index.html'.

 ?- debug( url_file ).
 ?- url_file('ftp://ftp.ncbi.nih.gov/gene/DATA/gene2ensembl.gz').
 Downloading URL: 'ftp://ftp.ncbi.nih.gov/gene/DATA/gene2ensembl.gz', onto file: '/usr/local/users/nicos/local/dnloads/gene2ensembl.gz'
 ?- ls( '/usr/local/users/nicos/local/dnloads/' ).
 ...
 gene2ensembl.gz
 ...

 ?- retractall(  user:file_search_path( downloads, Dn ) ).
 true.
 ?- url_file( 'http://stoics.org.uk/~nicos/index.html', File ).
 File = index.html.
 ?- ls.
 .... index.html ....
author
- nicos angelopoulos
version
- 0.1 2014/07/23
- 0.2 2015/11/24 added option overwrite/1
- 0.3 2018/03/13, removed url_file/1 but url_file/2 allows -File, moved to pack(stoics_lib)
 call_morph(+Term, +Input, -Morphed, +Opts)
If Term/+2 is a defined predicate, then it is called on Input and Morphed; else Morphed is unified to Term. The latter is also the case, if the call fails. Opts are passed to mod_call/4.

The main perceived use case is for enabling options that either transform another option or pass a static value. For instance to create output file stems from input filenames.

?- use_module(library(lib)).
?- lib(os_lib).
?- assert( (to_stem(File,Stem) :- os_ext(Ext,Stem,File)) ).
?- call_morph( to_stem, input.txt, Stem, true ).
Stem = input.
?- call_morph( static_stem, input.txt, Stem, true ).
Stem = static_stem.
author
- nicos angelopoulos
version
- 0.1 2019/2/22
 io_streams(?In, ?Out, ?Error)
Generalises set_prolog_IO/3 with enquiry mode.

Modes can be mixed, eg:

?-
   io_streams( In, user_output, Error1 ),
   io_streams( In, Out, Error2 ).

In = <stream>(0x7fdc8665e780),
Error1 = Error2, Error2 = <stream>(0x7fdc8665e980),
Out = <stream>(0x7fdc8665e880).
author
- nicos angelopoulos
version
- 0:1 2020/9/15
 lexi(?Lexi, ?CodeOr)
Convert any Lexi-cographical object to codes or other shaped form.

If CodeOr is a variable then Lexi is casted to codes.

Casts- mostly for Lexi, but work on CodesOr, if you are so inclined.

+ Lex
casts to atoms
&(Lex)
casts to strings
- Lex
casts to codes
#(Lex)
casts to number

This is a subset to os_lib casts, although here we also use code lists (something that should be propagated to os_lib).

?- lexi('Bone Marrow',Codes).
Codes = [66, 111, 110, 101, 32, 77, 97, 114, 114|...].

?- atom_codes('Bone Marrow',Codes),lexi(+Atom,Codes).
Codes = [66, 111, 110, 101, 32, 77, 97, 114, 114|...],
Atom = 'Bone Marrow'.

?- atom_codes('Peripheral Blood',Codes),lexi(&String,Codes).
Codes = [80, 101, 114, 105, 112, 104, 101, 114, 97|...],
String = "Peripheral Blood".

?- lexi( `Peripheral Blood`, &String ).
String = "Peripheral Blood".

?- atom_codes('Peripheral Blood',Codes),lexi(-Lex,Codes).
Codes = Lex, Lex = [80, 101, 114, 105, 112, 104, 101, 114, 97|...].

?- lexi( 123, Codes ).
Codes = [49, 50, 51].

?- lexi( 123, &String ).
String = "123".

?- lexi(a(term),Codes).

?- lexi(a(term),+Atom).
Atom = 'a(term)'.

?- lexi("Bone Marrow",Codes).
Codes = [66, 111, 110, 101, 32, 77, 97, 114, 114|...].

?- lexi("Bone Marrow",&String).
String = "Bone Marrow".
author
- nicos angelopoulos
version
- 0.1 2022/10/15
See also
- lexi_n/4
- has_cased/3
 has_cased(+Object, +Case, -Cased)
Polymorphic Object has cased subparts of case, Case, that is returned in Cased.

Predicate is polymorphic in Object: string, atom, number, term or codes. By default Cased is returned as a list of codes, however, other forms can be asked for using the shape grammar of lexi/2.

Case can be one of up or upper and down, low or lower and digit. Alternatively, Case can be a list of types recognised by code_type/2, in which case Cased contains all codes/text that satisfy at least one of the given Case types.

?- has_cased( 'Bone Marrow', up, UpCased ).
UpCased = [66, 77].

?- has_cased( 'Bone Marrow', up, +UpCased ).
UpCased = 'BM'.

?- has_cased( "Bone Marrow", down, +DwCased ).
DwCased = onearrow.

?- has_cased( 123, down, +DwCased ).
DwCased = ''.

?- has_cased( 123, digit, DwCased ).
DwCased = [49, 50, 51].

?- has_cased( 123, digit, #(DwCased) ).
DwCased = 123.

?- has_cased( "Bone Marrow", [lower,space], +DwCased ).
DwCased = 'one arrow'.

?- has_cased( "Bone Marrow", towards, +DwCased ).
ERROR: stoics_lib:stoics_lib:has_cased_codes/3: Token: towards, is not a recognisable: value in [upper,up,down,low,lower,digit]
author
- nicos angelopoulos
version
- 0.1 2022/10/15
See also
- lexi/2
 latex_colour(?FullName, -HexString, ?CodingName, -RGBterm)
This is a prolog facts base of the site latexolor.com .
?- latex_colour( _, Hex, apricot, RGB ).
Hex = "#FBCEB1",
RGB = rgb(0.98, 0.81, 0.69).
author
- nicos angelopoulos
version
- 0.1 2022/12/16
See also
- colour_hex/2
- https://latexcolor.com/
- http://en.wikipedia.org/wiki/List_of_colors
license
- Creative Commons (see links above).
 colour_hex(+Clr, -Hex)
Convert lexical input Clr to a hex string.

Clr is passed through lexi/2.

Currently passes through any represeantion of a hex and maps the long or code names from latex_colour/4 (1st and 3rd argument to second argument).

?- colour_hex( amber, Hex ).
Hex = "#FFBF00".

?- colour_hex( amberic, Hex ).
ERROR: colour_hex/2: Cannot find colour: amberic
false.

?- colour_hex( '#FFBB00', Hex ).
Hex = "#FFBB00".

?- colour_hex( '#FFBB00wrong', Hex ).
Hex = "#FFBB00wrong".
author
- nicos angelopoulos
version
- 0.1 2022/12/16
See also
- bio_volcano_plot/1
- lexi/2
To be done
- do some basic checks if a Hex is given
 lexi_n(+InLexi, +N, ?PadC, -Lexi)
Lexi is of length N lexical object containing either the last N codes of InLexi or all of InLexi left-padded by PadCs, to make its codes representation up to length N.

By default Lexi is returned as a list of codes but the result can be term shaped, as per lexi/2.

PadC will not be touched if length(InLexi) >= N. It should be a character code, but it can also be a singleton list, an atom of length 1 or a string of length 1. If it is a variable, it is bound to 0'0 if InLexi can be interpreted as a number and to 0' , (space) otherwise.

?- lexi_n( `2`, 3, 0'0, Codes ), atom_codes( Atom, Codes ).
Codes = [48, 48, 50],
Atom = '002'.

?- lexi_n( `2`, 3, 0'0, + Atom ).
Atom = '002'.

?- lexi_n( `text`, 8, 0' , Codes ), atom_codes( Atom, Codes ).
Codes = [32, 32, 32, 32, 116, 101, 120, 116],
Atom = '    text'.

?- lexi_n( `text`, 8, 0' , + Atom ).
Atom = '    text'.

?- lexi_n( 123, 8, PadC, + Atom ).
PadC = 48,
Atom = '00000123'.

?- lexi_n( `123`, 8, PadC, + Atom ).
PadC = 48,
Atom = '00000123'.

?- lexi_n( "123", 8, PadC, + Atom ).
PadC = 48,
Atom = '00000123'.

?- lexi_n( `123`, 8, '9', + Atom ).
Atom = '99999123'.

?- lexi_n( `2`, 3, 0'0,  & Atom ).
Atom = "002".
author
- nicos angelopoulos
version
- 0.1 2014/03/17
- 0.2 2022/11/06, this used to be codes_n_digits/3.
- 0.3 2023/01/02, allow PadC to be versatile + doc fixes
See also
- lexi/2
- n_digits_integer_codes/3

Undocumented predicates

The following predicates are exported, but not or incorrectly documented.

 en_list(Arg1, Arg2, Arg3)
 list_proportions(Arg1, Arg2)