Skip to content

Commit

Permalink
Dump reasonable turtle of schema to http
Browse files Browse the repository at this point in the history
  • Loading branch information
GavinMendelGleason committed Aug 19, 2019
1 parent f92da94 commit e7ba08d
Show file tree
Hide file tree
Showing 5 changed files with 69 additions and 21 deletions.
20 changes: 14 additions & 6 deletions library/api.pl
Original file line number Diff line number Diff line change
Expand Up @@ -61,12 +61,15 @@
% JSON manipulation
:- use_module(library(json_ld)).

% File processing - especially for turtle
:- use_module(library(file_utils), [checkpoint_to_turtle/3]).

%%%%%%%%%%%%% API Paths %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%

%% Set base location
% We may want to allow this as a setting...
http:location(root, '/', []).

%%%%%%%%%%%%% API Paths %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%

:- http_handler(root(.), connect_handler(Method),
[method(Method),
methods([get,post])]).
Expand Down Expand Up @@ -583,17 +586,22 @@
* try_dump_schema(DB_URI, Request) is det.
*
* This should write out to the current stream in the appropriate format.
*
* This is structured in such a way that
*/
try_dump_schema(DB_URI, Request) :-
with_mutex(
DB_URI,
(
try_get_param('terminus:encoding', Request, Encoding),
( Encoding = 'terminus:turtle'
-> true
; Encoding = 'terminus:json_ld'
-> true
; true
-> current_output(Out),
checkpoint_to_turtle(DB_URI, schema, TTL_File),
read_file_to_string(TTL_File, String, []),
format('Content-type: application/turtle~n~n~s', [String])
; format(atom(MSG), 'Unimplemented encoding ~s', [Encoding]),
% Give a better error code etc. This is silly.
throw(http_reply(method_not_allowed('try_dump_schema', MSG)))
)
)
).
Expand Down
51 changes: 41 additions & 10 deletions library/file_utils.pl
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,9 @@
make_checkpoint_directory/3,
ttl_to_hdt/2,
ntriples_to_hdt/2,
cleanup_edinburgh_escapes/1
cleanup_edinburgh_escapes/1,
last_checkpoint_file/3,
checkpoint_to_turtle/3
]).

:- use_module(utils).
Expand Down Expand Up @@ -491,25 +493,54 @@
; true),
close(Out).

/*
* last_checkpoint_file(Collection,File) is det.
*
* Give the file location of the last checkpoint for
* transformation (to turtle json-ld etc).
*/
last_checkpoint_file(C,G,File) :-
current_checkpoint_directory(C,G,CPD),
interpolate([CPD,'/1-ckp.hdt'],File).

/**
* hdt_to_turtle(+FileIn,+FileOut) is det.
* checkpoint_to_turtle(+C,+G,-Output_File) is det.
*
* Create a hdt file from ttl using the rdf2hdt tool.
*/
/*
This does not generate a reasonable header at all.
We can probably do better by dumping to ntriples and then piping through rapper/raptor.
hdt_to_turtle(FileIn,FileOut) :-
process_create(path(hdt2rdf), ['-f','turtle',FileIn,FileOut],
[ stdout(pipe(Out)),
checkpoint_to_turtle(Collection,Graph,Output_File) :-

last_checkpoint_file(Collection,Graph,FileIn),
user:file_search_path(terminus_home, Dir),
get_time(T),floor(T,N),
interpolate([Dir,'/tmp/',N,'.ntriples'],NTriples_File),
process_create(path(hdt2rdf), ['-f','ntriples',FileIn,NTriples_File],
[ stdout(pipe(NT_Out)),
process(PID)
]),
process_wait(PID,Status),
( Status=killed(Signal)
-> interpolate(["hdt2rdf killed with signal ",Signal], M),
throw(error(M))
; true),
close(NT_Out),

get_collection_prefix_list(Collection,List),
prefix_list_to_rapper_args(List,Prefix_Args),
append([['-i','ntriples','-o','turtle'],Prefix_Args,[NTriples_File]], Args),

interpolate([Dir,'/tmp/',N,'.ttl'],Output_File),
open(Output_File, write, Out),

process_create(path(rapper), Args,
[ stderr(null),
stdout(stream(Out)),
process(Rapper_PID)
]),
process_wait(Rapper_PID,Rapper_Status),
( Rapper_Status=killed(Rapper_Signal)
-> interpolate(["hdt2rdf killed with signal ",Rapper_Signal], M),
throw(error(M))
; true),

close(Out).
*/
14 changes: 12 additions & 2 deletions library/prefixes.pl
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,8 @@
get_collection_prefixes/2,
get_collection_prefix_list/2,
global_prefix_expand/2,
literal_expand/2
literal_expand/2,
prefix_list_to_rapper_args/2
]).

/** <module> Prefixes
Expand Down Expand Up @@ -172,11 +173,20 @@
List).

/*
* get_collection_prefixes_list(Collection:atom,Prefixes:dict) is det.
* get_collection_prefix_list(Collection:atom,Prefixes:dict) is det.
*
* return a list of pairs of prefixes.
*/
get_collection_prefix_list(Collection,List) :-
get_collection_prefix_pairs(Collection,Pairs),
maplist([A-B,A=B]>>(true), Pairs, List).

/*
* prefix_list_to_rapper_args(Collection:atom,Prefixes:dict) is det.
*
* return a list of arguments for rapper.
*/
prefix_list_to_rapper_args([],[]).
prefix_list_to_rapper_args([P=U|Rest],['-f',Arg|Arg_Rest]) :-
interpolate(['xmlns:',P,'="',U,'"'],Arg),
prefix_list_to_rapper_args(Rest,Arg_Rest).
5 changes: 2 additions & 3 deletions library/triplestore.pl
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,6 @@
commit/2,
rollback/2,
check_graph_exists/2,
last_plane_number/2,
graph_checkpoint/3,
current_checkpoint_directory/3,
last_checkpoint_number/2,
Expand Down Expand Up @@ -341,11 +340,11 @@
).

/**
* collapse_planes(+Collection_Id,+Graph_Id:graph_identifier) is det.
* checkpoint(+Collection_Id,+Graph_Id:graph_identifier) is det.
*
* Create a new graph checkpoint from our current dynamic triple state
*/
collapse_planes(Collection_Id,Graph_Id) :-
checkpoint(Collection_Id,Graph_Id) :-
make_checkpoint_directory(Collection_Id,Graph_Id, _),
with_output_graph(
graph(Collection_Id,Graph_Id,ckp,ttl),
Expand Down
Empty file added tmp/TMP_DIR
Empty file.

0 comments on commit e7ba08d

Please sign in to comment.