Skip to content

Commit

Permalink
Merge branch 'dev' of github.com:terminusdb/terminus-server into dev
Browse files Browse the repository at this point in the history
  • Loading branch information
rrooij committed Nov 18, 2019
2 parents 2257c9e + 5323b72 commit 6e079ec
Show file tree
Hide file tree
Showing 26 changed files with 140 additions and 134 deletions.
22 changes: 11 additions & 11 deletions library/api.pl
Original file line number Diff line number Diff line change
Expand Up @@ -47,37 +47,37 @@
:- use_module(library(http/http_authenticate)).

% Load capabilities library
:- use_module(library(capabilities)).
:- use_module(capabilities).

% woql libraries
:- use_module(library(woql_compile)).
:- use_module(woql_compile).

% Default utils
:- use_module(library(utils)).
:- use_module(utils).

% Database utils
:- use_module(library(database_utils)).
:- use_module(database_utils).

% Database construction utils
:- use_module(library(database)).
:- use_module(database).

% Frame and document processing
:- use_module(library(frame)).
:- use_module(frame).

% JSON manipulation
:- use_module(library(jsonld)).
:- use_module(jsonld).

% JSON Queries
:- use_module(library(json_woql)).
:- use_module(json_woql).

% File processing
:- use_module(library(file_utils), [terminus_path/1]).
:- use_module(file_utils, [terminus_path/1]).

% Validation
:- use_module(library(validate)).
:- use_module(validate).

% Dumping turtle
:- use_module(library(turtle_utils)).
:- use_module(turtle_utils).

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

Expand Down
16 changes: 8 additions & 8 deletions library/capabilities.pl
Original file line number Diff line number Diff line change
Expand Up @@ -38,14 +38,14 @@

:- use_module(config(config),[]).
:- use_module(library(crypto)).
:- use_module(library(utils)).
:- use_module(library(file_utils)).
:- use_module(library(triplestore)).
:- use_module(library(frame)).
:- use_module(library(jsonld)).
:- use_module(library(database)).
:- use_module(library(database_utils)).
:- use_module(library(sdk)).
:- use_module(utils).
:- use_module(file_utils).
:- use_module(triplestore).
:- use_module(frame).
:- use_module(jsonld).
:- use_module(database).
:- use_module(database_utils).
:- use_module(sdk).
:- op(1050, xfx, =>).

/**
Expand Down
6 changes: 3 additions & 3 deletions library/casting.pl
Original file line number Diff line number Diff line change
Expand Up @@ -26,9 +26,9 @@
* *
* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * */

:- use_module(library(utils)).
:- use_module(library(prefixes)).
:- use_module(library(speculative_parse)).
:- use_module(utils).
:- use_module(prefixes).
:- use_module(speculative_parse).

:- use_module(library(apply)).
:- use_module(library(yall)).
Expand Down
2 changes: 1 addition & 1 deletion library/database.pl
Original file line number Diff line number Diff line change
Expand Up @@ -174,7 +174,7 @@
DB_Resource, terminus:id, literal(type(_,Database_Name)))),
Database_Names),

maplist(string_to_atom, Database_Names, Database_Atomised),
maplist(atom_string, Database_Atomised, Database_Names),
exclude(terminus_database_name, Database_Atomised, Database_Atoms).

database_record_list(Databases) :-
Expand Down
10 changes: 5 additions & 5 deletions library/database_utils.pl
Original file line number Diff line number Diff line change
Expand Up @@ -31,11 +31,11 @@
* *
* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * */

:- use_module(library(file_utils)).
:- use_module(library(triplestore)).
:- use_module(library(utils)).
:- use_module(library(database)).
:- use_module(library(expansions)).
:- use_module(file_utils).
:- use_module(triplestore).
:- use_module(utils).
:- use_module(database).
:- use_module(expansions).

/*
* database_exists(DB_URI) is semidet.
Expand Down
2 changes: 1 addition & 1 deletion library/expansions.pl
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@
* *
* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * */

:- use_module(library(global_prefixes)).
:- use_module(global_prefixes).

% xrdf/5
user:goal_expansion(xrdf(DB,G,A,Y,Z),xrdf(DB,G,X,Y,Z)) :-
Expand Down
2 changes: 1 addition & 1 deletion library/file_utils.pl
Original file line number Diff line number Diff line change
Expand Up @@ -146,7 +146,7 @@
*/
excluded_file(File) :-
% emacs files
atom_concat('.#', _, File).
sub_atom(File, 0, _, _, '.#').
excluded_file(File) :-
% current directory and parent directory
member(File, ['.','..']).
Expand Down
26 changes: 13 additions & 13 deletions library/frame.pl
Original file line number Diff line number Diff line change
Expand Up @@ -54,19 +54,19 @@
* *
* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * */

