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]).
126:- meta_predicate
127 with_quasi_quotation_input(+, -, 0),
128 quasi_quotation_syntax(4),
129 phrase_from_quasi_quotation(//, +). 130
131:- set_prolog_flag(quasi_quotations, true).
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)).
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).
194quasi_quotation_syntax(M:Syntax) :-
195 must_be(atom, Syntax),
196 '$set_predicate_attribute'(M:Syntax/4, quasi_quotation_syntax, true).
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.
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 244
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 292
293:- multifile
294 prolog:error_message//1. 295
296prolog:error_message(syntax_error(unknown_quasi_quotation_syntax(Syntax, M))) -->
297 { functor(Syntax, Name, _) },
298 [ 'Quasi quotation syntax ~q:~q is not defined'-[M, Name] ].
299prolog:error_message(syntax_error(invalid_quasi_quotation_syntax(Syntax))) -->
300 [ '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_quotations
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.