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.
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].
?- 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].
date(Year,Month,Day)
.
?- stoics_lib_version( -V, -D ). D = 1:8:0, V = date(2024,4,5).
?- 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: :
As of version v0.2, Part can be a term:
? atom_sub( abc, xabcd ). true ; false. ? atom_sub( pfx(x), xabcd ). true.
?- directory_files( '.', All ), exclude( prefix_atom('.'), All, Adots ). All = ['.claws_cache', '.', '.mh_sequences', '541', .., '.claws_mark'], Adots = ['541'].
?- directory_files( '.', All ), map_succ_list( prefix_atom('.'), All, DotPsfxs ).
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.
?- 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: :
?- 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( Readable ). Readable = 'At 15:13:36 on 2nd of Jul 2014'.
?- 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'.
get_time(Stamp), stamp_date_time(Dtime).
CurrDatime should be a date_time/1 term.
SWI specific. Check YAP.
?- get_datetime( Dime ). Dime = datetime(2016, 12, 2, 10, 42, 26).
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
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'.
?- 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.
?- maplist( atom_codes, [abc,edf,xyz], Lines ), io_lines( test_out.txt, Lines ).
?- kv_compose( [a,b,c], [1,2,3], Kvs ).
?- kv_decompose( [a-1,b-2,c-3], Ks, Vs ). Ks = [a, b, c], Vs = [1, 2, 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].
Examples
?- kv_transpose( [a-3,b-5], Trans ). Trans = [3-a, 5-b].
?- 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].
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.
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.
?- break_on_list( [a,b,c,d], [b,c], L, R ). L = [a], R = [d].
?- 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( 2, a, [a,b,c,a] ). true. ?- has_at_least( 2, b, [a,b,c,a] ). false.
?- has_at_most( 1, a, [a,b,c,a] ). false. ?- has_at_most( 1, b, [a,b,c,a] ). true.
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)
Opts
false
atom,\br
it should be predicate name that produces a bin name for the element.?- list_frequency( [c,a,b,b,a,b,c,d], Freqs ). Freqs = [c-2, a-2, b-3, d-1]. ?- list_frequency( [c,a,b,b,a,b,c,d], Freqs, order(true) ). [a-2, b-3, c-2, d-1]. ?- list_frequency( [c,a,b,b,a,b,c,d], Freqs, order(freq) ). Freqs = [b-3, a-2, c-2, d-1]. ?- list_frequency( [c,a,b,b,a,b,c,d], Freqs, [order(freq),transpose(true)] ). Freqs = [3-b, 2-a, 2-c, 1-d]. ?- list_frequency( [c,a,b,b,a,b,c,d], Freqs, transpose(true) ). Freqs = [2-c, 2-a, 3-b, 1-d]. ?- 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.
Opts
r(Min,Max)
) that are assumed to be the min and values of list 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].
?- 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]].
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)].
select_all( List, Elem, [H|_], Rem )
, H = Elem.
?- select_first( [dbg(t),dbg(f),etc(x)], dbg(W), Rem ). W = t, Rem = [etc(x)].
?- 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( 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.
?- 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.
?- 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).
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.
imported_from(Mod)
.
Up to v0.2 this used to succeeed with =Mod
user== if Clauser was not imported from anywhere.
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
Opts
all
for backtrackingGoal 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]
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
?- 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].
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 ).
Opts
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]
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].
?- int_trailer( 1, R ). R = st. ?- int_trailer( 11, R ). R = th. ?- int_trailer( 21, R ). R = st.
?- letter_strings( a, 3, Letts ). Letts = ["a", "b", "c"]. ?- letter_strings( "C", 3, Letts ). Letts = ["C", "D", "E"].
?- 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.
v0.2 allows atomic Term, which breaks backward compatibility (previously these will fail).
Examples
?- compound( abc, Name, Args ). Name = abc, Args = []. ?- 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().
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]
?- op_compare( =<, 2, 3 ). true. ?- op_compare( Op, 2, 3 ). Op = (<). ?- op_compare( >:<, 2, 3 ).
OptS can be a list or single option term from the following:
Opts
?- 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).
positions( [1,2,3,4], P ).
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 ).
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)].
atomic(Data)
succeeds, Dtype is atomic.
If Dtype is not a variable and it unifies [_|_],
then Dtype unifies list, Otherwise,
Dtype is compound.?- 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 ...
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
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 ).
?- compare( Op, 3, 3.0 ). Op = (>). ?- compare_arithmetic( Op, 3, 3.0 ). Op = (=).
?- n_digits_min( 2, 2, Atom ). Atom = '02'.
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
?- numlist(1,4,ToFour), min_max(ToFour,Min,Max). Min = 1, Max = 4.
?- nth1( 3, [a,b,c,d], 3, What, New ). What = c, New = [a, b, 3, d].
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). ?- arg_add( 3, a(a,b,d,e), c, New ). New = a(a, b, c, d, e). ?- arg_add( -3, a(a,b,d,e), c, New ). New = a(a, b, c, d, e).
?- 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.
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).
?- 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.
Opts
sep_call(==(Line))
?- 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) ).
rep(Rep)
.
Currently the predicate does not protect the call to Call. This is likely to change.
Opts
?- 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.
pack(options)
)
the call of a predicate on partial results. ?- assert( to_integer(Num,Int) :- Int is integer(Num) ). ?- on_call( true, to_integer, 3.0, Three ). Three = 3.
?- 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.
?- 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.
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.
άμÏελοÏ;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].
downloads(Base)
, if downloads is a known file alias,
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
wget
?- 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 ....
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.
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).
If CodeOr is a variable then Lexi is casted to codes.
Casts- mostly for Lexi, but work on CodesOr, if you are so inclined.
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".
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]
?- latex_colour( _, Hex, apricot, RGB ). Hex = "#FBCEB1", RGB = rgb(0.98, 0.81, 0.69).
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".
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".
The following predicates are exported, but not or incorrectly documented.