amalgame/commit

REFACTORING: mv strategy structure manipulation from api to lib

authorJacco van Ossenbruggen
Sun Sep 7 09:18:08 2014 +0200
committerJacco van Ossenbruggen
Sun Sep 7 09:18:08 2014 +0200
commitcf4cfae3cfd04dd3cc3a8359f902923ea11c571d
tree917620f2f74f900ac27f8465de6f1cca789710ef
parent6741270a2fd86ef9e0e117ed72868af94c048b43
Diff style: patch stat
diff --git a/api/ag_process.pl b/api/ag_process.pl
index e3195b8..89329c2 100644
--- a/api/ag_process.pl
+++ b/api/ag_process.pl
@@ -3,26 +3,21 @@
 	  ]).
 
 :- use_module(library(lists)).
-:- use_module(library(option)).
-:- use_module(library(oset)).
 :- use_module(library(settings)).
-:- use_module(library(uri)).
 
 :- use_module(library(http/http_dispatch)).
 :- use_module(library(http/http_parameters)).
 :- use_module(library(http/http_json)).
 :- use_module(library(semweb/rdf_db)).
 :- use_module(library(semweb/rdfs)).
-
-:- use_module(library(semweb/rdf_label)).
 :- use_module(user(user_db)).
 
 :- use_module(library(amalgame/expand_graph)).
 :- use_module(library(amalgame/caching)).
 :- use_module(library(amalgame/ag_provenance)).
-:- use_module(library(amalgame/util)).
+:- use_module(library(amalgame/ag_strategy)).
 :- use_module(library(amalgame/json_util)).
-:- use_module(library(amalgame/map)).
+
 
 :- setting(amalgame:precompute, boolean, true,
 	   'When true (default) new mappings and virtual vocabularies are pre-computed in the background').
@@ -31,11 +26,6 @@
 :- http_handler(amalgame(data/updatenode), http_update_node, []).
 :- http_handler(amalgame(data/deletenode), http_delete_node, []).
 
-:- rdf_meta
-	new_output(r,r,r,r,r,r),
-	assert_output(r,r,r,r,r,r),
-	output_type(r,r).
-
 %%	http_add_process(+Request)
 %
 %
@@ -72,7 +62,12 @@ http_add_process(Request) :-
 	findall(secondary_input=S,member(secondary_input=S, Params1), SecParams),
 	subtract(Params1, SecParams, Params),
 	fix_not_expanded_options(Params, ExpandedParams),
-	new_process(Process, Strategy, Source, Target, Input, SecInputs, ExpandedParams, Focus),
+	flush_refs_cache_if_needed(Process),
+	strategy_new_process(Strategy, Process, Source, Target, Input, SecInputs, ExpandedParams, Focus, URI),
+	% precompute results to speed things up
+	(   setting(amalgame:precompute, true)
+	->  precompute_process(Strategy, URI)
+	;   true),
 	js_focus_node(Strategy, Focus, FocusNode),
 	js_strategy_nodes(Strategy, Nodes),
 	reply_json(json{focus:FocusNode,
@@ -102,9 +97,10 @@ http_update_node(Request) :-
 			],
 			[form_data(Params)
 			]),
-	rdf_transaction(update_node_props(Params, URI, Strategy)),
+	strategy_update_node(Strategy, Params, URI),
 	update_amalgame_prov(Strategy, URI),
 	change_ns_if_needed(PublishNS, URI, Strategy, NewStrategy),
+	flush_deps_if_needed(Strategy, URI, Params),
 	js_strategy_nodes(NewStrategy, Nodes),
 	js_focus_node(NewStrategy, URI, FocusNode),
 
@@ -134,211 +130,13 @@ http_delete_node(Request) :-
 				[uri,
 				 description('URI of input resource')])
 			]),
-	rdf_transaction((process_retract(URI, Strategy),
-			 node_retract(URI, Strategy)
-			)),
+	strategy_delete_node(Strategy, URI),
 	js_strategy_nodes(Strategy, Nodes),
 	js_focus_node(Strategy, Strategy, FocusNode),
 	reply_json(json{nodes:Nodes,
 			focus:FocusNode
 		       }).
 