:- use_module(library(utils)).
:- use_module(library(base_type)).
:- use_module(library(triplestore)).
:- use_module(library(validate_schema), except([document/2])).
:- use_module(library(validate_instance)).
:- use_module(library(inference)).
:- use_module(library(database)).
:- use_module(library(schema), []).
:- use_module(library(types)).
:- use_module(library(frame_types)).
:- use_module(library(jsonld)).
:- use_module(library(prefixes)).
:- use_module(library(expansions)).
:- use_module(utils).
:- use_module(base_type).
:- use_module(triplestore).
:- use_module(validate_schema, except([document/2])).
:- use_module(validate_instance).
:- use_module(inference).
:- use_module(database).
:- use_module(schema, []).
:- use_module(types).
:- use_module(frame_types).
:- use_module(jsonld).
:- use_module(prefixes).
:- use_module(expansions).

:- use_module(library(apply)).
:- use_module(library(yall)).
Expand Down
8 changes: 4 additions & 4 deletions library/inference.pl
Original file line number Diff line number Diff line change
Expand Up @@ -25,10 +25,10 @@
* *
* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * */

:- use_module(library(database)).
:- use_module(library(validate_schema)).
:- use_module(library(triplestore)).
:- use_module(library(expansions)).
:- use_module(database).
:- use_module(validate_schema).
:- use_module(triplestore).
:- use_module(expansions).

/**
* runChain(?X,?P:list(uri),?Y,+Instance:atom,+Database:database is nondet.
Expand Down
12 changes: 6 additions & 6 deletions library/json_woql.pl
Original file line number Diff line number Diff line change
Expand Up @@ -27,8 +27,8 @@
* *
* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * */

:- use_module(library(utils)).
:- use_module(library(jsonld)).
:- use_module(utils).
:- use_module(jsonld).

:- use_module(library(apply)).
:- use_module(library(yall)).
Expand Down Expand Up @@ -212,7 +212,7 @@
WOQL = not(WQ)
; _{'http://terminusdb.com/woql#as' : [ S, V ] } :< JSON
-> ( _{'@value' : WS} :< S
-> string_to_atom(WS,WA),
-> atom_string(WA,WS),
json_to_woql_ast(V,WV),
WOQL = as(WA,WV)
; throw(http_reply(not_found(_{'@type' : 'vio:WOQLSyntaxError',
Expand All @@ -228,11 +228,11 @@
-> WOQL = '@'(V,L)
; _{'http://terminusdb.com/woql#value' : V, '@type' : T } :< JSON
-> json_to_woql_ast(V,VE),
string_to_atom(T,TE),
atom_string(TE,T),
WOQL = '^^'(VE,TE)
; _{'http://terminusdb.com/woql#value' : V, '@lang' : L } :< JSON
-> json_to_woql_ast(V,VE),
string_to_atom(L,LE),
atom_string(LE,L),
WOQL = '@'(VE,LE)
; _{'@id' : ID } :< JSON
-> json_to_woql_ast(ID,WOQL)
Expand All @@ -258,7 +258,7 @@
'terminus:status' : 'terminus:failure'}))).

is_json_var(A) :-
atom_concat('http://terminusdb.com/woql/variable/',_,A).
sub_atom(A, 0, _, _, 'http://terminusdb.com/woql/variable/').

json_to_woql_arith(JSON,WOQL) :-
is_dict(JSON),
Expand Down
6 changes: 3 additions & 3 deletions library/jsonld.pl
Original file line number Diff line number Diff line change
Expand Up @@ -36,11 +36,11 @@
* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * */

:- use_module(library(pairs)).
:- use_module(library(utils)).
:- use_module(utils).
:- use_module(library(http/json)).
% Currently a bug in groundedness checking.
%:- use_module(library(mavis)).
:- use_module(library(database)).
:- use_module(database).

% efficiency
:- use_module(library(apply)).
Expand Down Expand Up @@ -234,7 +234,7 @@
-> ( is_dict(R)
-> Key = Key_Candidate,
Value = R
; string_to_atom(R,Key),
; atom_string(Key,R),
Value = _{})
; Key = Key_Candidate,
Value = _{}).
Expand Down
2 changes: 1 addition & 1 deletion library/literals.pl
Original file line number Diff line number Diff line change
Expand Up @@ -147,4 +147,4 @@
-> ( atom(O)
-> atom_string(O,S)
; O = S)
; string_to_atom(S,O)).
; atom_string(O,S)).
12 changes: 6 additions & 6 deletions library/prefixes.pl
Original file line number Diff line number Diff line change
Expand Up @@ -38,8 +38,8 @@
* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * */

