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:- autoload(library(error),[must_be/2]). 42:- autoload(library(pure_input),[stream_to_lazy_list/2]). 43 44 45/** <module> Define Quasi Quotation syntax 46 47Inspired by 48[Haskell](http://www.haskell.org/haskellwiki/Quasiquotation), SWI-Prolog 49support _quasi quotation_. Quasi quotation allows for embedding (long) 50strings using the syntax of an external language (e.g., HTML, SQL) in 51Prolog text and syntax-aware embedding of Prolog variables in this 52syntax. At the same time, quasi quotation provides an alternative to 53represent long strings and atoms in Prolog. 54 55The basic form of a quasi quotation is defined below. Here, `Syntax` is 56an arbitrary Prolog term that must parse into a _callable_ (atom or 57compound) term and Quotation is an arbitrary sequence of characters, not 58including the sequence =||}|=. If this sequence needs to be embedded, it 59must be escaped according to the rules of the target language or the 60`quoter' must provide an escaping mechanism. 61 62 == 63 {|Syntax||Quotation|} 64 == 65 66While reading a Prolog term, and if the Prolog flag =quasi_quotations= is 67set to =true= (which is the case if this library is loaded), the parser 68collects quasi quotations. After reading the final full stop, the parser 69makes the call below. Here, `SyntaxName` is the functor name of `Syntax` 70above and `SyntaxArgs` is a list holding the arguments, i.e., `Syntax 71=.. [SyntaxName|SyntaxArgs]`. Splitting the syntax into its name and 72arguments is done to make the quasi quotation parser a predicate with a 73consistent arity 4, regardless of the number of additional arguments. 74 75 == 76 call(+SyntaxName, +Content, +SyntaxArgs, +VariableNames, -Result) 77 == 78 79The arguments are defined as 80 81 - `SyntaxName` is the principal functor of the quasi quotation syntax. 82 This must be declared using quasi_quotation_syntax/1 and there must be 83 a predicate SyntaxName/4. 84 85 - `Content` is an opaque term that carries the content of the quasi 86 quoted material and position information about the source code. It is 87 passed to with_quasi_quote_input/3. 88 89 - `SyntaxArgs` carries the additional arguments of the `Syntax`. These are 90 commonly used to make the parameter passing between the clause and the 91 quasi quotation explicit. For example: 92 93 == 94 ..., 95 {|html(Name, Address)|| 96 <tr><td>Name<td>Address</tr> 97 |} 98 == 99 100 - `VariableNames` is the complete variable dictionary of the clause as 101 it is made available throug read_term/3 with the option 102 =variable_names=. It is a list of terms `Name = Var`. 103 104 - `Result` is a variable that must be unified to resulting term. 105 Typically, this term is structured Prolog tree that carries a 106 (partial) representation of the abstract syntax tree with embedded 107 variables that pass the Prolog parameters. This term is normally 108 either passed to a predicate that serializes the abstract syntax tree, 109 or a predicate that processes the result in Prolog. For example, HTML 110 is commonly embedded for writing HTML documents (see 111 library(http/html_write)). Examples of languages that may be embedded 112 for processing in Prolog are SPARQL, RuleML or regular expressions. 113 114The file library(http/html_quasiquotations) provides the, suprisingly 115simple, quasi quotation parser for HTML. 116 117@author Jan Wielemaker. Introduction of Quasi Quotation was suggested 118 by Michael Hendricks. 119@see [Why it's nice to be quoted: quasiquoting for 120 haskell](http://www.cs.tufts.edu/comp/150FP/archive/geoff-mainland/quasiquoting.pdf) 121@see [Why it's nice to be quoted: quasiquoting for 122 Prolog](https://www.swi-prolog.org/download/publications/quasiquoting.pdf) 123*/ 124 125 126:- meta_predicate 127 with_quasi_quotation_input( , , ), 128 quasi_quotation_syntax( ), 129 phrase_from_quasi_quotation( , ). 130 131:- set_prolog_flag(quasi_quotations, true). 132 133%! with_quasi_quotation_input(+Content, -Stream, :Goal) is det. 134% 135% Process the quasi-quoted Content using Stream parsed by Goal. 136% Stream is a temporary stream with the following properties: 137% 138% - Its initial _position_ represents the position of the 139% start of the quoted material. 140% - It is a text stream, using =utf8= _encoding_. 141% - It allows for repositioning 142% - It will be closed after Goal completes. 143% 144% @arg Goal is executed as once(Goal). Goal must succeed. 145% Failure or exceptions from Goal are interpreted as 146% syntax errors. 147% @see phrase_from_quasi_quotation/2 can be used to process a 148% quotation using a grammar. 149 150with_quasi_quotation_input(Content, Stream, Goal) :- 151 functor(Content, '$quasi_quotation', 3), 152 !, 153 setup_call_cleanup( 154 '$qq_open'(Content, Stream), 155 ( call(Goal) 156 -> true 157 ; quasi_quotation_syntax_error( 158 quasi_quotation_parser_failed, 159 Stream) 160 ), 161 close(Stream)). 162 163%! phrase_from_quasi_quotation(:Grammar, +Content) is det. 164% 165% Process the quasi quotation using the DCG Grammar. Failure of 166% the grammar is interpreted as a syntax error. 167% 168% @see with_quasi_quotation_input/3 for processing quotations from 169% stream. 170 171phrase_from_quasi_quotation(Grammar, Content) :- 172 functor(Content, '$quasi_quotation', 3), 173 !, 174 setup_call_cleanup( 175 '$qq_open'(Content, Stream), 176 phrase_quasi_quotation(Grammar, Stream), 177 close(Stream)). 178 179phrase_quasi_quotation(Grammar, Stream) :- 180 set_stream(Stream, buffer_size(512)), 181 stream_to_lazy_list(Stream, List), 182 phrase(Grammar, List), 183 !. 184phrase_quasi_quotation(_, Stream) :- 185 quasi_quotation_syntax_error( 186 quasi_quotation_parser_failed, 187 Stream). 188 189%! quasi_quotation_syntax(:SyntaxName) is det. 190% 191% Declare the predicate SyntaxName/4 to implement the the quasi 192% quote syntax SyntaxName. Normally used as a directive. 193 194quasi_quotation_syntax(M:Syntax) :- 195 must_be(atom, Syntax), 196 '$set_predicate_attribute'(M:Syntax/4, quasi_quotation_syntax, true). 197 198%! quasi_quotation_syntax_error(+Error) 199% 200% Report syntax_error(Error) using the current location in the 201% quasi quoted input parser. 202% 203% @throws error(syntax_error(Error), Position) 204 205quasi_quotation_syntax_error(Error) :- 206 quasi_quotation_input(Stream), 207 quasi_quotation_syntax_error(Error, Stream). 208 209quasi_quotation_syntax_error(Error, Stream) :- 210 stream_syntax_error_context(Stream, Context), 211 throw(error(syntax_error(Error), Context)). 212 213quasi_quotation_input(Stream) :- 214 '$input_context'(Stack), 215 memberchk(input(quasi_quoted, _File, _Line, StreamVar), Stack), 216 Stream = StreamVar. 217 218 219%! stream_syntax_error_context(+Stream, -Position) is det. 220% 221% Provide syntax error location for the current position of 222% Stream. 223 224stream_syntax_error_context(Stream, file(File, LineNo, LinePos, CharNo)) :- 225 stream_property(Stream, file_name(File)), 226 position_context(Stream, LineNo, LinePos, CharNo), 227 !. 228stream_syntax_error_context(Stream, stream(Stream, LineNo, LinePos, CharNo)) :- 229 position_context(Stream, LineNo, LinePos, CharNo), 230 !. 231stream_syntax_error_context(_, _). 232 233position_context(Stream, LineNo, LinePos, CharNo) :- 234 stream_property(Stream, position(Pos)), 235 !, 236 stream_position_data(line_count, Pos, LineNo), 237 stream_position_data(line_position, Pos, LinePos), 238 stream_position_data(char_count, Pos, CharNo). 239 240 241 /******************************* 242 * SYSTEM HOOK * 243 *******************************/ 244 245% system:'$parse_quasi_quotations'(+Quotations:list, +Module) is 246% det. 247% 248% @arg Quotations is a list of terms 249% 250% quasi_quotation(Syntax, Quotation, VarNames, Result) 251 252:- public 253 system:'$parse_quasi_quotations'/2. 254 255system'$parse_quasi_quotations'([], _). 256system'$parse_quasi_quotations'([H|T], M) :- 257 qq_call(H, M), 258 system:'$parse_quasi_quotations'(T, M). 259 260qq_call(quasi_quotation(Syntax, Content, VariableNames, Result), M) :- 261 current_prolog_flag(sandboxed_load, false), 262 Syntax =.. [SyntaxName|SyntaxArgs], 263 setup_call_cleanup( 264 '$push_input_context'(quasi_quoted), 265 call(M:SyntaxName, Content, SyntaxArgs, VariableNames, Result), 266 '$pop_input_context'), 267 !. 268qq_call(quasi_quotation(Syntax, Content, VariableNames, Result), M) :- 269 current_prolog_flag(sandboxed_load, true), 270 Syntax =.. [SyntaxName|SyntaxArgs], 271 Expand =.. [SyntaxName, Content, SyntaxArgs, VariableNames, Result], 272 QExpand = M:Expand, 273 '$expand':allowed_expansion(QExpand), 274 setup_call_cleanup( 275 '$push_input_context'(quasi_quoted), 276 call(QExpand), 277 '$pop_input_context'), 278 !. 279qq_call(quasi_quotation(_Syntax, Content, _VariableNames, _Result), _M) :- 280 setup_call_cleanup( 281 '$push_input_context'(quasi_quoted), 282 with_quasi_quotation_input( 283 Content, Stream, 284 quasi_quotation_syntax_error(quasi_quote_parser_failed, Stream)), 285 '$pop_input_context'), 286 !. 287 288 289 /******************************* 290 * MESSAGES * 291 *******************************/ 292 293:- multifile 294 prolog:error_message//1. 295 296prologerror_message(syntax_error(unknown_quasi_quotation_syntax(Syntax, M))) --> 297 { functor(Syntax, Name, _) }, 298 [ 'Quasi quotation syntax ~q:~q is not defined'-[M, Name] ]. 299prologerror_message(syntax_error(invalid_quasi_quotation_syntax(Syntax))) --> 300 [ 'Quasi quotation syntax must be a callable term. Found ~q'-[Syntax] ]