View source with formatted comments or as raw
    1/*  Part of ClioPatria SeRQL and SPARQL server
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@cs.vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (C): 2010, University of Amsterdam,
    7		   VU University Amsterdam
    8
    9    This program is free software; you can redistribute it and/or
   10    modify it under the terms of the GNU General Public License
   11    as published by the Free Software Foundation; either version 2
   12    of the License, or (at your option) any later version.
   13
   14    This program is distributed in the hope that it will be useful,
   15    but WITHOUT ANY WARRANTY; without even the implied warranty of
   16    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   17    GNU General Public License for more details.
   18
   19    You should have received a copy of the GNU General Public
   20    License along with this library; if not, write to the Free Software
   21    Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
   22
   23    As a special exception, if you link this library with other files,
   24    compiled with a Free Software compiler, to produce an executable, this
   25    library does not by itself cause the resulting executable to be covered
   26    by the GNU General Public License. This exception does not however
   27    invalidate any other reasons why the executable file might be covered by
   28    the GNU General Public License.
   29*/
   30
   31:- module(cp_menu,
   32	  [ cp_menu//0
   33	  ]).   34:- use_module(library(http/html_write)).   35:- use_module(library(http/html_head)).   36:- use_module(library(http/http_dispatch)).   37:- use_module(library(pairs)).   38:- use_module(library(apply)).   39:- use_module(library(uri)).   40:- use_module(library(ctypes)).   41:- use_module(user(user_db)).   42:- use_module(cliopatria(hooks)).   43
   44/** <module> ClioPatria menu-bar
   45
   46This  module  provides  the   ClioPatria    application   menu-bar.  The
   47application menu is attached by cliopatria(skin)  to all HTML pages that
   48match the style cliopatria(_) (see reply_html_page/3).
   49
   50@see	The menu is built using CSS from
   51	http://denilsonsa.selfip.org/~denilson/menu/menu.html
   52*/
   53
   54%%	cp_menu//
   55%
   56%	HTML Components that emits the ClioPatria   menu.  The menu is a
   57%	standard nested HTML =ul= list, turned   into  a horizontal menu
   58%	using CSS. The menu can be   extended and controlled using three
   59%	hooks in the module =cliopatria=:
   60%
   61%	    * cliopatria:menu_item/2 defines the menu-items present
   62%	    * cliopatria:menu_label/2 assigns non-standard labels
   63%	    * cliopatria:menu_popup_order/2 defines the order of the popups
   64
   65cp_menu -->
   66	{ findall(Key-Item, current_menu_item(Key, Item), Pairs0),
   67	  sort(Pairs0, Pairs),
   68	  group_pairs_by_key(Pairs, ByKey),
   69	  sort_menu_popups(ByKey, Menu)
   70	},
   71	html_requires(css('menu.css')),
   72	html(ul(id(nav),
   73		\menu(Menu))).
   74
   75menu([]) --> !.
   76menu([_-[Item]|T]) --> !,
   77	menu_item(Item),
   78	menu(T).
   79menu([Key-Items|T]) -->
   80	{ menu_label(Key, Key, Label) },
   81	html(li([ a([Label]),
   82		  ul(\menu_items(Items))
   83		])),
   84	menu(T).
   85
   86menu_items([]) --> [].
   87menu_items([H|T]) --> menu_item(H), menu_items(T).
   88
   89menu_item(item(_Rank, Spec, Label, Options)) -->
   90	{ atom(Spec) }, !,
   91	{ (   \+ sub_atom(Spec, 0, _, _, 'http://'),
   92	      catch(http_location_by_id(Spec, Location), E,
   93		    (   print_message(informational, E),
   94			fail))
   95	  ->  true
   96	  ;   Location = Spec
   97	  )
   98	},
   99	html(li(a([href(Location)|Options], Label))).
  100
  101
  102%%	current_menu_item(-PopupKey, -Item) is nondet.
  103%
  104%	Enumerate the menu-items.
  105%
  106%	@param PopupKey is the id  of  a   popup.  The  label thereof is
  107%	computed by menu_label/3 and the ordering by menu_popup_order/2.
  108%	@param Item is a term item(Rank, Location, Label).
  109
  110current_menu_item(Key, item(Rank, Location, Label, Options)) :-
  111	menu_item(Spec, DefLabel),
  112	rank(Spec, Rank, Where, Options),
  113	(   Where = Key/Location
  114	->  menu_label(Location, DefLabel, Label)
  115	;   Where = Location,
  116	    Key = Location,
  117	    menu_label(Location, DefLabel, Label)
  118	).
  119
  120rank(Rank=Spec, Rank, Where, Options) :- !,
  121	item_options(Spec, Where, Options).
  122rank(Spec,      0,    Where, Options) :-
  123	item_options(Spec, Where, Options).
  124
  125item_options(Spec+Option, Where, [Option|T]) :- !,
  126	item_options(Spec, Where, T).
  127item_options(Where, Where, []).
  128
  129
  130%%	menu_item(Item, ?Label) is nondet.
  131%
  132%	Define a menu-item for  the   ClioPatria  application menu. This
  133%	predicate is hooked by cliopatria:menu_item/2.
  134%
  135%	@param Item is of the form Rank=Popup/Handler, where Handler is
  136%	the identifier of the HTTP handler (see http_handler/3).
  137%
  138%	@param Label is the label of the popup.
  139
  140menu_item(Item, Label) :-
  141	cliopatria:menu_item(Item, Label).
  142
  143menu_item(100=repository/load_file_form,		'Load local file').
  144menu_item(200=repository/load_url_form,			'Load from HTTP').
  145menu_item(300=repository/load_library_rdf_form,		'Load from library').
  146menu_item(400=repository/remove_statements_form,	'Remove triples').
  147menu_item(500=repository/clear_repository_form,		'Clear repository').
  148
  149menu_item(100=query/yasgui_editor,		        'YASGUI SPARQL Editor').
  150menu_item(200=query/query_form,				'Simple Form').
  151
  152menu_item(100=places/home,				'Home').
  153menu_item(200=places/list_graphs,			'Graphs').
  154menu_item(200=places/list_prefixes,			'Prefixes').
  155
  156menu_item(100=admin/list_users,				'Users').
  157menu_item(200=admin/settings,				'Settings').
  158menu_item(300=admin/statistics,				'Statistics').
  159
  160menu_item(100=user/login_form+class(login),		'Login') :-
  161	\+ someone_logged_on.
  162menu_item(100=current_user/user_logout,			'Logout') :-
  163	someone_logged_on.
  164menu_item(200=current_user/change_password_form,	'Change password') :-
  165	local_user_logged_on.
  166menu_item(300=current_user/my_openid_page,		'My OpenID page') :-
  167	open_id_user(_).
  168
  169sort_menu_popups(List, Sorted) :-
  170	map_list_to_pairs(popup_order, List, Keyed),
  171	keysort(Keyed, KeySorted),
  172	pairs_values(KeySorted, Sorted).
  173
  174popup_order(Key-Members, Order-(Key-Members)) :-
  175	(   menu_popup_order(Key, Order)
  176	->  true
  177	;   Order = 550			% between application and help
  178	).
  179
  180%%	menu_popup_order(+Item, -Location)
  181%
  182%	Provide numeric locations for the   popup-items.  This predicate
  183%	can be hooked by cliopatria:menu_popup_order/2.
  184
  185menu_popup_order(Popup, Order) :-
  186	cliopatria:menu_popup_order(Popup, Order), !.
  187menu_popup_order(places,       100).
  188menu_popup_order(admin,	       200).
  189menu_popup_order(repository,   300).
  190menu_popup_order(query,	       400).
  191menu_popup_order(application,  500).
  192menu_popup_order(help,	       600).
  193menu_popup_order(user,	       700).
  194menu_popup_order(current_user, 800).
  195
  196%%	menu_label(+Id, +Default, -Label) is det.
  197
  198menu_label(Item, _Default, Label) :-
  199	cliopatria:menu_label(Item, Label), !.
  200menu_label(current_user, _Default, Label) :-
  201	logged_on(User, X),
  202	X \== User, !,
  203	(   user_property(User, realname(RealName))
  204	->  true
  205	;   RealName = 'My account'
  206	),
  207	(   user_property(User, url(URL))
  208	->  Label = a(href(URL), i(RealName))
  209	;   Label = i(RealName)
  210	).
  211menu_label(_, Default, Label) :-
  212	id_to_label(Default, Label).
  213
  214%%	id_to_label(+HandlerID, -Label) is det.
  215%
  216%	Computes a default label  from   the  HandlerID. Underscores are
  217%	mapped to spaces and the first character is capitalised.
  218
  219id_to_label(Atom, Capital) :-
  220	atom_codes(Atom, Codes0),
  221	maplist(underscore_to_space, Codes0, Codes),
  222	(   maplist(is_upper, Codes)
  223	->  Capital = Atom
  224	;   Codes = [First|Rest]
  225	->  code_type(First, to_lower(Up)),
  226	    UpCodes = [Up|Rest],
  227	    atom_codes(Capital, UpCodes)
  228	;   Capital = Atom
  229	).
  230
  231underscore_to_space(0'_, 32) :- !.
  232underscore_to_space(X, X).
  233
  234%%	local_user_logged_on is semidet.
  235%
  236%	True if the currently logged on user is a local user (as opposed
  237%	to an OpenID accredited logon).
  238
  239local_user_logged_on :-
  240	logged_on(User, X),
  241	X \== User,
  242	\+ ( uri_components(User, Components),
  243	     uri_data(scheme, Components, Scheme),
  244	     nonvar(Scheme)
  245	   ).
  246
  247%%	someone_logged_on is semidet.
  248%
  249%	True if some user is logged on.
  250
  251someone_logged_on :-
  252	logged_on(User, X),
  253	X \== User.
  254
  255		 /*******************************
  256		 *	      OpenID		*
  257		 *******************************/
  258
  259:- http_handler(root(my_openid_page), my_openid_page, []).  260
  261my_openid_page(Request) :-
  262	open_id_user(User),
  263	http_redirect(see_other, User, Request).
  264
  265open_id_user(User) :-
  266	logged_on(User, X),
  267	X \== User,
  268	uri_components(User, Components),
  269	uri_data(scheme, Components, Scheme),
  270	nonvar(Scheme)