% This LaTeX document was generated using the LaTeX backend of PlDoc, % The SWI-Prolog documentation system \section{library(quasi_quotations): Define Quasi Quotation syntax} \label{sec:quasiquotations} \begin{tags} \tag{author} Jan Wielemaker. Introduction of Quasi Quotation was suggested by Michael Hendricks. \tag{See also} \href{http://www.cs.tufts.edu/comp/150FP/archive/geoff-mainland/quasiquoting.pdf}{Why it's nice to be quoted: quasiquoting for haskell} \end{tags} Inspired by \href{http://www.haskell.org/haskellwiki/Quasiquotation}{Haskell}, SWI-Prolog support \textit{quasi quotation}. Quasi quotation allows for embedding (long) strings using the syntax of an external language (e.g., HTML, SQL) in Prolog text and syntax-aware embedding of Prolog variables in this syntax. At the same time, quasi quotation provides an alternative to represent long strings and atoms in Prolog. The basic form of a quasi quotation is defined below. Here, \arg{Syntax} is an arbitrary Prolog term that must parse into a \textit{callable} (atom or compound) term and Quotation is an arbitrary sequence of characters, not including the sequence \verb$|}$. If this sequence needs to be embedded, it must be escaped according to the rules of the target language or the `quoter' must provide an escaping mechanism. \begin{code} {|Syntax||Quotation|} \end{code} While reading a Prolog term, and if the Prolog flag \verb$quasi_quotes$ is set to \const{true} (which is the case if this library is loaded), the parser collects quasi quotations. After reading the final full stop, the parser makes the call below. Here, \arg{SyntaxName} is the functor name of \arg{Syntax} above and \arg{SyntaxArgs} is a list holding the arguments, i.e., \verb$Syntax =.. [SyntaxName|SyntaxArgs]$. Splitting the syntax into its name and arguments is done to make the quasi quotation parser a predicate with a consistent arity 4, regardless of the number of additional arguments. \begin{code} call(+SyntaxName, +Content, +SyntaxArgs, +VariableNames, -Result) \end{code} The arguments are defined as \begin{itemize} \item \arg{SyntaxName} is the principal functor of the quasi quotation syntax. This must be declared using \predref{quasi_quotation_syntax}{1} and there must be a predicate SyntaxName/4. \item \arg{Content} is an opaque term that carries the content of the quasi quoted material and position information about the source code. It is passed to \predref{with_quasi_quote_input}{3}. \item \arg{SyntaxArgs} carries the additional arguments of the \arg{Syntax}. These are commonly used to make the parameter passing between the clause and the quasi quotation explicit. For example: \begin{code} ..., {|html(Name, Address)|| NameAddress |} \end{code} \item \arg{VariableNames} is the complete variable dictionary of the clause as it is made available throug \predref{read_term}{3} with the option \verb$variable_names$. It is a list of terms \verb$Name = Var$. \item \arg{Result} is a variable that must be unified to resulting term. Typically, this term is structured Prolog tree that carries a (partial) representation of the abstract syntax tree with embedded variables that pass the Prolog parameters. This term is normally either passed to a predicate that serializes the abstract syntax tree, or a predicate that processes the result in Prolog. For example, HTML is commonly embedded for writing HTML documents (see \file{library(http/html_write)}). Examples of languages that may be embedded for processing in Prolog are SPARQL, RuleML or regular expressions. \end{itemize} The file \file{library(http/html_quasiquotations)} provides the, suprisingly simple, quasi quotation parser for HTML.\vspace{0.7cm} \begin{description} \predicate[det]{with_quasi_quotation_input}{3}{+Content, -Stream, :Goal} Process the quasi-quoted \arg{Content} using \arg{Stream} parsed by \arg{Goal}. \arg{Stream} is a temporary stream with the following properties: \begin{itemize} \item Its initial \textit{position} represents the position of the start of the quoted material. \item It is a text stream, using \const{utf8} \textit{encoding}. \item It allows for repositioning \item It will be closed after \arg{Goal} completes. \end{itemize} \begin{arguments} \arg{Goal} & is executed as \verb$once(Goal)$. \arg{Goal} must succeed. Failure or exceptions from \arg{Goal} are interpreted as syntax errors. \\ \end{arguments} \begin{tags} \tag{See also} \predref{phrase_from_quasi_quotation}{2} can be used to process a quotation using a grammar. \end{tags} \predicate[det]{phrase_from_quasi_quotation}{2}{:Grammar, +Content} Process the quasi quotation using the DCG \arg{Grammar}. Failure of the grammar is interpreted as a syntax error. \begin{tags} \tag{See also} \predref{with_quasi_quotation_input}{3} for processing quotations from stream. \end{tags} \predicate[det]{quasi_quotation_syntax}{1}{:SyntaxName} Declare the predicate \arg{SyntaxName}/4 to implement the the quasi quote syntax \arg{SyntaxName}. Normally used as a directive. \predicate{quasi_quotation_syntax_error}{1}{+Error} Report \verb$syntax_error(Error)$ using the current location in the quasi quoted input parser. \begin{tags} \tag{throws} \verb$error(syntax_error(Error), Position)$ \end{tags} \end{description}