1:- module( mtx, [ 2 mtx/1, mtx/2, mtx/3, % +Mtx,[?Canonical,[+Opts 3 mtx_data/2, mtx_dims/3, 4 % 5 mtx_lists/2, 6 mtx_header/2, mtx_header_body/3, mtx_header_body/5, 7 mtx_has_header_add/4, 8 mtx_header_column_name_pos/4, mtx_header_column_pos/3, 9 mtx_header_column_multi_pos/4, mtx_relative_pos/4, 10 mtx_header_cids_order/3, 11 mtx_name_prefix_column/5, 12 mtx_column/3, mtx_column/5, mtx_column_default/4, 13 mtx_column_set/3, mtx_column_set/4, 14 mtx_column_name_options/5, mtx_column_name_options/3, 15 mtx_options_select/4, mtx_options_select/5, 16 mtx_column_select/4, 17 mtx_columns/3,mtx_columns/4,mtx_column_kv/3,mtx_columns_kv/6, 18 mtx_column_add/4, 19 mtx_column_replace/5, mtx_column_replace/6, 20 mtx_column_threshold/5, mtx_column_threshold/6, 21 mtx_column_frequency_threshold/5, 22 mtx_column_include_rows/4, mtx_column_include_rows/5, % +Mtx, +Cid, +Call, -Incl,[+Opts] 23 mtx_column_values_select/6, 24 mtx_column_join/5, % +MtxBase, +Column, +MtxExt, -MtxOut, +Opts 25 mtx_columns_copy/4, 26 mtx_columns_partition/4, mtx_columns_partition/5, 27 mtx_rows_partition/5, 28 mtx_columns_remove/3, 29 mtx_columns_values/3, 30 mtx_value_plot/3, 31 mtx_value_column_frequencies/3, 32 mtx_columns_collapse/6, % +MtxIn, +Cids, +Cnm, +RowGoal, +Pos, -Mtx 33 mtx_columns_cross_table/5, 34 mtx_pos_elem/5, mtx_pos_elem/6, 35 mtx_apply/4, 36 mtx_row_apply/4, 37 mtx_factors/3, mtx_transpose/2, 38 mtx_prolog/2, mtx_prolog/3, % ?Mtx, ?Pl[, +Opts] 39 mtx_sort/3, mtx_sort/4, mtx_type/2, 40 mtx_sep_type/1, mtx_sep/2, 41 mtx_bi_opts/5, 42 mtx_column_subsets/3, 43 % 44 mtx_read_table/4, % +CsvF, +RowsName, -Table, +Opts 45 mtx_read_stream/3, mtx_read_stream/4, % [+Row0], +Stream, -Data, +CsvOpts 46 % 47 mtx_facts/1, mtx_facts/2, mtx_facts/3, % +CsvF,[?Module,[+Opts]] 48 mtx_facts_remove/1, % 49 mtx_in_memory/1, mtx_in_memory/2, 50 mtx_matrices_in_memory/1, 51 % 52 mtx_version/2 53 ] 54 ). 55 56 57% auto-load libraries 58:- use_module(library(lists)). 59:- use_module(library(apply)). 60:- use_module(library(option)). % select_option/3. 61:- use_module(library(filesex)). 62 63:- use_module(library(lib)). 64:- lib( source(mtx), homonyms(true) ). 65 66:- lib(debug). % this is auto-load, keeping here to encourage usage. 67 % src/mtx.pl has started using debug/3. use mtx(Pname), also move to pack(debug_call) 68 69:- lib(os_lib). 70:- lib(options). 71:- lib(pack_errors). 72:- lib(stoics_lib). 73 74:- dynamic( mtx:mtx_data_store/2 ). 75:- dynamic( mtx:mtx_data_handle_file/2 ). 76 77:- lib(alias_data/0). 78:- alias_data. 79 80:- lib(mtx/1). 81:- lib(mtx_column_kv/3). 82:- lib(mtx_header/2). 83:- lib(mtx_header_body/3). 84:- lib(mtx_has_header_add/4). 85:- lib(mtx_header_column_name_pos/4). 86:- lib(mtx_header_column_pos/3). 87:- lib(mtx_header_column_multi_pos/4). 88:- lib(mtx_in_memory/2). 89:- lib(mtx_matrices_in_memory/1). 90:- lib(mtx_sort/3). 91:- lib(mtx_facts/3). 92:- lib(mtx_column_add/4). 93:- lib(mtx_column/3). 94:- lib(mtx_column_default/4). 95:- lib(mtx_column_name_options/3). 96:- lib(mtx_column_name_options/5). 97:- lib(mtx_column_include_rows/4). 98:- lib(mtx_column_select/4). 99:- lib(mtx_column_threshold/5). 100:- lib(mtx_column_frequency_threshold/5). 101:- lib(mtx_column_replace/5). 102:- lib(mtx_column_values_select/6). 103:- lib(mtx_name_prefix_column/5). 104:- lib(mtx_relative_pos/4). 105:- lib(mtx_lists/2). 106:- lib(mtx_transpose/2). 107:- lib(mtx_factors/3). 108:- lib(mtx_columns_copy/4). 109:- lib(mtx_columns_kv/6). 110:- lib(mtx_header_cids_order/3). 111:- lib(mtx_columns_remove/3). 112:- lib(mtx_dims/3). 113:- lib(mtx_prolog/3). 114:- lib(mtx_columns_partition/5). 115:- lib(mtx_rows_partition/5). 116:- lib(mtx_columns_values/3). 117:- lib(mtx_value_plot/3). 118:- lib(mtx_value_column_frequencies/3). 119:- lib(mtx_columns_cross_table/5). 120:- lib(mtx_errors/0). 121:- lib(mtx_pos_elem/5). 122:- lib(mtx_apply/4). 123:- lib(mtx_type/2). 124:- lib(mtx_read_table/4). 125:- lib(mtx_columns_collapse/6). 126:- lib(mtx_row_apply/4). 127:- lib(mtx_bi_opts/5). 128:- lib(mtx_column_subsets/3). 129:- lib(mtx_read_stream/4). 130:- lib(mtx_column_join/5). 131:- lib(mtx_options_select/5). 132 133:- lib(end(mtx)).
pack(mtx/data)
.
Data is in canonical Mtx format.
SetName
?- 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(..., ..., ..., ..., ..., ..., ..., ..., ..., ..., ...)|...]
254mtx_data( mtcars, Mtcars ) :-
255 mtx( pack(mtx/data/mtcars), Mtcars ).
266mtx_sep_type( Sep ) :-
267 mtx_sep( Sep, _ ).
Sep can be a code, or one of:
288mtx_sep( Sep, Code ) :- 289 mtx_sep_known( Sep, Code ), 290 !. 291mtx_sep( Code, Code ) :- 292 integer( Code ). % fixme: better check ? 293 294mtx_sep_known( tab, 0'\t ). 295mtx_sep_known( comma, 0', ). 296mtx_sep_known( space, 0' ).
mtx
.
The pack is distributed under the MIT license.
?- mtx_version( Ver, Date ). Ver = 0:6:0, Date = date(2021, 6, 17).
315% mtx_version( 0:1:0, date(2018,4,2) ). 316% mtx_version( 0:2:0, date(2018,6,5) ). 317% mtx_version( 0:3:0, date(2019,4,18) ). 318% mtx_version( 0:4:0, date(2019,4,22) ). 319% mtx_version( 0:5:0, date(2020,3,18) ). 320mtx_version( 0:6:0, date(2021,6,17) ).% option:row_call()
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>
Where
mtcars.csv
is in some pack's data directory.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.
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 formatch_arity(Match)
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
Good starting points are the documentation for mtx/1, mtx/2 and mtx/3.
row_call(RowC)
*/
debug(mtx(Pred))
messages (seesrc/mtx.pl
for a start on this)