mtx.pl -- Working with data matrices

This is a library for working with data matrices, taking off from where library(csv) ends.
The library will hopefully grow to become useful tool for logic programming based data science.

In theory the library supports polymorphic representations of matrices, but in its current form is best to assume that the canonical form (see mtx/1) is the only one supported.
The library should be considered as still in developmental flux.

License: MIT.

Input/Output:

At the very least library(mtx) can be viewed as an addition/enhancement io of matrices to files via mtx/2.
The library can interrogate the data/ subdirectory of all installed packs for csv files using alias data.<br>

?- mtx( data(mtcars), Mtcars ).
Mtcars = [row(mpg, cyl, disp, hp, ....

Where mtcars.csv is in some pack's data directory.

?- mtx_data( mtcars, Mtcars ).
Mtx = [row(mpg, cyl, disp, hp, ....

Where mtcars.csv is in pack(mtx) data subdirectory.

mtx/2 works both as input and output.<br>

If 2nd argument is ground, mtx/2 with output the 2nd argument to the file pointed by the 1st.
Else, the 1st argument is inputed to the 2nd argument in standard form.

?- tmp_file( mtc, TmpF ), mtx( pack('mtx/data/mtcars'), Mtc ), mtx( TmpF, Mtc ).
TmpF = '/tmp/pl_mtc_14092_0',
Mtc = [row(mpg, cyl,

The first call to mtx/2 above, inputs the test csv mtcars.csv, to Mtc (instantiated to list of rows).
The second call, outputs Mtc to the temporary file TmpF.

mtx/3 provides a couple of options on top of csv_read_file/3 and csv_write_file/3.
sep(Sep) is short for separator, that also understands comma, tab and space (see mtx_sep/2). match(Match) is short for match_arity(Match)

?- mtx( data(mtcars), Mtcars, sep(comma) ).
Mtcars = [row(mpg, cyl, disp, hp, ....)|...]

Good places to start:

Notes for developers

Variable naming conventions

If a predicate definition has both Cnm and Cps define them in that order.

Options

has_header(HasH=true)
false, indicates columns do not have header
apply_on(AppOn=whole)
for predicate calling on columns or rows, which part to use: whole, head or body

Good starting points are the documentation for mtx/1, mtx/2 and mtx/3.

author
- nicos angelopoulos
version
- 0.6 2021/6/17, option:row_call(RowC)
- 0.5 2020/3/17, work-around SWI broken back-compatibility (std aliases)
- 0.4 2019/4/22
- 0.3 2019/4/18
- 0.1 2018/4/2 first public version
See also
- web-page: http://stoics.org.uk/~nicos/sware/mtx
- doc: http://stoics.org.uk/~nicos/sware/mtx/doc/html/mtx.html
- source: http://stoics.org.uk/~nicos/sware/packs/mtx/
- github: https://github.com/nicos-angelopoulos/mtx
license
- MIT
To be done
- add more debug(mtx(Pred)) messages (see src/mtx.pl for a start on this)
 mtx(+Mtx)
True iff Mtx is a valid representation of a matrix.

This is a synonym for mtx(Mtx, _Canonical). Cite this predicate for valid input representations of Mtx variables.

Valid representations are (see mtx_type/2):

atomic
where the atom corresponds to a predicate name and the predicate with arity N is defined to succeeds with the returned argument instantiated to a list
csv_file_or_its_stem
as possible to be read by csv_read_file/2 alias paths and normal delimited file extension can be ommited
list_of_lists
which is assumed to be a per-column representation (see mtx_lists/2).
list_of_terms
such as those read in with csv_read_file/2 but there is no restriction on term name and arity this is the canonical representation and each term is a row of the matrix

Notes for developers

For examples use:

?- mtx_data( mtcars, Mtcars ).
M = [row(mpg, cyl, disp, hp, ....

?- mtx( pack(mtx/data/mtcars), Mtc ).

?- mtx( data(mtcars), Mtx ).

Variable naming conventions

MtxIn
matrix in any acceptable representation (1st arg of mtx/2)
Mtx
canonical Mtx (2nd arg of mtx/2)
Hdr
header
Clm
column data
Cnm
column name
Cps
column position (also Cpos)

If a predicate definition has both Cnm and Cps define them in that order.

?- mtx_data( mtcars, Cars ), mtx( Cars ).
See also
- library(mtx)
 mtx(+Any, -Canonical)
mtx(?Res, +Canonical)
 mtx(?Any, ?Canonical, +Opts)
Convert to Canonical representation of matrix Any or pass the Canonical representation to output Res.

The canonical representation of a matrix is a list of compounds, the first of which is the header and the rest are the rows. The term name of the compounds is not strict but header is often and by convention either hdr or row and rows are usually term named by row.

When Opts is missing, it is set to the empty list (see options/2).

Modes

When +Any is ground and -Canonical is unbound, Any is converted from any of the accepted input formats (see mtx_type/2) to the canonical form.

When both +Canonical and +Res are ground, Res is taken to be a file to write Canonical on.

Under +Canonical and -Res, Res is bound to Canonical (allows non-output).

This predicate is often called from within mtx pack predicates to translate inputs/outputs to canonical matrices, before and after performing the intended operations.

The predicate can be used with data/1 alias, to look at data directories of packs for input data matrices.
The following three calls are equivalent.

?- mtx( data(mtcars), Mtcars, sep(comma) ).
?- mtx( data(mtcars), Mtcars ).
?- mtx( pack('mtx/data/mtcars.csv'), Mtcars).

Data matrices can be debug-ed via the dims and length goals in debug_call/3.<br>

?- debug(mtx_ex).
?- use_module(library(lib)).
?- lib(debug_call).
?- mtx( data(mtcars), Mtcars ), debug_call( mtx_ex, dims, mtcars/Mtcars ).
% Dimensions for matrix,  (mtcars) nR: 33, nC: 11.
Mtcars = [row(mpg, cyl, disp, hp, ....)|...]

?- mtx( data(mtcars), Mtcars ), debug_call( mtx_ex, len, mtcars/Mtcars ).
?- mtx( data(mtcars), Mtcars ), debug_call( mtx_ex, length, mtcars/Mtcars ).
% Length for list, mtcars: 33
Mtcars = [row(mpg, cyl, disp, hp, ....)|...]

Options

Opts is a term or list of terms from the following:

cache(Cache=false)
if true file is cached as a fact and attempts to reload the same csv file will use the cache. Any other value (Handle) than true or false will cache the file and in addition to using the cache when reloading the csv file it also allow access to the matrix via Handle, that is mtx(Handle,Mtx).
convert(Conv=false)
adds convert(Conv) to Wopts and Ropts (the default here, flips the current convert(true) default in csv_write_file/3 - also for read)
csv_read(Ropts=[])
options for csv_read_file/3
csv_write(Wopts=[])
options for csv_write_file/3
from_cache(FromCache=true)
when true reads from cache if it can match Any to a handle or a file
input_file(InpFile)
defines input file for the purposes of creating an output file in conjuction with Psfx
match(Match)
if present adds match_arity(Match) into Wopts and Ropts
output_postfix(Psfx)
the postfix of the output file (added at end of stem of InpFile)
output_file(OutF)
defines output to csv when Any is a var/1 and Canonical is ground/1.
report(Rep=false)
report the read/write and dims of corresponding matrix
ret_mtx_input(InpF)
full path of the input file
row_call(RowG=false)
when not equal to false, execute call(RowG,Ln,RowIn,RowOut) which allows arbitrary transformation of Rows while reading-in (see example below)
rows_name(RowsName)
if present the header is left padded with RowsName
sep(Sep)
if present adds separator(SepCode) into Wopts and Ropts, via mtx_sep(Sep,SepCode), mtx_sep/2
skip_heading(Skh=false)
provide prefix (number, seen as code; atom; or list, seen as codes) that removes heading lines
type(Type)
returns the type of input matrix, see mtx_type/2

?- mtx( pack(mtx/data/mtcars), Cars ),
   length( Cars, Length ).
Cars = [row(mpg, cyl, disp, hp, drat, wt, qsec, vs, am, gear, carb), row(21.0, ....],
Length = 33.

?- mtx( What, [hdr(a,b,c),row(1,2,3),row(4,5,6),row(7,8,9)], [output_file(testo)] ).
What = testo.

?- shell( 'more testo' ).
a,b,c
1,2,3
4,5,6
7,8,9
true.

?- mtx( What, [hdr(a,b,c),row(1,2,3),row(4,5,6),row(7,8,9)], [input_file('testo.csv'),output_postfix('_demo')] ).
What = testo_demo.csv.

?- mtx( pack(mtx/data/mtcars), Cars, cache(cars) ).
Cars = [row(mpg, cyl...)|...]
?- debug(mtx(mtx)).
?- mtx( cars, Cars ).
Using cached mtx with handle: cars
Cars = [row(mpg, cyl...)|...]

?- mtx( pack(mtx/data/mtcars), Mtx, cache(mtcars) ), assert(mc(Mtx)), length( Mtx, Len ).
...
Len = 33.
?- mtx( mtcars, Mtcars ), length( Mtcars, Len ).
...
Len = 33.
?- mtx( mc, Mc), length( Mc, Len ).
...
Len = 33.
?- assert( (
          only_c_b(Cb,Ln,RowIn,RowOut) :-
               ( Ln=:=1 ->
                    once(arg(Cb,RowIn,c_b)),
                    RowOut = row(c_b)
                    ;
                    arg(Cb,RowIn,CbItem),
                    RowOut = row(CbItem)
               )
          )
        ).
?-  tmp_file( testo, TmpF ),
    csv_write_file( TmpF, [row(c_a,c_b,c_c),row(1,a,b),row(2,aa,bb)], [] ),
    mtx( TmpF, Mtx, row_call(only_c_b(_)) ).

TmpF = '/tmp/swipl_testo_8588_1',
Mtx = [row(c_b), row(a), row(aa)].

?- mtx( '/tmp/swipl_testo_8588_1', Full ).
Full = [row(c_a, c_b, c_c), row(1, a, b), row(2, aa, bb)].
version
- 1:0, 2014/9/22
- 1:1, 2016/11/10, added call to mtx_type/2 and predicated matrices
- 1:2, 2021/6/17, option:row_call()
See also
- library(mtx)
- mtx/1
To be done
- option read_options(ReadCsvOpts)
- option fill_header(true) then with new_header(HeaderArgsList)
- fill_header(replace) then, replaces header new_header(...) new_header(1..n) by default.
 mtx_column_kv(+Mtx, +ColumnId, -KVs)
Create KV pairs of the form NthColumnValue-Row where N is the position of ColumnId. KVs do not include the header KV.
 ?- mtx_data( mtcars, Mt ), mtx_column_kv( Mt, mpg, KVs ).
 KVs = [21.0-row(21.0, 6.0, 160.0, 110.0, 3.9, 2.62, 16.46, 0.0, 1.0, 4.0, 4.0), 21.0-row(21.0, 6.0, 160.0, 110.0, 3.9, 2.875, 17.02, 0.0, 1.0, 4.0, 4.0), 22.8-row(22.8, 4.0, 108.0, 93.0, 3.85, 2.32, 18.61, 1.0, 1.0, 4.0, 1.0), 21.4-row(21.4, 6...)|...]
author
- nicos angelopoulos
version
- 0.2 2014/8/7, this was csv_kvs_column_row( CId, Csv, KVs )
 mtx_header(+Mtx, -Header)
 mtx_header(+Mtx, -Header, -Template)
True iff Header is the header of Mtx. Template shares functor details with Header, with all its arguments being free variables. We start supporting memory files here.
author
- nicos angelopoulos
version
- 0.1 2014/02/02
To be done
- add specialist clause for the case Mtx is a file. no need then to use mtx/2.
 mtx_header_body(+Mtx, -Header, -Body)
 mtx_header_body(+Mtx, -Header, -Body, -HasH, Opts)
True iff Header is the header of Mtx and Body are the data rows. HasH is taken from iff has_header(HasH) in Options. If HasH is false, Header is a made up row of the shape row(1,...,N)

Opts

has_header(HasH=true)
If true, first line is removed before partitioning and added to both Incl and Excl
author
- nicos angelopoulos
version
- 0.1 2014/9/24
 mtx_has_header_add(+HasH, +Header, +Body, -Rows)
Add Header and Body to create Rows iff HasH = true. For any other value of HasH, Body = Rows.

The predicate is meant as a companion to mtx_header_body/5.

author
- nicos angelopoulos
version
- 0.1 2016/2/17
See also
- mtx_header_body/5
 mtx_header_column_name_pos(+Hdr, ?Cid, -Cnm, -Pos)
N is the nth position of the column identifier Cid that is present in Hdr. Only first match is returned. Predicate is kept to a minimal implementation, for instance just fails if no Cid is in Hdr. Is the column name corresponding to Pos. Can be used to enumerate columns (name and position, v0.4)

Here, unlike in the alternative implementation, we first look for Cid in Hdr args if that is successful the corresponding position is returned, only then we check if Cid is integer before returning it as the requested position. We also check Pos in this case is within range. jjj

 ?- mtx_mtcars( Mt ), Mt = [Hdr|_Rows], mtx_header_column_name_pos( Hdr, mpg, Cnm, Cpos ).
 Cnm = mpg,
 Cpos = 1.
 
 ?- mtx_mtcars( Mt ), Mt = [Hdr|_Rows], mtx_header_column_name_pos( Hdr, 3, Cnm, Cpos ).
 Cnm = disp,
 Cpos = 3.
author
- nicos angelopoulos
version
- 0.2 2014/6/30, this was header_column_id_pos/3,4
- 0.3 2015/1/26, changed the /4 name to header_column_name_pos/4
- 0.4 2016/6/22, added enumeration for unbound (Cid)
- 0.5 2016/12/20, added nth(Cid)
 mtx_header_column_pos(+Hdr, +Cid, -Pos)
Same as mtx_header_column_name_pos( Hdr, Cid, _, Pos ).
 ?- mtx_mtcars(M), mtx_header(M,H), mtx:mtx_header_column_pos(H,carb,Pos).
See also
- mtx_header_column_name_pos/4
 mtx_header_column_multi_pos(+Hdr, +Cid, -Cnms, -Poss)
Findall Cnms and Poss corresponding to Cid. Cid could be a number (Cnms and Poss are then singletons), a list of Cids (numbers or column names) or predicate that can be called on all Hdr args (then Cnms and Poss correspond to the column names that were true).
 ?- mtx_header_column_multi_pos( hdr(a,b,a,c), =(a), Cnms, Poss ).
  Cnms = [a, a],
  Poss = [1, 3].

 ?- mtx_header_column_multi_pos( hdr(a,b,a,c), [b,c], Cnms, Pos ).
 Cnms = [b, c],
 Pos = [2, 4].
author
- nicos angelopoulos
version
- 0.1 2014/9/22
 mtx_in_memory(?Mtx)
 mtx_in_memory(?Mtx, -File)
True iff Mtx is a memory stored matrix, as loaded via mtx_in_memory/2 from File. Memory matrices, are kept in Mtx module with one hdr/n and many row/n clauses.
 ?- mtx_facts( data('mtcars.csv'), Mtcars ).
 ?- mtx_in_memory( Mod ).
 Mod = mtcars.
 ?- mtx_in_memory( Mod, File ).
 Mod = mtcars,
 File = '/home/nicos/.local/share/swi-prolog/pack/mtx/data/mtcars.csv'.
author
- nicos angelopoulos
version
- 0.2 2014/02/18, added /2 version.
 mtx_matrices_in_memory(+Mtcs)
Mtcs is the list of matrices currently loaded in memory in the form of Module-AbsF. Each matrix is loaded in a separate module (see mtx_in_memory/2).
 ?- mtx_facts( data('mtcars.csv'), Mtcars ).
 ?- mtx_matrices_in_memory( Mtcs ).
 Mtcs = [mtcars-'/home/nicos/.local/share/swi-prolog/pack/mtx/data/mtcars.csv'].
author
- nicos angelopoulos
version
- 2.1 2014/02/09.
To be done
- get all nb_ access to a single file, probably rename this with facts
 mtx_sort(+Mtx, +Column, -Out)
 mtx_sort(+Mtx, +Column, +Ord, -Out)
Sort matrix Mtx by Column in order (Ord) into Out. Ord should be either *<* (ascending) or _>_ (since 2.0). Column can be an integer or column name (see mtx_header_column_pos/3). Mtx and Out are passed through mtx/2.
 ?- mtx_sort( [row(a,b,c),row(1,2,3),row(7,8,9),row(4,5,6)], b, Ord ).
 Ord = [row(a, b, c), row(1, 2, 3), row(4, 5, 6), row(7, 8, 9)].
author
- nicos angelopoulos
version
- 2.0
 mtx_facts(+CsvF)
 mtx_facts(+CsvF, ?Module)
 mtx_facts(+CsvF, ?Module, +Opts)
Csv file CsvF is consulted into Module as a set of facts.

When module is missing or is variable, it is taken to be the stem of the base name of CsvF. When Opts is missing it defaults to the empty list. If basename(CsvF).pl exists and no option pl_ignore(true) is given, then the .pl file is consulted into Module with no further questions asked of Opts. A warning message is printed on user_output except if pl_warning(false) is in Opts.

Opts it should be one, or a list of the following

header(Hdr=true)
does file include headers ?
true
csv file has header and this is asserted
false
file has no header and hdr(1,...,n) is asserted
void
csv file has no header and none is asserted
ignore
file has a header but this is ignored (nothing asserted)
pl_ignore(PlI=false)
If true predicate does not check for existance of corresponding .pl file.
pl_warning(PlW=true)
If false the latter case no warning is printed if pre-canned .pl file is loaded "as-is".
pl_record(PlR=false)
If true, record the loaded program to corresponding .pl file.

Any remaining options are passed to csv_read_file/3.

?- debug(mtx(facts)).
true.

?- mtx_facts( data('mtcars.csv'), Mtcars ).
% Expanded facts file to: /home/nicos/.local/share/swi-prolog/pack/mtx/data/mtcars.csv, (type: csv)
% Asserting rows of file:'/home/nicos/.local/share/swi-prolog/pack/mtx/data/mtcars.csv' to module:mtcars.
Mtcars = mtcars.

?- listing( mtcars:_ ).

:- dynamic hdr/11.

hdr(mpg, cyl, disp, hp, drat, wt, qsec, vs, am, gear, carb).

:- dynamic row/11.

row(21.0, 6.0, 160.0, 110.0, 3.9, 2.62, 16.46, 0.0, 1.0, 4.0, 4.0).
row(21.0, 6.0, 160.0, 110.0, 3.9, 2.875, 17.02, 0.0, 1.0, 4.0, 4.0).
...

Listens to debug(mtx(facts)).

author
- nicos angelopoulos
version
- 0.1 2014/02/02
See also
- was csv_memory/1,2,3
 mtx_facts_remove(+FileOrModule)
Remove from a memory module an Mtx represented as facts.

FileOrModule can be either the absolute filename of the input matrix file or the module the facts are.

% assumes example on mtx_facts/2 has ran, then:

?- debug(mtx(facts)).
?- mtx_facts_remove(mtcars).
% Removing mod: mtcars, from file:'/home/nicos/.local/share/swi-prolog/pack/mtx/data/mtcars.csv'
true.

?- listing(mtcars:_).
true.
See also
- mtx_facts/2
 mtx_column_add(+Mtx, +N, +Values, -Out)
Add Values as the Nth column in Out with input columns taken from Mtx.

Values should be a list of values, or a term of the form:

transform(K, Goal, Hdr)
K is the input column id, Goal transform in to out, Hdr is either an atom or a goal that is applied to the input header to produce output header
transform(K, WholeG, Goal, Hdr)
in this case WholeG is called with call(WholeG,AllClmdata), where AllClmData is the whole Kth Column (minus header).
transform(Ks, Goal, Hdr)
take input from many columns (Ks) to produce a single output column
derive(Goal, InpPos, OutPos, Cnm)
derives the column from applying goal to each row of Mtx by inserting the Row at place InpPos and the result in OutPos of Goal
derive(Goal, InpPos, OutPos, Cnm, false)
as derive/4, but converts row to list before calling Goal

Note that for callable K, all columns of Mtx that succeed on the K(Cid) are transformed. N is taken to be relative to each input and can be an expression except if of the form abs_pos(Abs) (see mtx_relative_pos/5).

 ?- Mtx = [row(a, b, d), row(1, 2, 4), row(5, 6, 8)], assert( an_mtx(Mtx) ).

 ?- an_mtx(Mtx), mtx_column_add( Mtx, 3, [c,3,7], New ).
 New = [row(a, b, c, d), row(1, 2, 3, 4), row(5, 6, 7, 8)].

 ?- an_mtx(Mtx), mtx_column_add( Mtx, 1+2, [c,3,7], New ).
 New = [row(a, b, c, d), row(1, 2, 3, 4), row(5, 6, 7, 8)].

 ?- an_mtx(Mtx), mtx_column_add( Mtx, -1, [c,3,7], New ).
 New = [row(a, b, c, d), row(1, 2, 3, 4), row(5, 6, 7, 8)].

 ?- an_mtx(Mtx), mtx_column_add( Mtx, d, [c,3,7], New ).
 New = [row(a, b, c, d), row(1, 2, 3, 4), row(5, 6, 7, 8)].

 ?- an_mtx(Mtx), mtx_column_add( Mtx, 3, transform(3,plus(1),plus1), New ).
 New = [row(a, b, d, plus1), row(1, 2, 4, 5), row(5, 6, 8, 9)].
 
 ?- Mtx = [hdr(a,b,a,c), row(1,2,1,3), row(2,3,2,4)],
    mtx_column_add( Mtx, +(1), transform(=(a),plus(2),plus2), Out ).
 Out = [hdr(a, plus2, b, a, plus2, c), row(1, 3, 2, 1, 3, 3), row(2, 4, 3, 2, 4, 4)].

 ?- Mtx = [hdr(a,b,a,c), row(1,2,1,3), row(2,3,2,4)],
 mtx_column_add( Mtx, 1, transform(=(a),plus(2),atom_concat('2+')), Out  ).
 Out = [hdr(a, '2+a', b, a, '2+a', c), row(1, 3, 2, 1, 3, 3), row(2, 4, 3, 2, 4, 4)].

 ?- Mtx = [hdr(a, b, c), row(1, 2, 3), row(4,5,6)],
 mtx_column_add( Mtx, 4, transform([1,2],sum_list,atom_concat('a+b')), Out  ).
 Out = [hdr(a, b, c, ab), row(1, 2, 3, 3), row(4, 5, 6, 9)].

 ?- ['/home/nicos/pl/lib/src/meta/aggregate'].
 ?- Mtx = [r(a,b,c,d),r(x,1,2,3),r(y,4,5,6),r(z,7,8,9)],
    mtx_column_add( Mtx, 5, derive(aggregate(plus(),0,indices([3,2,4])),1,3,sum), Otx ).
 Otx = [r(a, b, c, d, sum), r(x, 1, 2, 3, 6), r(y, 4, 5, 6, 15), r(z, 7, 8, 9, 24)].
 
author
- nicos angelopoulos
version
- 0.1 2014/6/5 added comments.
- 0.2 2014/6/16 added transform(K,G,H) terms as 3rd argument
To be done
- complete the documentation
 mtx_column(+Mtx, ?Cid, -Column)
 mtx_column(+Mtx, ?Cid, -Column, -Cname, -Cpos)
Select column data from Csv for column identified by Cid. Cid identifies a column in Mtx either by mean of name or an integer corresponding to position. Note that name of selected header (Nhdr) is not in Column. Cpos is the position of Cid and Cname is its column name.

When Cid is an unbound all possible values are erumerated, whic Cid = Cname.

 ?- mtx_mtcars(Mtc), mtx_column( Mtc, carb, Carbs ).
 Carbs = [4.0, 4.0, 1.0, 1.0, 2.0, 1.0, 4.0, 2.0, 2.0|...].
See also
- The order of the args 4 and 5 was swapped on 15.1.26
 mtx_column_set(+Mtx, ?Cid, -Set)
 mtx_column_set(+Mtx, ?Cid, -Column, -Set)
A shortcut for mtx_column/3 followed by sort/2 on the column values to produce Set
See also
- mtx_column/3
 mtx_column(+Mtx, ?Cid, -Column, -Cname, -Cpos)
 mtx_columns(+Csv, +Names, -Columns)
 mtx_columns(+Csv, +Names, +Order, -Columns)
Select data Columns from columns with header names Names (a list). Note that headers (ie. Names are not in Columns). Caution: this version only returns rows that have ALL associated columns. This now accepts column positions within Names as per column_id_header_nth/3. Order is a boolean, true returns the Columns in header ordered form, whereas false returns Columns in same order as Names.

Since v.0.2 supports memory csvs.

Since v.0.3 supports Order. Previously Order = true was assumed which remains the default for back compatibility

% fixme: use the cars csv from pac() ?- mtx_read_file( 'example.csv', Ex ), mtx_columns( Ex, [c,b], ABs ). Ex = [row(a, b, c), row(1, 2, 3), row(4, 5, 6), row(7, 8, 9)], ABs = [row(2, 3), row(5, 6), row(8, 9)].

% fixme: use the cars csv from pac() ?- mtx_read_file( 'example.csv', Ex ), mtx_columns( Ex, [c,b], false, ABs ). Ex = [row(a, b, c), row(1, 2, 3), row(4, 5, 6), row(7, 8, 9)], ABs = [row(3, 2), row(6, 5), row(9, 8)].

author
- nicos angelopoulos
version
- 0:2, 2014/2/2
 mtx_column_default(+Csv, +Cid, +DefGoal, -Clm)
As mtx_column/3, but if Cid is not in Csv, instead of propagating the mtx_header_column_name_pos/4 ball DefGoal is called.
 ?- mtx_data( mtcars, Mt ), mtx_column_default( Mt, mpg, true, Mpg ).
 Mt =...,
 Mpg = [21.0, 21.0, 22.8, 21.4, 18.7, 18.1, 14.3, 24.4, 22.8|...].

 ?- mtx_data( mtcars, Mt ), mtx_column( Mt, typo, NaL ).
 ERROR: Unhandled exception: could_not_locate_column_in_header_row(typo,row(mpg,cyl,disp,hp,drat,wt,qsec,vs,am,gear,carb))
 
 ?- G = ( Mpg=[] ),
    mtx_data( mtcars, Mt ), mtx_column_default( Mt, typo, G, Mpg ).
 G = ([]=[]),
 Mpg = [],
 Mt = ... .
See also
- mtx_column/3
 mtx_column_name_options(+Mtx, +StdCnm, +Def, -Column, +Opts)
Select data Column from Mtx. StdCnm is the standard/expected name of the column, but this is overriden by Cnm if cnm_StdCnm(Cnm) is in Opts. Def is propagated as the 3rd argument to mtx_column_default/4, except when it is an atomic different to true and false. In the latter case, a ball is prepared which includes Def in its arguments with the intution that in that case Def is an atom identifying the matrix or its source, to the user.
 ?- Mtx = [r(a,sec,c),r(1,2,3),r(4,5,6)], assert( m(Mtx) ).
 ?- m(Mtx), mtx_column_name_options( Mtx, b, example, Column, [] ).
 ERROR: Unhandled exception: matrix_required_column_missing(example,b)

 ?- m(Mtx), mtx_column_name_options( Mtx, b, false, Column, [] ).
 false.

 ?- m(Mtx),  mtx_column_name_options( Mtx, b, example, Column, [cnm_b(sec)] ).
 Mtx = [r(a, sec, c), r(1, 2, 3), r(4, 5, 6)],
 Column = [2, 5].

Opts

cnm_from(From=from)from
cnm_to(To=to)to
cnm_weight(Weight=weight)weight
See also
- mtx_column_default/4
 mtx_column_name_options(+StdCnm, -Cnm, +OptS)
From StdCnm, the standard/expected name of the column, get Cnm which is SrdCnm except when cnm_StdCnm(Cnm) is in Opts and Cnm is ground.
 mtx_column_include_rows(+Mtx, +Cid, +Call, -Incl)
 mtx_column_include_rows(+Mtx, +Cid, +Call, -Incl, +Opts)
Filter matrix Mtx according to the values in its column Cid. Call, is called on all Column values and only rows for which this succeeds make it to matrix Out.

Mtx and Out can be either files or read in rows: see mtx/3. Opts are passed to the two calls.

Opts

header(Hdr=true)
shall we preserve Mtx's first row ?
excludes(Excl=_339938)
if present, returns the excluded rows
?- assert( mtx1([row(a,b,c),row(1,2,3),row(4,5,6)]) ).
?- mtx1( Mtx1 ), mtx_column_include_rows( Mtx1, 2, =:=(2), Rows ).
Rows = [row(a, b, c), row(1, 2, 3)].

?- mtx1( Mtx1 ), mtx_column_include_rows( Mtx1, 2, =:=(4), Rows ).
Mtx1 = [row(a, b, c), row(1, 2, 3), row(4, 5, 6)],
Rows = [row(a, b, c)].

?- mtx1( Mtx1 ), mtx_column_include_rows( Mtx1, 2, =:=(2), Rows, excludes(Exc) ).
Mtx1 = [row(a, b, c), row(1, 2, 3), row(4, 5, 6)],
Rows = [row(a, b, c), row(1, 2, 3)],
Exc = [row(4, 5, 6)].
author
- nicos angelopoulos
version
- 0.2 2014/10/15 renamed from csv_filter_by_column/4
- 0.3 2017/10/25 implement via loop rather than 3 meta calls
- 0.4 2018/2/3 added options header(Hdr) and excludes(Excl)
 mtx_column_select(+Mtx, +ColumnS, -Rem, -Sel)
mtx_column_select(+Mtx, +CallStr, -Rem, -Sel)
Select column or columns (header(s) or number(s) of) from Mtx to produce Sel with remainder Rem. Sel is the removed column(s), and Rem is the remainder of Mtx. Rem is a matrix whereas Sel is a list of values if ColumnS was atomic or a list of list values if ColumnS was a list. When CallStr is of the form @(Goal) or call(Goal), it will be applied to each column, with succeeding columns Selected for Sel. (Note that dealing with presence/absence of column name is delegated to Goal). Goal is called in user if it is not module prepended (see mod_goal/4).
 ?- Mtx = [row(a,b,c,d),row(1,1,1,1),row(1,1,2,3),row(2,2,2,2)], assert( ex_mtx(Mtx) ).
 ?- ex_mtx(Mtx), mtx_column_select( Mtx, b, Red, Sel ).
 Mtx, = [row(a,b,c,d),row(1,1,1,1),row(1,1,2,3),row(2,2,2,2)],
 
 ?- mtx_column_select( Mtx, [a,b], Red, Sel ).
 Red = [row(c, d), row(1, 1), row(2, 3), row(2, 2)],
 Sel = [[a, b], [1, 1], [1, 1], [2, 2]].
 
 ?- assert( ( has_at_least(Tms,Val,List) :- findall( 1, member(Val,List), Ones ), sum_list(Ones,Sum), Tms =< Sum) ).
 ?- has_at_least(2,a,[a,b,c,a] ).
 true.
 ?- has_at_least(2,b,[a,b,c,a] ).
 false.

 ?- ex_mtx(Mtx), mtx_column_select( Mtx, call(has_at_least(2,1)), Red, Sel ).
 Mtx = [row(a, b, c, d), row(1, 1, 1, 1), row(1, 1, 2, 3), row(2, 2, 2, 2)],
 Red = [row(c, d), row(1, 1), row(2, 3), row(2, 2)],
 Sel = [[a, b], [1, 1], [1, 1], [2, 2]].
author
- nicos angelopoulos
version
- 0.2 2014/6/3, fixed ColumnS = [b] bug
 mtx_column_threshold(+Csv, +Clm, +Val, +Dir, -Out)
 mtx_column_threshold(+Csv, +Clm, +Val, +Dir, -Sel, -Rej)
Cuts rows off Csv by thresholding Clm over or below Val according to Dir. The resulting csv is in Out. When Dir is < predicate keeps values below the threshold and Dir > keeps values (strictly) above the threshold. Note that the Clm_th value of each row is also tested for being numeric. This makes sure we dont test against non-numerics. Rows that have non-numeric Clm_th values are not in Out. Clm is fed through mtx_header_column_pos/3 and can be an argument of the first term in Csv (the header) or the corresponding number. Csv and Out are passed through mtx/2, so the can be list of row terms or csv filenames.

The predicate assumes Csv is of the form [Hdr|Rows] and includes Hdr to result. If you want to call on non headers Rows then with numeric NumClm you can call:

?- mtx_column_threshold( [_|Rows], NumClm, Val, Dir, [_|OutRows] ).

Exaamples

?- assert( csv([row(a,b,c),row(1,2,3),row(1,4,5),row(3,6,7),row('',8,9),row(3,b,10)]) ).
?- csv( Csv ), mtx_column_threshold( Csv, a, 2, <, Out ).
   Out = [row(a, b, c), row(1, 2, 3), row(1, 4, 5)].
?- csv( Csv ), mtx_column_threshold( Csv, 1, 2, >, Out ).
   Out = [row(a, b, c), row(3, 6, 7), row(3, b, 10)].
author
- nicos angelopoulos
version
- 0.1, 2014/1/29
To be done
- was csv_threshold/5
- fixme: change multi_comparison to op_compare/3
 mtx_column_frequency_threshold(+Mtx, +Cid, +Op, +Thresh, -Reduced)
Shorten Mtx into Reduced by removing all rows that correspond to Cid identified column values that occur below or above a threshold value number of times.

Header is assumed.

Op should be a recognisable operator, see stoics_lib: op_compare/). The predicate will call op_compare( Op, Freq, Thresh ), for the Frequency of every distinct value on column Cid in Mtx.

?- assert( a_mtx([r(a,b,c),r(1,2,1),r(1,2,1),r(1,6,7),r(8,9,10)]) ).
?- a_mtx(Mtx), mtx_column_frequency_threshold( Mtx, a, >, 2, Red ).
Red = [r(a, b, c), r(1, 2, 1), r(1, 2, 1), r(1, 6, 7)].

?- a_mtx(Mtx), mtx_column_frequency_threshold( Mtx, a, <, 2, Red ).
Red = [r(a, b, c), r(8, 9, 10)].

?- a_mtx(Mtx), mtx_column_frequency_threshold( Mtx, a, <, 1, Red ).
Red = [r(a, b, c)].

?- a_mtx(Mtx), mtx_column_frequency_threshold( Mtx, a, =<, 1, Red ).
Red = [r(a, b, c), r(8, 9, 10)].
author
- nicos angelopoulos
version
- 0.1 2017/5/17
See also
- stoics_lib: op_compare/3
 mtx_column_replace(+Mtx, +Cid, +NewVals, -OldVals, -NewMtx)
 mtx_column_replace(+Mtx, +Cid, ?NewClmName, +NewVals, -OldVals, -NewMtx)
Replace a column in a Mtx. When there is no NewClmName (or when it is an unbound variable), then the existing column name is used.
NewClmName can be atomic or a compound, when the latter it is called with NewClmName(ClmName,New) where New is used as the new column name.
NewVal could be a list of values, (equal length as Cid's?); a @(Goal) term where Goal will be maplist applied to Cid's elements to produce the new values;
Goal which will be applied to the list of Cid's elements to produce the list of new values.
By default, _Goal_s are called in module user if they are no module prepended. See mod_goal/4, with false in 3rd argument.
 ?- assert( (plus_one(A,B):-B is A + 1) ).   % plus/3 only works on integers...
 ?- mtx( pack('mtx/data/mtcars'), Mtx, cache(mtcars) ),
    mtx_column_replace( Mtx, mpg, mpgp1, @(user:plus_one()), _, New ).

 Mtx = [row(mpg, cyl, disp, hp, drat, wt, qsec, vs, am, gear, carb), row(21.0, 6.0, 160.0, 110.0, 3.9, 2.62, 16.46, 0.0, 1.0, 4.0, 4.0),
        row(21.0, 6.0, 160.0, 110.0, 3.9, 2.875, 17.02, 0.0, 1.0, 4.0, 4.0), row(22.8, 4.0, 108.0, 93.0, 3.85, 2.32, 18.61, 1.0, 1.0, 4.0, 1.0),
        row(21.4, 6.0, 258.0, 110.0, 3.08, 3.215, 19.44, 1.0, 0.0, 3.0, 1.0), row(18.7, 8.0, 360.0, 175.0, 3.15, 3.44, 17.02, 0.0, 0.0, 3.0, 2.0),
        row(18.1, 6.0, 225.0, 105.0, 2.76, 3.46, 20.22, 1.0, 0.0, 3.0, 1.0), row(14.3, 8.0, 360.0, 245.0, 3.21, 3.57, 15.84, 0.0, 0.0, 3.0, 4.0),
        row(..., ..., ..., ..., ..., ..., ..., ..., ..., ..., ...)|...],
 New = [row(mpgp1, cyl, disp, hp, drat, wt, qsec, vs, am, gear, carb), row(22.0, 6.0, 160.0, 110.0, 3.9, 2.62, 16.46, 0.0, 1.0, 4.0, 4.0),
        row(22.0, 6.0, 160.0, 110.0, 3.9, 2.875, 17.02, 0.0, 1.0, 4.0, 4.0), row(23.8, 4.0, 108.0, 93.0, 3.85, 2.32, 18.61, 1.0, 1.0, 4.0, 1.0),
        row(22.4, 6.0, 258.0, 110.0, 3.08, 3.215, 19.44, 1.0, 0.0, 3.0, 1.0), row(19.7, 8.0, 360.0, 175.0, 3.15, 3.44, 17.02, 0.0, 0.0, 3.0, 2.0),
        row(19.1, 6.0, 225.0, 105.0, 2.76, 3.46, 20.22, 1.0, 0.0, 3.0, 1.0), row(15.3, 8.0, 360.0, 245.0, 3.21, 3.57, 15.84, 0.0, 0.0, 3.0, 4.0),
        row(..., ..., ..., ..., ..., ..., ..., ..., ..., ..., ...)|...].
 
 ?- assert( (psfx_one(Name,Psfxed) :- atomic_list_concat([Name,one],'_',Psfxed)) ).
 ?- mtx_column_replace( mtcars, mpg, user:psfx_one(), @(user:plus_one()), _, New ).
 New = [row(mpg_one, cyl, disp, hp, drat, wt, qsec, vs, am, gear, carb),
        row(22.0, 6.0, 160.0, 110.0, 3.9, 2.62, 16.46, 0.0, 1.0, 4.0, 4.0),
        row(..., ..., ..., ..., ..., ..., ..., ..., ..., ..., ...)|...].

 ?- mtx_column_replace( mtcars, mpg, mpgp1, @(plus_one()), _, New ).
 New = [row(mpgp1, cyl, disp, hp, drat, wt, qsec, vs, am, gear, carb),
        row(22.0, 6.0, 160.0, 110.0, 3.9, 2.62, 16.46, 0.0, 1.0, 4.0, 4.0),
        row(..., ..., ..., ..., ..., ..., ..., ..., ..., ..., ...)|...].
author
- nicos angelopoulos
version
- 0.2 2017/9/11
To be done
- check NewVals list is equal to Column list ?
 mtx_column_values_select(+Csv, +Cid, +ValS, -Sel, -Rej, +Opts)
Select rows from Csv that have matching values ValS in column identified by Cid. Sel is the selected rows and Rej are all the other rows.

Hdr is protected and added to both Sel and Rej.

Opts

mtx/2
Opts are passed to mtx/2 for input and output of selected rows: Sel
csv_write_rejected(CWRejOpts=[])
Opts passed to mtx/2 for rejected rows
compare(Compare=term)
or arithmetic see compare/4
 ?- Csv = [row(a,b,c),row(1,2,3),row(4,5,6)],
    csv_column_values_select( Csv, c, 3, Red, _ ).
 Csv = [row(a, b, c), row(1, 2, 3), row(4, 5, 6)],
 Red = [row(a, b, c), row(1, 2, 3)].
author
- nicos angelopoulos
version
- 0.2 2015/2/16 was csv_select_rows_on_column_values/5
- 0.1 2014/6/3
 mtx_name_prefix_column(+Mtx, +Prefix, -Pos, -Cnm, -Clm)
Retrieve the column data (Clm) from Mtx for the column with name prefixed by Prefix. Pos, Cnm and Clm are the position in the header, the fulll column name and the column data respectively. If there are more than 1 matching columns the predicate throws an error, if there are no matching columns the predicate fails as to allow alternatives to be tried.
 % throws error
 ?- Mtx = [hdr(aa,ab,ba,bb),row(1,2,3)],
    mtx_name_prefix_column( Mtx, a, Pos, Cnm, Clm ).

 ?- Mtx = [hdr(aa,ab,ba,bb),row(1,2,3)],
    mtx_name_prefix_column( Mtx, aa, Pos, Cnm, Clm ).
 Pos = 1,
 Cnm = aa,
 Clm = [1].
author
- nicos angelopoulos
version
- 0.1 2014/10/8
 mtx_relative_pos(+N, +K, +Hdr, -Pos)
 mtx_relative_pos(+N, +K, +Hdr, +Nadj, -Pos)
R is the absolute position of the Nth position relative to K. If N is compound it is assumed to be the RHS of an addition which is evaluated- LHS is K. If relative position evalutes to a negative is assumed to mean right relative postion in Hdr and thus mapped to the absolute position of that. In this case Nadj is also added. This provides a convenient method for referring to negative location of transformed (relative to Hdr) matrices.
 ?- mtx_relative_pos( 2, 2, _, Pos ).
 Pos = 4.
 ?- mtx_relative_pos( -2, 0, c(a,b,c), Pos ).
 Pos = 2.
 ?- mtx_relative_pos( -2, 0, c(a,b,c), Nadj, Pos ).
 Pos = 2.
version
- 0.1 2014/9/22
 mtx_lists(?Mtx, ?Lists)
Dismantle or construct matrix Mtx to and from list of nested Lists.
 mtx_transpose(+Mtx, -Trans)
Transpose a matrix. Both Mtx and Trans are passed through mtx/2.
author
- nicos angelopoulos
version
- 0.2 2014/4/24
- 0.3 2020/3/17, docs update
See also
- mtx/2
- was csv_transpose/2
 mtx_factors(+Mtx, -FactorPairs, +Opts)
Get and possibly report sets of values appearing in Mtx columns (default) or rows.

Opts by(By=column) use row to get the report row-wise

frequency(Freq=false) to report factors, or add number each factor appeared

max(Max=0) if positive, the maximum number of items to be displayed for each vector. if negative no reporting takes place.

?- mtx( pack(mtx/data/mtcars), Cars ), mtx_factors( Cars, _,  [max(5)] ), fail.
mpg: [10.4,13.3,14.3,14.7,15.0,...]
cyl: [4.0,6.0,8.0]
disp: [71.1,75.7,78.7,79.0,95.1,...]
hp: [52.0,62.0,65.0,66.0,91.0,...]
drat: [2.76,2.93,3.0,3.07,3.08,...]
wt: [1.513,1.615,1.835,1.935,2.14,...]
qsec: [14.5,14.6,15.41,15.5,15.84,...]
vs: [0.0,1.0]
am: [0.0,1.0]
gear: [3.0,4.0,5.0]
carb: [1.0,2.0,3.0,4.0,6.0,...]
false.

?- mtx( pack(mtx/data/mtcars), Cars ), mtx_factors( Cars, _,  [max(3),frequency(true)] ), fail.
mpg: [21.0-2,22.8-2,21.4-2,...]
cyl: [6.0-7,4.0-11,8.0-14]
disp: [160.0-2,108.0-1,258.0-1,...]
hp: [110.0-3,93.0-1,175.0-3,...]
drat: [3.9-2,3.85-1,3.08-2,...]
wt: [2.62-1,2.875-1,2.32-1,...]
qsec: [16.46-1,17.02-2,18.61-1,...]
vs: [0.0-18,1.0-14]
am: [1.0-13,0.0-19]
gear: [4.0-12,3.0-15,5.0-5]
carb: [4.0-10,1.0-7,2.0-10,...]
false.

author
- nicos angelopoulos
version
- 0.1 2015/11/25
See also
- this started as mtx_factors_report/2
 mtx_columns_copy(+MtxFrom, +MtxTo, -MtxOut, +Opts)
For each column(CidIn,PosOut) term in Opts column with Cid, CidIn, is copied from Mtx to MtxOut. In MtxOut, the column is placed in position PosOut. The predicate scans Opts as they come, so PosOut should take account of all operation to its left.
 ?- M1 = [r(a,b,c),r(1,2,3),r(4,5,6)],
    M2 = [r(d,e,f),r(7,8,9),r(10,11,12)],
    mtx_columns_copy( M1, M2, M3, column_copy(c,2) ).
 M3 = [r(d, c, e, f), r(7, 3, 8, 9), r(10, 6, 11, 12)].
author
- nicos angelopoulos
version
- 0.1 2014/01/22
See also
- mtx_column_add/4.
To be done
- add rem(Rem) option- to return remaining options
 mtx_columns_kv(+Csv, +Cid1, +Cid2, -KVs, -Cnms, -Cpos)
Create a KV pairs list from mtx/1:Mtx and identifiers for two of its columns: Cid1 and Cid2. Cnms is Cnm1-Cnm2 and Cpos is Cpos1-Cpos2 as returned by mtx_header_column_name_pos/4. KVs have all the pair values of Cid1 and Cid2.
 ?- mtx_data( mtcars, Mt ), mtx_columns_kv( Mt, mpg, hp, KVs, _, _ ).
 Mt = [row(mpg, cyl, disp,..)|...],
 KVs = [21.0-110.0, 21.0-110.0, 22.8-93.0, 21.4-110.0, 18.7-175.0, 18.1-105.0, ... - ...|...].
To be done
- allow for Clm2 to be a list of column ids?
 mtx_header_cids_order(+Hdr, +Cids, -Order)
Order is the order set of column positions corresponding to Cids in Hdr.
?- mtx_data( mtcars, Mt ), mtx_header( Mt, Hdr ),
   mtx_header_cids_order( Hdr, [drat,cyl], Order ).
        
Mt = ...,
Hdr = row(mpg, cyl, disp, hp, drat, wt, qsec, vs, am, gear, carb),
Order = [2, 5].
 mtx_columns_remove(+Mtx, +CidsOrGoal, -Out)
Remove a number of columns from Mtx resulting to Out.

CidsOrGoal should be either be a Cid, a list of Cids or a Goal.

?- mtx_data( mtcars, Mt ), mtx_columns_remove( Mt, [wt,cyl], Red ).
Mt = [row(mpg, cyl, disp, hp, drat, wt, qsec, vs, am, gear, carb), row(21.0, 6.0, 160.0, 110.0, 3.9, 2.62, 16.46, 0.0, 1.0, 4.0, 4.0), .... ],
Red = [row(mpg, disp, hp, drat, qsec, vs, am, gear, carb), row(21.0, 160.0, 110.0, 3.9, 16.46, 0.0, 1.0, 4.0, 4.0), row(21.0, 160.0, 110.0, 3.9, 17.02, 0.0, 1.0, 4.0, 4.0), ...].

?- mtx_data( mtcars, Mt ), mtx_columns_remove( Mt, [wt,cyl], Red ),
   mtx_dims( Mt, MtR, MtC ), mtx_dims( Red, RdR, RdC ).

MtR = RdR, RdR = 33,
MtC = 11,
RdC = 9.

?- assert( mtx1( [row(a,b,c,c), row(1,2,3,4), row(1,5,6,7), row(1,8,9,10)] ) ).true.
?- assert( ( below_min_length_of_factor(Min,Clm) :- Clm = [_|Vals], sort( Vals, Ord ), length( Ord, Len ), Len < Min) ).
true.

?- mtx1( Mtx1 ), mtx_columns_remove( Mtx1, below_min_length_of_factor(2), Red ).
Mtx1 = [row(a, b, c, c), row(1, 2, 3, 4), row(1, 5, 6, 7), row(1, 8, 9, 10)],
Red = [row(b, c, c), row(2, 3, 4), row(5, 6, 7), row(8, 9, 10)].

?- lib(stoics_lib:has_at_least/3).

?- mtx1( Mtx1 ), mtx_columns_remove( Mtx1, has_at_least(2,1), Red ).
Red = [row(b, c, c), row(2, 3, 4), row(5, 6, 7), row(8, 9, 10)].

?- lib(stoics_lib:has_at_most/3).
?- mtx1( Mtx1 ), mtx_columns_remove( Mtx1, has_at_most(2,1), Red ).
version
- 0.0.2 2015/12/01 added goals
See also
- mtx_header_cids_order/3
 mtx_dims(+Mtx, -Nrows, -Ncols)
mtx_dims(-Mtx, +Nrows, +Ncols)
 mtx_dims(-Mtx, +Nrows, +Ncols, +Value)
Mtx has Nrows number of rows and Ncols number of columns. Mtx is a mtx/1. Predicate can also being used to generate a matrix of given dimensions. In that mode, when Value is missing it is defaulted to 0.
?- mtx_data( mtcars, Mt ), mtx_dims( Mt, Nr, Nc ).
Mt = ...,
Nr = 33,
Nc = 11.

?- mtx_dims( Mtx, 2, 3 ).
Mtx = [row(0, 0, 0), row(0, 0, 0)].
author
- nicos angelopoulos
version
- 0:2 2016/12/08, added -++ mode
 mtx_prolog(?Mtx, ?Prolog)
 mtx_prolog(?Mtx, ?Prolog, -Opts)
Write/convert an Mtx to a prolog file.

Prolog can be given, in which case it is considered to be a full filename. If Prolog is free, it instantiates to the filename of the file the facts were dumped on, or the Rows themselves if consult(consult) was in Opts.

In what follows, Stem is the first of:

Opts

consult(Cons=save)
should the facts be consulted (consult), saved (save) or both ?
out_stem(Fstem=stem(Mtx))
stem for filename, .pl is added. The default is the stem of Mtx. (Was file_stem(Fstem).)
out_ext(Fext={csv,pl})
extension for ouput file. The default depends whether the predicate is writing out to Mtx on to Prolog
out_dir(Fdir=dir(InpF))
output directory, default is '.' or taken from input file if one was given
header_remove(Rmv=false)
whether to ignore the first row, else true, or pname for header fact
mtx_opt(MtxOpt)
option(s) to be passed to mtx/3
predicate_name(Pname=stem(basename(Mtx)))
predicate name for facts
rows_transform(Rtrans)
if present the predicate is called on the input rows to transform them before they converted to facts. Use Rtrans = maplist(Pred) if you want to use maplist on each row for Pred rather than the default of calling Pred with RowsIn and RowsOut

Modalities

Mtx=os_file(),Prolog=os_file()
(write from one existing, and if both exist Mtx -> Prolog
Mtx=os_file(),Prolog=var
Mtx=var,Prolog=os_file
author
- nicos angelopoulos
version
- 0.1 2015/3/20
- 0.2 2018/12/3, added conversion from Prolog to mtx.
To be done
- change header_remove(Rmv) to keep_header({true,false,as_comment}).
- change allow for header pred names (harmonize with bio_db ?'s _info...)
- modalities list
- add examples and test conversion from Prolog to mtx
 mtx_columns_partition(+Mtx, +Goal, -Incl, -Excl)
 mtx_columns_partition(+Mtx, +Goal, +ClmPart, -Incl, -Excl)
Partitions Mtx to columns for which Goal succeeds (Incl) against those that fails (Excl). ClmPart should be one of body, head or whole.

Goal is elliptically expanded to an expresssion.

?- assert( mtx1([row(a,b,c),row(1,2,3),row(4,5,6),row(7,8,9)] ) ).
?- lib(lists).    % this is needed for sum_list/2
?- mtx1( Mtx1 ), mtx_columns_partition( Mtx1, sum_list > 0, Mtx2, Excl ).
Mtx1 = Mtx2, Mtx2 = [row(a, b, c), row(1, 2, 3), row(4, 5, 6), row(7, 8, 9)],
Excl = [].

?- mtx1( Mtx1 ), mtx_columns_partition( Mtx1, sum_list > 12, body, Acc, Rej ).
Mtx1 = [row(a, b, c), row(1, 2, 3), row(4, 5, 6), row(7, 8, 9)],
Acc = [row(b, c), row(2, 3), row(5, 6), row(8, 9)],
Rej = [row(a), row(1), row(4), row(7)].

?- mtx1( Mtx1 ), mtx_columns_partition( Mtx1, sum_list > 15, body, Acc, Rej ).
Mtx1 = [row(a, b, c), row(1, 2, 3), row(4, 5, 6), row(7, 8, 9)],
Acc = [row(c), row(3), row(6), row(9)],
Rej = [row(a, b), row(1, 2), row(4, 5), row(7, 8)].

?- assert( (chkmember(List,Elem):-memberchk(Elem,List)) ).
?- mtx1( Mtx1 ), mtx_columns_partition( Mtx1, chkmember([a,c]), head, Acc, Rej ).
author
- nicos angelopoulos
version
- 0.1 2015/12/2
See also
- goal_expression/3
To be done
- use options apply_on(AppOn) see mtx/0
 mtx_rows_partition(+Mtx, +Goal, -Incl, -Excl, +Opts)
Partition matrix Mtx by calling Goal on each row of the matrix.

If Mtx, Incl and Excl are ground and non-lists are taken to be files to read/write upon
in which case an optimised version is used, that does not read the whole file
into memory but processes each line as it is read. In this case Incl and Excl can be the special atom false which will indicated the specified channel is not required.

Opts

has_header(HasH=true)
If true, first line is removed before partitioning and added to both Incl and Excl
apply_on(AppOn=whole)
which part of row to use: whole, head (first argument of row term) or body (the list of arguments of the row term)\br
?- assert( (arg_val(N,Val,Row) :- arg(N,Row,Val)) ).
?- mtx_data( mtcars, Mtcars ),
   mtx_rows_partition( Mtcars, arg_val(1,21.0), Incl, Excl, true ),
   length( Excl, Nxcl ), maplist( writeln, Incl ), write( xLen:Nxcl ), nl, fail.

row(mpg,cyl,disp,hp,drat,wt,qsec,vs,am,gear,carb)
row(21.0,6.0,160.0,110.0,3.9,2.62,16.46,0.0,1.0,4.0,4.0)
row(21.0,6.0,160.0,110.0,3.9,2.875,17.02,0.0,1.0,4.0,4.0)
xLen:31
author
- nicos angelopoulos
version
- 0.1 2016/2/16
- 0.2 2018/3/23, added optmised version for when all io is on files
See also
- mtx_header_body/5 (has_header(HasH))
To be done
- if AppOn is of the form arg(Arg) then Arg is taken to be a column name or
 mtx_columns_values(+Mtx, -Values, +Opts)
Return the Values for each column of Mtx. By default it returns the list of values, but it can
also return pairs where key is the column name, and/or sets of frequencies instead of listed values.

Opts

has_header(HasH=true)
false indicates that the first element of each column should not be excluded
header_pair(Hpair=false)
when Mtx has header and this is true each return element is a pair of Cname-ClmValues
values_as(As=list)
default returns values as lists, alternatively
set
returns sets
frequencies/freqs
returns value-freqs pairs
 ?- mtx_data( mtcars, MtCars ), mtx_columns_sets( MtCars, Sets, true ),
    maplist( length, Sets, Lengths ), write( lengths(Lengths) ), nl.

  lengths([25,3,27,22,22,29,30,2,2,3,6])
  ...
author
- nicos angelopoulos
version
- 0.2 2016/01/21, was mtx_columns_sets/3
 mtx_value_plot(+Mtx, +Value, +Opts)
Plot the occurrences of a value in the columns of a matrix via mlu's mlu_frequency_plot/2.

Requires pack(mlu).

Opts

sort(Sort=true)
overrides default for mlu_frequency_plot/2
?- [pack(mtx/examples/ones_plots)].  ones_plots.
% displays 2 frequency plots one with a vertical separator line and
% the other with 3 frequency groups distinguished by colour.
author
- nicos angelopoulos
version
- 0.1 2017/1/13
See also
- mtx_value_column_frequencies/3
- mlu_frequency_plot/2
 mtx_value_column_frequencies(+Mtx, +Value, -VCFreqs)
VCFreqs are the frequencies of Value in each column of Mtx.
The result is a KV pair list where the key (K) is the column name.
It was part of mtx_value_plot/3.
?- Mtx = [r(a,b,c,d),r(1,0,0,0),r(1,1,0,0),r(1,1,1,0)], maplist(writeln,Mtx),
   mtx_value_column_frequencies(Mtx,1,VC).
r(a,b,c,d)
r(1,0,0,0)
r(1,1,0,0)
r(1,1,1,0)
Mtx = [r(a, b, c, d), r(1, 0, 0, 0), r(1, 1, 0, 0), r(1, 1, 1, 0)],
VC = [a-3, b-2, c-1, d-0].
author
- nicos angelopoulos
version
- 0.1 2018/02/16
See also
- mtx_value_plot/3
 mtx_columns_cross_table(+Mtx, +Cid1, +Cid2, -Tbl, +Opts)
Get the matrix Tbl showing cross reference abundance of values from two columns (Cid1 and Cid2) in Mtx.

Opts

binary(Bin=true)
when true only record absense/presense, else record number of occurances
sort_rows(Sr=true)
sorts rows according to row name
sort_columns(Sc-trye)
sorts columns according to column names
?- Mtx = [w(lets,nums),w(a,1),w(a,2),w(b,3),w(c,2),w(c,3)],
        mtx_columns_cross_table( Mtx, lets, nums, Tbl, true ),
        maplist( writeln, Mtx ),
        maplist( writeln, Tbl ).
w(lets,nums)
w(a,1)
w(a,2)
w(b,3)
w(c,2)
w(c,3)
hdr(,1,2,3)
row(a,1,1,0)
row(b,0,0,1)
row(c,0,1,1)
Mtx = [w(lets, nums), w(a, 1), w(a, 2), w(b, 3), w(c, 2), w(c, 3)],
Tbl = [hdr('', 1, 2, 3), row(a, 1, 1, 0), row(b, 0, 0, 1), row(c, 0, 1, 1)].
author
- nicos angelopoulos
version
- 0.1 2017/1/17
 mtx_pos_elem(+Mtx, ?I, ?J, -Elem, +Opts)
 mtx_pos_elem(+Mtx, +I, +J, +Elem, -Out, +Opts)
Access or change matrix's Mtx the element at position (I,J). In the latter case Out is Mtx with the element at position (I,J) set to Elem.

mtx_pos_elem/5 can be used to generate all positions and elements

Please note this uses the canonical representation and not optimised for other formats.

Opts

has_header(HasH)
default as per mtx_header_body/5.
?- Mtx = [row(a,b,c),row(1,2,3),row(4,5,6)], assert( a_mtx(Mtx) ).
?- a_mtx(Amtx), mtx_pos_elem(Amtx,I,J,Elem,true).
Amtx = [row(a, b, c), row(1, 2, 3), row(4, 5, 6)],
I = J, J = Elem, Elem = 1 ;
...
?- a_mtx(Amtx), mtx_pos_elem(Amtx,2,3,0,Bmtx,true).
Amtx = [row(a, b, c), row(1, 2, 3), row(4, 5, 6)],
Bmtx = [row(a, b, c), row(1, 2, 3), row(4, 5, 0)].
 mtx_apply(+Mtx, +Goal, -Res, +Opts)
Apply Goal to all non-header cells of Mtx to produce Res.

Opts

default_value(DefV=undefined)
use value(Val)=DefV when you want to set the elements that fail ij_constraint
has_header(HasH=true)
see mtx_header_body/5. Header is removed before application and then added to Res (if exists).
ij_constraint(IJc=true)
alternatives are any operator accepted by op_compare/3 (ground Op), with < meaning operate on (strict) upper matrix and >:< operate on all pairs
mod(Mod=user)
module in which to call Goal
mtx_in_goal(MinG=false)
whether to pass scaffold to Goal call. If true call is call(Gname,Scf,I,J,Elem|Gargs,NtxScf), else it is call(Gname,Elem|Gargs,OutElem)
on_mtx(OnMtx=self)
scaffold matrix for results. self means use Mtx itself
row_start(Rst=top)
set to bottom for upward looking ij_constraints
?- Mtx = [row(a,b,c),row(1,2,3),row(4,5,6),row(7,8,9)], assert( a_mtx(Mtx) ).

?- a_mtx( Amtx ), mtx_apply( Amtx, plus(1), Bmtx, true ).
Bmtx = [row(a, b, c), row(2, 3, 4), row(5, 6, 7), row(8, 9, 10)].

?- a_mtx( Amtx ), mtx_apply( Amtx, plus(1), Bmtx, ij_constraint(<) ).
Bmtx = [row(a, b, c), row(1, 3, 4), row(4, 5, 7), row(7, 8, 9)].

?- a_mtx( Amtx ), mtx_apply( Amtx, plus(1), Bmtx, [ij_constraint(=<),default_value(0),row_start(bottom)] ).
Bmtx = [row(a, b, c), row(0, 0, 4), row(0, 6, 7), row(8, 9, 10)].

?- a_mtx( Amtx ), mtx_apply( Amtx, plus(1), Bmtx, [ij_constraint(=<),default_value(0),row_start(top)] ).
Bmtx = [row(a, b, c), row(2, 3, 4), row(0, 6, 7), row(0, 0, 10)].

?- a_mtx( Amtx ), mtx_apply( Amtx, plus(1), Bmtx, [ij_constraint(=<),default_value(0),row_start(top)] ).
Bmtx = [row(a, b, c), row(0, 3, 4), row(0, 0, 7), row(0, 0, 0)].
author
- nicos angelopoulos
version
- 0.1 2016/2/17
 mtx_type(+Mtx, -Type)
Mtx is of type Type.

Types:

asserted (atomic) when Mtx is not a current handle and given that predicate Mtx/1 exists with its argument instantiating to a list, this list is taken to be a matrix in canonical representation

by_column (list of lists) which is assumed to be a per-column representation (see mtx_lists/2)

by_row (list of compounds) such as those read in with csv_read_file/2 but there is no restriction on term name and arity. this is the canonical representation and each term is a row of the matrix

predicated (Pid of the form Pname/Arity) where the atom Pname corresponds to a predicate name and the predicate with arity N is defined to succeeds with the returned arguments

predfile (atomic) when Mtx is not a current mtx handle and given that predicate Mtx/1 exists with its argument instantiating to a non-list; this argument is taken to be the stem (with possible exts csv and tsv) or filename of a csv/tsv file which csv_read_file/3 can read as a canonical matrix

on_file (ground; non-list) (atomic or compound: csv file or its stem) as possible to be read by csv_read_file/2 alias paths and normal delimited file extension can be ommitted

asserted (atomic) atomic, when mtx was cached at loading time (see option cache(Cache) in mtx/3)

If Mtx is a list, its contents are first checked for sublists (by_column) and then for compounds (by_row). When Mtx is a predicate identifier of the form Pname/Arity, it is taken to define the corresponding Mtx (predicated). If Mtx is atomic the options are Mtx matrix handle exists (see mtx/2) then the type is in_memory Mtx/1 is defined and returns a list type is asserted Mtx/1 is defined and returns a non list type on_file(File)

?- mtx_type( [[a],[b],[c]], Type ).
Type = by_column.

?- mtx_type( [r(a,b,c),r(1,2,3),r(4,5,6)], Type ).
Type = by_row.

?- mtx_type( pack(mtx/data/mtcars), Type ).
Type = on_file.
% was: Type = on_file('/usr/local/users/na11/local/git/lib/swipl-7.3.29/pack/mtx/data/mtcars.csv').

?- assert( mc_file(pack(mtx/data/mtcars)) ).
?- mtx_type( mc_file, Type ).

?- mtx( pack(mtx/data/mtcars), Mtx, cache(mtcars) ), assert(mc(Mtx)).
?- mtx_type( mtcars, Type ).
Type = handled.

?- mtx_type( mc, Type ).
Type = asserted.

?- mtx( mc, Mc ), findall( _, (member(Row,Mc),assert(Row)), _ ).
?- mtx( mc, [Hdr|_Rows] ), functor( Hdr, Pname, Arity ), mtx_type( Pname/Arity, Type ).
Hdr = ...,
Rows = ...,
Pname = row,
Arity = 11,
Type = predicated.
author
- nicos angelopoulos
version
- 0.1 2016/11/10
See also
- mtx/1, mtx/2, mtx/3
 mtx_read_table(+CsvF, +RowsName, -Table, +OptS)
Reads a table in from a file (CsvF). A table is a delimited file in which the first row is one short than the rest.
RowsName is added as the first argument in the read-in Table's first row.

OptS

match(Match=true)
whether to match_arity(Match) rows read in (see csv//2 options).
sep(Sep=_334042)
the mtx/2 version of separator(Sep) option of csv//2 (mtx_sep/2). Defaults to csv//2 version which is based on filename extension.

Any other OptS are passed to csv//2.
As per mtx/3 convention OptS can be a single option (un-listed) or a list of options.

?-  tmp_file( testo, TmpF ),
    csv_write_file( TmpF, [row(c_a,c_b),row(1,a,b),row(2,aa,bb)], [match_arity(false),separator(0'\t)] ),
    mtx_read_table( TmpF, samples, Tbl, sep(tab) ).

TmpF = '/tmp/pl_testo_12445_0',
Tbl = [row(samples, c_a, c_b), row(1, a, b), row(2, aa, bb)].
author
- nicos angelopoulos
version
- 0.1 2018/2/3
See also
- mtx_sep/2, csv//2
 mtx_columns_collapse(+MtxIn, +Cids, +Cnm, +RowGoal, +Pos, -Mtx)
Collapse a number of columns into a single column.
MtxIn is the input matrix, Cids are the column identifiers for the columns to be collapsed,
Cnm is the column name of the new, collapsed column, Pos is the position of the new column
and Mtx is the new matrix.
?- assert( ( or_gate(List,And) :- sum_list(List,Sum), ( Sum > 0 -> And is 1; And is 0)) ).
?- Mtx = [r(a,b1,b2,c),r(0,1,0,1),r(0,0,1,0),r(1,0,0,1),r(1,1,1,0)],
   mtx_columns_collapse( Mtx, [b1,b2], b, or_gate, 2, OutMtx ).

Mtx = ...
OutMtx = [r(a, b, c), r(0, 0, 1), r(0, 0, 0), r(1, 0, 1), r(1, 1, 0)].
author
- nicos angelopoulos
version
- 0.1 2018/04/27
 mtx_row_apply(+Goal, +MtxIn, -Out, +Opts)
Apply Goal to all rows of MtxIn to produce Out.
If MtxIn and MtxOut are files (ground atoms), the rows are processed on-the-fly with no
intermediate data structures being created. This reduces memory usage which
which used to be prohibitive when using csv_write_file/3 (that has been fixed, but it is more memory efficient to use the specialised version). Goal is called in user by default (use Mod:G, to overwrite this).

Please note that Out would usually be another matrix, however, the predicate can also produce other outputs. You need to set is_mtx(false) in this case, (note thaugh this will also (a) change the default of Hdr to false and (b) by pass calling mtx/2 on the output).

Opts

in_MtxOpt(InpMtxOpt)
any option you want to pass to the input mtx/3 call
on_header(OnH=false)
do not apply Call on header row
out_has_header(Hdr=true)
reply has header (default changes to false, if IsMtx=false)
out_is_mtx(IsMtx=true)
set to false if output is not a matrix
out_MtxOpt(MtxOutOpt)
any option you want to pass to the output mtx/3 call

In addition you can give any option that you want to pass to both mtx/3 calls from those that are recognised by mtx/3 (see mtx_options_select/5). For example, convert(true) will be passed to both mtx/3 calls, whereas in_convert(true) will only be pased to the input call.

?- mtx( data('mtcars.csv'), MtC ), mtx_row_apply( =, MtC, MtA, [] ).
MtC = MtA, MtA = [row(mpg, cyl, disp, hp, drat, wt, qsec, vs, am, gear, carb), row('21.0', ...), ... ].

?- mtx( data('mtcars.csv'), MtC ), mtx_row_apply( =, MtC, MtA, out_has_header(false) ).
MtC = [row(mpg, cyl, disp, hp, drat, wt, qsec, vs, am, gear, carb), row(21.0, ...), ... ],
MtA = [row('21.0', '6.0', '160.0', '110.0', '3.9', '2.62', '16.46', '0.0', '1.0', '4.0', '4.0'), ...].

?- assert((sum_args(Term,Sum) :- Term=..[_|Args], sumlist(Args,Sum))).
?- sum_args( a(1,2,3), Sum ).
Sum = 6.
?- mtx_row_apply(sum_args,data('mtcars.csv'),Sums,[convert(true),out_is_mtx(false)]).
Sums = [328.97999999999996, 329.79499999999996, 259.58, ... ].

?- tmp_file( mtcars_clone, TmpF ), mtx_row_apply( =, data('mtcars.csv', TmpF, [] ).

On *nix only: == ?- library(by_unix). ?- tmp_file( mtcars_clone, TmpF ), mtx_row_apply( =, data('mtcars.csv'), TmpF, [] ), @ head( -2, TmpF ). mpg,cyl,disp,hp,drat,wt,qsec,vs,am,gear,carb 21.0,6.0,160.0,110.0,3.9,2.62,16.46,0.0,1.0,4.0,4.0 TmpF = '/tmp/swipl_mtcars_clone_21824_1'. ===

author
- nicos angelopoulos
version
- 0.1 2018/6/5
- 0.2 2019/2/1, added support for non Mtx outputs: out_has_header() and out_is_mtx(). use mtx_otpions_select/5
See also
- mtx_bi_opts/2, mtx_options_select/5.
 mtx_bi_opts(+BiOpts, +MtxIn, +MtxOut, -InOpts, -OutOpts)
Standarise options when both an input and output matrices are needed.
If MtxIn or MtxOut map to a file matrix, then default separators are via default_separator/3.

Opts

match_in(OutMatch)
to define match option that is specific to input (overrides match/1)
match_out(OutMatch)
to define match option that is specific to ouput (overrides match/1)
sep_in(InSep)
to define sep option that is input specific (overrides sep/1)
sep_out(OutSep)
to define sep option that is output specific (overrides sep/1)
?- mtx_bi_opts( [], true.csv, out.csv, Ins, Outs ).
min([])-sin([])-mou([])-sou([sep(44)])
Ins = [],
Outs = [sep(44)].
author
- nicos angelopoulos
version
- 0.1 2018/6/5
 mtx_column_subsets(+Mtx, +Cid, -Subsets)
Create Value-SubMtx pair list Subsets where Value is each distinct value for column Cid of matrix Mtx. Each SubMtx does not include the header.
?- mtx_column_subsets( [w(c1,c2),w(a,1),w(a,2),w(b,1),w(b,2),w(c,3)], 1, Subs ).
Subs = [a-[w(a, 1), w(a, 2)], b-[w(b, 1), w(b, 2)], c-[w(c, 3)]].
author
- nicos angelopoulos
version
- 0.1 2017/5/8
 mtx_read_stream(+Stream, -Data, +CsvOpts)
 mtx_read_stream(+Row0, +Stream, -Data, CsvOpts)
Read rows from a stream.

This should really be in library(csv).

CsvOpts are Csv specificially compiled options.

?- mtx_read_stream( S, D, O ).
author
- nicos angelopoulos
version
- 0.1 2018/11/12
 mtx_column_join(+MtxBase, +ClmBase, +MtxMatch, -Mtx, +Opts)
Mtx is the join of MtxBase and MtxMatch based on the column values of two columns in those matrices. By default all other columns of MtxMatch are added at the end position and

Opts

add_columns([])
which columns to add (by default all but ClmBase and ClmMatch)
at(At=[])
if an integer, additional columns are added from that position onwards. Alternatively it can be a list of positions to be used. The default is the empty list which is a token for adding the columns at the end.
is_exhaustive(IsExh=false)
should we check that all rows of MtxMatch were used ? if false matched lines are not "consumed"
is_unique(IsUnique=true)
should we check that only a single row matches, true throws a ball, false creates a new row for each matching row and first selects the first matching one (debug(mtx(column_join(multi)) triggers the printing of discarded matching rows))
match_column(ClmMatch)
column id of MtxExt if different that ClmBase
?- assert( mtx1([r(a,b,c),r(1,2,3),r(4,5,6)]) ).
?- assert( mtx2([r(a,e,f),r(1,7,7),r(4,8,8)]) ).
?- mtx1(Mtx1),mtx2(Mtx2),mtx_column_join(Mtx1, a, Mtx2, Mtx, []).
?- mtx1(Mtx1),mtx2(Mtx2),mtx_column_join(Mtx1, a, Mtx2, Mtx, [at(2)]).
author
- nicos angelopoulos
version
- 0.1 2019/1/20
 mtx_options_select(+InOpts, +Pfx, -MtxOpts, -RemOpts)
 mtx_options_select(+InOpts, +Pfx, -MtxOpts, -RemOpts, +Opts)
Helper predicate that separates possibly prefixed and non prefixed options that match to mtx/3 options from Opts producing MtxOpts and RemOpts. RemOpts has anything that did not match.

Default values for mtx/3 are fished out at run-time.

Opts

match_generic(Gen=true)
matches generic version if prefixed version is not there
?- mtx_options_select( [convert(false)], in, Ms, Rs, [] ).
Ms = [convert(false)],
Rs = [].

?- mtx_options_select( [in_convert(false)], in, Ms, Rs, [] ).
Ms = [convert(false)],
Rs = [].

?- mtx_options_select( [convert(false)], in, Ms, Rs, [match_generic(false)] ).
Ms = [],
Rs = [convert(false)].

This could possibly be folded into mtx/3 with prefix(Pfx) and rem_opts(RemOpts), however, it is handy to clean the options before the output call. So the current model is:

mtx_lib_pred( MtxIn, MtxOut, Args ) :-
    options_append( mtx_lib_pred, Args, AllOpts ),
    mtx_options_select( AllOpts, in, InMtxOpts, NonInOpts ),
    mtx( MtxIn, Mtx, InMtxOpts ),
    mtx_options_select( NonInOpts, out, OutMtxOpts, Opts ),
    ...
    mtx( MtxOut, MtxForOut, Opts ).
author
- nicos angelopoulos
version
- 0.1 2019/2/1
See also
- mtx_row_apply/4 for a usage example
 mtx_data(+Set, -Data)
Access tinned example datasets from pack(mtx/data). Data is in canonical Mtx format.

SetName

mtcars
from the mtcars variable in R
 ?- mtx( pack(mtx/data/mtcars), Mtcars ), mtx_data(mtcars, Mtcars).
 Mtcars = [row(mpg, cyl, disp, hp, drat, wt, qsec, vs, am, gear, carb), row(21.0, 6.0, 160.0, 110.0, 3.9, 2.62, 16.46, 0.0, 1.0, 4.0, 4.0), row(21.0, 6.0, 160.0, 110.0, 3.9, 2.875, 17.02, 0.0, 1.0, 4.0, 4.0), row(22.8, 4.0, 108.0, 93.0, 3.85, 2.32, 18.61, 1.0, 1.0, 4.0, 1.0), row(21.4, 6.0, 258.0, 110.0, 3.08, 3.215, 19.44, 1.0, 0.0, 3.0, 1.0), row(18.7, 8.0, 360.0, 175.0, 3.15, 3.44, 17.02, 0.0, 0.0, 3.0, 2.0), row(18.1, 6.0, 225.0, 105.0, 2.76, 3.46, 20.22, 1.0, 0.0, 3.0, 1.0), row(14.3, 8.0, nle.360.0, 245.0, 3.21, 3.57, 15.84, 0.0, 0.0, 3.0, 4.0), row(..., ..., ..., ..., ..., ..., ..., ..., ..., ..., ...)|...]
 mtx_sep_type(+SepType)
True iff SepType is a recognised mtx separator.
author
- nicos angelopoulos
version
- 0.1 2017/06/27
See also
- mtx_sep/2
 mtx_sep(+Sep, -Code)
Code is the code representation (as accepted by csv/4) of the mtx_separator Sep.

Sep can be a code, or one of:

tab
for tab delimeted files
comma
for csvs (comma separated)
space
for space separated files (eg. GOBNILP data files)
author
- nicos angelopoulos
version
- 0.2 2018/03/07, added space
 mtx_version(-Version, -Date)
Current version and release date for pack mtx.

The pack is distributed under the MIT license.

?- mtx_version( Ver, Date ).
Ver = 0:6:0,
Date = date(2021, 6, 17).
author
- nicos angelopoulos
version
- 0.6 2021/6/17
license
- MIT