Did you know ... Search Documentation:
Pack mtx -- prolog/mtx.pl
PublicShow source

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

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

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

Undocumented predicates

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

 mtx(Arg1)
 mtx(Arg1, Arg2)
 mtx(Arg1, Arg2, Arg3)
 mtx_dims(Arg1, Arg2, Arg3)
 mtx_lists(Arg1, Arg2)
 mtx_header(Arg1, Arg2)
 mtx_header_body(Arg1, Arg2, Arg3)
 mtx_header_body(Arg1, Arg2, Arg3, Arg4, Arg5)
 mtx_has_header_add(Arg1, Arg2, Arg3, Arg4)
 mtx_header_column_name_pos(Arg1, Arg2, Arg3, Arg4)
 mtx_header_column_pos(Arg1, Arg2, Arg3)
 mtx_header_column_multi_pos(Arg1, Arg2, Arg3, Arg4)
 mtx_relative_pos(Arg1, Arg2, Arg3, Arg4)
 mtx_header_cids_order(Arg1, Arg2, Arg3)
 mtx_name_prefix_column(Arg1, Arg2, Arg3, Arg4, Arg5)
 mtx_column(Arg1, Arg2, Arg3)
 mtx_column(Arg1, Arg2, Arg3, Arg4, Arg5)
 mtx_column_default(Arg1, Arg2, Arg3, Arg4)
 mtx_column_set(Arg1, Arg2, Arg3)
 mtx_column_set(Arg1, Arg2, Arg3, Arg4)
 mtx_column_name_options(Arg1, Arg2, Arg3, Arg4, Arg5)
 mtx_column_name_options(Arg1, Arg2, Arg3)
 mtx_options_select(Arg1, Arg2, Arg3, Arg4)
 mtx_options_select(Arg1, Arg2, Arg3, Arg4, Arg5)
 mtx_column_select(Arg1, Arg2, Arg3, Arg4)
 mtx_columns(Arg1, Arg2, Arg3)
 mtx_columns(Arg1, Arg2, Arg3, Arg4)
 mtx_column_kv(Arg1, Arg2, Arg3)
 mtx_columns_kv(Arg1, Arg2, Arg3, Arg4, Arg5, Arg6)
 mtx_column_add(Arg1, Arg2, Arg3, Arg4)
 mtx_column_replace(Arg1, Arg2, Arg3, Arg4, Arg5)
 mtx_column_replace(Arg1, Arg2, Arg3, Arg4, Arg5, Arg6)
 mtx_column_threshold(Arg1, Arg2, Arg3, Arg4, Arg5)
 mtx_column_threshold(Arg1, Arg2, Arg3, Arg4, Arg5, Arg6)
 mtx_column_frequency_threshold(Arg1, Arg2, Arg3, Arg4, Arg5)
 mtx_column_include_rows(Arg1, Arg2, Arg3, Arg4)
 mtx_column_include_rows(Arg1, Arg2, Arg3, Arg4, Arg5)
 mtx_column_values_select(Arg1, Arg2, Arg3, Arg4, Arg5, Arg6)
 mtx_column_join(Arg1, Arg2, Arg3, Arg4, Arg5)
 mtx_columns_copy(Arg1, Arg2, Arg3, Arg4)
 mtx_columns_partition(Arg1, Arg2, Arg3, Arg4)
 mtx_columns_partition(Arg1, Arg2, Arg3, Arg4, Arg5)
 mtx_rows_partition(Arg1, Arg2, Arg3, Arg4, Arg5)
 mtx_columns_remove(Arg1, Arg2, Arg3)
 mtx_columns_values(Arg1, Arg2, Arg3)
 mtx_value_plot(Arg1, Arg2, Arg3)
 mtx_value_column_frequencies(Arg1, Arg2, Arg3)
 mtx_columns_collapse(Arg1, Arg2, Arg3, Arg4, Arg5, Arg6)
 mtx_columns_cross_table(Arg1, Arg2, Arg3, Arg4, Arg5)
 mtx_pos_elem(Arg1, Arg2, Arg3, Arg4, Arg5)
 mtx_pos_elem(Arg1, Arg2, Arg3, Arg4, Arg5, Arg6)
 mtx_apply(Arg1, Arg2, Arg3, Arg4)
 mtx_row_apply(Arg1, Arg2, Arg3, Arg4)
 mtx_factors(Arg1, Arg2, Arg3)
 mtx_transpose(Arg1, Arg2)
 mtx_prolog(Arg1, Arg2)
 mtx_prolog(Arg1, Arg2, Arg3)
 mtx_sort(Arg1, Arg2, Arg3)
 mtx_sort(Arg1, Arg2, Arg3, Arg4)
 mtx_type(Arg1, Arg2)
 mtx_bi_opts(Arg1, Arg2, Arg3, Arg4, Arg5)
 mtx_column_subsets(Arg1, Arg2, Arg3)
 mtx_read_table(Arg1, Arg2, Arg3, Arg4)
 mtx_read_stream(Arg1, Arg2, Arg3)
 mtx_read_stream(Arg1, Arg2, Arg3, Arg4)
 mtx_facts(Arg1)
 mtx_facts(Arg1, Arg2)
 mtx_facts(Arg1, Arg2, Arg3)
 mtx_facts_remove(Arg1)
 mtx_in_memory(Arg1)
 mtx_in_memory(Arg1, Arg2)
 mtx_matrices_in_memory(Arg1)