amalgame/commit

EXPERIMENTAL: split up caching of deep label and depth stats

authorJacco van Ossenbruggen
Thu May 14 17:36:05 2015 +0200
committerJacco van Ossenbruggen
Thu May 14 17:36:05 2015 +0200
commitc5447b2e16a06055c63946e9d901e0c7595849f1
treeff9c04248075cc7a24674a9d170840879e2bfaad
parent64f488b02802a2b55a9f523b5b4d6415afaee289
Diff style: patch stat
diff --git a/api/node_info.pl b/api/node_info.pl
index 6dab632..8cc8ae1 100644
--- a/api/node_info.pl
+++ b/api/node_info.pl
@@ -223,7 +223,7 @@ amalgame_info(Scheme, Strategy, Stats) :-
 		'# counted top concepts:'    - span('~d (~1f%)'-[NrTopConcepts, (100*NrTopConcepts)/Total])
 			 | DTops
 	    ],
-	    option(topConceptCount(NrTopConcepts), DDict, [])
+	    option(topConceptCount(NrTopConcepts), DDict, 0)
 	;   ExtraStats = [ 'other stats:' - 'still computing, try later ...']
 	),
 	(   V == true
@@ -232,8 +232,9 @@ amalgame_info(Scheme, Strategy, Stats) :-
 	;   Virtual = materialized,
 	    findall(Top, skos_top_concept(Scheme, Top), Tops),
 	    length(Tops, NrDeclaredTops),
+	    save_perc(NrDeclaredTops,NrTopConcepts,TopPerc),
 	    DTops = ['# declared top concepts:'  -
-		     span('~d (~1f%)'-[NrDeclaredTops, (100*NrDeclaredTops/NrTopConcepts)])]
+		     span('~d (~1f%)'-[NrDeclaredTops, TopPerc])]
 	),
 	label_property_stats(PDict, PStats, [totalCount(Total)]),
 	depth_stats(DDict, DStats),
diff --git a/lib/amalgame/ag_stats.pl b/lib/amalgame/ag_stats.pl
index be6aaa5..1c0dce6 100644
--- a/lib/amalgame/ag_stats.pl
+++ b/lib/amalgame/ag_stats.pl
@@ -6,6 +6,7 @@
 
 :- use_module(library(apply)).
 :- use_module(library(assoc)).
+:- use_module(library(debug)).
 :- use_module(library(option)).
 :- use_module(library(lists)).
 :- use_module(library(semweb/rdf_db)).
@@ -46,13 +47,17 @@ node_counts(_, URL, Strategy, Stats, Options) :-
 
 node_counts(scheme, Scheme, Strategy, Stats, Options) :-
 	select_option(compute(deep), Options, Options1, true),
+	node_counts(scheme, Scheme, Strategy, _Stats, [compute(labelprop)|Options1]),
+	node_counts(scheme, Scheme, Strategy, Stats, [compute(depth)|Options1]).
+
+node_counts(scheme, Scheme, Strategy, Stats, Options) :-
+	select_option(compute(Level), Options, Options1, true),
+	(   Level == depth; Level == labelprop),
 	!,
-	node_counts(scheme, Scheme, Strategy, Stats0, [compute(true)|Options1]),
-	(   get_dict(properties, Stats0, _)
-	->  Stats = Stats0
-	;   expand_node(Strategy, Scheme, ConceptAssoc),
-	    scheme_stats_deep(Strategy, Scheme, ConceptAssoc, Stats)
-	).
+	expand_node(Scheme, Strategy, _),
+	atomic_list_concat([Level, '_stats_cache_',Scheme], Mutex),
+	debug(mutex, 'waiting for deep stats mutex ~w', [Mutex]),
+	with_mutex(Mutex, node_counts(scheme, Scheme, Strategy, Stats, Options1)).
 
 node_counts(_, URL, Strategy, Stats, _Options) :-
 	get_stats_cache(Strategy, URL, Stats),
diff --git a/lib/amalgame/caching.pl b/lib/amalgame/caching.pl
index eec84a2..2ff844e 100644
--- a/lib/amalgame/caching.pl
+++ b/lib/amalgame/caching.pl
@@ -104,30 +104,29 @@ handle_scheme_stats(Strategy, Process, Scheme, Result) :-
 	debug(mutex, 'finished ~w', [Mutex]).
 
 handle_scheme_stats_(Strategy, Process, Scheme, Result) :-
-	flush_stats_cache(Scheme, Strategy),
 	scheme_stats(Strategy, Scheme, Result, Stats),
+	flush_stats_cache(Scheme, Strategy),
 	assert(stats_cache(Scheme-Strategy, Stats)),
 
 	thread_create(
             (   set_stream(user_output, alias(current_output)),
-		handle_deep_scheme_stats(Strategy, Process, Scheme, Result)
+		handle_deep_scheme_stats(Strategy, Process, Scheme, Result, labelprop),
+		handle_deep_scheme_stats(Strategy, Process, Scheme, Result, depth)
             ),
 	    _,[ detached(true) ]).
 
 