-is_dependent_chk(Mapping, Process, Strategy) :-
-	rdf_has(Mapping, amalgame:wasGeneratedBy, Process, RP),
-	rdf(Mapping, RP, Process, Strategy),
-	!.
-is_dependent_chk(Mapping, Process, Strategy) :-
-	rdf_has(Mapping, amalgame:wasGeneratedBy, OtherProcess, RP1),
-	rdf(Mapping, RP1, OtherProcess, Strategy),
-	rdf_has(OtherProcess, amalgame:input, OtherMapping, RP2),
-	rdf(OtherProcess, RP2, OtherMapping, Strategy),
-	is_dependent_chk(OtherMapping, Process, Strategy),!.
-
-
-%%	new_process(+Process, +Strategy, +Source, +Target, +Input,
-%%	+SecInputs, +Params, -NewFocus)
-%
-%	Create new amalgame process.
-
-new_process(Type, Strategy, Source, Target, Input, SecInputs, Params, Focus) :-
-	% hack needed till we have nested rdf transactions:
-	retractall(ag_map:nickname_cache(Strategy,_,_)),
-
-	rdf_bnode(URI),
-	rdf_transaction( % this rdf_transaction is to make it MT safe
-	    (	assert_process(URI, Type, Strategy, Params),
-		assert_user_provenance(URI, Strategy),
-		assert_input(URI, Type, Strategy, Source, Target, Input, Params),
-		assert_secondary_inputs(SecInputs, URI, Type, Strategy),
-		assert_output(URI, Type, Strategy, Input, SecInputs, Focus)
-	    )),
-
-	% precompute results to speed things up
-	(   setting(amalgame:precompute, true)
-	->  precompute_process(Strategy, URI)
-	;   true).
-
-assert_input(_Process, Type, _Graph, _Source, _Target, _Input, _Params) :-
-	rdfs_subclass_of(Type, amalgame:'MultiInputComponent'),
-	!.
-assert_input(Process, Type, Graph, Source, Target, _Input, Params) :-
-	nonvar(Source),
-	nonvar(Target),
-	!,
-	rdf_assert(Process, amalgame:source, Source, Graph),
-	rdf_assert(Process, amalgame:target, Target, Graph),
-	assert_preloaded_input(Process, Type, Graph, Params).
-assert_input(Process, Type, Graph, _Source, _Target, Input, Params) :-
-	nonvar(Input),
-	!,
-	rdf_assert(Process, amalgame:input, Input, Graph),
-	assert_preloaded_input(Process, Type, Graph, Params).
-
-assert_preloaded_input(Process, Type, Graph, Params) :-
-	(   rdfs_subclass_of(Type, amalgame:'SelectPreLoaded'),
-	    option(name(Name), Params)
-	->  rdf_assert(Process, amalgame:input, Name, Graph),
-	    rdf_assert(Name, amalgame:status, amalgame:reference, Graph),
-	    rdf_assert(Name, rdf:type, amalgame:'LoadedMapping', Graph),
-	    flush_refs_cache(Graph)
-	;   true
-	).
-
-assert_secondary_inputs([], _, _, _).
-assert_secondary_inputs([URI|URIs], Process, Type, Strategy) :-
-	(   rdfs_subclass_of(Type, amalgame:'SetOperator')
-	->  rdf_equal(Pred, amalgame:input)
-	;   rdf_equal(Pred, amalgame:secondary_input)
-	),
-	(   is_dependent_chk(URI, Process, Strategy)
-	->  debug(eq, 'Not adding secondary input ~p, it will lead to cyclic dependency on process ~p', [URI, Process])
-	;   rdf_assert(Process, Pred, URI, Strategy)
-	),
-	assert_secondary_inputs(URIs, Process, Type, Strategy).
-
-assert_process(Process, Type, Graph, Params) :-
-	process_label(Type, Label),
-	uri_query_components(Search, Params),
-	rdf_assert(Process, rdf:type, Type, Graph),
-	rdf_assert(Process, rdfs:label, literal(Label), Graph),
-	rdf_assert(Process, amalgame:parameters, literal(Search), Graph).
-
-assert_output(Process, Type, Graph, Input, _, MainOutput) :-
-	rdfs_subclass_of(Type, amalgame:'Partitioner'),
-	!,
-	output_type(Type, OutputClass),
-	new_output(OutputClass, Process, amalgame:selectedBy,  Input, Graph, MainOutput),
-	new_output(OutputClass, Process, amalgame:discardedBy, Input, Graph, _),
-	new_output(OutputClass, Process, amalgame:undecidedBy, Input, Graph, _).
-
-assert_output(Process, Type, Strategy, Input, SecInputs, Strategy) :-
-	rdfs_subclass_of(Type, amalgame:'OverlapComponent'),
-	!,
-	output_type(Type, OutputClass),
-	oset_power(SecInputs, [[]|PowSet]),
-	forall(member(InSet0, PowSet),
-	       (   sort(InSet0, InSet),
-		   term_to_atom(InSet, InSetAtom),
-		   new_output(OutputClass, Process, amalgame:wasGeneratedBy, Input, Strategy, OutputUri),
-		   findall(Nick,
-			   (	member(Id, InSet),
-				map_nickname(Strategy,Id,Nick)
-			   ),
-			   Nicks),
-		   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)
-	       )
-	      ).
-
-assert_output(Process, Type, Graph, Input, _, MainOutput) :-
-	output_type(Type, OutputClass),
-	new_output(OutputClass, Process, amalgame:wasGeneratedBy, Input, Graph, MainOutput).
-
-new_output(Type, Process, P, Input, Strategy, OutputURI) :-
-	mint_node_uri(Strategy, dataset, OutputURI),
-	rdf_assert(OutputURI, rdf:type, Type, Strategy),
-	rdf_assert(OutputURI, amalgame:status, amalgame:intermediate, Strategy),
-        rdf_assert(OutputURI, P, Process, Strategy),
-
-	rdfs_individual_of(Process, PType),
-	(   rdf_has(PType, amalgame:materialize, amalgame:always)
-	->  rdf_assert(OutputURI, amalgame:recordEvidence, amalgame:enabled, Strategy)
-	;   true
-	),
-
-	assert_relation(OutputURI, Input, Strategy),
-	map_nickname(Strategy, OutputURI, _Nick).
-
-assert_relation(Output, Input, Strategy) :-
-	nonvar(Input),
-	rdf(Input, amalgame:default_relation, Relation, Strategy),
-	rdf_assert(Output, amalgame:default_relation, Relation, Strategy),
-	!.
-
-assert_relation(_,_,_).
-
-output_type(ProcessType, amalgame:'VirtualConceptScheme') :-
-	rdfs_subclass_of(ProcessType, amalgame:'VocabPartitioner'),
-	!.
-output_type(_ProcessType, amalgame:'Mapping').
-
-process_label(P, Lit) :-
-	(   rdf_display_label(P, L)
-	->  Lit = L
-	;   rdf_global_id(_:Local, P),
-	    Lit = literal(Local)
-	).
-
-
-
-
-update_node_props([], _, _).
-update_node_props([T|Ts], URI, Strategy) :-
-	update_node_prop(T, URI, Strategy),
-	!,
-	update_node_props(Ts, URI, Strategy).
-update_node_props([_|Ts], URI, Strategy) :-
-	update_node_props(Ts, URI, Strategy).
-
-
-update_node_prop(label=Label, URI, Strategy) :-
-	rdf_retractall(URI, rdfs:label, _, Strategy),
-	(   Label == ''
-	->  true
-	;   rdf_assert(URI, rdfs:label, literal(Label), Strategy)
-	).
-
-update_node_prop(abbrev=Abbrev, URI, Strategy) :-
-	rdf_retractall(URI, amalgame:nickname, _, Strategy),
-	(   Abbrev == ''
-	->  true
-	;   rdf_assert(URI, amalgame:nickname, literal(Abbrev), Strategy)
-	).
-
-update_node_prop(comment=Comment, URI, Strategy) :-
-	rdf_retractall(URI, rdfs:comment, _, Strategy),
-	(   Comment == ''
-	->  true
-	;   rdf_assert(URI, rdfs:comment, literal(Comment), Strategy)
-	).
-update_node_prop(status=Status, URI, Strategy) :-
-	rdf_retractall(URI, amalgame:status, _, Strategy),
-	(   Status == ''
-	->  true
-	;   rdf_assert(URI, amalgame:status, Status, Strategy)
-	).
-
-update_node_prop(default_relation=Relation, URI, Strategy) :-
-	rdf_retractall(URI, amalgame:default_relation, _, Strategy),
-	flush_dependent_caches(URI, Strategy),
-	(   Relation == ''
-	->  true
-	;   rdf_assert(URI, amalgame:default_relation, Relation, Strategy)
-	).
 
 
 change_ns_if_needed(NS, URI, Strategy, NewStrategy) :-
