34
35:- module(quasi_quotations,
36 [ with_quasi_quotation_input/3, 37 phrase_from_quasi_quotation/2, 38 quasi_quotation_syntax_error/1, 39 quasi_quotation_syntax/1 40 ]). 41:- autoload(library(error),[must_be/2]). 42:- autoload(library(pure_input),[stream_to_lazy_list/2]).
124:- meta_predicate
125 with_quasi_quotation_input(+, -, 0),
126 quasi_quotation_syntax(4),
127 phrase_from_quasi_quotation(//, +). 128
129:- set_prolog_flag(quasi_quotations, true).
148with_quasi_quotation_input(Content, Stream, Goal) :-
149 functor(Content, '$quasi_quotation', 3),
150 !,
151 setup_call_cleanup(
152 '$qq_open'(Content, Stream),
153 ( call(Goal)
154 -> true
155 ; quasi_quotation_syntax_error(
156 quasi_quotation_parser_failed,
157 Stream)
158 ),
159 close(Stream)).
169phrase_from_quasi_quotation(Grammar, Content) :-
170 functor(Content, '$quasi_quotation', 3),
171 !,
172 setup_call_cleanup(
173 '$qq_open'(Content, Stream),
174 phrase_quasi_quotation(Grammar, Stream),
175 close(Stream)).
176
177phrase_quasi_quotation(Grammar, Stream) :-
178 set_stream(Stream, buffer_size(512)),
179 stream_to_lazy_list(Stream, List),
180 phrase(Grammar, List),
181 !.
182phrase_quasi_quotation(_, Stream) :-
183 quasi_quotation_syntax_error(
184 quasi_quotation_parser_failed,
185 Stream).
192quasi_quotation_syntax(M:Syntax) :-
193 must_be(atom, Syntax),
194 '$set_predicate_attribute'(M:Syntax/4, quasi_quotation_syntax, true).
203quasi_quotation_syntax_error(Error) :-
204 quasi_quotation_input(Stream),
205 quasi_quotation_syntax_error(Error, Stream).
206
207quasi_quotation_syntax_error(Error, Stream) :-
208 stream_syntax_error_context(Stream, Context),
209 throw(error(syntax_error(Error), Context)).
210
211quasi_quotation_input(Stream) :-
212 '$input_context'(Stack),
213 memberchk(input(quasi_quoted, _File, _Line, StreamVar), Stack),
214 Stream = StreamVar.
222stream_syntax_error_context(Stream, file(File, LineNo, LinePos, CharNo)) :-
223 stream_property(Stream, file_name(File)),
224 position_context(Stream, LineNo, LinePos, CharNo),
225 !.
226stream_syntax_error_context(Stream, stream(Stream, LineNo, LinePos, CharNo)) :-
227 position_context(Stream, LineNo, LinePos, CharNo),
228 !.
229stream_syntax_error_context(_, _).
230
231position_context(Stream, LineNo, LinePos, CharNo) :-
232 stream_property(Stream, position(Pos)),
233 !,
234 stream_position_data(line_count, Pos, LineNo),
235 stream_position_data(line_position, Pos, LinePos),
236 stream_position_data(char_count, Pos, CharNo).
237
238
239 242
249
250:- public
251 system:'$parse_quasi_quotations'/2. 252
253system:'$parse_quasi_quotations'([], _).
254system:'$parse_quasi_quotations'([H|T], M) :-
255 qq_call(H, M),
256 system:'$parse_quasi_quotations'(T, M).
257
258qq_call(quasi_quotation(Syntax, Content, VariableNames, Result), M) :-
259 current_prolog_flag(sandboxed_load, false),
260 Syntax =.. [SyntaxName|SyntaxArgs],
261 setup_call_cleanup(
262 '$push_input_context'(quasi_quoted),
263 call(M:SyntaxName, Content, SyntaxArgs, VariableNames, Result),
264 '$pop_input_context'),
265 !.
266qq_call(quasi_quotation(Syntax, Content, VariableNames, Result), M) :-
267 current_prolog_flag(sandboxed_load, true),
268 Syntax =.. [SyntaxName|SyntaxArgs],
269 Expand =.. [SyntaxName, Content, SyntaxArgs, VariableNames, Result],
270 QExpand = M:Expand,
271 '$expand':allowed_expansion(QExpand),
272 setup_call_cleanup(
273 '$push_input_context'(quasi_quoted),
274 call(QExpand),
275 '$pop_input_context'),
276 !.
277qq_call(quasi_quotation(_Syntax, Content, _VariableNames, _Result), _M) :-
278 setup_call_cleanup(
279 '$push_input_context'(quasi_quoted),
280 with_quasi_quotation_input(
281 Content, Stream,
282 quasi_quotation_syntax_error(quasi_quote_parser_failed, Stream)),
283 '$pop_input_context'),
284 !.
285
286
287 290
291:- multifile
292 prolog:error_message//1. 293
294prolog:error_message(syntax_error(unknown_quasi_quotation_syntax(Syntax, M))) -->
295 { functor(Syntax, Name, _) },
296 [ 'Quasi quotation syntax ~q:~q is not defined'-[M, Name] ].
297prolog:error_message(syntax_error(invalid_quasi_quotation_syntax(Syntax))) -->
298 [ 'Quasi quotation syntax must be a callable term. Found ~q'-[Syntax] ]
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.While reading a Prolog term, and if the Prolog flag
quasi_quotes
is set totrue
(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.The arguments are defined as
variable_names
. It is a list of termsName = Var
.The file library(http/html_quasiquotations) provides the, suprisingly simple, quasi quotation parser for HTML.