2:- module(csv_wrapper,
    3    [
    4        csv_input_record/2,
    5        csv_input_record/3,
    6        csv_input_records/2,
    7        csv_input_records/3,
    8        csv_is_header/1,
    9        csv_output_record/2,
   10        csv_output_record/3,
   11        csv_output_records/2,
   12        csv_output_records/3
   13    ]).

An Interface for CSV file operations

This is an attempt to define a standard interface for CSV file operations, to be used in different Prolog environments. This module implements this standard for the SWI-Prolog platform.

author
- GT Nunes
version
- 1.3.2
license
- BSD-3-Clause License */
   27%-------------------------------------------------------------------------------------
   28
   29:- use_module(library(apply),
   30    [
   31        convlist/3,
   32        maplist/2,
   33        maplist/3
   34    ]).   35
   36:- use_module(library(csv),
   37    [
   38        csv_read_row/3,
   39        csv_read_stream/3,
   40        csv_write_stream/3
   41    ]).   42
   43%-------------------------------------------------------------------------------------
 csv_input_record(+Stream:ref, +Records:list) is det
Retrieve the next CSV record from Stream.
Arguments:
Stream- The input stream
Record- List of fields
   52csv_input_record(Stream, Record) :-
   53    csv_input_record(Stream, Record, []).
 csv_input_record(+Stream:ref, +Records:list, +CompiledOptions:list) is det
Retrieve the next CSV record from Stream.
Arguments:
Stream- The input stream
Record- List of fields
CompiledOptions- Compiled input options
   63csv_input_record(Stream, Record, CompiledOptions) :-
   64
   65    csv_read_row(Stream, Row, CompiledOptions),
   66    unwrap_row(Row, Record).
   67
   68%-------------------------------------------------------------------------------------
 csv_input_records(+Stream:ref, +Records:list) is det
Retrieve all CSV records from Stream.
Arguments:
Stream- The input stream
Records- List of lists of fields
   77csv_input_records(Stream, Records) :-
   78	csv_input_records(Stream, Records, []).
 csv_input_records(+Stream:ref, +Records:list, +Options:list) is det
Retrieve all CSV records from Stream.
Arguments:
Stream- The input stream
Records- List of lists of fields
Options- Input options
   88csv_input_records(Stream, Records, Options) :-
   89
   90    csv_read_stream(Stream, Rows, Options),
   91    convlist(unwrap_row, Rows, Records).
   92
   93% build a record from the items in a row
   94unwrap_row(Row, Record) :-
   95    Row =.. [_|Record].
   96
   97%-------------------------------------------------------------------------------------
 csv_output_record(+Stream:ref, +Record:list) is det
Write the given CSV record to Stream.
Arguments:
Stream- The output stream
Record- List of fields
  106csv_output_record(Stream, Record) :-
  107    csv_output_record(Stream, Record, []).
 csv_output_record(+Stream:ref, +Record:list, +Options:list) is det
Write the given CSV record to Stream.
Arguments:
Stream- The output stream
Record- List of fields
Options- The output options
  117csv_output_record(Stream, Record, Options) :-
  118
  119    (memberchk(functor(Functor), Options) ; Functor = row),
  120    !,
  121    Row =.. [Functor|Record],
  122    csv_write_stream(Stream, [Row], Options).
  123
  124%-------------------------------------------------------------------------------------
 csv_output_records(+Stream:ref, +Records:list) is det
Write the given CSV records to Stream.
Arguments:
Stream- The output stream
Records- List of lists of fields
  133csv_output_records(Stream, Records) :-
  134	csv_output_records(Stream, Records, []).
 csv_output_records(+Stream:ref, +Records:list, +Options:list) is det
Write the given CSV records to Stream.
Arguments:
Stream- The output stream
Records- List of lists of fields
Options- The output options
  144csv_output_records(Stream, Records, Options) :-
  145    maplist(csv_output_records_(Stream, Options), Records).
  146
  147csv_output_records_(Stream, Options, Record) :-
  148    csv_output_record(Stream, Record, Options).
  149
  150%-------------------------------------------------------------------------------------
 csv_is_header(+Record:list) is semidet
Assert whether all fields in Record may be column names.
Arguments:
Record- List of fields
  158csv_is_header(Record) :-
  159    maplist(is_col_name, Record).
 is_col_name(+Field:data) is semidet
Assert whether Field may be a column name.
Arguments:
Field- The column name candidate
  167is_col_name(Field) :-
  168
  169    % fail points
  170    atom(Field),
  171    atom_length(Field, Len),
  172    Len =< 32