@@ -354,25 +152,6 @@ change_ns_if_needed(NS, URI, Strategy, NewStrategy) :-
 	    change_namespace(OldNS, NS, Strategy, NewStrategy)
 	).
 
-node_retract(URI, Strategy) :-
-	provenance_graph(Strategy, ProvGraph),
-	rdf_retractall(URI, _, _, Strategy),
-	rdf_retractall(URI, _, _, ProvGraph),
-	forall(rdf(Subj,_,URI,Strategy),
-	       node_retract(Subj, Strategy)).
-
-process_retract(URI, Strategy) :-
-	rdf_has(URI, amalgame:wasGeneratedBy, P),
-	findall(S, rdf_has(S, amalgame:wasGeneratedBy, P), [URI]),
-	provenance_graph(Strategy, ProvGraph),
-	!,
-	rdf_retractall(P, _, _, Strategy),
-	rdf_retractall(P, _, _, ProvGraph).
-process_retract(_, _).
-
-
-
-
 change_namespace(Old, New, Strategy, NewStrategy) :-
 	(   sub_atom(Strategy, 0, Len, After, Old)
 	->  sub_atom(Strategy, Len, After, 0, Local),
@@ -425,3 +204,14 @@ fix_not_expanded_options([Key=Value|Tail], [Key=FixedValue|Results]):-
 	;   FixedValue = Value
 	),
 	fix_not_expanded_options(Tail, Results).
