| Did you know ... | Search Documentation: |
| html_write.pl -- Write HTML text |
Most code doesn't need to use this directly; instead use library(http/http_server), which combines this library with the typical HTTP libraries that most servers need.
The purpose of this library is to simplify writing HTML pages. Of course, it is possible to use format/3 to write to the HTML stream directly, but this is generally not very satisfactory:
This module tries to remedy these problems. The idea is to translate a Prolog term into an HTML document. We use DCG for most of the generation.
The library supports the generation of international documents, but this is currently limited to using UTF-8 encoded HTML or XHTML documents. It is strongly recommended to use the following mime-type.
Content-type: text/html; charset=UTF-8
When generating XHTML documents, the output stream must be in UTF-8 encoding.
html_set_options(+Options) is dethtml4, xhtml or html5 (default). For
compatibility reasons, html is accepted as an
alias for html4.<|DOCTYPE DocType > line for page//1 and
page//2.Content-type for reply_html_page/3
Note that the doctype and content_type flags are covered by
distinct prolog flags: html4_doctype, xhtml_doctype and
html5_doctype and similar for the content type. The Dialect
must be switched before doctype and content type.
html_current_option(?Option) is nondet
init_options is det[private]
xml_header(-Header)[private]
ns(?Which, ?Atom)[private]
page(+Content:dom)// is det
page(+Head:dom, +Body:dom)// is det<!DOCTYPE> header. The
actual doctype is read from the option doctype as defined by
html_set_options/1.
doctype//[private]<DOCTYPE ... header. The doctype comes from the
option doctype(DOCTYPE) (see html_set_options/1). Setting the
doctype to '' (empty atom) suppresses the header completely.
This is to avoid a IE bug in processing AJAX output ...
html(+Content:dom)// is det
raw(+List, +Module)// is det[private]
html_begin(+Env)// is det
html_end(+End)// is det
html(table(border=1, \table_content))
html_begin(table(border=1)
table_content,
html_end(table)
xhtml_empty(+Env, +Attributes)// is det[private]
xhtml_ns(+Id, +Value)//xmlns channel. Rdfa
(http://www.w3.org/2006/07/SWD/RDFa/syntax/), embedding RDF in
(x)html provides a typical usage scenario where we want to
publish the required namespaces in the header. We can define:
rdf_ns(Id) -->
{ rdf_global_id(Id:'', Value) },
xhtml_ns(Id, Value).
After which we can use rdf_ns//1 as a normal rule in html//1 to
publish namespaces from library(semweb/rdf_db). Note that this
macro only has effect if the dialect is set to xhtml. In
html mode it is silently ignored.
The required xmlns receiver is installed by html_begin//1
using the html tag and thus is present in any document that
opens the outer html environment through this library.
html_root_attribute(+Name, +Value)//
html(div(...)),
html_root_attribute(lang, en),
...
attributes(+Env, +Attributes)// is det[private]encode(V)
Emit URL-encoded version of V. See www_form_encode/2.encode(Value1)&Name2=encode(Value2) ...
The hook expand_attribute_value//1 can be defined to
provide additional `function like' translations. For example,
http_dispatch.pl defines location_by_id(ID) to refer to a
location on the current server based on the handler id. See
http_location_by_id/2.
attribute_value_m(+List)//[private]
body(class([c1, c2]), Body)
Emits <body class="c1 c2"> ...
html_quoted(Text)// is det
html(b(Text))
html_quoted_attribute(+Text)// is det
cdata_element(?Element)[private]</
needs to be escaped.
html_post(+Id, :HTML)// is detA typical usage scenario is to get required CSS links in the document head in a reusable fashion. First, we define css//1 as:
css(URL) -->
html_post(css,
link([ type('text/css'),
rel('stylesheet'),
href(URL)
])).
Next we insert the unique CSS links, in the pagehead using the following call to reply_html_page/2:
reply_html_page([ title(...),
\html_receive(css)
],
...)
html_receive(+Id)// is det
html_receive(+Id, :Handler)// is detphrase(Handler, PostedTerms, HtmlTerms, Rest)
Typically, Handler collects the posted terms, creating a term suitable for html//1 and finally calls html//1.
html_noreceive(+Id)// is det[private]
mailman(+Tokens) is det[private]head and script boxes at
the end.
html_token(?Token, +Tokens) is nondet[private]cdata(Elem, Tokens).
mailboxes(+Tokens, -MailBoxes) is det[private]
mail_handlers(+Boxes, -Handlers, -Posters) is det[private]post(Module,HTML) into Posters and the remainder in
Handlers. Handlers consists of accept(Handler, Tokens) and
ignore(_,_).
sorted_html(+Content:list)// is det[private]
head_html(+Content:list)// is det[private]html_receive(head). Unlike sorted_html//1, it calls
a user hook html_head_expansion/2 to process the
collected head material into a term suitable for html//1.
layout(+Tag, -Open, -Close) is det[multifile]
print_html(+List) is det
print_html(+Out:stream, +List) is det
valid_cdata(+Env, +String) is det[private]<script>. This implies it cannot contain </script/.
There is no escape for this and the script generator must use a
work-around using features of the script language. For example,
when using JavaScript, "</script>" can be written as
"<\/script>".
html_print_length(+List, -Len) is det
phrase(html(DOM), Tokens),
html_print_length(Tokens, Len),
format('Content-type: text/html; charset=UTF-8~n'),
format('Content-length: ~d~n~n', [Len]),
print_html(Tokens)
reply_html_page(:Head, :Body) is det
reply_html_page(+Style, :Head, :Body) is detContent-type is
provided by html_current_option/1.
reply_html_partial(+HTML) is detDOCTYPE
header, <html>, <head> or <body>. It is intended for
JavaScript handlers that request a partial document and insert that
somewhere into the existing page DOM.
html_header_hook(+Style) is nondet[multifile]Content-type
header is emitted. It allows for emitting additional headers
depending on the first argument of reply_html_page/3.The following predicates are exported from this file while their implementation is defined in imported modules or non-module files loaded by this module.
html_meta +Heads is dethtml. For example:
:- html_meta
page(html,html,?,?).
html(+Content, +Vars, +VarDict, -DOM) is dethtml indicator. If
the variable defines content, it must be the only content. Here
is an example, replacing both a content element and an
attribute. Note that the document is valid HTML.
html({|html(Name, URL)||
<p>Dear <span class="name">Name</span>,
<p>You can <a href="URL">download</a> the requested
article now.
|}
print_html(+List) is det
print_html(+Out:stream, +List) is det
reply_html_page(:Head, :Body) is det
reply_html_page(+Style, :Head, :Body) is detContent-type is
provided by html_current_option/1.
The following predicates are exported, but not or incorrectly documented.