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:0:0, V = date(2018,3,18).
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: :
? atom_sub( abc, xabcd ). true ; false.
?- 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 )
.
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, 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: :
?- codes_n_digits( '2', 3, Codes ), atom_codes( Atom, Codes ). Codes = [48, 48, 50], Atom = '002'.
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( Readable ). Readable = 'At 15:13:36 on 2nd of Jul 2014'.
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'.
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 exapnd_file_name/2 for Atomic FileSpec but it also works on termed and aliaed args (abc/def.pl
andabc(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'.
?- 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.
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 ).
?- 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].
?- 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
?- 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.
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)].
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( 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).
Goal is called deterministically withHolds = 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)
, else
Mod is user.
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
if Cat should either be atomic (a description of the category expected for Tkn), In addition it can be of the form
values(Cat)
values of the first Tkn arg of Goal are appended to Catvaluess()
values of the first Tkn arg of Coal become Cat
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])
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 ).
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 = k:g(a). ?- mod_goal( m, k:g(a), true, MG ). MG = m:g(a). ?- mod_goal( g(a), MG ). MG = user:g(a).
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.
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().
?- 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(_))
?- op_compare( =<, 2, 3 ). true. ?- op_compare( Op, 2, 3 ). Op = (<). ?- op_compare( >:<, 2, 3 ).
Opts
pack(by_unix)
is present File will be
passed through by_unix_term_to_serial/2 before passed to open/3positions( [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].
arg( N, row(a,b,c), 3, c, Out ). N = 3, Out = row(a, b, 3) ; false.
?- 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)].
?- 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))
?- cd( '/usr/local/users/nicos/work/2015/15.10.05-lmtk3_substrates' ). ?- io_sections( 'uniprot_sprot.dat', Sects, process(length) ).
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
?- 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.
?- 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
?- 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 following predicates are exported, but not or incorrectly documented.