+
+flush_refs_cache_if_needed(Process) :-
+	(   rdfs_individual_of(Process, amalgame:'SelectPreLoaded')
+	->  flush_refs_cache(Process)
+	;   true
+	).
+flush_deps_if_needed(Strategy, URI, Params) :-
+	(   option(default_relation(R), Params), R \= ''
+	->  flush_dependent_caches(URI, Strategy)
+	;   true
+	).
diff --git a/api/evaluate.pl b/api/evaluate.pl
index 0022d90..a5b903a 100644
--- a/api/evaluate.pl
+++ b/api/evaluate.pl
@@ -67,7 +67,7 @@ http_data_evaluate(Request) :-
 	->  evaluation_graph(Strategy, Mapping, Graph)
 	;   Graph = Mapping
 	),
-	process_entity(Strategy, EvalProcess,  Graph),
+	strategy_process_entity(Strategy, EvalProcess,  Graph),
 	flush_expand_cache(EvalProcess, Strategy),  % graph cache is now outdated
 	flush_refs_cache(Strategy),                 % to recompute all reference stats
 	flush_stats_cache(Graph, Strategy),         % to recompute G's basic stats
diff --git a/lib/amalgame/ag_strategy.pl b/lib/amalgame/ag_strategy.pl
index ad46a31..f31b86b 100644
--- a/lib/amalgame/ag_strategy.pl
+++ b/lib/amalgame/ag_strategy.pl
@@ -1,12 +1,244 @@
 :- module(ag_strategy,
-	  [ process_entity/3
+	  [ strategy_process_entity/3,
+	    strategy_new_process/9,
+	    strategy_update_node/3,
+	    strategy_delete_node/2,
+
+	    assert_output/6 % used in strategy_backward_compatability.pl
 	  ]).
 
+:- use_module(library(option)).
+:- use_module(library(oset)).
+:- use_module(library(uri)).
 :- use_module(library(semweb/rdf_db)).
+:- 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)).
 
 :- rdf_meta
