1:- module(interpolate, ['$interpolate_macro_sentinel'/0]). 2:- use_module(library(dcg/basics), [prolog_var_name//1, string//1]). 3:- use_module(library(function_expansion)). 4:- use_module(library(error), [type_error/2]).
12template(Vars, [Static,_|Formats], [Arg|Args]) -->
13 string(Codes),
14 variable(VarName),
15 { memberchk(VarName=Arg, Vars) },
16 { atom_codes(Static, Codes) },
17 template(Vars, Formats, Args).
18template(_, [Format], []) -->
19 string(Codes),
20 { atom_codes(Format, Codes) }.
29variable(VarName) -->
30 "$",
31 prolog_var_name(VarName).
32
33
36wants_interpolation :-
37 prolog_load_context(module, Module),
38 Module \== interpolate, 39 predicate_property(
40 Module:'$interpolate_macro_sentinel',
41 imported_from(interpolate)
42 ).
48textual(_,Var,_) :-
49 var(Var),
50 !,
51 fail.
52textual(atom, Atom, Codes) :-
53 atom(Atom),
54 !,
55 atom_codes(Atom,Codes).
56textual(Type, Text, Codes) :-
57 is_list(Text),
58 !,
59 Text = [H|_], 60 ( atom(H) ->
61 Type = chars,
62 catch(atom_chars(Atom,Text),_,fail),
63 atom_codes(Atom,Codes)
64 ; integer(H) ->
65 Type = codes,
66 Codes = Text
67 ). 68textual(string, String, Codes) :-
69 string(String),
70 string_to_list(String,Codes).
77build_text(Output, Formats0, Args) :-
78 instantiate_formats(Formats0, Args, Formats),
79 atomic_list_concat(Formats, Format),
80 format(Output, Format, Args).
81
82
84instantiate_formats([], _, []).
85instantiate_formats([Static|Formats0],Args,[Static|Formats]) :-
86 atom(Static),
87 !,
88 instantiate_formats(Formats0,Args,Formats).
89instantiate_formats([Var|Formats0],[Arg|Args],[Format|Formats]) :-
90 var(Var),
91 !,
92 preferred_tilde(Arg,Format),
93 instantiate_formats(Formats0,Args,Formats).
94instantiate_formats([X|_],_,[_|_]) :-
95 type_error(atom_or_var,X).
96
97
99preferred_tilde(X,'~s') :-
100 textual(Type, X, _),
101 ( Type = codes; Type = chars; Type = string ),
102 !.
103preferred_tilde(_,'~p').
104
105
106:- multifile user:function_expansion/3. 107user:function_expansion(Term,Replacement,Guard) :-
108 wants_interpolation,
109 prolog_load_context(variable_names, Vars),
110 Vars \== [], 111
112 113 textual(Type, Term, TextCodes),
114 phrase(template(Vars, Formats, Args), TextCodes),
115 Args \== [], 116
117 118 Output =.. [Type, Replacement],
119 Guard = interpolate:build_text(Output, Formats, Args).
132'$interpolate_macro_sentinel'