-handle_deep_scheme_stats(Strategy, Process, Scheme, Result) :-
-	atomic_list_concat([stats_cache_,Scheme], Mutex),
+handle_deep_scheme_stats(Strategy, Process, Scheme, Result, Level) :-
+	atomic_list_concat([Level, '_stats_cache_',Scheme], Mutex),
 	debug(mutex, 'starting deep ~w', [Mutex]),
 	with_mutex(Mutex,
-		   handle_deep_scheme_stats_(Strategy, Process, Scheme, Result)),
+		   handle_deep_scheme_stats_(Strategy, Process, Scheme, Result, Level)),
 	debug(mutex, 'finished deep ~w', [Mutex]).
-handle_deep_scheme_stats_(Strategy, _Process, Scheme, Result) :-
-	scheme_stats_deep(Strategy, Scheme, Result, DeepStats),
-	(   stats_cache(Scheme-Strategy, Stats)
-	->  retractall(stats_cache(Scheme-Strategy, Stats))
-	;   scheme_stats(Strategy, Scheme, Result, Stats)
-	),
+handle_deep_scheme_stats_(Strategy, _Process, Scheme, Result, Level) :-
+	scheme_stats_deep(Strategy, Scheme, Result, DeepStats, Level),
+	stats_cache(Scheme-Strategy, Stats),
 	put_dict(Stats, DeepStats, NewStats),
+	retractall(stats_cache(Scheme-Strategy, Stats)),
 	assert(stats_cache(Scheme-Strategy, NewStats)).
 
 cache_mapped_concepts(Strategy, Type, Mapping, Concepts) :-
@@ -153,6 +152,8 @@ amalgame_computed_node(Strategy, Id) :-
 amalgame_computed_node(Strategy, Id) :-
 	rdfs_individual_of(Id,  amalgame:'Process'),
 	rdf(Id, rdf:type, _, Strategy).
+amalgame_computed_node(Strategy, Id) :-
+	rdf(Id, rdf:type, skos:'ConceptScheme', Strategy), fail. % change to true to flush cache
 
 %%	flush_expand_cache(+Strategy)
 %
diff --git a/lib/amalgame/scheme_stats.pl b/lib/amalgame/scheme_stats.pl
index 669b0de..fcc72c3 100644
--- a/lib/amalgame/scheme_stats.pl
+++ b/lib/amalgame/scheme_stats.pl
@@ -1,7 +1,7 @@
 :- module(ag_scheme_stats,
 	  [
 	      scheme_stats/4,
-	      scheme_stats_deep/4,
+	      scheme_stats_deep/5,
 	      compute_label_stats/2
 	  ]).
 
@@ -44,19 +44,21 @@ scheme_stats(Strategy, Scheme, ConceptAssoc, Stats) :-
 	assoc_to_keys(ConceptAssoc, Concepts),
 	length(Concepts, TotalCount).
 
-scheme_stats_deep(Strategy, Scheme, ConceptAssoc, Stats) :-
-	atomic_list_concat([scheme_stats_deep_,Scheme], Mutex),
-	with_mutex(Mutex, scheme_stats_deep_(Strategy, Scheme, ConceptAssoc, Stats)).
+scheme_stats_deep(Strategy, Scheme, ConceptAssoc, Stats, Level) :-
+	atomic_list_concat([scheme_stats_deep_,Scheme, Level], Mutex),
+	with_mutex(Mutex, scheme_stats_deep_(Strategy, Scheme, ConceptAssoc, Stats, Level)).
 
-scheme_stats_deep_(_Strategy, Scheme, ConceptAssoc, Stats) :-
-	DepthStats = scheme_stats_dict{
+scheme_stats_deep_(_Strategy, _Scheme, ConceptAssoc, Stats, labelprop) :-
+	assoc_to_keys(ConceptAssoc, Concepts),
+	compute_label_stats(Concepts, Stats).
+
+scheme_stats_deep_(_Strategy, Scheme, ConceptAssoc, Stats, depth) :-
+	Stats = scheme_stats_dict{
 			 '@private': Private,
 			  structure: DStatsPub
 		     },
-	compute_depth_stats(Scheme, ConceptAssoc, DStatsPub, Private),
-	assoc_to_keys(ConceptAssoc, Concepts),
-	compute_label_stats(Concepts, LabelStats),
-	Stats = DepthStats.put(LabelStats).
+	compute_depth_stats(Scheme, ConceptAssoc, DStatsPub, Private).
+
 
 compute_label_stats(Concepts, Stats) :-
 	Stats = scheme_stats_dict{
diff --git a/lib/amalgame/vocabulary.pl b/lib/amalgame/vocabulary.pl
index a9b15aa..cf27a23 100644
--- a/lib/amalgame/vocabulary.pl
+++ b/lib/amalgame/vocabulary.pl
@@ -249,8 +249,8 @@ lang_used(Strategy-Vocs, Languages) :-
 
 lang_used(Strategy, Voc, Languages) :-
 	debug(ag_stats, 'Computing languages used in ~p for ~p', [Voc, Strategy]),
-	node_stats(Strategy, Voc, Stats, [compute(deep)]),
-	option(languages(Languages), Stats).
+	node_stats(Strategy, Voc, Stats, [compute(labelprop)]),
+	option(languages(Languages), Stats, []).
 
 skos_util:skos_is_vocabulary(Graph) :-
 	setting(amalgame:consider_all_labeled_resources, true),