View source with raw comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2013-2015, 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(quasi_quotations,
   36          [ with_quasi_quotation_input/3,       % +Content, -Stream, :Goal
   37            phrase_from_quasi_quotation/2,      % :Grammar, +Content
   38            quasi_quotation_syntax_error/1,     % +Error
   39            quasi_quotation_syntax/1            % :Syntax
   40          ]).   41:- use_module(library(error)).   42:- use_module(library(pure_input)).

Define Quasi Quotation syntax

Inspired by Haskell, SWI-Prolog support 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, Syntax is an arbitrary Prolog term that must parse into a callable (atom or compound) term and Quotation is an arbitrary sequence of characters, not including the sequence |}. 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.

{|Syntax||Quotation|}

While reading a Prolog term, and if the Prolog flag quasi_quotes is set to 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, SyntaxName is the functor name of Syntax above and SyntaxArgs is a list holding the arguments, i.e., 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.

call(+SyntaxName, +Content, +SyntaxArgs, +VariableNames, -Result)

The arguments are defined as

The file library(http/html_quasiquotations) provides the, suprisingly simple, quasi quotation parser for HTML.

author
- Jan Wielemaker. Introduction of Quasi Quotation was suggested by Michael Hendricks.
See also
-
Why it's nice to be quoted: quasiquoting for haskell */
  123:- meta_predicate
  124    with_quasi_quotation_input(+, -, 0),
  125    quasi_quotation_syntax(4),
  126    phrase_from_quasi_quotation(//, +).  127
  128:- set_prolog_flag(quasi_quotations, true).
 with_quasi_quotation_input(+Content, -Stream, :Goal) is det
Process the quasi-quoted Content using Stream parsed by Goal. Stream is a temporary stream with the following properties:
Arguments:
Goal- is executed as once(Goal). Goal must succeed. Failure or exceptions from Goal are interpreted as syntax errors.
See also
- phrase_from_quasi_quotation/2 can be used to process a quotation using a grammar.
  147with_quasi_quotation_input(Content, Stream, Goal) :-
  148    functor(Content, '$quasi_quotation', 3),
  149    !,
  150    setup_call_cleanup(
  151        '$qq_open'(Content, Stream),
  152        (   call(Goal)
  153        ->  true
  154        ;   quasi_quotation_syntax_error(
  155                quasi_quotation_parser_failed,
  156                Stream)
  157        ),
  158        close(Stream)).
 phrase_from_quasi_quotation(:Grammar, +Content) is det
Process the quasi quotation using the DCG Grammar. Failure of the grammer is interpreted as a syntax error.
See also
- with_quasi_quotation_input/3 for processing quotations from stream.
  168phrase_from_quasi_quotation(Grammar, Content) :-
  169    functor(Content, '$quasi_quotation', 3),
  170    !,
  171    setup_call_cleanup(
  172        '$qq_open'(Content, Stream),
  173        phrase_quasi_quotation(Grammar, Stream),
  174        close(Stream)).
  175
  176phrase_quasi_quotation(Grammar, Stream) :-
  177    set_stream(Stream, buffer_size(512)),
  178    stream_to_lazy_list(Stream, List),
  179    phrase(Grammar, List),
  180    !.
  181phrase_quasi_quotation(_, Stream) :-
  182    quasi_quotation_syntax_error(
  183        quasi_quotation_parser_failed,
  184        Stream).
 quasi_quotation_syntax(:SyntaxName) is det
Declare the predicate SyntaxName/4 to implement the the quasi quote syntax SyntaxName. Normally used as a directive.
  191quasi_quotation_syntax(M:Syntax) :-
  192    must_be(atom, Syntax),
  193    '$set_predicate_attribute'(M:Syntax/4, quasi_quotation_syntax, true).
 quasi_quotation_syntax_error(+Error)
Report syntax_error(Error) using the current location in the quasi quoted input parser.
throws
- error(syntax_error(Error), Position)
  202quasi_quotation_syntax_error(Error) :-
  203    quasi_quotation_input(Stream),
  204    quasi_quotation_syntax_error(Error, Stream).
  205
  206quasi_quotation_syntax_error(Error, Stream) :-
  207    stream_syntax_error_context(Stream, Context),
  208    throw(error(syntax_error(Error), Context)).
  209
  210quasi_quotation_input(Stream) :-
  211    '$input_context'(Stack),
  212    memberchk(input(quasi_quoted, _File, _Line, StreamVar), Stack),
  213    Stream = StreamVar.
 stream_syntax_error_context(+Stream, -Position) is det
Provide syntax error location for the current position of Stream.
  221stream_syntax_error_context(Stream, file(File, LineNo, LinePos, CharNo)) :-
  222    stream_property(Stream, file_name(File)),
  223    position_context(Stream, LineNo, LinePos, CharNo),
  224    !.
  225stream_syntax_error_context(Stream, stream(Stream, LineNo, LinePos, CharNo)) :-
  226    position_context(Stream, LineNo, LinePos, CharNo),
  227    !.
  228stream_syntax_error_context(_, _).
  229
  230position_context(Stream, LineNo, LinePos, CharNo) :-
  231    stream_property(Stream, position(Pos)),
  232    !,
  233    stream_position_data(line_count,    Pos, LineNo),
  234    stream_position_data(line_position, Pos, LinePos),
  235    stream_position_data(char_count,    Pos, CharNo).
  236
  237
  238                 /*******************************
  239                 *         SYSTEM HOOK          *
  240                 *******************************/
  241
  242%       system:'$parse_quasi_quotations'(+Quotations:list, +Module) is
  243%       det.
  244%
  245%       @arg    Quotations is a list of terms
  246%
  247%                   quasi_quotation(Syntax, Quotation, VarNames, Result)
  248
  249:- public
  250    system:'$parse_quasi_quotations'/2.  251
  252system:'$parse_quasi_quotations'([], _).
  253system:'$parse_quasi_quotations'([H|T], M) :-
  254    qq_call(H, M),
  255    system:'$parse_quasi_quotations'(T, M).
  256
  257qq_call(quasi_quotation(Syntax, Content, VariableNames, Result), M) :-
  258    current_prolog_flag(sandboxed_load, false),
  259    Syntax =.. [SyntaxName|SyntaxArgs],
  260    setup_call_cleanup(
  261        '$push_input_context'(quasi_quoted),
  262        call(M:SyntaxName, Content, SyntaxArgs, VariableNames, Result),
  263        '$pop_input_context'),
  264    !.
  265qq_call(quasi_quotation(Syntax, Content, VariableNames, Result), M) :-
  266    current_prolog_flag(sandboxed_load, true),
  267    Syntax =.. [SyntaxName|SyntaxArgs],
  268    Expand =.. [SyntaxName, Content, SyntaxArgs, VariableNames, Result],
  269    QExpand = M:Expand,
  270    '$expand':allowed_expansion(QExpand),
  271    setup_call_cleanup(
  272        '$push_input_context'(quasi_quoted),
  273        call(QExpand),
  274        '$pop_input_context'),
  275    !.
  276qq_call(quasi_quotation(_Syntax, Content, _VariableNames, _Result), _M) :-
  277    setup_call_cleanup(
  278        '$push_input_context'(quasi_quoted),
  279        with_quasi_quotation_input(
  280            Content, Stream,
  281            quasi_quotation_syntax_error(quasi_quote_parser_failed, Stream)),
  282        '$pop_input_context'),
  283    !.
  284
  285
  286                 /*******************************
  287                 *             MESSAGES         *
  288                 *******************************/
  289
  290:- multifile
  291    prolog:error_message//1.  292
  293prolog:error_message(syntax_error(unknown_quasi_quotation_syntax(Syntax, M))) -->
  294    { functor(Syntax, Name, _) },
  295    [ 'Quasi quotation syntax ~q:~q is not defined'-[M, Name] ].
  296prolog:error_message(syntax_error(invalid_quasi_quotation_syntax(Syntax))) -->
  297    [ 'Quasi quotation syntax must be a callable term.  Found ~q'-[Syntax] ]