% Import global definitions
:- use_module(library(global_prefixes)).
:- reexport(library(global_prefixes)).
:- use_module(global_prefixes).
:- reexport(global_prefixes).

% Use prolog persistency for prefix management.
% We could use the DB itself but this gets a bit too metacircular!
Expand All @@ -48,15 +48,15 @@
% Set up the database style
:- persistent prefix(collection:atom,prefix:atom,uri:atom).

:- use_module(library(file_utils)).
:- use_module(library(utils)).
:- use_module(file_utils).
:- use_module(utils).

% JSON manipulation
:- use_module(library(http/json)).

:- use_module(library(jsonld)).
:- use_module(jsonld).

:- use_module(library(database), [
:- use_module(database, [
database_name_list/1,
terminus_database_name/1
]).
Expand Down
8 changes: 4 additions & 4 deletions library/relationships.pl
Original file line number Diff line number Diff line change
Expand Up @@ -28,10 +28,10 @@
* *
* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * */

:- use_module(library(utils)).
:- use_module(library(validate_schema)).
:- use_module(library(database)).
:- use_module(library(triplestore)).
:- use_module(utils).
:- use_module(validate_schema).
:- use_module(database).
:- use_module(triplestore).
:- use_module(library(semweb/rdf_db)).

relationship_source_property(Relationship,Property,Database) :-
Expand Down
12 changes: 6 additions & 6 deletions library/schema.pl
Original file line number Diff line number Diff line change
Expand Up @@ -28,12 +28,12 @@
* *
* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * */

:- use_module(library(prefixes), [global_prefix_expand/2]).
:- use_module(library(database)).
:- use_module(library(triplestore)).
:- use_module(library(schema_definitions)).
:- use_module(library(schema_util)).
:- use_module(library(utils)).
:- use_module(prefixes, [global_prefix_expand/2]).
:- use_module(database).
:- use_module(triplestore).
:- use_module(schema_definitions).
:- use_module(schema_util).
:- use_module(utils).

:- reexport(schema_util).

Expand Down
8 changes: 4 additions & 4 deletions library/schema_util.pl
Original file line number Diff line number Diff line change
Expand Up @@ -31,10 +31,10 @@
* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * */


:- use_module(library(utils), [intersperse/3]).
:- use_module(library(database)).
:- use_module(library(types)).
:- use_module(library(schema_definitions)).
:- use_module(utils, [intersperse/3]).
:- use_module(database).
:- use_module(types).
:- use_module(schema_definitions).

/*
* database_module(+Database:database, -Module:atom) is det.
Expand Down
8 changes: 4 additions & 4 deletions library/sdk.pl
Original file line number Diff line number Diff line change
Expand Up @@ -27,10 +27,10 @@
* *
* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * */

:- use_module(library(utils)).
:- use_module(library(database)).
:- use_module(library(woql_compile)).
:- use_module(library(woql_term)).
:- use_module(utils).
:- use_module(database).
:- use_module(woql_compile).
:- use_module(woql_term).

:- reexport(woql_term).

Expand Down
2 changes: 1 addition & 1 deletion library/skolemise.pl
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,7 @@
:- use_module(library(apply)).
:- use_module(library(yall)).
:- use_module(library(apply_macros)).
:- use_module(library(triplestore)).
:- use_module(triplestore).

/*
* blank_node(+URI) is det.
Expand Down
14 changes: 7 additions & 7 deletions library/triplestore.pl
Original file line number Diff line number Diff line change
Expand Up @@ -17,14 +17,14 @@
except([create_named_graph/3,
open_named_graph/3])).

:- use_module(library(file_utils)).
:- use_module(library(utils)).
:- use_module(library(schema), [cleanup_schema_module/1]).
:- use_module(library(prefixes)).
:- use_module(library(types)).
:- use_module(file_utils).
:- use_module(utils).
:- use_module(schema, [cleanup_schema_module/1]).
:- use_module(prefixes).
:- use_module(types).
% feeling very circular :(
:- use_module(library(database)).
:- use_module(library(literals)).
:- use_module(database).
:- use_module(literals).

:- use_module(library(apply)).
:- use_module(library(yall)).
Expand Down
4 changes: 2 additions & 2 deletions library/turtle_utils.pl
Original file line number Diff line number Diff line change
Expand Up @@ -25,8 +25,8 @@
* *
* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * */

:- use_module(library(prefixes)).
:- use_module(library(triplestore)).
:- use_module(prefixes).
:- use_module(triplestore).
:- use_module(library(semweb/turtle)).

/**
Expand Down

0 comments on commit 6e079ec

Please sign in to comment.