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:
- It is a lot of typing
- It does not guarantee proper HTML syntax. You have to deal
with HTML quoting, proper nesting and reasonable layout.
- It is hard to use satisfactory abstraction
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.
International documents
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 det
- Set options for the HTML output. Options are stored in prolog
flags to ensure proper multi-threaded behaviour where setting an
option is local to the thread and new threads start with the
options from the parent thread. Defined options are:
- dialect(Dialect)
- One of
html4
, xhtml
or html5
(default). For
compatibility reasons, html
is accepted as an
alias for html4
.
- doctype(+DocType)
- Set the
<|DOCTYPE
DocType >
line for page//1 and
page//2.
- content_type(+ContentType)
- Set the
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
- True if Option is an active option for the HTML generator.
- page(+Content:dom)// is det
- page(+Head:dom, +Body:dom)// is det
- Generate a page including the HTML
<!DOCTYPE>
header. The
actual doctype is read from the option doctype
as defined by
html_set_options/1.
- html(+Content:dom)// is det
- Generate HTML from Content. Generates a token sequence for
print_html/2.
- html_begin(+Env)// is det
- html_end(+End)// is det
- For html_begin//1, Env is a term Env(Attributes); for
html_end//1 it is the plain environment name. Used for
exceptional cases. Normal applications use html//1. The
following two fragments are identical, where we prefer the first
as it is more concise and less error-prone.
html(table(border=1, \table_content))
html_begin(table(border=1)
table_content,
html_end(table)
- xhtml_ns(+Id, +Value)//
- Demand an xmlns:id=Value in the outer html tag. This uses the
html_post/2 mechanism to post to the
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)//
- Add an attribute to the HTML root element of the page. For
example:
html(div(...)),
html_root_attribute(lang, en),
...
- html_quoted(Text)// is det
- Quote the value for normal (CDATA) text. Note that text
appearing in the document structure is normally quoted using
these rules. I.e. the following emits properly quoted bold text
regardless of the content of Text:
html(b(Text))
- To be done
- - Assumes UTF-8 encoding of the output.
- html_quoted_attribute(+Text)// is det
- Quote the value according to the rules for tag-attributes
included in double-quotes. Note that -like html_quoted//1-,
attributed values printed through html//1 are quoted
atomatically.
- To be done
- - Assumes UTF-8 encoding of the output.
- html_post(+Id, :HTML)// is det
- Reposition HTML to the receiving Id. The html_post//2 call
processes HTML using html//1. Embedded \-commands are executed
by mailman/1 from print_html/1 or html_print_length/2. These
commands are called in the calling context of the html_post//2
call.
A 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
- Receive posted HTML tokens. Unique sequences of tokens posted
with html_post//2 are inserted at the location where
html_receive//1 appears.
- See also
- - The local predicate sorted_html//1 handles the output of
html_receive//1.
- - html_receive//2 allows for post-processing the posted
material.
- html_receive(+Id, :Handler)// is det
- This extended version of html_receive//1 causes Handler to be
called to process all messages posted to the channal at the time
output is generated. Handler is called as below, where
PostedTerms is a list of Module:Term created from calls to
html_post//2. Module is the context module of html_post and Term
is the unmodified term. Members in PostedTerms are in the
order posted and may contain duplicates.
phrase(Handler, PostedTerms, HtmlTerms, Rest)
Typically, Handler collects the posted terms, creating a term
suitable for html//1 and finally calls html//1.
- layout(+Tag, -Open, -Close) is det[multifile]
- Define required newlines before and after tags. This table is
rather incomplete. New rules can be added to this multifile
predicate.
- Arguments:
-
Tag | - Name of the tag |
Open | - Tuple M-N, where M is the number of lines before
the tag and N after. |
Close | - Either as Open, or the atom - (minus) to omit the
close-tag or empty to indicate the element has
no content model. |
- To be done
- - Complete table
- print_html(+List) is det
- print_html(+Out:stream, +List) is det
- Print list of atoms and layout instructions. Currently used layout
instructions:
- nl(N)
- Use at minimum N newlines here.
- mailbox(Id, Box)
- Repositioned tokens (see html_post//2 and
html_receive//2)
- html_print_length(+List, -Len) is det
- Determine the content length of a token list produced using
html//1. Here is an example on how this is used to output an
HTML compatible to HTTP:
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 det
- Provide the complete reply as required by http_wrapper.pl for a page
constructed from Head and Body. The HTTP
Content-type
is
provided by html_current_option/1.
- See also
- - reply_html_partial/1 to avoid adding a
DOCTYPE
, and
required outer HTML elements such as <html>
.
- reply_html_partial(+HTML) is det
- Reply with partial HTML document. The reply only contains the
element from HTML, i.e., this predicate does not add a
DOCTYPE
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.
- See also
- - reply_html_page/3 to reply with a complete (valid) HTML page.
- Since
- - 9.1.20
- html_header_hook(+Style) is nondet[multifile]
- This multifile hook is called just before the
Content-type
header is emitted. It allows for emitting additional headers
depending on the first argument of reply_html_page/3.
- html_meta(+Heads) is det
- This directive can be used to declare that an HTML rendering
rule takes HTML content as argument. It has two effects. It
emits the appropriate meta_predicate/1 and instructs the
built-in editor (PceEmacs) to provide proper colouring for the
arguments. The arguments in Head are the same as for
meta_predicate or can be constant
html
. For example:
:- html_meta
page(html,html,?,?).
Re-exported predicates
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(+Content, +Vars, +VarDict, -DOM) is det
- The predicate html/4 implements HTML quasi quotations. These
quotations produce a DOM term that is suitable for html//1 and
other predicates that are declared to consume this format. The
quasi quoter only accepts valid, but possibly partial HTML
documents. The document must begin with a tag. The quoter
replaces attributes or content whose value is a Prolog variable
that appears in the argument list of the
html
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
- Print list of atoms and layout instructions. Currently used layout
instructions:
- nl(N)
- Use at minimum N newlines here.
- mailbox(Id, Box)
- Repositioned tokens (see html_post//2 and
html_receive//2)
- reply_html_page(:Head, :Body) is det
- reply_html_page(+Style, :Head, :Body) is det
- Provide the complete reply as required by http_wrapper.pl for a page
constructed from Head and Body. The HTTP
Content-type
is
provided by html_current_option/1.
- See also
- - reply_html_partial/1 to avoid adding a
DOCTYPE
, and
required outer HTML elements such as <html>
.
Undocumented predicates
The following predicates are exported, but not or incorrectly documented.
- page(Arg1, Arg2, Arg3, Arg4)
- html_end(Arg1, Arg2, Arg3)
- page(Arg1, Arg2, Arg3, Arg4, Arg5)