View source with raw comments or as raw
    1/*  Part of SWISH
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2014, VU University Amsterdam
    7    All rights reserved.
    8
    9    Redistribution and use in source and binary forms, with or without
   10    modification, are permitted provided that the following conditions
   11    are met:
   12
   13    1. Redistributions of source code must retain the above copyright
   14       notice, this list of conditions and the following disclaimer.
   15
   16    2. Redistributions in binary form must reproduce the above copyright
   17       notice, this list of conditions and the following disclaimer in
   18       the documentation and/or other materials provided with the
   19       distribution.
   20
   21    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   22    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   23    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   24    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   25    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   26    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   27    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   28    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   29    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   30    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   31    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   32    POSSIBILITY OF SUCH DAMAGE.
   33*/
   34
   35:- module(swish_render_codes,
   36	  [ term_rendering//3			% +Term, +Vars, +Options
   37	  ]).   38:- use_module(library(option)).   39:- use_module(library(http/html_write)).   40:- use_module('../render').   41
   42:- register_renderer(codes, "Render a list of character codes").

SWISH code-list renderer

Render lists of character codes as a string */

 term_rendering(+Codes, +Vars, +Options)//
Renders a list of character codes as a string. Options processed:
min_length(+Integer)
Codes must be a list of at least Integer length. Default is 3.
ellipsis(+Integer)
Write list as `bla bla ... bla` if longer than Integer. Default is 30.
partial(+Boolean)
It true (default), allow a partial list (ending in a variable).
charset(+Charset)
Set of characters to accept. Currently allows for
ascii
Allow 32..126
iso_latin_1
Allow 32..126 and 160..255
   70term_rendering(Codes, _Vars, Options) -->
   71	{ is_code_list(Codes, Len, Options)
   72	},
   73	(   { option(ellipsis(Ellipsis), Options, 30),
   74	      Len > Ellipsis
   75	    }
   76	->  { First is Ellipsis - 5,
   77	      Skip is Len - 5,
   78	      skip_first(Skip, Codes, Rest),
   79	      phrase(put_n_codes(First, Codes), PrefixCodes),
   80	      phrase(put_codes(Rest), PostfixCodes),
   81	      string_codes(Prefix, PrefixCodes),
   82	      string_codes(Postfix, PostfixCodes)
   83	    },
   84	    html(span([ 'data-render'('Truncated list of codes as a string'),
   85			class('render-code-list'),
   86			title('Code list of length: '+Len)
   87		      ],
   88		      [ '`~s'-[Prefix],
   89			span(class('render-ellipsis'), ...),
   90			'~s`'-[Postfix]
   91		      ]))
   92	;   { phrase(put_codes(Codes), TextCodes),
   93	      string_codes(String, TextCodes)
   94	    },
   95	    html(span([ 'data-render'('List of codes as a string'),
   96			class('render-code-list')
   97		      ],
   98		  '`~s`'-String))
   99	).
  100
  101skip_first(N, [_|T0], T) :-
  102	succ(N2, N), !,
  103	skip_first(N2, T0, T).
  104skip_first(_, L, L).
  105
  106put_n_codes(N, [H|T]) -->
  107	{ succ(N2, N) }, !,
  108	emit_code(H),
  109	put_n_codes(N2, T).
  110put_n_codes(_, _) --> [].
  111
  112put_codes(Var) -->
  113	{ var_or_numbered(Var) }, !,
  114	dcg_format('|~p', [Var]).
  115put_codes([]) --> [].
  116put_codes([H|T]) -->
  117	emit_code(H),
  118	put_codes(T).
  119
  120emit_code(0'\b) --> !, "\\b".
  121emit_code(0'\r) --> !, "\\r".
  122emit_code(0'\n) --> !, "\\n".
  123emit_code(0'\t) --> !, "\\t".
  124emit_code(C)	--> [C].
  125
  126dcg_format(Fmt, Args, List, Tail) :-
  127	format(codes(List, Tail), Fmt, Args).
 is_code_list(+Codes, -Length, +Options) is semidet
  131is_code_list(Codes, Length, Options) :-
  132	'$skip_list'(Length, Codes, Tail),
  133	code_list_tail(Tail, Options),
  134	option(min_length(MinLen), Options, 3),
  135	Length >= MinLen,
  136	option(charset(Charset), Options, ascii),
  137	all_codes(Codes, Charset).
  138
  139code_list_tail([], _) :- !.
  140code_list_tail(Var, Options) :-
  141	var_or_numbered(Var),
  142	option(partial(true), Options, true).
  143
  144var_or_numbered(Var) :-
  145	var(Var), !.
  146var_or_numbered('$VAR'(_)).
  147
  148all_codes(Var, _) :-
  149	var_or_numbered(Var), !.
  150all_codes([], _).
  151all_codes([H|T], Charset) :-
  152	integer(H),
  153	is_code(H, Charset), !,
  154	all_codes(T, Charset).
  155
  156is_code(9,  _).
  157is_code(10, _).
  158is_code(13, _).
  159is_code(C, Charset) :-
  160	charset_code(Charset, C).
  161
  162charset_code(ascii,       C) :- between(32,126,C).
  163charset_code(iso_latin_1, C) :- between(32,126,C) ; between(160,255,C)