amalgame/commit

rdf11

authorJacco van Ossenbruggen
Sun Mar 29 13:23:26 2020 +0200
committerJacco van Ossenbruggen
Sun Mar 29 13:30:27 2020 +0200
commit60b9503efd80163f337c4f2dd4468b74270df1e3
tree1d4c0ae627ecc91dccc0788998778e7284065266
parent87985e71a2033030ac9dbe95abc8532661de5536
Diff style: patch stat
diff --git a/applications/publisher.pl b/applications/publisher.pl
index 7e2d9f8..60cc565 100644
--- a/applications/publisher.pl
+++ b/applications/publisher.pl
@@ -7,7 +7,7 @@
 :- use_module(library(http/html_head)).
 :- use_module(library(http/html_write)).
 :- use_module(library(http/http_dispatch)).
-:- use_module(library(semweb/rdf_db)).
+:- use_module(library(semweb/rdf11)).
 :- use_module(library(amalgame/ag_publish)).
 :- use_module(library(amalgame/map)).
 :- use_module(components(amalgame/util)).
diff --git a/components/amalgame/startpage.pl b/components/amalgame/startpage.pl
index ccace4a..39400ba 100644
--- a/components/amalgame/startpage.pl
+++ b/components/amalgame/startpage.pl
@@ -7,7 +7,7 @@
 	  ]).
 
 :- use_module(library(option)).
-:- use_module(library(semweb/rdf_db)).
+:- use_module(library(semweb/rdf11)).
 :- use_module(library(http/http_dispatch)).
 :- use_module(library(http/html_head)).
 :- use_module(library(http/html_write)).
diff --git a/components/amalgame/util.pl b/components/amalgame/util.pl
index a1c4502..6babe69 100644
--- a/components/amalgame/util.pl
+++ b/components/amalgame/util.pl
@@ -9,7 +9,7 @@
 :- use_module(library(option)).
 :- use_module(library(http/html_write)).
 :- use_module(library(http/http_dispatch)).
-:- use_module(library(semweb/rdf_db)).
+:- use_module(library(semweb/rdf11)).
 :- use_module(library(semweb/rdf_label)).
 
 :- multifile
diff --git a/lib/amalgame/ag_strategy.pl b/lib/amalgame/ag_strategy.pl
index 9be8834..e075905 100644
--- a/lib/amalgame/ag_strategy.pl
+++ b/lib/amalgame/ag_strategy.pl
@@ -19,13 +19,14 @@
 :- use_module(library(option)).
 :- use_module(library(oset)).
 :- use_module(library(uri)).
-:- use_module(library(semweb/rdf_db)).
+:- use_module(library(semweb/rdf11)).
 :- use_module(library(semweb/rdfs)).
 :- use_module(library(semweb/rdf_label)).
 :- use_module(library(amalgame/util)).
 :- use_module(library(amalgame/map)).
 :- use_module(library(amalgame/ag_provenance)).
 :- use_module(library(amalgame/ag_stats)).
+:- use_module(user(preferences)).
 
 
 :- rdf_meta
@@ -124,7 +125,7 @@ strategy_update_process_parameters(Strategy, Process, SecInputs, Params) :-
 	rdf(Process, rdf:type, Type, Strategy),
 	assert_secondary_inputs(SecInputs, Process, Type, Strategy),
 	rdf_transaction((rdf_retractall(Process, amalgame:parameters, _),
-			 rdf_assert(Process, amalgame:parameters, literal(Search), Strategy)
+			 rdf_assert(Process, amalgame:parameters, Search^^xsd:string, Strategy)
 			)).
 
 
@@ -151,6 +152,7 @@ assert_output(Process, Type, Graph, Input, _, MainOutput) :-
 assert_output(Process, Type, Strategy, Input, SecInputs, Strategy) :-
 	rdfs_subclass_of(Type, amalgame:'OverlapComponent'),
 	!,
+	user_preference(user:lang, literal(Lang)),
 	output_type(Type, OutputClass),
 	oset_power(SecInputs, [[]|PowSet]),
 	forall(member(InSet0, PowSet),
@@ -165,9 +167,9 @@ assert_output(Process, Type, Strategy, Input, SecInputs, Strategy) :-
 		   atomic_list_concat(Nicks, AllNicks),
 		   format(atom(Comment), 'Mappings found only in: ~p', [InSet]),
 		   format(atom(Label), 'Intersect: ~w', [AllNicks]),
-		   rdf_assert(OutputUri, amalgame:overlap_set, literal(InSetAtom), Strategy),
-		   rdf_assert(OutputUri, rdfs:comment, literal(Comment), Strategy),
-		   rdf_assert(OutputUri, rdfs:label, literal(Label), Strategy)
+		   rdf_assert(OutputUri, amalgame:overlap_set, InSetAtom^^xsd:string, Strategy),
+		   rdf_assert(OutputUri, rdfs:comment, Comment@Lang, Strategy),
+		   rdf_assert(OutputUri, rdfs:label, Label@Lang, Strategy)
 	       )
 	      ).
 
@@ -217,7 +219,7 @@ assert_process(Process, Type, Graph, Params) :-
 	uri_query_components(Search, Params),
 	rdf_assert(Process, rdf:type, Type, Graph),
 	rdf_assert(Process, rdfs:label, Label, Graph),
-	rdf_assert(Process, amalgame:parameters, literal(Search), Graph).
+	rdf_assert(Process, amalgame:parameters, Search^^xsd:string, Graph).
 
 new_output(Type, Process, P, Input, Strategy, OutputURI) :-
 	mint_node_uri(Strategy, dataset, OutputURI),
diff --git a/lib/amalgame/hooks/strategy_backward_compatability.pl b/lib/amalgame/hooks/strategy_backward_compatability.pl
index 10a0c4b..a456a48 100644
--- a/lib/amalgame/hooks/strategy_backward_compatability.pl
+++ b/lib/amalgame/hooks/strategy_backward_compatability.pl
@@ -102,13 +102,13 @@ fix_opmv_ns(Strategy) :-
 fix_arity_params(Strategy) :-
 	rdf_equal(amalgame:parameters, ParamProp),
 	findall(rdf(S,ParamProp,O),
-		(   rdf(S,ParamProp, literal(O), Strategy),
+		(   rdf(S,ParamProp, O^^xsd:string, Strategy),
 		    rdfs_individual_of(S, amalgame:'AritySelect')
 		), ToBeFixed),
 	forall(member(rdf(S,P,O), ToBeFixed),
-	       (   rdf_retractall(S,P,literal(O),Strategy),
+	       (   rdf_retractall(S,P,O^^xsd:string,Strategy),
 		   arity_param_convert(O,NewO),
-		   rdf_assert(S,P,literal(NewO), Strategy)
+		   rdf_assert(S,P,NewO^^xsd:string, Strategy)
 	       )
 	      ).