:- module(csvrdf, [load_csv_as_rdf/2, flush_table_map/1 ]). :- use_module(library(csv)). :- use_module(library(semweb/rdf_db)). :- dynamic table_map/3. %% load_csv_as_rdf(+Input, +Options) % % % * graph(+Graph) % RDF Graph for storing the output. Default is =data= % % * prefix(+Prefix) % Create a URI from the column header name by putting Prefix % in front of it. Also used for the class. If no prefix is % defined the name in the column header is used. % % * class(+ClassName) % ClassName given to each row % % * see options for csv/2 load_csv_as_rdf(File, Options) :- flush_table_map(File), option(graph(Graph), Options, data), option(prefix(Prefix), Options, _), csv_read_file(File, [Header|Content], Options), length(Content, Length), debug(csvrdf, '~w rows', [Length]), create_table_map(Header, Prefix, File), class_name(Prefix, Class, Options), write_rows(Content, Class, File, Graph). write_rows([], _, _, _). write_rows([Row|Rows], Class, Table, Graph) :- Row =.. [_|Cs], rdf_bnode(BNode), ( nonvar(Class) -> rdf_assert(BNode, rdf:type, Class, Graph) ; true ), write_props(Cs, 0, BNode, Table, Graph), write_rows(Rows, Class, Table, Graph). write_props([], _, _, _, _). write_props([V|Vs], N, S, Table, Graph) :- N1 is N+1, ( V = '' -> true ; table_map(Table, N1, P) -> value_assert(S, P, V, Graph) ; true ), write_props(Vs, N1, S, Table, Graph). value_assert(S, P, V, Graph) :- ( number(V) -> atom_number(A, V) ; A = V ), rdf_assert(S, P, literal(V), Graph). %% create_table_map(+Header, +TableMapId) % % create_table_map(Header, Prefix, Table) :- Header =.. [_|Cols], create_table_map_(Cols, 0, Prefix, Table). create_table_map_([], _, _, _). create_table_map_([C|Cs], N, Prefix, Table) :- N1 is N + 1, downcase_atom(C, PName), ( var(Prefix) -> P = PName ; atom_concat(Prefix, PName, P) ), assert(table_map(Table, N1, P)), create_table_map_(Cs, N1, Prefix, Table). %% class_name(+Prefix, -Class, Options) class_name(Prefix, Class, Options) :- option(class(ClassName), Options), !, ( var(Prefix) -> Class = ClassName ; atom_concat(Prefix, ClassName, Class) ). class_name(_, _Class, _). capitalise(X, Y) :- atom_codes(X, [H0|T]), code_type(H0, to_lower(H)), atom_codes(Y, [H|T]). flush_table_map(Table) :- retractall(table_map(Table, _, _)).