Search code examples
csvprologprolog-directive-dynamic

Adapting csv reading for multiple tables


I have the following:

:- use_module(library(csv)).
:- dynamic mb/3.
:- dynamic mb_column_keys/1.

prepare_db(File) :-
    retractall(mb_column_keys(_)),
    retractall(mb(_,_,_)),
    forall(read_row(File, Row), store_row(Row)).

store_row(Row) :-
    Row =.. [row|Cols],
    (   mb_column_keys(ColKeys)
    ->  Cols = [RowKey|Samples],
    maplist(store_sample(RowKey), ColKeys, Samples)
    ;   (Cols = [_H|T],assertz(mb_column_keys(T)))
    ).

store_sample(RowKey, ColKey, Sample) :-
    assertz(mb(RowKey, ColKey, Sample)).

read_row(File, Row) :-
     csv_read_file_row(File, Row, []),
     writeln(read_row(Row)).

What is the best way to adapt this so that prepare_db can take two additional arguments to define the predicates for column_keys and mb.

For example ?-prepare_db('my_file.csv',mb_column_keys,mb).

Would result in facts being asserted for mb/3 and mb_column_keys/1

Ok I have changed the file to the following which works:

:- use_module(library(csv)).
:- set_prolog_stack(global, limit(4*10**9)).

prepare_db(File, Column_Key,Relation) :-
     Column_Key_Term =.. [Column_Key,_],
     Relation_Term =.. [Relation,_,_,_],
     retractall(Column_Key_Term),
     retractall(Relation_Term),
     forall(read_row(File, Row), store_row(Row,Column_Key,Relation)).

store_row(Row,Column_Key,Relation) :-
     Column_Key_Test =.. [Column_Key,ColKeys],
     Row =.. [row|Cols],
     (   call(Column_Key_Test)
     ->  Cols = [RowKey|Values],
         maplist(store_relation(Relation,RowKey), ColKeys, Values)
         ;   ( Cols = [_H|T],
               Column_Key_Term =.. [Column_Key,T],
               assertz(Column_Key_Term)
             )
     ).

store_relation(Relation,RowKey, ColKey, Values) :-
     Relation_Term =.. [Relation,RowKey,ColKey,Values],
     assertz(Relation_Term).

read_row(File, Row) :-
    csv_read_file_row(File, Row, []),
    writeln(read_row(Row)).

But it does seem a bit ugly, is there a more elegant way to accomplish this?


Solution

  • Since retractall/1 declares its argument as a dynamic, you could pass a list of predicate Heads to prepare_db, like this:

    prepare_db(File, Heads) :-
        maplist(retractall, Heads),
        % etc
    
    ?- prepare_db('my_file.csv', [mb_column_keys(_) ,mb(_,_,_)]).
    

    And keep in mind that SWI-Prolog at least allows you to call dynamic/1:

    ?- foo(_).
    ERROR: toplevel: Undefined procedure: foo/1 (DWIM could not correct goal)
    ?- dynamic(foo/1).
    true.
    
    ?- foo(_).
    false.
    

    (You would see this is possible if you read between the lines of the footnote to the documentation of retractall/1...)

    As false remarked under your question, there are reasons why it would be still good to declare your dynamic predicates.