1/*  File:    canny/csv.pl
    2    Author:  Roy Ratcliffe
    3    Created: Jan 10 2026
    4    Purpose: Canny CSV
    5
    6Copyright (c) 2026, Roy Ratcliffe, Northumberland, United Kingdom
    7
    8Permission is hereby granted, free of charge,  to any person obtaining a
    9copy  of  this  software  and    associated   documentation  files  (the
   10"Software"), to deal in  the   Software  without  restriction, including
   11without limitation the rights to  use,   copy,  modify,  merge, publish,
   12distribute, sub-license, and/or sell copies  of   the  Software,  and to
   13permit persons to whom the Software is   furnished  to do so, subject to
   14the following conditions:
   15
   16    The above copyright notice and this permission notice shall be
   17    included in all copies or substantial portions of the Software.
   18
   19THE SOFTWARE IS PROVIDED "AS IS", WITHOUT  WARRANTY OF ANY KIND, EXPRESS
   20OR  IMPLIED,  INCLUDING  BUT  NOT   LIMITED    TO   THE   WARRANTIES  OF
   21MERCHANTABILITY, FITNESS FOR A PARTICULAR   PURPOSE AND NONINFRINGEMENT.
   22IN NO EVENT SHALL THE AUTHORS  OR   COPYRIGHT  HOLDERS BE LIABLE FOR ANY
   23CLAIM, DAMAGES OR OTHER LIABILITY,  WHETHER   IN  AN ACTION OF CONTRACT,
   24TORT OR OTHERWISE, ARISING FROM,  OUT  OF   OR  IN  CONNECTION  WITH THE
   25SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.
   26
   27*/
   28
   29:- module(canny_csv,
   30          [ csv_read_file_by_row/3              % +Spec, -Row:list, +Options
   31          ]).   32:- autoload(library(apply), [maplist/3, maplist/4]).   33:- autoload(library(atom), [restyle_identifier/3]).   34:- autoload(library(csv), [csv_read_file_row/3]).   35:- autoload(library(option), [option/3]).

Canny CSV

This module provides predicates for reading CSV files in a memory-efficient manner using Prolog engines. The main predicate, csv_read_file_by_row/3, allows for non-deterministic reading of CSV rows, yielding one row at a time.

author
- Roy Ratcliffe */
 csv_read_file_by_row(+Spec, -Row:list, +Options) is nondet
Extracts records from a CSV file, using the given read Options. The resulting Row terms have fields named after the CSV header columns like an options list.

This predicate uses a Prolog engine to read the CSV file non-deterministically, yielding one Row term at a time. This is useful for processing large CSV files without loading the entire file into memory.

Arguments:
Spec- specifies the CSV file.
Row- is unified with each row.
Options- are passed to csv_read_file_row/3.
   61csv_read_file_by_row(Spec, Row, Options) :-
   62    absolute_file_name(Spec, Path, [extensions([csv])]),
   63    engine_create(Row1, csv_read_file_row(Path, Row1, Options), Engine),
   64    option(functor(Functor), Options, row),
   65
   66    % Naughty but nice. Read the CSV file for the first time to get the header
   67    % row, then again to get each data row, mapping the header columns to field
   68    % names.
   69    engine_next(Engine, Row0),
   70    Row0 =.. [Functor|Columns0],
   71    maplist(restyle_identifier(one_two), Columns0, Columns1),
   72
   73    % Now read each data row and map to row terms non-deterministically. The row
   74    % terms have fields named after the header columns. Note that we use
   75    % engine_next_reified/2 to capture end-of-file and errors. At end-of-file,
   76    % we cut-fail to stop the iteration. On error, we re-throw the error in the
   77    % caller's context. Note the difference betwen =/2 and ==/2 here; they are
   78    % not the same. One tests unification, the other tests identity. Assume that
   79    % the reified term is either: the(Row), no, or throw(Error). Do not allow
   80    % for any other possibilities; delegate that responsibility to the engine.
   81    repeat,
   82    engine_next_reified(Engine, Term),
   83    (   Term = the(Row_)
   84    ->  Row_ =.. [Functor|Columns_],
   85        maplist(csv_read_file_by_row_, Columns1, Columns_, Row)
   86    ;   Term == no
   87    ->  !, fail
   88    ;   Term = throw(Error)
   89    ->  throw(Error)
   90    ).
   91
   92csv_read_file_by_row_(Name, Value, Row) :- Row =.. [Name, Value]