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:- use_module(library(error)). 42:- use_module(library(pure_input)).
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).
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)).
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).
191quasi_quotation_syntax(M:Syntax) :-
192 must_be(atom, Syntax),
193 '$set_predicate_attribute'(M:Syntax/4, quasi_quotation_syntax, true).
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.
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 241
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 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] ]
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
.library(http/html_write)
). Examples of languages that may be embedded for processing in Prolog are SPARQL, RuleML or regular expressions.The file
library(http/html_quasiquotations)
provides the, suprisingly simple, quasi quotation parser for HTML.