+	strategy_process_entity(r,r,r),
+	strategy_delete_node(r,r),
+	strategy_update_node(r,+,r),
+	assert_output(r,r,r,r,r,r),
+	new_output(r,r,r,r,r,r),
+	output_type(r,r),
 	process_entity(r,r,r).
 
-process_entity(Strategy, Process,Entity) :-
+strategy_process_entity(Strategy, Process,Entity) :-
 	rdf_has(Entity, amalgame:wasGeneratedBy, Process, RealProperty),
 	rdf(Entity, RealProperty, Process, Strategy).
+
+%%	new_process(+Process, +Strategy, +Source, +Target, +Input,
+%%	+SecInputs, +Params, -NewFocus)
+%
+%	Create new amalgame process.
+
+strategy_new_process(Strategy, Type, Source, Target, Input, SecInputs, Params, Focus, URI) :-
+	% hack needed till we have nested rdf transactions:
+	retractall(ag_map:nickname_cache(Strategy,_,_)),
+
+	rdf_bnode(URI),
+	rdf_transaction( % this rdf_transaction is to make it MT safe
+	    (	assert_process(URI, Type, Strategy, Params),
+		assert_user_provenance(URI, Strategy),
+		assert_input(URI, Type, Strategy, Source, Target, Input, Params),
+		assert_secondary_inputs(SecInputs, URI, Type, Strategy),
+		assert_output(URI, Type, Strategy, Input, SecInputs, Focus)
+	    )).
+%%	strategy_update_node(+Strategy, +Properties, +Node) is det.
+%
+%	Update Properties of Node in Strategy named graph.
+
+strategy_update_node(Strategy, Properties, Node) :-
+	rdf_transaction(strategy_update_props(Strategy, Properties, Node)).
+
+strategy_delete_node(Strategy, Node) :-
+	rdf_transaction((process_retract(Node, Strategy),
+			 node_retract(Node, Strategy)
+			)).
+
+assert_output(Process, Type, Graph, Input, _, MainOutput) :-
+	rdfs_subclass_of(Type, amalgame:'Partitioner'),
+	!,
+	output_type(Type, OutputClass),
+	new_output(OutputClass, Process, amalgame:selectedBy,  Input, Graph, MainOutput),
+	new_output(OutputClass, Process, amalgame:discardedBy, Input, Graph, _),
+	new_output(OutputClass, Process, amalgame:undecidedBy, Input, Graph, _).
+
+assert_output(Process, Type, Strategy, Input, SecInputs, Strategy) :-
+	rdfs_subclass_of(Type, amalgame:'OverlapComponent'),
+	!,
+	output_type(Type, OutputClass),
+	oset_power(SecInputs, [[]|PowSet]),
+	forall(member(InSet0, PowSet),
+	       (   sort(InSet0, InSet),
+		   term_to_atom(InSet, InSetAtom),
+		   new_output(OutputClass, Process, amalgame:wasGeneratedBy, Input, Strategy, OutputUri),
+		   findall(Nick,
+			   (	member(Id, InSet),
+				map_nickname(Strategy,Id,Nick)
+			   ),
+			   Nicks),
+		   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)
+	       )
+	      ).
+
+assert_output(Process, Type, Graph, Input, _, MainOutput) :-
+	output_type(Type, OutputClass),
+	new_output(OutputClass, Process, amalgame:wasGeneratedBy, Input, Graph, MainOutput).
+
+assert_input(_Process, Type, _Graph, _Source, _Target, _Input, _Params) :-
+	rdfs_subclass_of(Type, amalgame:'MultiInputComponent'),
+	!.
+assert_input(Process, Type, Graph, Source, Target, _Input, Params) :-
+	nonvar(Source),
+	nonvar(Target),
+	!,
+	rdf_assert(Process, amalgame:source, Source, Graph),
+	rdf_assert(Process, amalgame:target, Target, Graph),
+	assert_preloaded_input(Process, Type, Graph, Params).
+assert_input(Process, Type, Graph, _Source, _Target, Input, Params) :-
+	nonvar(Input),
+	!,
+	rdf_assert(Process, amalgame:input, Input, Graph),
+	assert_preloaded_input(Process, Type, Graph, Params).
+
+assert_preloaded_input(Process, Type, Graph, Params) :-
+	(   rdfs_subclass_of(Type, amalgame:'SelectPreLoaded'),
+	    option(name(Name), Params)
+	->  rdf_assert(Process, amalgame:input, Name, Graph),
+	    rdf_assert(Name, amalgame:status, amalgame:reference, Graph),
+	    rdf_assert(Name, rdf:type, amalgame:'LoadedMapping', Graph)
+	;   true
+	).
+
+assert_secondary_inputs([], _, _, _).
+assert_secondary_inputs([URI|URIs], Process, Type, Strategy) :-
+	(   rdfs_subclass_of(Type, amalgame:'SetOperator')
+	->  rdf_equal(Pred, amalgame:input)
+	;   rdf_equal(Pred, amalgame:secondary_input)
+	),
+	(   is_dependent_chk(URI, Process, Strategy)
+	->  debug(eq, 'Not adding secondary input ~p, it will lead to cyclic dependency on process ~p', [URI, Process])
+	;   rdf_assert(Process, Pred, URI, Strategy)
+	),
+	assert_secondary_inputs(URIs, Process, Type, Strategy).
+
+assert_process(Process, Type, Graph, Params) :-
+	process_label(Type, Label),
+	uri_query_components(Search, Params),
+	rdf_assert(Process, rdf:type, Type, Graph),
+	rdf_assert(Process, rdfs:label, literal(Label), Graph),
+	rdf_assert(Process, amalgame:parameters, literal(Search), Graph).
+
+new_output(Type, Process, P, Input, Strategy, OutputURI) :-
+	mint_node_uri(Strategy, dataset, OutputURI),
+	rdf_assert(OutputURI, rdf:type, Type, Strategy),
+	rdf_assert(OutputURI, amalgame:status, amalgame:intermediate, Strategy),
+        rdf_assert(OutputURI, P, Process, Strategy),
+
+	rdfs_individual_of(Process, PType),
+	(   rdf_has(PType, amalgame:materialize, amalgame:always)
+	->  rdf_assert(OutputURI, amalgame:recordEvidence, amalgame:enabled, Strategy)
+	;   true
+	),
+
+	assert_relation(OutputURI, Input, Strategy),
+	map_nickname(Strategy, OutputURI, _Nick).
+
+assert_relation(Output, Input, Strategy) :-
+	nonvar(Input),
+	rdf(Input, amalgame:default_relation, Relation, Strategy),
+	rdf_assert(Output, amalgame:default_relation, Relation, Strategy),
+	!.
+
+assert_relation(_,_,_).
+
+output_type(ProcessType, amalgame:'VirtualConceptScheme') :-
+	rdfs_subclass_of(ProcessType, amalgame:'VocabPartitioner'),
+	!.
+output_type(_ProcessType, amalgame:'Mapping').
+
+process_label(P, Lit) :-
+	(   rdf_display_label(P, L)
+	->  Lit = L
+	;   rdf_global_id(_:Local, P),
+	    Lit = literal(Local)
+	).
+
+is_dependent_chk(Mapping, Process, Strategy) :-
+	rdf_has(Mapping, amalgame:wasGeneratedBy, Process, RP),
+	rdf(Mapping, RP, Process, Strategy),
+	!.
+is_dependent_chk(Mapping, Process, Strategy) :-
+	rdf_has(Mapping, amalgame:wasGeneratedBy, OtherProcess, RP1),
+	rdf(Mapping, RP1, OtherProcess, Strategy),
+	rdf_has(OtherProcess, amalgame:input, OtherMapping, RP2),
+	rdf(OtherProcess, RP2, OtherMapping, Strategy),
+	is_dependent_chk(OtherMapping, Process, Strategy),!.
+
+strategy_update_props(_, [], _).
+strategy_update_props(Strategy, [T|Ts], URI) :-
+	update_node_prop(T, URI, Strategy),
+	!,
+	strategy_update_props(Strategy, Ts, URI).
+strategy_update_props(Strategy, [_|Ts], URI) :-
+	strategy_update_props(Strategy, Ts, URI).
+
+
+update_node_prop(label=Label, URI, Strategy) :-
+	rdf_retractall(URI, rdfs:label, _, Strategy),
+	(   Label == ''
+	->  true
+	;   rdf_assert(URI, rdfs:label, literal(Label), Strategy)
+	).
+
+update_node_prop(abbrev=Abbrev, URI, Strategy) :-
+	rdf_retractall(URI, amalgame:nickname, _, Strategy),
+	(   Abbrev == ''
+	->  true
+	;   rdf_assert(URI, amalgame:nickname, literal(Abbrev), Strategy)
+	).
+
+update_node_prop(comment=Comment, URI, Strategy) :-
+	rdf_retractall(URI, rdfs:comment, _, Strategy),
+	(   Comment == ''
+	->  true
+	;   rdf_assert(URI, rdfs:comment, literal(Comment), Strategy)
+	).
+update_node_prop(status=Status, URI, Strategy) :-
+	rdf_retractall(URI, amalgame:status, _, Strategy),
+	(   Status == ''
+	->  true
+	;   rdf_assert(URI, amalgame:status, Status, Strategy)
+	).
+
+update_node_prop(default_relation=Relation, URI, Strategy) :-
+	rdf_retractall(URI, amalgame:default_relation, _, Strategy),
+	(   Relation == ''
+	->  true
+	;   rdf_assert(URI, amalgame:default_relation, Relation, Strategy)
+	).
+
+node_retract(URI, Strategy) :-
+	provenance_graph(Strategy, ProvGraph),
+	rdf_retractall(URI, _, _, Strategy),
+	rdf_retractall(URI, _, _, ProvGraph),
+	forall(rdf(Subj,_,URI,Strategy),
+	       node_retract(Subj, Strategy)).
+
+process_retract(URI, Strategy) :-
+	rdf_has(URI, amalgame:wasGeneratedBy, P),
+	findall(S, rdf_has(S, amalgame:wasGeneratedBy, P), [URI]),
+	provenance_graph(Strategy, ProvGraph),
+	!,
+	rdf_retractall(P, _, _, Strategy),
+	rdf_retractall(P, _, _, ProvGraph).
+process_retract(_, _).
diff --git a/lib/amalgame/hooks/strategy_backward_compatability.pl b/lib/amalgame/hooks/strategy_backward_compatability.pl
index d7cac20..67e1e48 100644
--- a/lib/amalgame/hooks/strategy_backward_compatability.pl
+++ b/lib/amalgame/hooks/strategy_backward_compatability.pl
@@ -1,14 +1,12 @@
 :- module(strategy_backward_compatability, []).
 
 :- use_module(library(lists)).
-:- use_module(library(apply)).
 :- use_module(library(settings)).
 
 :- use_module(library(semweb/rdf_db)).
 :- use_module(library(semweb/rdfs)).
 :- use_module(library(skos/util)).
-:- use_module(library(amalgame/rdf_util)).
-:- use_module(api(ag_process)). % hack: we use ag_process:assert_output
+:- use_module(library(amalgame/ag_strategy)).
 
 :- multifile
 	amalgame:prebuilder/1.
@@ -41,7 +39,7 @@ is_old_vocab_selecter_triple(S,amalgame:wasGeneratedBy,O, G) :-
 	skos_is_vocabulary(S).
 
 old_vocab_selecter_to_new(rdf(S,_,Process,Strategy)) :-
-	ag_process:assert_output(Process, amalgame:'VocabPartitioner', Strategy, _, _, S).
+	ag_strategy:assert_output(Process, amalgame:'VocabPartitioner', Strategy, _, _, S).
 
 fix_publish_ns(S) :-
 	(   rdf(S, amalgame:publish_ns, _,S)