annotation_dashboard/commit

REFACTORING: split up overly large dashboard annotation over multiple files

authorJacco van Ossenbruggen
Sun Sep 21 15:25:33 2014 +0200
committerJacco van Ossenbruggen
Sun Sep 21 15:25:33 2014 +0200
commit7e18910829cfbf47cf597711461e0087972c2a09
treeeab36ca3dac465c903088cd395cfaa992fd732a8
parentf7e3983887f224f0bcabb6df2252dbcb039b0e6c
Diff style: patch stat
diff --git a/applications/dashboard.pl b/applications/dashboard.pl
deleted file mode 100644
index f5de959..0000000
--- a/applications/dashboard.pl
+++ /dev/null
@@ -1,623 +0,0 @@
-:- module(an_dashboard, []).
-
-% from SWI-Prolog libraries:
-:- use_module(library(apply)).
-:- use_module(library(lists)).
-:- use_module(library(option)).
-:- use_module(library(pairs)).
-
-:- use_module(library(semweb/rdf_db)).
-:- use_module(library(http/http_dispatch)).
-:- use_module(library(http/http_parameters)).
-:- use_module(library(http/html_write)).
-:- use_module(library(http/html_head)).
-:- use_module(library(http/js_write)).
-
-% from ClioPatria:
-:- use_module(library(semweb/rdf_label)).
-:- use_module(cliopatria(hooks)).
-:- use_module(components(label)).
-:- use_module(user(user_db)).
-
-% from other cpacks:
-:- use_module(library(yui3_beta)). % needed for html resource declarations
-:- use_module(library(oa_schema)).
-:- use_module(library(oa_annotation)).
-:- use_module(library(ac_list_util)).
-:- use_module(api(media_caching)).       % needed for http api handlers
-:- use_module(applications(annotation)).
-
-% from this pack:
-:- use_module(api(dashboard_api)).
-:- use_module(library(dashboard_util)).
-:- use_module(library(region_merge)).
-
-:- http_handler(cliopatria(annotate/dashboard/home), http_dashboard_home, []).
-:- http_handler(cliopatria(annotate/dashboard/user), http_dashboard_user, []).
-:- http_handler(cliopatria(annotate/dashboard/task), http_dashboard_task, []).
-
-:- setting(annotation:dashboard_admin_only, boolean, true,
-	   'Dashboard only for users with admin rights').
-
-cliopatria:menu_item(100=annotation/http_dashboard_home, 'dashboard').
-
-:- html_resource(dashboard,
-		 [ virtual(true),
-		   ordered(true),
-		   requires([bootstrap,
-			     css('deniche-dashboard.css'),
-			     css('deniche-tags.css'),
-			     yui3('yui/yui-min.js'),
-			     js('dashboard.js')
-			    ])
-		 ]).
-:- html_resource(task_stats,
-		 [ virtual(true),
-		   requires([d3js,
-			    css('task_stats.css')])
-		 ]).
-:- html_resource(d3js,
-		 [ virtual(true),
-		   requires(['http://d3js.org/d3.v3.min.js'])
-		 ]).
-
-:- html_resource(bootstrap,
-	      [ virtual(true),
-		requires(
-		    [ '//netdna.bootstrapcdn.com/bootstrap/3.1.1/css/bootstrap.min.css'
-		    ])
-	      ]).
-
-
-http_dashboard_home(_Request) :-
-	(setting(annotation:dashboard_admin_only, true)
-	-> authorized(admin(dashboard)); true),
-	dashboard_page([]).
-
-http_dashboard_task(Request) :-
-	(setting(annotation:dashboard_admin_only, true)
-	-> authorized(admin(dashboard)); true),
-	http_parameters(Request,
-			[task(Task, []),
-			 limit(Limit, [nonneg, default(5)]),
-			 offset(Offset, [nonneg, default(0)])
-			]),
-
-	task_page(Task, [showTag(always), limit(Limit), offset(Offset)]).
-
-http_dashboard_user(Request) :-
-	(setting(annotation:dashboard_admin_only, true)
-	-> authorized(admin(dashboard)); true),
-	http_parameters(Request, [user(User, [])]),
-	user_page(User, []).
-
-task_page(Task, Options0) :-
-	option(limit(Limit), Options0, 5),
-	option(offset(Offset), Options0, 0),
-	rdf_display_label(Task, Label),
-	rdf_has(Task, ann_ui:taskUI, UI),
-	get_metafields(UI, [], MetadataFields),
-	% get_anfields(UI, [], [], AnnotationFields),
-	AnnotationFields = [ 'http://eculture.cs.vu.nl/sealinc/ns/demo/ui/CommonBirdNameAnnotation'],
-	find_annotations_by_task(Task, Annotations),
-	partition(is_tag, Annotations, Tags, Judgements),
-	maplist(rdf_get_annotation_target, Tags, RawTargets),
-	sort(RawTargets, AllTargets), % de-dup
-	% list_offset(['http://purl.org/collections/nl/rma/collection/r-108494'|AllTargets], Offset, OffTargets),
-	list_offset(AllTargets, Offset, OffTargets),
-	list_limit(OffTargets, Limit, Objects, _Rest),
-	length(AllTargets, Total),
-	maplist(count_annotations, Objects, CountPairs),
-	sort(CountPairs, SortedPairs0),
-	reverse(SortedPairs0, ReversePairs),
-	pairs_values(ReversePairs, SortedObjects),
-	Options = [annotations(Annotations),
-		   judgements(Judgements),
-		   annotation_fields(AnnotationFields),
-		   metadata_fields(MetadataFields),
-		   ui(UI),
-		   task(Task),
-		   lazy(true),
-		   limit(Limit),
-		   offset(Offset),
-		   total(Total),
-		   image_link_predicate(http_mediumscale) |
-		   Options0
-		  ],
-	reply_html_page(
-	    [ title(Label),
-	      meta([name(viewport),
-		   content('width=device-width, initial-scale=1')]),
-	      \html_requires(dashboard)
-	    ],
-	    [ \top_navbar,
-	      div([class('container-fluid')],
-		  [
-		    div([class(row)],
-			[ div([class('col-sm-12 main')],
-			      [ h1([class('page-header')], ['Dashboard']),
-				h2([class('sub-header')],
-				   [Label]),
-				div([class(row)], \task_stats(Task)),
-				h3([class('sub-header')],
-				   ['Task objects']),
-				\show_objects(Objects, Options),
-				\pagination(Options)
-			      ])
-			])
-		  ])
-	    ]).
-
-user_page(User, Options0) :-
-	findall(Prop, user_property(User, Prop), Props),
-	find_annotations_by_user(User, Annotations),
-	partition(is_tag, Annotations, Tags, Judgements),
-	maplist(rdf_get_annotation_target, Tags, Targets),
-	sort(Targets, Objects),
-	Options = [annotations(Annotations),
-		   judgements(Judgements),
-		   lazy(true),
-		   user(User),
-		   showTag(mine),
-		   image_link_predicate(http_mediumscale) |
-		   Options0
-		  ],
-	reply_html_page(
-	    [title(User),
-	     meta([name(viewport),
-		    content('width=device-width, initial-scale=1')],
-		   []),
-	     \html_requires(dashboard)
-	    ],
-	    [ \top_navbar,
-	      div([class('container-fluid')],
-		  [ div([class(row)],
-			[ div([class('col-sm-12 main')
-			      ],
-			      [ h1([class('page-header')], ['Dashboard']),
-				h2([class('sub-header')],
-				   ['User information']),
-				div([class('table-responsive')],
-				    [table([class('table table-striped')],
-					   [ \show_option_list(Props)
-					   ])
-				    ]),
-				h2([class('sub-header')],
-				   ['Annotations made so far']),
-				\show_objects(Objects, Options)
-			      ])
-			])
-		  ])
-	    ]).
-
-
-dashboard_page(_Options) :-
-	find_tasks(Tasks),
-	find_workers(Users),
-	find_annotations_without_task(TaskLess),
-	length(TaskLess, NrTaskless),
-	length(Users, NrOfUsers),
-	reply_html_page(
-	    [ title('Annotation dashboard'),
-	      meta([name(viewport),
-		    content('width=device-width, initial-scale=1')],
-		   []),
-	      \html_requires(dashboard)
-	    ],
-	    [ \top_navbar,
-	      div([class('container-fluid')],
-		  [ div([class(row)],
-			[ div([class('col-sm-12 main')],
-			      [ h1([class('page-header')], ['Dashboard']),
-				\show_tasks(Tasks),
-				h2([class('sub-header')],
-				   ['Total annotations not associated with a defined task: ', NrTaskless]),
-				div([class('table-responsive')],
-				    [table([class('table table-striped')],
-					   [\show_annotations(TaskLess, [])
-					   ])
-				    ]),
-				h2([id(leaderboard), class('sub-header')],
-				   ['Leaderboard: #', NrOfUsers, ' annotators']),
-				div([class('table-responsive')],
-				    [table([class('table table-striped')],
-					   [ thead([
-						 tr([th('User rank'),
-						     th('Name'),
-						     th('Number of annotations')])
-					     ]),
-					     tbody([
-						 \show_users(Users, 1)
-					     ])
-					   ])
-				    ])
-			      ])
-			])
-		  ])
-	    ]).
-
-top_navbar -->
-	{ http_link_to_id(http_annotation, [], AnnotateLink)
-	},
-	html(
-	    div([class('navbar navbar-inverse navbar-fixed-top'),
-		 role('navigation')],
-		[div([class('container-fluid')],
-		     [div([class('navbar-header')],
-			  [button([type('button'), class('navbar-toggle'),
-				   'data-toggle'(collapse), 'data-target'('.navbar-collapse')],
-				   [ span([class('sr-only')], 'Toggle navigation'),
-				     span([class('icon-bar')],[]),
-				     span([class('icon-bar')],[]),
-				     span([class('icon-bar')],[])
-				   ]),
-			   a([class('navbar-brand'),
-			      href('http://sealincmedia.wordpress.com/tag/accurator/')
-			     ], ['Accurator for ',
-				 span([class(role)],['Curator'])])
-			  ]),
-		      div(class('navbar-collapse collapse'),
-			  [ ul(class('nav navbar-nav navbar-right'),
-				[ li([a([href('home')],['Dashboard'])]),
-				  li([a([href(AnnotateLink)],['Annotate'])]),
-				  li([a([href('../../admin')],['Admin'])]),
-				  li([a([href('../../user/logout')],['Logout'])])
-
-				])
-			  ])
-		     ])
-		])
-	).
-
-
-
-
-show_objects(Targets,Options) -->
-	{ true,
-	  option(task(Task), Options),
-	  rdf_has(Task, ann_ui:taskUI, UI),
-	  get_metafields(UI, [], MetadataFields),
-	  get_anfields(UI, [], [], AnnotationFields),
-	  NewOptions = [
-	      ui(UI),
-	      metadata_fields(MetadataFields),
-	      annotation_fields(AnnotationFields) |
-	      Options
-	  ]
-	},
-	html(
-	    [div([class(row)],
-		 [div([class('col-xs-6')],
-		      [\annotation_page_body([targets(Targets)|NewOptions])
-		      ])
-		 ])
-	    ]).
-
-
-match_target(T,A) :-
-	rdf_get_annotation_target(A,T).
-
-show_object_old(O, Options) -->
-	{ option(annotations(A), Options, []),
-	  include(match_target(O), A, Annotations),
-	  (   ( option(metadata_fields(_), Options),
-		option(ui(_), Options),
-		option(annotation_fields(_), Options))
-	  ->  NewOptions = Options
-	  ;   ( option(task(Task), Options)
-	      ->  true
-	      ;	  member(First, A),
-		  guess_task(First, Task-First)
-	      ),
-	      rdf_has(Task, ann_ui:taskUI, UI),
-	      get_metafields(UI, [], MetadataFields),
-	      get_anfields(UI, [], [], AnnotationFields),
-	      NewOptions = [
-		  ui(UI),
-		  metadata_fields(MetadataFields),
-		  annotation_fields(AnnotationFields) |
-		  Options
-	      ]
-	  )
-	},
-	html(
-	    [div([class(row)],
-		 [div([class('col-xs-6')],
-		      [\annotation_page_body([target(O)|NewOptions])
-		      ]),
-		  div([class('col-xs-6 table-responsive')],
-		      [ table([class('table table-striped')], [
-				  \show_annotations(Annotations, NewOptions)
-			      ])
-		      ])
-		 ])
-	    ]).
-
-task_compare(Order, Task1, Task2) :-
-	compare(Order, Task1.order, Task2.order).
-
-show_tasks([]) --> !.
-show_tasks([H|T]) -->
-	show_task(H),
-	show_tasks(T).
-
-show_task(Task) -->
-	{ rdf_display_label(Task,Title),
-	  http_link_to_id(http_dashboard_task, [task(Task)], TaskLink),
-	  find_task_properties(Task, Props0, Representative,[]),
-	  predsort(task_compare, Props0, Props),
-	  object_image(Representative, Image),
-	  http_link_to_id(http_medium_fit, [uri(Image)], ImageHref)
-
-	},
-	html([div(class(row),
-		  [ h3([class('sub-header')],
-		       [a([href(TaskLink)],Title)]),
-		    div(class('col-sm-5'),
-			[
-			    img([src(ImageHref), alt('Example image for this task'),
-				 class('img-responsive')],[])
-			]),
-		    div(class('col-sm-7'),
-			[
-			  div([class('table-responsive')],
-			      [table([class('table table-striped')],
-				     [ % thead([tr([th('Property'), th('Value')])]),
-				       tbody([\show_option_list(Props)])
-				     ])
-			      ])
-			])
-		  ])
-	     ]).
-
-ann_sort_key(Annotation, Key-Annotation) :-
-	rdf_has(Annotation, ann_ui:annotationField, Field),
-	rdf_display_label(Field, FieldLabel),
-	rdf_display_label(Annotation,BodyLabel),
-	Key=key(FieldLabel, BodyLabel).
-
-show_annotations(List, Options) -->
-	{ maplist(ann_sort_key, List, KeyList),
-	  keysort(KeyList, KeySorted),
-	  pairs_values(KeySorted, Sorted)
-	},
-	show_annotations_(Sorted, Options).
-
-show_annotations_([], _) --> !.
-show_annotations_([H|T], Options) -->
-	html(tr([],
-		\show_annotation_summery(H, Options))),
-	show_annotations_(T, Options).
-
-
-show_users([], _) --> !.
-show_users([U|T], Rank) -->
-	{ Next is Rank + 1
-	},
-	show_user(U, Rank),
-	show_users(T, Next).
-
-show_user(U, Rank) -->
-	{ option(id(Uid), U),
-	  option(done(Done), U),
-	  iri_xml_namespace(Uid, _, ScreenName),
-	  http_link_to_id(http_dashboard_user, [user(Uid)], UserLink)
-	},
-	html(tr([td([class(rank)],[Rank]),
-		 td(a([href(UserLink)],[ScreenName])),
-		 td([class='an_nr_of_annotations'],Done)])).
-
-show_option_list([]) --> !.
-show_option_list([Prop|Tail]) -->
-	{ (   is_dict(Prop)
-	  ->  V = Prop.'@value',
-	      Key = Prop.label
-	  ;   (   Prop = K-V
-	      ;	    Prop =.. [K,V]),
-		    (   rdf_current_predicate(K)
-		    ->  Key = \rdf_link(K)
-		    ;   Key = K
-		    )
-	  ),
-	  (   rdf_is_resource(V)
-	  ->  (   rdf_subject(V)
-	      ->  Value = \rdf_link(V)
-	      ;	   (  rdf_global_id(_:Value, V)
-		   ->  true
-		   ;   Value = V
-		   )
-	      )
-	  ;   (   rdf_is_literal(V)
-	      ->  literal_text(V, Value)
-	      ;   V = Value
-	      )
-	  )
-	},
-	html(tr([td(Key), td(Value)])),
-	show_option_list(Tail).
-
-show_option_list(Dict) -->
-	{ is_dict(Dict),
-	  dict_pairs(Dict, _Tag, Pairs)
-	},
-	show_option_list(Pairs).
-
-current_judgment(Type, A, Jlist, J, checked) :-
-	member(J, Jlist),
-	rdf_has(J, oa:hasTarget, A),
-	rdf_has(J, dc:title, literal(Type)),
-	!.
-
-current_judgment(_Type, A, Jlist, J, unchecked) :-
-	member(J, Jlist),
-	rdf_has(J, oa:hasTarget, A),!.
-
-current_judgment(_,_,_, null, unchecked).
-
-button_glyph(agree) -->
-	html(span([class([glyphicon,'glyphicon-thumbs-up'])],[' agree'])).
-button_glyph(disagree) -->
-	html(span([class([glyphicon,'glyphicon-thumbs-down'])],[' disagree'])).
-
-checked_active(checked, active).
-checked_active(_, '').
-
-judge_button(Type, Annotation, Field, Judgements) -->
-	{  current_judgment(Type, Annotation, Judgements, J, Checked),
-	   checked_active(Checked, Active)
-	},
-	html([
-	    label([class([Active, btn,'btn-primary'])],
-		  [ input([class([judgebutton, Type, Checked
-				 ]),
-			   field(Field),
-			   judgement(J),
-			   annotation(Annotation),
-			   type(radio),
-			   title(Type), 'data-toggle'(tooltip)
-			  ],
-			  [
-			      \button_glyph(Type)
-			  ])
-		  ])
-	]).
-
-
-is_judgement_of(A, J) :-
-	rdf_has(J, oa:hasTarget, A).
-
-show_annotation_summery(A, Options) -->
-	{ rdf_has(A, oa:annotatedBy, User),
-	  (   rdf_has(A, ann_ui:annotationField, Field)
-	  ->  true
-	  ;   Field = undefined
-	  ),
-	  option(judgements(J), Options, []),
-	  include(is_judgement_of(A), J, Js)
-	},
-	html([
-	    td([class(judgebuttoncell)],
-	       div([class('btn-group'), 'data-toggle'(buttons)],
-		   [ \judge_button(agree, A, Field, Js),
-		     \judge_button(disagree, A, Field, Js)
-		   ])
-	      ),
-	    td(\rdf_link(Field, [resource_format(label)])),
-	    td(\rdf_link(A,     [resource_format(label)])),
-	    td(\rdf_link(User,  [resource_format(label)]))
-	]).
-
-multiply(A,B,P) :- P is A * B.
-pitem(_, []) --> !.
-pitem(Offset, [H1|T]) -->
-	{ ( T = [H2|_], between(H1, H2, Offset) -> Class = [active] ; Class = [])
-	},
-	html(li([class(Class)],a([href('#')],H1))),
-	pitem(Offset,T).
-
-pagination(Options) -->
-	{ option(limit(Limit), Options),
-	  option(offset(Offset), Options),
-	  option(total(Total), Options),
-	  Max is floor(Total/Limit),
-	  numlist(0,Max, List1),
-	  maplist(multiply(Limit), List1, List)
-	},
-	html(ul([class(pagination)],[\pitem(Offset, List)])).
-
-task_stats(Task) -->
-	{ http_link_to_id(http_api_dashboard_task,
-			  [task(Task), filter(number)], DataSource),
-	  gensym(chart, Class),
-	  atom_concat('svg.', Class, Selector)
-	},
-	html([
-	    \html_requires(task_stats),
-	    svg([class(Class)],[]),
-	    \js_script({|javascript(DataSource, Selector)||
-			var cwidth = document.body.clientWidth;
-			var margin = {top: 20, right: 40, bottom: 50, left: 50},
-			width =  0.45*cwidth - margin.left - margin.right,
-			height = 200 - margin.top - margin.bottom;
-
-
-			var x = d3.scale.ordinal()
-			.rangeRoundBands([5, width], .1);
-
-			var y = d3.scale.linear()
-			.range([height, 0]);
-
-			var xAxis = d3.svg.axis()
-			.scale(x)
-			.tickSize(10,0)
-			.orient("bottom");
-
-			var yAxis = d3.svg.axis()
-			.scale(y)
-			.orient("left")
-			.ticks(10, "");
-
-			var svg = d3.select(Selector)
-			.attr("width", width + margin.left + margin.right)
-			.attr("height", height + margin.top + margin.bottom)
-			.append("g")
-			.attr("transform", "translate(" + margin.left + "," + margin.top + ")");
-
-			d3.json(DataSource, function(error, data) {
-						data.sort(compare_value);
-
-						x.domain(data.map(function(d) { return d.label; }));
-						y.domain([0, d3.max(data, function(d) { return d['@value']; })]);
-
-						var bar = svg.selectAll("g")
-						.data(data)
-						.enter()
-						.append("g");
-
-						bar.append("rect")
-						.attr("class", function(d) { return "bar " + d.key; })
-						.attr("x", function(d) { return x(d.label); })
-						.attr("width", x.rangeBand())
-						.attr("y", function(d) { return y(d['@value']); })
-						.attr("height", function(d) { return height - y(d['@value']); });
-
-						bar.append("text")
-						.style("text-anchor", "middle")
-						.attr("class", "count")
-						.attr("x", function(d) { return x(d.label) + 0.5 * x.rangeBand(); })
-						.attr("y", function(d) { return Math.min(y(0), y(d['@value'])); })
-						.attr("dy", "-1ex")
-						.text(function(d) { return d['@value']; });
-
-						svg.append("g")
-						.attr("class", "x axis")
-						.attr("transform", "translate(0," + height + ")")
-						.call(xAxis).selectAll("text")
-						.style("text-anchor", "middle")
-						.attr("dx", '.1em')
-						.attr("dy", function(d,i) { return 0 + 14*(i%3); });
-
-						d3.selectAll("g.x.axis g.tick line")
-						.style("stroke-opacity", 0.2)
-						.attr("y2", function(d,i){ return 15 + 14*(i%3); });
-
-						svg.append("g")
-						.attr("class", "y axis")
-						.call(yAxis)
-						.append("text")
-						.attr("transform", "rotate(-90)")
-						.attr("y", 6)
-						.attr("dy", "0.7ex")
-						.style("text-anchor", "end")
-						.text("Count");
-					    });
-
-			function compare_value(a,b) {
-				     if (a.value < b.value) return 1;
-				     if (a.value > b.value) return -1;
-				     return 0;
-				 }
-
-
-		       |})
-	]).
diff --git a/applications/dashboard_startpage.pl b/applications/dashboard_startpage.pl
new file mode 100644
index 0000000..e962973
--- /dev/null
+++ b/applications/dashboard_startpage.pl
@@ -0,0 +1,110 @@
+:- module(an_dashboard_startpage, []).
+
+% from SWI-Prolog libraries:
+:- use_module(library(settings)).
+
+:- use_module(library(http/http_dispatch)).
+:- use_module(library(http/html_write)).
+:- use_module(library(http/html_head)).
+
+% from ClioPatria:
+:- use_module(cliopatria(hooks)).
+:- use_module(user(user_db)).
+
+% from other cpacks:
+:- use_module(library(yui3_beta)). % needed for html resource declarations
+:- use_module(library(oa_schema)).
+:- use_module(api(media_caching)).       % needed for http api handlers
+
+% from this pack:
+:- use_module(api(dashboard_api)).
+:- use_module(library(dashboard_util)).
+:- use_module(components(dashboard/show_annotations)).
+:- use_module(components(dashboard/show_tasks)).
+:- use_module(components(dashboard/show_users)).
+:- use_module(components(dashboard/top_nav_bar)).
+
+:- http_handler(cliopatria(annotate/dashboard/home), http_dashboard_home, []).
+
+:- setting(annotation:dashboard_admin_only, boolean, true,
+	   'Dashboard only for users with admin rights').
+
+cliopatria:menu_item(100=annotation/http_dashboard_home, 'dashboard').
+
+:- html_resource(dashboard,
+		 [ virtual(true),
+		   ordered(true),
+		   requires([bootstrap,
+			     css('deniche-dashboard.css'),
+			     css('deniche-tags.css'),
+			     yui3('yui/yui-min.js'),
+			     js('dashboard.js')
+			    ])
+		 ]).
+:- html_resource(task_stats,
+		 [ virtual(true),
+		   requires([d3js,
+			    css('task_stats.css')])
+		 ]).
+:- html_resource(d3js,
+		 [ virtual(true),
+		   requires(['http://d3js.org/d3.v3.min.js'])
+		 ]).
+
+:- html_resource(bootstrap,
+	      [ virtual(true),
+		requires(
+		    [ '//netdna.bootstrapcdn.com/bootstrap/3.1.1/css/bootstrap.min.css'
+		    ])
+	      ]).
+
+
+http_dashboard_home(_Request) :-
+	(setting(annotation:dashboard_admin_only, true)
+	-> authorized(admin(dashboard)); true),
+	dashboard_page([]).
+
+dashboard_page(_Options) :-
+	find_tasks(Tasks),
+	find_workers(Users),
+	find_annotations_without_task(TaskLess),
+	length(TaskLess, NrTaskless),
+	length(Users, NrOfUsers),
+	reply_html_page(
+	    [ title('Annotation dashboard'),
+	      meta([name(viewport),
+		    content('width=device-width, initial-scale=1')],
+		   []),
+	      \html_requires(dashboard)
+	    ],
+	    [ \top_navbar,
+	      div([class('container-fluid')],
+		  [ div([class(row)],
+			[ div([class('col-sm-12 main')],
+			      [ h1([class('page-header')], ['Dashboard']),
+				\show_tasks(Tasks),
+				h2([class('sub-header')],
+				   ['Total annotations not associated with a defined task: ', NrTaskless]),
+				div([class('table-responsive')],
+				    [table([class('table table-striped')],
+					   [\show_annotations(TaskLess, [])
+					   ])
+				    ]),
+				h2([id(leaderboard), class('sub-header')],
+				   ['Leaderboard: #', NrOfUsers, ' annotators']),
+				div([class('table-responsive')],
+				    [table([class('table table-striped')],
+					   [ thead([
+						 tr([th('User rank'),
+						     th('Name'),
+						     th('Number of annotations')])
+					     ]),
+					     tbody([
+						 \show_users(Users, 1)
+					     ])
+					   ])
+				    ])
+			      ])
+			])
+		  ])
+	    ]).
diff --git a/applications/dashboard_task_page.pl b/applications/dashboard_task_page.pl
new file mode 100644
index 0000000..69dc42d
--- /dev/null
+++ b/applications/dashboard_task_page.pl
@@ -0,0 +1,139 @@
+:- module(an_dashboard_taskpage, []).
+
+% from SWI-Prolog libraries:
+:- use_module(library(apply)).
+:- use_module(library(lists)).
+:- use_module(library(option)).
+:- use_module(library(pairs)).
+:- use_module(library(settings)).
+
+:- use_module(library(semweb/rdf_db)).
+:- use_module(library(http/http_dispatch)).
+:- use_module(library(http/http_parameters)).
+:- use_module(library(http/html_write)).
+:- use_module(library(http/html_head)).
+
+% from ClioPatria:
+:- use_module(library(semweb/rdf_label)).
+:- use_module(cliopatria(hooks)).
+:- use_module(user(user_db)).
+
+% from other cpacks:
+:- use_module(library(yui3_beta)). % needed for html resource declarations
+:- use_module(library(oa_schema)).
+:- use_module(library(oa_annotation)).
+:- use_module(library(ac_list_util)).
+:- use_module(api(media_caching)).       % needed for http api handlers
+:- use_module(applications(annotation)).
+
+% from this pack:
+:- use_module(api(dashboard_api)).
+:- use_module(library(dashboard_util)).
+% :- use_module(library(region_merge)).
+:- use_module(components(dashboard/task_stats)).
+:- use_module(components(dashboard/show_objects)).
+:- use_module(components(dashboard/top_nav_bar)).
+:- use_module(components(dashboard/pagination)).
+
+:- http_handler(cliopatria(annotate/dashboard/task), http_dashboard_task, []).
+
+:- setting(annotation:dashboard_admin_only, boolean, true,
+	   'Dashboard only for users with admin rights').
+
+cliopatria:menu_item(100=annotation/http_dashboard_home, 'dashboard').
+
+:- html_resource(dashboard,
+		 [ virtual(true),
+		   ordered(true),
+		   requires([bootstrap,
+			     css('deniche-dashboard.css'),
+			     css('deniche-tags.css'),
+			     yui3('yui/yui-min.js'),
+			     js('dashboard.js')
+			    ])
+		 ]).
+:- html_resource(task_stats,
+		 [ virtual(true),
+		   requires([d3js,
+			    css('task_stats.css')])
+		 ]).
+:- html_resource(d3js,
+		 [ virtual(true),
+		   requires(['http://d3js.org/d3.v3.min.js'])
+		 ]).
+
+:- html_resource(bootstrap,
+	      [ virtual(true),
+		requires(
+		    [ '//netdna.bootstrapcdn.com/bootstrap/3.1.1/css/bootstrap.min.css'
+		    ])
+	      ]).
+
+
+http_dashboard_task(Request) :-
+	(setting(annotation:dashboard_admin_only, true)
+	-> authorized(admin(dashboard)); true),
+	http_parameters(Request,
+			[task(Task, []),
+			 limit(Limit, [nonneg, default(5)]),
+			 offset(Offset, [nonneg, default(0)])
+			]),
+
+	task_page(Task, [showTag(always), limit(Limit), offset(Offset)]).
+
+task_page(Task, Options0) :-
+	option(limit(Limit), Options0, 5),
+	option(offset(Offset), Options0, 0),
+	rdf_display_label(Task, Label),
+	rdf_has(Task, ann_ui:taskUI, UI),
+	get_metafields(UI, [], MetadataFields),
+	% get_anfields(UI, [], [], AnnotationFields),
+	AnnotationFields = [ 'http://eculture.cs.vu.nl/sealinc/ns/demo/ui/CommonBirdNameAnnotation'],
+	find_annotations_by_task(Task, Annotations),
+	partition(is_tag, Annotations, Tags, Judgements),
+	maplist(rdf_get_annotation_target, Tags, RawTargets),
+	sort(RawTargets, AllTargets), % de-dup
+	% list_offset(['http://purl.org/collections/nl/rma/collection/r-108494'|AllTargets], Offset, OffTargets),
+	list_offset(AllTargets, Offset, OffTargets),
+	list_limit(OffTargets, Limit, Objects, _Rest),
+	length(AllTargets, Total),
+	maplist(count_annotations, Objects, CountPairs),
+	sort(CountPairs, SortedPairs0),
+	reverse(SortedPairs0, ReversePairs),
+	pairs_values(ReversePairs, _SortedObjects),
+	Options = [annotations(Annotations),
+		   judgements(Judgements),
+		   annotation_fields(AnnotationFields),
+		   metadata_fields(MetadataFields),
+		   ui(UI),
+		   task(Task),
+		   lazy(true),
+		   limit(Limit),
+		   offset(Offset),
+		   total(Total),
+		   image_link_predicate(http_mediumscale) |
+		   Options0
+		  ],
+	reply_html_page(
+	    [ title(Label),
+	      meta([name(viewport),
+		   content('width=device-width, initial-scale=1')]),
+	      \html_requires(dashboard)
+	    ],
+	    [ \top_navbar,
+	      div([class('container-fluid')],
+		  [
+		    div([class(row)],
+			[ div([class('col-sm-12 main')],
+			      [ h1([class('page-header')], ['Dashboard']),
+				h2([class('sub-header')],
+				   [Label]),
+				div([class(row)], \task_stats(Task)),
+				h3([class('sub-header')],
+				   ['Task objects']),
+				\show_objects(Objects, Options),
+				\pagination(Options)
+			      ])
+			])
+		  ])
+	    ]).
diff --git a/applications/dashboard_user_page.pl b/applications/dashboard_user_page.pl
new file mode 100644
index 0000000..d23bdc7
--- /dev/null
+++ b/applications/dashboard_user_page.pl
@@ -0,0 +1,74 @@
+:- module(an_dashboard_user_page, []).
+
+% from SWI-Prolog libraries:
+:- use_module(library(apply)).
+:- use_module(library(http/http_dispatch)).
+:- use_module(library(http/http_parameters)).
+:- use_module(library(http/html_write)).
+:- use_module(library(http/html_head)).
+
+% from ClioPatria:
+:- use_module(cliopatria(hooks)).
+:- use_module(user(user_db)).
+
+% from other cpacks:
+:- use_module(library(oa_schema)).
+:- use_module(library(oa_annotation)).
+:- use_module(api(media_caching)).       % needed for http api handlers
+
+% from this pack:
+:- use_module(api(dashboard_api)).
+:- use_module(library(dashboard_util)).
+:- use_module(components(dashboard/top_nav_bar)).
+:- use_module(components(dashboard/show_objects)).
+:- use_module(components(dashboard/show_option_list)).
+
+:- http_handler(cliopatria(annotate/dashboard/user), http_dashboard_user, []).
+
+http_dashboard_user(Request) :-
+	(setting(annotation:dashboard_admin_only, true)
+	-> authorized(admin(dashboard)); true),
+	http_parameters(Request, [user(User, [])]),
+	user_page(User, []).
+
+user_page(User, Options0) :-
+	findall(Prop, user_property(User, Prop), Props),
+	find_annotations_by_user(User, Annotations),
+	partition(is_tag, Annotations, Tags, Judgements),
+	maplist(rdf_get_annotation_target, Tags, Targets),
+	sort(Targets, Objects),
+	Options = [annotations(Annotations),
+		   judgements(Judgements),
+		   lazy(true),
+		   user(User),
+		   showTag(mine),
+		   image_link_predicate(http_mediumscale) |
+		   Options0
+		  ],
+	reply_html_page(
+	    [title(User),
+	     meta([name(viewport),
+		    content('width=device-width, initial-scale=1')],
+		   []),
+	     \html_requires(dashboard)
+	    ],
+	    [ \top_navbar,
+	      div([class('container-fluid')],
+		  [ div([class(row)],
+			[ div([class('col-sm-12 main')
+			      ],
+			      [ h1([class('page-header')], ['Dashboard']),
+				h2([class('sub-header')],
+				   ['User information']),
+				div([class('table-responsive')],
+				    [table([class('table table-striped')],
+					   [ \show_option_list(Props)
+					   ])
+				    ]),
+				h2([class('sub-header')],
+				   ['Annotations made so far']),
+				\show_objects(Objects, Options)
+			      ])
+			])
+		  ])
+	    ]).
diff --git a/components/dashboard/pagination.pl b/components/dashboard/pagination.pl
new file mode 100644
index 0000000..099a00a
--- /dev/null
+++ b/components/dashboard/pagination.pl
@@ -0,0 +1,28 @@
+:- module(an_dashboard_components_pagination,
+	  [ pagination//1
+	  ]).
+
+:- use_module(library(apply)).
+:- use_module(library(lists)).
+:- use_module(library(option)).
+:- use_module(library(http/html_write)).
+
+pagination(Options) -->
+	{ option(limit(Limit), Options),
+	  option(offset(Offset), Options),
+	  option(total(Total), Options),
+	  Max is floor(Total/Limit),
+	  numlist(0,Max, List1),
+	  maplist(multiply(Limit), List1, List)
+	},
+	html(ul([class(pagination)],[\pitem(Offset, List)])).
+
+multiply(A,B,P) :- P is A * B.
+pitem(_, []) --> !.
+pitem(Offset, [H1|T]) -->
+	{ ( T = [H2|_], between(H1, H2, Offset)
+	  ->  Class = [active]
+	  ;   Class = [])
+	},
+	html(li([class(Class)],a([href('#')],H1))),
+	pitem(Offset,T).
diff --git a/components/dashboard/show_annotations.pl b/components/dashboard/show_annotations.pl
new file mode 100644
index 0000000..bc26269
--- /dev/null
+++ b/components/dashboard/show_annotations.pl
@@ -0,0 +1,98 @@
+:- module(an_dashboard_components_show_annotations,
+	  [ show_annotations//2
+	  ]).
+
+:- use_module(library(apply)).
+:- use_module(library(lists)).
+:- use_module(library(option)).
+:- use_module(library(pairs)).
+
+:- use_module(library(semweb/rdf_db)).
+:- use_module(library(semweb/rdf_label)).
+:- use_module(library(http/html_write)).
+
+:- use_module(components(label)).
+
+show_annotations(List, Options) -->
+	{ maplist(ann_sort_key, List, KeyList),
+	  keysort(KeyList, KeySorted),
+	  pairs_values(KeySorted, Sorted)
+	},
+	show_annotations_(Sorted, Options).
+
+show_annotations_([], _) --> !.
+show_annotations_([H|T], Options) -->
+	html(tr([],
+		\show_annotation_summery(H, Options))),
+	show_annotations_(T, Options).
+
+ann_sort_key(Annotation, Key-Annotation) :-
+	rdf_has(Annotation, ann_ui:annotationField, Field),
+	rdf_display_label(Field, FieldLabel),
+	rdf_display_label(Annotation,BodyLabel),
+	Key=key(FieldLabel, BodyLabel).
+
+show_annotation_summery(A, Options) -->
+	{ rdf_has(A, oa:annotatedBy, User),
+	  (   rdf_has(A, ann_ui:annotationField, Field)
+	  ->  true
+	  ;   Field = undefined
+	  ),
+	  option(judgements(J), Options, []),
+	  include(is_judgement_of(A), J, Js)
+	},
+	html([
+	    td([class(judgebuttoncell)],
+	       div([class('btn-group'), 'data-toggle'(buttons)],
+		   [ \judge_button(agree, A, Field, Js),
+		     \judge_button(disagree, A, Field, Js)
+		   ])
+	      ),
+	    td(\rdf_link(Field, [resource_format(label)])),
+	    td(\rdf_link(A,     [resource_format(label)])),
+	    td(\rdf_link(User,  [resource_format(label)]))
+	]).
+
+is_judgement_of(A, J) :-
+	rdf_has(J, oa:hasTarget, A).
+
+
+judge_button(Type, Annotation, Field, Judgements) -->
+	{  current_judgment(Type, Annotation, Judgements, J, Checked),
+	   checked_active(Checked, Active)
+	},
+	html([
+	    label([class([Active, btn,'btn-primary'])],
+		  [ input([class([judgebutton, Type, Checked
+				 ]),
+			   field(Field),
+			   judgement(J),
+			   annotation(Annotation),
+			   type(radio),
+			   title(Type), 'data-toggle'(tooltip)
+			  ],
+			  [
+			      \button_glyph(Type)
+			  ])
+		  ])
+	]).
+
+current_judgment(Type, A, Jlist, J, checked) :-
+	member(J, Jlist),
+	rdf_has(J, oa:hasTarget, A),
+	rdf_has(J, dc:title, literal(Type)),
+	!.
+
+current_judgment(_Type, A, Jlist, J, unchecked) :-
+	member(J, Jlist),
+	rdf_has(J, oa:hasTarget, A),!.
+
+current_judgment(_,_,_, null, unchecked).
+
+button_glyph(agree) -->
+	html(span([class([glyphicon,'glyphicon-thumbs-up'])],[' agree'])).
+button_glyph(disagree) -->
+	html(span([class([glyphicon,'glyphicon-thumbs-down'])],[' disagree'])).
+
+checked_active(checked, active).
+checked_active(_, '').
diff --git a/components/dashboard/show_objects.pl b/components/dashboard/show_objects.pl
new file mode 100644
index 0000000..a0cec9b
--- /dev/null
+++ b/components/dashboard/show_objects.pl
@@ -0,0 +1,74 @@
+:- module(an_dashboard_components_show_objects,
+	  [ show_objects//2
+	  ]).
+
+:- use_module(library(apply)).
+:- use_module(library(lists)).
+:- use_module(library(option)).
+:- use_module(library(http/html_write)).
+:- use_module(library(semweb/rdf_db)).
+:- use_module(library(oa_annotation)).
+:- use_module(applications(annotation)).
+:- use_module(components(dashboard/show_annotations)).
+:- use_module(components(dashboard/show_option_list)).
+:- use_module(library(dashboard_util)).
+
+show_objects(Targets,Options) -->
+	{ true,
+	  option(task(Task), Options),
+	  rdf_has(Task, ann_ui:taskUI, UI),
+	  get_metafields(UI, [], MetadataFields),
+	  get_anfields(UI, [], [], AnnotationFields),
+	  NewOptions = [
+	      ui(UI),
+	      metadata_fields(MetadataFields),
+	      annotation_fields(AnnotationFields) |
+	      Options
+	  ]
+	},
+	html(
+	    [div([class(row)],
+		 [div([class('col-xs-6')],
+		      [\annotation_page_body([targets(Targets)|NewOptions])
+		      ])
+		 ])
+	    ]).
+
+match_target(T,A) :-
+	rdf_get_annotation_target(A,T).
+
+show_object_old(O, Options) -->
+	{ option(annotations(A), Options, []),
+	  include(match_target(O), A, Annotations),
+	  (   ( option(metadata_fields(_), Options),
+		option(ui(_), Options),
+		option(annotation_fields(_), Options))
+	  ->  NewOptions = Options
+	  ;   ( option(task(Task), Options)
+	      ->  true
+	      ;	  member(First, A),
+		  guess_task(First, Task-First)
+	      ),
+	      rdf_has(Task, ann_ui:taskUI, UI),
+	      get_metafields(UI, [], MetadataFields),
+	      get_anfields(UI, [], [], AnnotationFields),
+	      NewOptions = [
+		  ui(UI),
+		  metadata_fields(MetadataFields),
+		  annotation_fields(AnnotationFields) |
+		  Options
+	      ]
+	  )
+	},
+	html(
+	    [div([class(row)],
+		 [div([class('col-xs-6')],
+		      [\annotation_page_body([target(O)|NewOptions])
+		      ]),
+		  div([class('col-xs-6 table-responsive')],
+		      [ table([class('table table-striped')], [
+				  \show_annotations(Annotations, NewOptions)
+			      ])
+		      ])
+		 ])
+	    ]).
diff --git a/components/dashboard/show_option_list.pl b/components/dashboard/show_option_list.pl
new file mode 100644
index 0000000..73da129
--- /dev/null
+++ b/components/dashboard/show_option_list.pl
@@ -0,0 +1,44 @@
+:- module(an_dashboard_components_show_option_list,
+	  [ show_option_list//1
+	  ]).
+
+:- use_module(library(http/html_write)).
+:- use_module(library(semweb/rdf_db)).
+:- use_module(library(semweb/rdf_label)).
+:- use_module(components(label)).
+
+show_option_list([]) --> !.
+show_option_list([Prop|Tail]) -->
+	{ (   is_dict(Prop)
+	  ->  V = Prop.'@value',
+	      Key = Prop.label
+	  ;   (   Prop = K-V
+	      ;	    Prop =.. [K,V]),
+		    (   rdf_current_predicate(K)
+		    ->  Key = \rdf_link(K)
+		    ;   Key = K
+		    )
+	  ),
+	  (   rdf_is_resource(V)
+	  ->  (   rdf_subject(V)
+	      ->  Value = \rdf_link(V)
+	      ;	   (  rdf_global_id(_:Value, V)
+		   ->  true
+		   ;   Value = V
+		   )
+	      )
+	  ;   (   rdf_is_literal(V)
+	      ->  literal_text(V, Value)
+	      ;   V = Value
+	      )
+	  )
+	},
+	html(tr([td(Key), td(Value)])),
+	show_option_list(Tail).
+
+show_option_list(Dict) -->
+	{ is_dict(Dict),
+	  dict_pairs(Dict, _Tag, Pairs)
+	},
+	show_option_list(Pairs).
+
diff --git a/components/dashboard/show_tasks.pl b/components/dashboard/show_tasks.pl
new file mode 100644
index 0000000..d7a67d8
--- /dev/null
+++ b/components/dashboard/show_tasks.pl
@@ -0,0 +1,51 @@
+:- module(an_dashboard_components_show_tasks,
+	  [ show_tasks//1
+	  ]).
+
+:- use_module(library(sort)).
+:- use_module(library(http/html_write)).
+:- use_module(library(http/http_dispatch)).
+
+:- use_module(library(semweb/rdf_db)).
+:- use_module(library(semweb/rdf_label)).
+:- use_module(library(dashboard_util)).
+:- use_module(applications(annotation)).
+:- use_module(show_option_list).
+
+
+show_tasks([]) --> !.
+show_tasks([H|T]) -->
+	show_task(H),
+	show_tasks(T).
+
+task_compare(Order, Task1, Task2) :-
+	compare(Order, Task1.order, Task2.order).
+
+show_task(Task) -->
+	{ rdf_display_label(Task,Title),
+	  http_link_to_id(http_dashboard_task, [task(Task)], TaskLink),
+	  find_task_properties(Task, Props0, Representative,[]),
+	  predsort(task_compare, Props0, Props),
+	  object_image(Representative, Image),
+	  http_link_to_id(http_medium_fit, [uri(Image)], ImageHref)
+
+	},
+	html([div(class(row),
+		  [ h3([class('sub-header')],
+		       [a([href(TaskLink)],Title)]),
+		    div(class('col-sm-5'),
+			[
+			    img([src(ImageHref), alt('Example image for this task'),
+				 class('img-responsive')],[])
+			]),
+		    div(class('col-sm-7'),
+			[
+			  div([class('table-responsive')],
+			      [table([class('table table-striped')],
+				     [ % thead([tr([th('Property'), th('Value')])]),
+				       tbody([\show_option_list(Props)])
+				     ])
+			      ])
+			])
+		  ])
+	     ]).
diff --git a/components/dashboard/show_users.pl b/components/dashboard/show_users.pl
new file mode 100644
index 0000000..2f75eee
--- /dev/null
+++ b/components/dashboard/show_users.pl
@@ -0,0 +1,25 @@
+:- module(an_dashboard_components_show_users,
+	  [ show_users//2
+	  ]).
+
+:- use_module(library(option)).
+:- use_module(library(sgml)).
+:- use_module(library(http/html_write)).
+:- use_module(library(http/http_dispatch)).
+
+show_users([], _) --> !.
+show_users([U|T], Rank) -->
+	{ Next is Rank + 1
+	},
+	show_user(U, Rank),
+	show_users(T, Next).
+
+show_user(U, Rank) -->
+	{ option(id(Uid), U),
+	  option(done(Done), U),
+	  iri_xml_namespace(Uid, _, ScreenName),
+	  http_link_to_id(http_dashboard_user, [user(Uid)], UserLink)
+	},
+	html(tr([td([class(rank)],[Rank]),
+		 td(a([href(UserLink)],[ScreenName])),
+		 td([class='an_nr_of_annotations'],Done)])).
diff --git a/components/dashboard/task_stats.pl b/components/dashboard/task_stats.pl
new file mode 100644
index 0000000..a5939c1
--- /dev/null
+++ b/components/dashboard/task_stats.pl
@@ -0,0 +1,106 @@
+:- module(an_dashboard_components_task_stats,
+	  [ task_stats//1
+	  ]).
+
+:- use_module(library(gensym)).
+:- use_module(library(http/js_write)).
+:- use_module(library(http/http_dispatch)).
+:- use_module(library(http/html_head)).
+:- use_module(library(http/html_write)).
+
+task_stats(Task) -->
+	{ http_link_to_id(http_api_dashboard_task,
+			  [task(Task), filter(number)], DataSource),
+	  gensym(chart, Class),
+	  atom_concat('svg.', Class, Selector)
+	},
+	html([
+	    \html_requires(task_stats),
+	    svg([class(Class)],[]),
+	    \js_script({|javascript(DataSource, Selector)||
+			var cwidth = document.body.clientWidth;
+			var margin = {top: 20, right: 40, bottom: 50, left: 50},
+			width =  0.45*cwidth - margin.left - margin.right,
+			height = 200 - margin.top - margin.bottom;
+
+
+			var x = d3.scale.ordinal()
+			.rangeRoundBands([5, width], .1);
+
+			var y = d3.scale.linear()
+			.range([height, 0]);
+
+			var xAxis = d3.svg.axis()
+			.scale(x)
+			.tickSize(10,0)
+			.orient("bottom");
+
+			var yAxis = d3.svg.axis()
+			.scale(y)
+			.orient("left")
+			.ticks(10, "");
+
+			var svg = d3.select(Selector)
+			.attr("width", width + margin.left + margin.right)
+			.attr("height", height + margin.top + margin.bottom)
+			.append("g")
+			.attr("transform", "translate(" + margin.left + "," + margin.top + ")");
+
+			d3.json(DataSource, function(error, data) {
+						data.sort(compare_value);
+
+						x.domain(data.map(function(d) { return d.label; }));
+						y.domain([0, d3.max(data, function(d) { return d['@value']; })]);
+
+						var bar = svg.selectAll("g")
+						.data(data)
+						.enter()
+						.append("g");
+
+						bar.append("rect")
+						.attr("class", function(d) { return "bar " + d.key; })
+						.attr("x", function(d) { return x(d.label); })
+						.attr("width", x.rangeBand())
+						.attr("y", function(d) { return y(d['@value']); })
+						.attr("height", function(d) { return height - y(d['@value']); });
+
+						bar.append("text")
+						.style("text-anchor", "middle")
+						.attr("class", "count")
+						.attr("x", function(d) { return x(d.label) + 0.5 * x.rangeBand(); })
+						.attr("y", function(d) { return Math.min(y(0), y(d['@value'])); })
+						.attr("dy", "-1ex")
+						.text(function(d) { return d['@value']; });
+
+						svg.append("g")
+						.attr("class", "x axis")
+						.attr("transform", "translate(0," + height + ")")
+						.call(xAxis).selectAll("text")
+						.style("text-anchor", "middle")
+						.attr("dx", '.1em')
+						.attr("dy", function(d,i) { return 0 + 14*(i%3); });
+
+						d3.selectAll("g.x.axis g.tick line")
+						.style("stroke-opacity", 0.2)
+						.attr("y2", function(d,i){ return 15 + 14*(i%3); });
+
+						svg.append("g")
+						.attr("class", "y axis")
+						.call(yAxis)
+						.append("text")
+						.attr("transform", "rotate(-90)")
+						.attr("y", 6)
+						.attr("dy", "0.7ex")
+						.style("text-anchor", "end")
+						.text("Count");
+					    });
+
+			function compare_value(a,b) {
+				     if (a.value < b.value) return 1;
+				     if (a.value > b.value) return -1;
+				     return 0;
+				 }
+
+
+		       |})
+	]).
diff --git a/components/dashboard/top_nav_bar.pl b/components/dashboard/top_nav_bar.pl
new file mode 100644
index 0000000..5854b8f
--- /dev/null
+++ b/components/dashboard/top_nav_bar.pl
@@ -0,0 +1,39 @@
+:- module(an_dashboard_comp_top_nav_bar,
+	  [ top_navbar//0
+	  ]).
+
+:- use_module(library(http/http_dispatch)).
+:- use_module(library(http/html_write)).
+
+top_navbar -->
+	{ http_link_to_id(http_annotation, [], AnnotateLink)
+	},
+	html(
+	    div([class('navbar navbar-inverse navbar-fixed-top'),
+		 role('navigation')],
+		[div([class('container-fluid')],
+		     [div([class('navbar-header')],
+			  [button([type('button'), class('navbar-toggle'),
+				   'data-toggle'(collapse), 'data-target'('.navbar-collapse')],
+				   [ span([class('sr-only')], 'Toggle navigation'),
+				     span([class('icon-bar')],[]),
+				     span([class('icon-bar')],[]),
+				     span([class('icon-bar')],[])
+				   ]),
+			   a([class('navbar-brand'),
+			      href('http://sealincmedia.wordpress.com/tag/accurator/')
+			     ], ['Accurator for ',
+				 span([class(role)],['Curator'])])
+			  ]),
+		      div(class('navbar-collapse collapse'),
+			  [ ul(class('nav navbar-nav navbar-right'),
+				[ li([a([href('home')],['Dashboard'])]),
+				  li([a([href(AnnotateLink)],['Annotate'])]),
+				  li([a([href('../../admin')],['Admin'])]),
+				  li([a([href('../../user/logout')],['Logout'])])
+
+				])
+			  ])
+		     ])
+		])
+	).
diff --git a/config-available/annotation_dashboard.pl b/config-available/annotation_dashboard.pl
index c382247..69ed8a6 100644
--- a/config-available/annotation_dashboard.pl
+++ b/config-available/annotation_dashboard.pl
@@ -3,4 +3,6 @@
 /** <module> Web interface to view who does what in the annotation_service module
 */
 
-:- use_module(applications(dashboard)).
+:- use_module(applications(dashboard_startpage)).
+:- use_module(applications(dashboard_user_page)).
+:- use_module(applications(dashboard_task_page)).