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
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 = 0:5:0,
V = date(2017,8,15).
 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.
 ? atom_sub( abc, xabcd ).
 true ;
 false.
author
- nicos angelopoulos
version
- 0.1 2013/12/19
 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 ).

Succeds multiple times. for +Full, +Part.

See also atom_sub/2.

 ?- 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, ?Pre, ?Post, ?Part)
 ?- 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)
 codes_n_digits(+InCodes, +N, Codes)
Codes is of length N and contains either the last N digits of InCodes or all codes of Numb left-padded by 0s to make its codes representation up to N (see n_digits_integer_codes/3).
?- codes_n_digits( '2', 3, Codes ), atom_codes( Atom, Codes ).
Codes = [48, 48, 50],
Atom = '002'.
author
- nicos angelopoulos
version
- 0.1 2014/03/17
 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 a simple
Similar to exapnd_file_name/2 for Atomic FileSpec but it also works on termed and aliaed args (abc/def.pl and abc(def.pl) respectively).
?- expand_spec( '$HOME', Home ).
Home = '/home/na11'

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

?- expand_spec( pack(real), Exp ).
Exp = '/home/na11/lib/swipl/pack/real' ;
Exp = '/usr/local/users/na11/local/git/lib/swipl-7.5.1/pack/real'.
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
 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
 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

order(Ord=false)
order of results: elem 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 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].

NOTE: arguments changed bewteen 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
 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

:- ensure_loaded( library(terms) ).

 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.
 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
To be done
- interact with autoloading
 goal(+Partial, +ArgS, +Mod, -Goal)
Construct Goal from a partial or predicate name either of which might be moded and some arguments. If none of these is moded, Mod is used.
?- 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
 imported_from(+Clauser, +Mod)
Holds if Goal corresponding to Clauser (a goal or predicate identifier) hs predicate_property/2 defined property imported_from(Mod), else Mod is user.
author
- nicos angelopoulos
version
- 0.1 2017/2/22
 known(+Goal)
 known(+Goal, +Cat)
 known(+Goal, +Tkn, +Cat)
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 idea is that Goal is a predicate whose 1st argument indexes a number of options and this wrapper provides
  1. a uniform way of dealing with failure
  2. a away to avoid creating an intermediate predicate
if Cat should either be atomic (a description of the category expected for Tkn), In addition it can be of the form
If Tkn is missing is taken to be the first arg of Goal. If category is missing it is taken to be values().
Goal will call with a cut after it is invocations so it will only be allowed to succeed once.
?- [user]
theme_background( colour, blue ).
theme_background( monochromoe, 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), values(colour_theme) ).
ERROR: user:theme_background/2: Token: wrong, is not a recognisable: colour_theme (values: [colour,monochromoe])
author
- nicos angelopoulos
version
- 0.1 2017/2/22
 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, +Override, -Moal)
 mod_goal(+Mod, +Goal, -Moal)
mod_goal(-Mod, -Goal, +Moal)
Construct and deconstruct a goal and its module prepended form. Argument Override, controls what happends when constructing over a Goal that already has a module prepention: false ignores the new Mod, true (default) replaces Goal's prepention with Mod and 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

?- 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 = m:g(a).

?- mod_goal( m, k:g(a), false, MG ).
MG = k:g(a).
author
- nicos angelopoulos
version
- 0.1 2014
 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
 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)
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.
 ?- en_list( x(y), Opts ).
 Opts = [x(y)].

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

 ?- en_list( X, Opts ).
 ERROR: Unhandled exception: en_list(encoutered_variable_in_1st_arg(_))
author
- nicos angelopoulos
version
- 0.2 2016/12/10
 portray_clauses(+List, +OptS)
Record a bunch of clauses to either a stream or file. Supports append and write modes. OptS can be a list or single option term from the following:

Opts

mode(Mode=append)
append or write
stream(Stream)
default is user_output
file(File)
if present, overwrites Stream. if pack(by_unix) is present File will be passed through by_unix_term_to_serial/2 before passed to open/3

@author nicos angelopoulos @verison 0.1 2016/12/10, modified for public release

 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.
 termplate( t(a,b,c), Arity, Template ).
 Arity = 3,
 Template = t(_G6305, _G6306, _G6307).
author
- nicos angelopoulos
version
- 0.1 2016/12/11
 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
 max_min_list(+List, -Max, -Min)
Find the maximum and the minimum of a list of numbers in one pass.
author
- nicos angelopoulos
version
- 0.1 2014/5/7
 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(?N, +TermIn, +NewNth, ?Nth, -TermOut)
Find and replace nth arg in a term.
 arg( N, row(a,b,c), 3, c, Out ).

 N = 3,
 Out = row(a, b, 3) ;
 false.
 
author
- Nicos Angelopoulos
version
- 0.1 2012/06/06
See also
- nth1/5
 arg(+N, +TermIn, -Nth, -TermOut)
Extends arg/3 to an extra argument that returns TermIn without the N position argument.
?- 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)].
author
- nicos angelopoulos
version
- 0.1 2016/6/15
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 =< 1 =< 2. -1 stands for not inclusions of the argument (default). Npos is the position at which the location 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).

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
 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

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
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
 ?- 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
 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