1:- module(mustache, [
2 mustache//2, % +Variables:list, +TemplateCodes:codes
3 mustache_from_file/3 % +FileSpec, +Variables:list, -Out:codes
4]).
?(Goal)
then the output is produced by the execution of the predicate once(call(Goal, Value, Result))
where result is consider as the actual value associated with the property.Some transformed {{?- my_goal. variable }}
In this case the output is produced by calling once(call(my_goal, Value, Result))
. The goal itself
is retrieved by the call to the read_term/2 therefore it must be ended by a dot.
19:- use_module(library(dcg/basics)). 20:- use_module(library(error)). 21 22%%% PUBLIC PREDICATES %%%%%%%%%%%%%%%%%%%%%%%%%%
{{ variable }}
placeholders with the variables
specified in the Variables list. Variables are of the form
Var - Value
or Var = Value
. The value can be atomic, codes, string, or list of values
29mustache(Variables, TemplateCodes) -->
30 { must_be(codes, TemplateCodes) },
31 mustache_impl( Variables, [ [0'{, 0'{], [0'}, 0'}] ], TemplateCodes).
36mustache_from_file(FilePath, Variables, Out) :- 37 absolute_file_name(FilePath, AbsolutePath), 38 read_file_to_codes(AbsolutePath, Codes, [encoding(utf8)]), 39 phrase(mustache(Variables, Codes), Out). 40 41 42%%% PRIVATE PREDICATES %%%%%%%%%%%%%%%%%%%%%%%%% 43 44close_placeholder( [_, [] | _ ], In, In) --> []. 45 close_placeholder( [_, [ H | T ] |_], [ H|In], Out) --> 46 close_placeholder( [_, T ], In, Out). 47 48comment(Delimiters, In, Out) --> 49 open_placeholder(comment, Delimiters, In, R1), 50 { phrase(string(_), R1, R2) }, 51 close_placeholder(Delimiters, R2, Out), 52 !. 53 54condition_body(_, _, In, In) --> []. 55 condition_body(Variables, Delimiters, In, Out) --> 56 next(Variables, Delimiters, In, Rest0), 57 condition_body(Variables, Delimiters, Rest0, Out). 58 59condition_start(Delimiters, Variable, In, Out) --> 60 condition_placeholder(condition, Delimiters, Variable, In, Out). 61 62condition_negated(Delimiters, Variable, In, Out) --> 63 condition_placeholder(negation, Delimiters, Variable, In, Out). 64 65condition_end(Delimiters, Variable, In, Out) --> 66 condition_placeholder(block_end, Delimiters, Variable, In, Out). 67 68condition_placeholder(Type, Delimiters, Variable, In, Out) --> 69 open_placeholder(Type, Delimiters, In, Rest0), 70 variable(Variable, Rest0, Rest1), 71 close_placeholder(Delimiters, Rest1, Out). 72 73delimiters(Delimiters, [Start, End], In, Out) --> 74 open_placeholder(delimiter, Delimiters, In, R1), 75 delimiter_start(Start, R1, R2), 76 delimiter_space(R2, R3), 77 delimiter_end(End, R3, R4), 78 close_placeholder(Delimiters, R4, Out), 79 { 80 \+ length(Start, 0), 81 \+ length(End, 0) 82 }. 83 84delimiter_end([], [ 0'=|In], In) --> []. 85 delimiter_end([C|T], [C|In], Out) --> 86 { C\= 0'= }, 87 delimiter_end(T, In, Out). 88 89delimiter_space([C|In], [C|In]) --> 90 { \+ is_white(C) }. 91 delimiter_space([C|In], Out) --> 92 { is_white(C) }, 93 delimiter_space(In, Out). 94 95delimiter_start([], [S|In], [S|In]) --> 96 { is_white(S) }, 97 !. 98 delimiter_start([C|T], [C|In], Out) --> 99 { \+ is_white(C) }, 100 delimiter_start(T, In, Out). 101 102 103 104expand_variable(Key, VariablesIn, VariablesOut) :- 105 variables_key_value(VariablesIn, Key, Value), 106 expand_variable_impl(Value, VariablesIn, VariablesOut), 107 !. 108expand_variable(_, Variables, Variables). 109 110expand_variable_impl(Term, VariablesIn, VariablesOut) :- 111 is_dict(Term), 112 dict_pairs(Term, _, Pairs), 113 append(Pairs, VariablesIn, VariablesOut), 114 !. 115expand_variable_impl(_, Variables, Variables). 116 117instruction(Variables, Delimiters, In, Out) --> 118 ( comment( Delimiters, In, Out) 119 ; loop(Variables, Delimiters, In, Out) 120 ; negation(Variables, Delimiters, In, Out) 121 ; partial(Delimiters, In, Out) 122 ; query(Variables, Delimiters, In, Out) 123 ; lambda(Variables, Delimiters, In, Out), ! 124 ; placeholder(Variables, Delimiters, In, Out) 125 ). 126 127lambda(Variables, Delimiters, In, Out) --> 128 condition_placeholder(normal, Delimiters, Key, In, Out), 129 { variables_key_value(Variables, Key, ?(Goal)), 130 call(Goal, Value) 131 }, 132 push_variable_codes(Value). 133 134 135loop(Variables, Delimiters, In, Out) --> 136 condition_start(Delimiters, Key, In, Rest1), 137 {( variables_key_value(Variables, Key, Value) 138 -> ( is_list(Value) 139 -> List = Value 140 ; List = [ Value ] 141 ) 142 ; List = [] 143 )}, 144 loop_elements(Key-List, Variables, Delimiters, Rest1, Out). 145 146loop_elements( Key-[], _, Delimiters, In, Out) --> % ignore the block on empty list and move on 147 { phrase( condition_body( [], Delimiters, In, Rest), _) }, 148 condition_end(Delimiters, Key, Rest, Out), 149 []. 150 loop_elements( Key-[ Var | List], Variables, Delimiters, In, Out) --> 151 { 152 Variables1 = [Key-Var | Variables], 153 expand_variable(Key, Variables1, Variables2), 154 phrase( condition_body( Variables2, Delimiters, In, Rest), Body) 155 }, 156 condition_end(Delimiters, Key, Rest, _), 157 , 158 loop_elements(Key-List, Variables, Delimiters, In, Out). 159 160mustache_impl(_, _, []) --> [], !. 161mustache_impl(Variables, Delimiters, In) --> 162 delimiters(Delimiters, Delimiters1, In, Out), 163 mustache_impl( Variables, Delimiters1, Out), 164 !. 165 mustache_impl(Variables, Delimiters, In) --> 166 next( Variables, Delimiters, In, Out), 167 mustache_impl( Variables, Delimiters, Out). 168 169negation(Variables, Delimiters, In, Out) --> 170 negation_start(Key, Delimiters, In, Rest1), 171 ( { variables_key_value(Variables, Key, _) } 172 -> loop_elements(Key-[], Variables, Delimiters, Rest1, Out) 173 ; loop_elements(Key-[ [] ], Variables, Delimiters, Rest1, Out) 174 ). 175 176negation_start(Variable, Delimiters, In, Out) --> 177 condition_placeholder(negation, Delimiters, Variable, In, Out). 178 179next(Variables, Delimiters, In, Out) --> 180 instruction(Variables, Delimiters, In, Out), !. 181 next(_, _, [C|Out], Out) --> [C]. 182 183open_placeholder(Type, [DelimiterStart | _], In, Out) --> 184 { memberchk( 185 Type-Suffix, 186 [ block_end-[0'/], 187 comment-[0'!], 188 condition-[0'#], 189 delimiter-[0'=], 190 negation-[0'^], 191 normal-[], 192 partial-[0'>], 193 query-[0'?, 0'-] 194 ] 195 ), 196 append(DelimiterStart, Suffix, Opener) 197 }, 198 open_placeholder_impl(Opener, In, Out). 199 200open_placeholder_impl([], In, In) --> []. 201 open_placeholder_impl([ C| T], [C|In], Out) --> 202 open_placeholder_impl(T, In, Out). 203 204partial( Delimiters, In, Out) --> 205 condition_placeholder(partial, Delimiters, Base, In, Rest1), 206 { file_name_extension(Base, 'mustache', Path), 207 exists_file(Path), 208 read_file_to_codes(Path, Codes, [encoding(utf8)]), 209 append(Codes, Rest1, Out) 210 }. 211 212placeholder(Variables, Delimiters, In, Out) --> 213 open_placeholder(normal, Delimiters, In, Rest0), 214 variable(Variable, Rest0, Rest1), 215 close_placeholder(Delimiters, Rest1, Out), 216 push_variable(Variable, Variables). 217 218push_variable(Key, Variables) --> 219 { variables_key_value(Variables, Key, Term) }, 220 push_variable_codes( Term ), 221 !. 222 push_variable(_, _) --> []. 223 224 225push_variable_codes( Codes) --> 226 { 227 is_of_type(codes, Codes) 228 }, 229 . 230 push_variable_codes( Atom) --> 231 { 232 is_of_type(atom, Atom), 233 atom_codes(Atom, Codes) 234 }, 235 . 236 push_variable_codes( String) --> 237 { 238 is_of_type(string, String), 239 string_codes(String, Codes) 240 }, 241 . 242 push_variable_codes( Term ) --> 243 { 244 format(codes(Codes), '~w', Term) 245 }, 246 . 247 248query(Variables, Delimiters, In, Out) --> 249 open_placeholder(query, Delimiters, In, R1), 250 { query_goal(Goal, R1, Rest0) }, 251 variable(Variable, Rest0, Rest1), 252 close_placeholder(Delimiters, Rest1, Out), 253 { variables_key_value(Variables, Variable, Value) }, 254 { once(call(Goal, Value, Result) ), 255 ( is_of_type(codes, Result) 256 -> ResultCodes = Result 257 ; atomic_list_concat([Result], Atom), 258 atom_codes(Atom, ResultCodes) 259 ) 260 }, 261 . 262 263query_goal(Goal, In, Out) :- 264 setup_call_cleanup( 265 open_any(string(In), read, Stream, Close, []), 266 ( read_term(Stream, Goal, [syntax_errors(fail)]), 267 stream_property(Stream, position(Position) ) 268 ), 269 close_any(Close) 270 ), 271 stream_position_data(char_count, Position, Offset), 272 append(Prefix, Out, In), 273 length(Prefix, Offset), 274 !. 275 276var_chars([]) --> []. 277var_chars([C|Var]) --> 278 [C], 279 { 280 ( 281 code_type(C,csym) 282 ; 283 memberchk(C, [ 0'-, 0'., 0'/, 0'(, 0'), 0'[, 0'], 0'\\ ] ) 284 ) 285 }, 286 var_chars(Var). 287 288variable(Variable, In, Out) --> 289 { 290 phrase(variable_impl(VariableC), In, Out), 291 atom_codes(Variable, VariableC) 292 }. 293 294variable_impl(Var) --> 295 whites, 296 var_chars(Var), 297 whites. 298 299variables_key_value(Variables, Key, Value) :- 300 is_dict(Variables), 301 !, 302 Value = Variables.get(Key), 303 \+ memberchk(Value, [ [], undefined, null, false ]). 304 variables_key_value(Variables, Key, Value) :- 305 memberchk(Key-Value, Variables), 306 \+ memberchk(Value, [ [], undefined, null, false ]). 307 variables_key_value(Variables, Key, Value) :- 308 memberchk(Key=Value, Variables), 309 \+ memberchk(Value, [ [], undefined, null, false ]). % false values do not counts!