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 VU University Amsterdam
    7
    8    This program is free software; you can redistribute it and/or
    9    modify it under the terms of the GNU General Public License
   10    as published by the Free Software Foundation; either version 2
   11    of the License, or (at your option) any later version.
   12
   13    This program is distributed in the hope that it will be useful,
   14    but WITHOUT ANY WARRANTY; without even the implied warranty of
   15    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   16    GNU General Public License for more details.
   17
   18    You should have received a copy of the GNU General Public
   19    License along with this library; if not, write to the Free Software
   20    Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
   21
   22    As a special exception, if you link this library with other files,
   23    compiled with a Free Software compiler, to produce an executable, this
   24    library does not by itself cause the resulting executable to be covered
   25    by the GNU General Public License. This exception does not however
   26    invalidate any other reasons why the executable file might be covered by
   27    the GNU General Public License.
   28*/
   29
   30:- module(html_basics,
   31	  [ hidden//2,			% +Name, +Value
   32	    form_input//2,		% +Label, +Input
   33	    form_submit//1,		% +Label
   34	    n//2,			% +Format, +Value
   35	    nc//2,			% +Format, +Value
   36	    nc//3,			% +Format, +Value, +Options
   37	    odd_even_row//3,		% +Row, -Next, :Content
   38	    sort_th//3,			% +Field, +ByNow, :Content
   39	    insert_html_file//1		% +FileSpec
   40	  ]).   41:- use_module(library(http/html_write)).   42:- use_module(library(sgml)).   43:- use_module(library(lists)).   44:- use_module(library(option)).   45:- use_module(library(occurs)).   46:- use_module(library(http/http_dispatch)).   47:- use_module(library(http/http_wrapper)).   48
   49:- html_meta((
   50	form_input(html, html, ?, ?),
   51	odd_even_row(+, -, html, ?, ?),
   52	sort_th(+, +, html, ?, ?))).   53
   54/** <module> Simple Small HTML components
   55*/
   56
   57		 /*******************************
   58		 *	       FORMS		*
   59		 *******************************/
   60
   61%%	hidden(+Name, +Value)// is det.
   62%
   63%	Create a hidden input field with given name and value
   64
   65hidden(Name, Value) -->
   66	html(input([ type(hidden),
   67		     name(Name),
   68		     value(Value)
   69		   ])).
   70
   71
   72%%	form_input(+Label, +Input)// is det.
   73%%	form_submit(+Label)// is det.
   74%
   75%	Building blocks for HTML forms. The  form itself is a two-column
   76%	table of class =form= with labels at  the left and inputs at the
   77%	right. These rules create rows for input and submit.
   78
   79form_input(Label, Input) -->
   80	html(tr([ th(class(label), Label),
   81		  td(Input)
   82		])).
   83
   84
   85form_submit(Label) -->
   86	html(tr(class(buttons),
   87		[ th([align(right), colspan(2)],
   88		     input([ type(submit),
   89			     value(Label)
   90			   ]))
   91		])).
   92
   93
   94		 /*******************************
   95		 *	       TABLES		*
   96		 *******************************/
   97
   98%%	nc(+Format, +Value)// is det.
   99%%	nc(+Format, +Value, +Options)// is det.
  100%
  101%	Numeric  cell.  The  value  is    formatted   using  Format  and
  102%	right-aligned in a table cell (td).
  103%
  104%	@param	Format is a (numeric) format as described by format/2 or
  105%		the constant =human=.  _Human_ formatting applies to
  106%		integers and prints then in abreviated (K,M,T) form,
  107%		e.g., 4.5M for 4.5 million.
  108%	@param	Options is passed as attributed to the =td= element.
  109%		Default alignment is =right=.
  110
  111nc(Fmt, Value) -->
  112	nc(Fmt, Value, []).
  113
  114nc(Fmt, Value, Options) -->
  115	{ class(Value, Class),
  116	  merge_options(Options,
  117			[ align(right),
  118			  class(Class)
  119			], Opts),
  120	  number_html(Fmt, Value, HTML)
  121	},
  122	html(td(Opts, HTML)).
  123
  124class(Value, Class) :-
  125	(   integer(Value)
  126	->  Class = int
  127	;   float(Value)
  128	->  Class = float
  129	;   Class = value
  130	).
  131
  132
  133%%	odd_even_row(+Row, -Next, :Content)//
  134%
  135%	Create odd/even alternating table rows from a DCG.
  136
  137odd_even_row(Row, Next, Content) -->
  138	{ (   Row mod 2 =:= 0
  139	  ->  Class = even
  140	  ;   Class = odd
  141	  ),
  142	  Next is Row+1
  143	},
  144	html(tr(class(Class), Content)).
  145
  146%%	sort_th(+Field, +ByNow, :Label)
  147%
  148%	Provide a column-header for a table   that can be resorted. This
  149%	call creates a =th= element holding an   =a=. The =a= has either
  150%	CSS class =sorted= if the column is   sorted  or =resort= if the
  151%	column can be sorted on this column.   The use of this component
  152%	demands that the handler processes the parameter =sort_by= using
  153%	the field-name as argument.
  154%
  155%	@param	Field is the field-name that describes the sort on this
  156%		column.
  157%	@param	ByNow is the field on which the table is currently
  158%		sorted.
  159%	@param  Label is the label of the =a= element
  160
  161sort_th(Name, Name, Label) -->
  162	html(th(a([class(sorted)], Label))).
  163sort_th(Name, _By, Label) -->
  164	{ http_current_request(Request),
  165	  http_reload_with_parameters(Request, [sort_by(Name)], HREF)
  166	},
  167	html(th(a([href(HREF), class(resort)], Label))).
  168
  169
  170		 /*******************************
  171		 *	       NUMBERS		*
  172		 *******************************/
  173
  174%%	n(+Format, +Value)//
  175%
  176%	HTML component to emit a number.
  177%
  178%	@see nc//2 for details.
  179
  180n(Fmt, Value) -->
  181	{ number_html(Fmt, Value, HTML) },
  182	html(HTML).
  183
  184number_html(human, Value, HTML) :-
  185	integer(Value), !,
  186	human_count(Value, HTML).
  187number_html(Fmt, Value, HTML) :-
  188	number(Value), !,
  189	HTML = Fmt-[Value].
  190number_html(_, Value, '~p'-[Value]).
  191
  192
  193human_count(Number, HTML) :-
  194	Number < 1024, !,
  195	HTML = '~d'-[Number].
  196human_count(Number, HTML) :-
  197	Number < 1024*1024, !,
  198	KB is Number/1024,
  199	digits(KB, N),
  200	HTML = '~*fK'-[N, KB].
  201human_count(Number, HTML) :-
  202	Number < 1024*1024*1024, !,
  203	MB is Number/(1024*1024),
  204	digits(MB, N),
  205	HTML = '~*fM'-[N, MB].
  206human_count(Number, HTML) :-
  207	TB is Number/(1024*1024*1024),
  208	digits(TB, N),
  209	HTML = '~*fG'-[N, TB].
  210
  211digits(Count, N) :-
  212	(   Count < 100
  213	->  N = 1
  214	;   N = 0
  215	).
  216
  217
  218		 /*******************************
  219		 *	   INCLUDE FILES	*
  220		 *******************************/
  221
  222%%	insert_html_file(+Specification)//
  223%
  224%	Insert the content of an HTML   file  into the current document.
  225%	Only the content of the =body= element is included.
  226
  227insert_html_file(Alias) -->
  228	{ absolute_file_name(Alias, Page, [access(read)]),
  229	  load_html_file(Page, DOM),
  230	  contains_term(element(body, _, Body), DOM),
  231	  Style = element(style, _, _),
  232	  findall(Style, sub_term(Style, DOM), Styles),
  233	  append(Styles, Body, Content)
  234	},
  235	html(Content)