comparison interps/brachylog/brachylog/Brachylog-master/src/transpile.pl @ 11868:70dedbc831e9 draft

<ais523> ` mv ibin/brachylog interps/brachylog
author HackEso <hackeso@esolangs.org>
date Tue, 16 Jul 2019 21:39:11 +0000
parents ibin/brachylog/Brachylog-master/src/transpile.pl@318de151d0ec
children
comparison
equal deleted inserted replaced
11867:b0414b6b332f 11868:70dedbc831e9
1 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2 ____ ____
3 \ \ / /
4 \ \ ____ / /
5 \ \/ \/ /
6 \ /\ / BRACHYLOG
7 \ / \ / A terse declarative logic programming language
8 / \ / \
9 / \/ \ Written by Julien Cumin - 2017
10 / /\____/\ \ https://github.com/JCumin/Brachylog
11 / / ___ \ \
12 /___/ /__/ \___\
13
14 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
15
16
17 :- module(transpile, [parse/2,
18 parse_no_file/2,
19 parse_argument/2,
20 contains_write/1
21 ]).
22
23 :- use_module(tokenize).
24 :- use_module(symbols).
25
26
27 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
28 PARSE
29 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
30 parse(Code, TranspiledPath) :-
31 parse_no_file(Code, Predicates),
32 open(TranspiledPath, write, File),
33 maplist(write_to_file(File), Predicates),
34 close(File).
35
36 parse_no_file(Code, Predicates) :-
37 atom_chars(Code, SplittedCode),
38 tokenize(SplittedCode, TokensNoOutputs),
39 append_trailing_output(TokensNoOutputs, Tokens),
40 fix_predicates(Tokens, FixedPredicates),
41 fix_metapredicates(FixedPredicates, FixedMetapredicates),
42 fill_implicit_variables(FixedMetapredicates, FilledTokens),
43 fix_variables_superscripts(FilledTokens, FixedVariables, GlobalVariables),
44 fix_lists(FixedVariables, FixedLists),
45 fix_forks(FixedLists, FixedForks),
46 fix_arrows(FixedForks, Program),
47 atomic_list_concat(GlobalVariables, ',', G),
48 atomic_list_concat(['[', G, ']'], GlobalVariablesAtom),
49 transpile(Program, Predicates, GlobalVariablesAtom),
50 !.
51
52
53 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
54 PARSE_ARGUMENT
55 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
56 parse_argument(Arg, Term) :-
57 ( atom(Arg),
58 AtomArg = Arg
59 ; \+ atom(Arg),
60 term_to_atom(Arg, AtomArg)
61 ),
62 atom_chars(AtomArg, SplittedArg),
63 tokenize(SplittedArg, Token),
64 fix_variables_superscripts(Token, FixedSuperscripts, _),
65 fix_lists(FixedSuperscripts, Program),
66 transpile(Program, Parsed, '[]'),
67 !,
68 reverse(Parsed, [TempMainPredicate|_]),
69 nth0(3, TempMainPredicate, Atom),
70 atom_concat(',\n ', AtomT, Atom),
71 atom_concat(ParsedArg, ' = Var_Input_Local', AtomT),
72 term_to_atom(Term, ParsedArg)
73 ;
74 throw('Incorrect variable format.').
75
76
77 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
78 APPEND_TRAILING_OUTPUT
79 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
80 append_trailing_output([], ['variable':'Output':'sup':'default']).
81 append_trailing_output(['control':'\n'|T], ['variable':'Output':'sup':'default','control':'\n'|T2]) :-
82 append_trailing_output(T, T2).
83 append_trailing_output(['control':'}'|T], ['variable':'Output':'sup':'default','control':'}'|T2]) :-
84 append_trailing_output(T, T2).
85 append_trailing_output(['control':'⟩'|T], ['variable':'Output':'sup':'default','control':'⟩'|T2]) :-
86 append_trailing_output(T, T2).
87 append_trailing_output(['control':'|'|T], ['variable':'Output':'sup':'default','control':'|'|T2]) :-
88 append_trailing_output(T, T2).
89 append_trailing_output([H|T], [H|T2]) :-
90 H \= 'control':'\n',
91 H \= 'control':'}',
92 H \= 'control':'⟩',
93 H \= 'control':'|',
94 append_trailing_output(T, T2).
95
96
97 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
98 FIX_PREDICATES'⟨', '⟩'
99 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
100 fix_predicates(Tokens, FixedPredicates) :-
101 fix_predicates(Tokens, 1, L),
102 append(L, FixedPredicates).
103
104 fix_predicates([], _, [[]]).
105 fix_predicates(['control':'{'|T], I, [['predicate':PredName:0|Rest], ['control':'\n'|Predicate]|AllOtherPredicates]) :-
106 atomic_list_concat(['brachylog_predicate_',I], PredName),
107 J is I + 1,
108 fix_predicates_(T, J, [Predicate|OtherPredicates1], Z, Remaining),
109 fix_predicates(Remaining, Z, [Rest|OtherPredicates2]),
110 append(OtherPredicates1, OtherPredicates2, AllOtherPredicates).
111 fix_predicates(['control':'⟨'|T], I, [['predicate':PredName:0|Rest], ['control':'\n','fork':'start'|Predicate]|AllOtherPredicates]) :-
112 atomic_list_concat(['brachylog_predicate_',I], PredName),
113 J is I + 1,
114 fix_predicates_(T, J, [Predicate|OtherPredicates1], Z, Remaining),
115 fix_predicates(Remaining, Z, [Rest|OtherPredicates2]),
116 append(OtherPredicates1, OtherPredicates2, AllOtherPredicates).
117 fix_predicates(['control':'\n'|T], I, [[],['control':'\n'|Rest]|OtherPredicates]) :-
118 J is I + 1,
119 fix_predicates(T, J, [Rest|OtherPredicates]).
120 fix_predicates([Type:A|T], I, [[Type:A|Rest]|OtherPredicates]) :-
121 \+ (Type = 'control', A = '{'),
122 \+ (Type = 'control', A = '}'),
123 \+ (Type = 'control', A = '⟨'),
124 \+ (Type = 'control', A = '⟩'),
125 \+ (Type = 'control', A = '\n'),
126 fix_predicates(T, I, [Rest|OtherPredicates]).
127
128 fix_predicates_([], _, [[]]).
129 fix_predicates_(['control':'{'|T], I, [['predicate':PredName:0|Rest], ['control':'\n'|Predicate]|AllOtherPredicates], Z, Remaining) :-
130 atomic_list_concat(['brachylog_predicate_',I], PredName),
131 J is I + 1,
132 fix_predicates_(T, J, [Predicate|OtherPredicates1], Z2, Remaining2),
133 fix_predicates_(Remaining2, Z2, [Rest|OtherPredicates2], Z, Remaining),
134 append(OtherPredicates1, OtherPredicates2, AllOtherPredicates).
135 fix_predicates_(['control':'⟨'|T], I, [['predicate':PredName:0|Rest], ['control':'\n','fork':'start'|Predicate]|AllOtherPredicates], Z, Remaining) :-
136 atomic_list_concat(['brachylog_predicate_',I], PredName),
137 J is I + 1,
138 fix_predicates_(T, J, [Predicate|OtherPredicates1], Z2, Remaining2),
139 fix_predicates_(Remaining2, Z2, [Rest|OtherPredicates2], Z, Remaining),
140 append(OtherPredicates1, OtherPredicates2, AllOtherPredicates).
141 fix_predicates_(['control':'}'|T], I, [[]], I, T).
142 fix_predicates_(['control':'⟩'|T], I, [['fork':'end']], I, T).
143 fix_predicates_([Type:A|T], I, [[Type:A|Rest]|OtherPredicates], Z, Remaining) :-
144 \+ (Type = 'control', A = '{'),
145 \+ (Type = 'control', A = '}'),
146 \+ (Type = 'control', A = '⟨'),
147 \+ (Type = 'control', A = '⟩'),
148 \+ (Type = 'control', A = '\n'),
149 fix_predicates_(T, I, [Rest|OtherPredicates], Z, Remaining).
150
151
152 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
153 FIX_METAPREDICATES
154 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
155 fix_metapredicates([], []).
156 fix_metapredicates(['predicate':PredName:Sub,'metapredicate':MetapredName:Sup|T], ['predicate':PredName:Sub:MetapredName:Sup|T2]) :-
157 fix_metapredicates(T, T2).
158 fix_metapredicates(['predicate':PredName:Sub|T], ['predicate':PredName:Sub:'no':0|T2]) :-
159 fix_metapredicates(T, T2).
160 fix_metapredicates([H|T], [H|T2]) :-
161 fix_metapredicates(T, T2).
162
163
164 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
165 FILL_IMPLICIT_VARIABLES
166 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
167 fill_implicit_variables(Tokens, Program) :-
168 fill_implicit_variables(Tokens, 0, Program).
169
170 fill_implicit_variables([], _, []).
171 fill_implicit_variables(['control':':','predicate':A|T], I, ['control':':','predicate':A|T2]) :-
172 fill_implicit_variables(T, I, T2).
173 fill_implicit_variables(['predicate':A,Type:B|T], I, ['predicate':A,'variable':V|T2]) :-
174 Type \= 'variable',
175 atom_concat('V', I, V),
176 J is I + 1,
177 fill_implicit_variables([Type:B|T], J, T2).
178 fill_implicit_variables(['predicate':A], I, ['predicate':A,'variable':V]) :-
179 atom_concat('V', I, V).
180 fill_implicit_variables(['predicate':A,'variable':B|T], I, ['predicate':A,'variable':B|T2]) :-
181 fill_implicit_variables(T, I, T2).
182 fill_implicit_variables(['control':H,Type:B|T], I, ['control':H,'variable':V|T2]) :-
183 Type \= 'variable',
184 ( H = '∧'
185 ; H = '∨'
186 ),
187 atom_concat('V', I, V),
188 J is I + 1,
189 fill_implicit_variables([Type:B|T], J, T2).
190 fill_implicit_variables(['control':H,'variable':B,Type:C|T], I, ['control':H,'variable':B,'variable':V|T2]) :-
191 Type \= 'variable',
192 ( H = '↖'
193 ; H = '↙'
194 ),
195 atom_concat('V', I, V),
196 J is I + 1,
197 fill_implicit_variables([Type:C|T], J, T2).
198 fill_implicit_variables([Type:A|T], I, [Type:A|T2]) :-
199 Type \= 'predicate',
200 \+ (Type = 'control', A = ':', T = ['predicate':_|_]),
201 \+ (Type = 'control', A = '∧', T \= ['variable':_|_]),
202 \+ (Type = 'control', A = '∨', T \= ['variable':_|_]),
203 \+ (Type = 'control', A = '↖', T \= ['variable':_|_]),
204 \+ (Type = 'control', A = '↙', T \= ['variable':_|_]),
205 fill_implicit_variables(T, I, T2).
206
207
208 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
209 FIX_VARIABLES_SUPERSCRIPTS
210 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
211 fix_variables_superscripts(Input, Output, GlobalVariables) :-
212 fix_variables_superscripts_(Input, Output, GlobVars),
213 sort(GlobVars, GlobalVariables). % Remove duplicates
214
215 fix_variables_superscripts_([], [], []).
216 fix_variables_superscripts_(['variable':A:'sup':Sup|T], ['variable':V|T2], [V|GlobalVariables]) :-
217 atomic_list_concat(['integer', SupAtom], ':', Sup),
218 atom_number(SupAtom, J),
219 atomic_list_concat(['Var_',A,'_',J], V),
220 fix_variables_superscripts_(T, T2, GlobalVariables).
221 fix_variables_superscripts_(['variable':A:'sup':'default'|T], ['variable':V|T2], GlobalVariables) :-
222 atomic_list_concat(['Var_',A,'_Local'], V),
223 fix_variables_superscripts_(T, T2, GlobalVariables).
224 fix_variables_superscripts_(['variable':List|T], ['variable':FixedList|T2], GlobalVariables) :-
225 is_list(List),
226 fix_variables_superscripts_(List, FixedList, Vars),
227 fix_variables_superscripts_(T, T2, GlobalVariables2),
228 append(Vars, GlobalVariables2, GlobalVariables).
229 fix_variables_superscripts_([X|T], [X|T2], GlobalVariables) :-
230 fix_variables_superscripts_(T, T2, GlobalVariables).
231
232
233
234 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
235 FIX_LISTS
236 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
237 fix_lists([], []).
238 fix_lists(['variable':List|T], ['variable':FixedList|T2]) :-
239 is_list(List),
240 fix_list(List, FixedList),
241 fix_lists(T, T2).
242 fix_lists([X|T], [X|T2]) :-
243 ( X = 'variable':L,
244 \+ (is_list(L))
245 ; X \= 'variable':_
246 ),
247 fix_lists(T, T2).
248
249 fix_list([], []).
250 fix_list(['control':','|T], T2) :-
251 fix_list(T, T2).
252 fix_list([X|T], [Y|T2]) :-
253 X \= 'control':',',
254 ( X = 'variable':L,
255 is_list(L),
256 fix_list(L, Y)
257 ; X = 'variable':Y
258 ; X = 'predicate':_,
259 Y = X
260 ; Y = X
261 ),
262 fix_list(T, T2).
263
264
265 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
266 FIX_FORKS
267 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
268 fix_forks(L, Z) :-
269 fix_forks(L, 0, Z).
270
271 fix_forks([], _, []). % Ignore each useless implicit var after
272 fix_forks(['fork':'start', F1, _, F2, Output, 'fork':'end'|T], I, ['control':'unpair','variable':V1,F1,Output,F2,'variable':V1,'control':'∧'|T2]) :-
273 atom_concat('Fork', I, V1),
274 J is I + 1,
275 fix_forks(T, J, T2).
276 fix_forks(['fork':'start', F1, _, F2, _, F3, Output, 'fork':'end'|T], I, ['control':'&',F1,'variable':V1,'control':'&',F3,'variable':V2,'control':'∧','variable':V1,'control':';','variable':V2,F2,Output|T2]) :-
277 atom_concat('Fork', I, V1),
278 J is I + 1,
279 atom_concat('Fork', J, V2),
280 K is I + 1,
281 fix_forks(T, K, T2).
282 fix_forks([H|T], I, [H|T2]) :-
283 dif(H, 'fork':'start'),
284 fix_forks(T, I, T2).
285
286
287 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
288 FIX_ARROWS
289 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
290 fix_arrows([], []).
291 fix_arrows(['predicate':P:_:Meta:Sup,'variable':_,'control':'↙','variable':V|T], T2) :- !,
292 ( atom(V) ->
293 V = VA
294 ; term_to_atom(V, VA)
295 ),
296 fix_arrows(['predicate':P:VA:Meta:Sup|T], T2).
297 fix_arrows(['predicate':P:Sub:Meta:_,'variable':_,'control':'↖','variable':V|T], T2) :- !,
298 ( atom(V) ->
299 V = VA
300 ; term_to_atom(V, VA)
301 ),
302 fix_arrows(['predicate':P:Sub:Meta:VA|T], T2).
303 fix_arrows(['predicate':P:_:Meta:Sup,'control':'↙','variable':V|T], T2) :- !,
304 ( atom(V) ->
305 V = VA
306 ; term_to_atom(V, VA)
307 ),
308 fix_arrows(['predicate':P:VA:Meta:Sup|T], T2).
309 fix_arrows(['predicate':P:Sub:Meta:_,'control':'↖','variable':V|T], T2) :- !,
310 ( atom(V) ->
311 V = VA
312 ; term_to_atom(V, VA)
313 ),
314 fix_arrows(['predicate':P:Sub:Meta:VA|T], T2).
315 fix_arrows([H|T], [H|T2]) :-
316 fix_arrows(T, T2).
317
318
319 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
320 TRANSPILE
321 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
322 transpile(Program, [[':- style_check(-singleton).'],
323 [':- use_module(library(clpfd)).'],
324 [':- use_module(predicates).'],
325 [':- use_module(metapredicates).'],
326 [':- use_module(constraint_variables).\n'],
327 [MainPredHeader,
328 ConstraintVariables,
329 ' (1=1'|MainPred]|OtherPredicates], GlobalVariables) :-
330 atomic_list_concat(['brachylog_main(',
331 GlobalVariables,
332 ',_, Var_Input_Local,Var_Output_Local) :-\n',
333 ' Name = brachylog_main,\n',
334 ' GlobalVariables = ',
335 GlobalVariables,',\n',
336 ' nb_setval(\'declw\',[]),\n'], % Initialize declarative write variable
337 MainPredHeader),
338 constraint_variables(GlobalVariables, ConstraintVariables),
339 transpile_(Program, 'Var_Input_Local', no, no, 0, 0, [T|OtherPredicates], GlobalVariables),
340 reverse(T, [_|RT]),
341 reverse(RT, T2),
342 append(T2, ['\n',
343 ' ),\n',
344 ' (',
345 '(Var_Output_Local = integer:_ ; ',
346 'Var_Output_Local = [_|_], ',
347 'forall(member(E, Var_Output_Local), E = integer:_)) ',
348 '-> brachylog_label(default, Var_Output_Local, _) ',
349 '; true),\n',
350 ' nb_getval(\'declw\', DeclwFinal),\n',
351 ' maplist(write, DeclwFinal).'], % execute declarative write
352 MainPred).
353
354 transpile_([], _, _, _, _, _, [['\n ).\n']], _).
355 transpile_(['variable':B|T], A, Reverse, Negate, AppendNumber, PredNumber, [[Unification|T2]|OtherPredicates], GlobalVariables) :-
356 A \= 'nothing',
357 ( is_list(A),
358 brachylog_list_to_atom(A, Var1)
359 ; A = Type:L,
360 term_to_atom(Type:L, Var1)
361 ; A = Var1
362 ),
363 ( is_list(B),
364 brachylog_list_to_atom(B, Var2)
365 ; B = _:_,
366 term_to_atom(B, Var2)
367 ; Var2 = B
368 ),
369 ( Negate = yes,
370 UnificationAtom = ' \\= '
371 ; Negate = no,
372 UnificationAtom = ' = '
373 ),
374 ( Reverse = no,
375 atomic_list_concat([',\n ',Var2,UnificationAtom,Var1], Unification),
376 transpile_(T, B, no, no, AppendNumber, PredNumber, [T2|OtherPredicates], GlobalVariables)
377 ; Reverse = yes,
378 atomic_list_concat([',\n ',Var1,UnificationAtom,Var2], Unification),
379 transpile_(T, B, no, no, AppendNumber, PredNumber, [T2|OtherPredicates], GlobalVariables)
380 ).
381 transpile_(['variable':B|T], 'nothing', _, _, AppendNumber, PredNumber, [T2|OtherPredicates], GlobalVariables) :-
382 transpile_(T, B, no, no, AppendNumber, PredNumber, [T2|OtherPredicates], GlobalVariables).
383 transpile_(['predicate':P:Sub:Meta:Sup,'variable':B|T], A, Reverse, Negate, AppendNumber, PredNumber, [[Predicate|T2]|OtherPredicates], GlobalVariables) :-
384 A \= 'nothing',
385 ( P = 'brachylog_call_predicate',
386 ( Sub = 'default' ->
387 RealSub = 'Name-GlobalVariables'
388 ; atomic_list_concat(['(',Sub,')-','GlobalVariables'], RealSub)
389 )
390 ; P \= 'brachylog_call_predicate',
391 RealSub = Sub
392 ),
393 ( is_list(A),
394 brachylog_list_to_atom(A, Var1)
395 ; A = Type:L,
396 term_to_atom(Type:L, Var1)
397 ; A = Var1
398 ),
399 ( is_list(B),
400 brachylog_list_to_atom(B, Var2)
401 ; B = _:_,
402 term_to_atom(B, Var2)
403 ; Var2 = B
404 ),
405 ( Negate = yes,
406 NegateAtom = '\\+ '
407 ; Negate = no,
408 NegateAtom = ''
409 ),
410 ( Reverse = no ->
411 PredName = P
412 ; atomic_list_concat([P,'_reversed'], PredName)
413 ),
414 ( atomic_list_concat(['brachylog','predicate',_], '_', P)
415 -> atomic_list_concat([GlobalVariables,','], GlobVars)
416 ; GlobVars = ''
417 ),
418 ( Meta = no ->
419 atomic_list_concat([',\n ',NegateAtom,PredName,'(',GlobVars,RealSub,',',Var1,',',Var2,')'], Predicate)
420 ; ( atomic_list_concat(['brachylog','predicate',_], '_', P)
421 -> atomic_list_concat([GlobalVariables,','], GlobVarsMeta)
422 ; GlobVarsMeta = 'ignore,'
423 ),
424 atomic_list_concat([',\n ',NegateAtom,Meta,'(',GlobVarsMeta,Sup,',',PredName,',',RealSub,',',Var1,',',Var2,')'], Predicate)
425 ),
426 transpile_(T, B, no, no, AppendNumber, PredNumber, [T2|OtherPredicates], GlobalVariables).
427 transpile_(['control':'∧'|T], _, _, _, AppendNumber, PredNumber, [T2|OtherPredicates], GlobalVariables) :-
428 transpile_(T, 'nothing', no, no, AppendNumber, PredNumber, [T2|OtherPredicates], GlobalVariables).
429 transpile_(['control':'&'|T], _, _, _, AppendNumber, PredNumber, [T2|OtherPredicates], GlobalVariables) :-
430 transpile_(T, 'Var_Input_Local', no, no, AppendNumber, PredNumber, [T2|OtherPredicates], GlobalVariables).
431 transpile_(['control':'`'|T], B, _, _, AppendNumber, PredNumber, [['\n *->\n 1=1'|T2]|OtherPredicates], GlobalVariables) :-
432 transpile_(T, B, no, no, AppendNumber, PredNumber, [T2|OtherPredicates], GlobalVariables).
433 transpile_(['control':'∨'|T], _, _, _, AppendNumber, PredNumber, [['\n ;\n 1=1'|T2]|OtherPredicates], GlobalVariables) :-
434 transpile_(T, 'nothing', no, no, AppendNumber, PredNumber, [T2|OtherPredicates], GlobalVariables).
435 transpile_(['control':'('|T], B, _, Negate, AppendNumber, PredNumber, [[Parenthesis|T2]|OtherPredicates], GlobalVariables) :-
436 ( Negate = yes,
437 Parenthesis = ',\n \\+ (\n 1=1'
438 ; Negate = no,
439 Parenthesis = ',\n (\n 1=1'
440 ),
441 transpile_(T, B, no, no, AppendNumber, PredNumber, [T2|OtherPredicates], GlobalVariables).
442 transpile_(['control':')'|T], B, _, _, AppendNumber, PredNumber, [['\n )'|T2]|OtherPredicates], GlobalVariables) :-
443 transpile_(T, B, no, no, AppendNumber, PredNumber, [T2|OtherPredicates], GlobalVariables).
444 transpile_(['control':'!'|T], B, _, _, AppendNumber, PredNumber, [[',\n !'|T2]|OtherPredicates], GlobalVariables) :-
445 transpile_(T, B, no, no, AppendNumber, PredNumber, [T2|OtherPredicates], GlobalVariables).
446 transpile_(['control':'⊥'|T], B, _, _, AppendNumber, PredNumber, [[',\n false'|T2]|OtherPredicates], GlobalVariables) :-
447 transpile_(T, B, no, no, AppendNumber, PredNumber, [T2|OtherPredicates], GlobalVariables).
448 transpile_(['control':'~'|T], B, Reverse, Negate, AppendNumber, PredNumber, [T2|OtherPredicates], GlobalVariables) :-
449 ( Reverse = yes,
450 NewReverse = no
451 ; Reverse = no,
452 NewReverse = yes
453 ),
454 transpile_(T, B, NewReverse, Negate, AppendNumber, PredNumber, [T2|OtherPredicates], GlobalVariables).
455 transpile_(['control':'¬'|T], B, Reverse, Negate, AppendNumber, PredNumber, [T2|OtherPredicates], GlobalVariables) :-
456 ( Negate = yes,
457 NewNegate = no
458 ; Negate = no,
459 NewNegate = yes
460 ),
461 transpile_(T, B, Reverse, NewNegate, AppendNumber, PredNumber, [T2|OtherPredicates], GlobalVariables).
462 transpile_(['control':'unpair','variable':A|T], B, _, _, AppendNumber, PredNumber, [[Unpair|T2]|OtherPredicates], GlobalVariables) :-
463 ( A = TypeA:LA,
464 term_to_atom(TypeA:LA, TailElem)
465 ; A = TailElem
466 ),
467 ( B = TypeB:LB,
468 term_to_atom(TypeB:LB, Pair)
469 ; B = Pair
470 ),
471 atomic_list_concat(['UnpairTemp',AppendNumber],HeadElem),
472 atomic_list_concat([',\n ',
473 Pair,'=[',HeadElem,',',TailElem,']'],Unpair),
474 NewAppendNumber is AppendNumber + 1,
475 transpile_(T, HeadElem, no, no, NewAppendNumber, PredNumber, [T2|OtherPredicates], GlobalVariables).
476 transpile_(['control':';',Type:A|T], B, _, _, AppendNumber, PredNumber, [T2|OtherPredicates], GlobalVariables) :-
477 ( Type = 'variable'
478 ; Type = 'predicate'
479 ),
480 append([B], [A], NewVar),
481 transpile_(T, NewVar, no, no, AppendNumber, PredNumber, [T2|OtherPredicates], GlobalVariables).
482 transpile_(['control':',','variable':A|T], B, _, _, AppendNumber, PredNumber, [[Append|T2]|OtherPredicates], GlobalVariables) :-
483 ( is_list(A),
484 brachylog_list_to_atom(A, Arg1)
485 ; A = TypeA:LA,
486 term_to_atom(TypeA:LA, Arg1)
487 ; A = Arg1
488 ),
489 ( is_list(B),
490 brachylog_list_to_atom(B, Arg2)
491 ; B = TypeB:LB,
492 term_to_atom(TypeB:LB, Arg2)
493 ; B = Arg2
494 ),
495 atomic_list_concat(['AppendTemp',AppendNumber],TempVar),
496 atomic_list_concat([',\n ',
497 '((',Arg2,' == [], \\+ is_brachylog_list(',Arg1,')) -> ',TempVar,' = [',Arg1,'] ; ',
498 'brachylog_concatenate(default,',
499 '[',Arg2,',',Arg1,']',
500 ',',TempVar,') -> true ; is_brachylog_list(',
501 Arg2,
502 '), brachylog_concatenate(default,',
503 '[',Arg2,',[',Arg1,']]',
504 ',',TempVar,') -> true ; brachylog_concatenate(default,',
505 '[[',Arg2,'],[',Arg1,']],',TempVar,'))'
506 ], Append),
507 NewAppendNumber is AppendNumber + 1,
508 transpile_(T, TempVar, no, no, NewAppendNumber, PredNumber, [T2|OtherPredicates], GlobalVariables).
509 transpile_(['control':'\n'|T], _, _, _, AppendNumber, PredNumber, [['\n ).\n'],[ReversedPred],[PredHead|T2]|OtherPredicates], GlobalVariables) :-
510 J is PredNumber + 1,
511 constraint_variables(GlobalVariables, ConstraintVariables),
512 atomic_list_concat(['brachylog_predicate_',
513 J,
514 '_reversed(',
515 GlobalVariables,
516 ',_, Input, Output',
517 ') :-\n',
518 ' brachylog_predicate_',
519 J,
520 '(',
521 GlobalVariables,
522 ',_, Output, Input',
523 ').\n'], ReversedPred),
524 atomic_list_concat(['brachylog_predicate_',
525 J,
526 '(',
527 GlobalVariables,
528 ',_, ',
529 'Var_Input_Local',
530 ',Var_Output_Local',
531 ') :-\n Name = brachylog_predicate_',
532 J,
533 ',\n GlobalVariables = ',
534 GlobalVariables,
535 ',\n',
536 ConstraintVariables,
537 ' (1=1'], PredHead),
538 transpile_(T, 'Var_Input_Local', no, no, AppendNumber, J, [T2|OtherPredicates], GlobalVariables).
539 transpile_(['control':'|'|T], _, _, _, AppendNumber, PredNumber, [['\n ).\n'],[PredHead|T2]|OtherPredicates], GlobalVariables) :-
540 ( PredNumber = 0,
541 PredName = 'brachylog_main'
542 ; PredNumber \= 0,
543 atomic_list_concat(['brachylog_predicate_',PredNumber], PredName)
544 ),
545 constraint_variables(GlobalVariables, ConstraintVariables),
546 atomic_list_concat([PredName,
547 '(',
548 GlobalVariables,
549 ',_, ',
550 'Var_Input_Local',
551 ',Var_Output_Local',
552 ') :-\n Name = ',
553 PredName,
554 ',\n GlobalVariables = ',
555 GlobalVariables,
556 ',\n',
557 ConstraintVariables,
558 ' (1=1'], PredHead),
559 transpile_(T, 'Var_Input_Local', no, no, AppendNumber, PredNumber, [T2|OtherPredicates], GlobalVariables).
560
561
562 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
563 CONTAINS_WRITE
564 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
565 contains_write(Code) :-
566 atom_chars(Code, SplittedCode),
567 tokenize(SplittedCode, Tokens),
568 fix_predicates(Tokens, FixedPredicates),
569 ( member(predicate:brachylog_write:_, FixedPredicates)
570 ; member(predicate:brachylog_writeln:_, FixedPredicates)
571 ).
572
573
574 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
575 CONSTRAINT_VARIABLES
576 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
577 constraint_variables(GlobalVariables, ConstraintVariables) :-
578 atom_chars(GlobalVariables, [_|Gs]),
579 reverse(Gs, [_|RGs]),
580 reverse(RGs, RRGs),
581 atomic_list_concat(RRGs, GGs),
582 atomic_list_concat(GlobVars, ',', GGs),
583 findall(S, (member(X, GlobVars),
584 atomic_list_concat(['Var', Name, _], '_', X),
585 atom_chars(Name, CName),
586 reverse(CName, [_,'t','n','i','a','r','t','s','n','o','C']),
587 constraint_variable(X, S)), Ss),
588 atomic_list_concat(Ss, GlobalConstraintVariables),
589 findall(T, (member(X, ['A','B','C','D','E','F','G','H','I','J','K','L','M','N','O','P','Q','R','S','T','U','V','W','X','Y','Z']),
590 atomic_list_concat([' constraint',X,'(Var_Constraint',X,'_Local','),\n'], T)),
591 Ts
592 ),
593 atomic_list_concat(Ts, LocalConstraintVariables),
594 atomic_list_concat([GlobalConstraintVariables, LocalConstraintVariables], ConstraintVariables).
595
596 constraint_variable(X, S) :-
597 atomic_list_concat(['Var', ConstraintName, _], '_', X),
598 atom_chars(ConstraintName, [C|Cs]),
599 downcase_atom(C, CDown),
600 atomic_list_concat([CDown|Cs], PredName),
601 atomic_list_concat([' ',PredName,'(',X,'),\n'], S).
602
603
604 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
605 BRACHYLOG_LIST_TO_ATOM
606 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
607 brachylog_list_to_atom(List, Atom) :-
608 brachylog_list_to_atom_(List, T2),
609 atomic_list_concat(['[',T2,']'], Atom).
610
611 brachylog_list_to_atom_([], '').
612 brachylog_list_to_atom_([A], AtomA) :-
613 ( is_list(A),
614 brachylog_list_to_atom(A, AtomA)
615 ; A = _:_,
616 term_to_atom(A, AtomA)
617 ; \+ is_list(A),
618 A \= _:_,
619 AtomA = A
620 ).
621 brachylog_list_to_atom_([A,B|T], Atom) :-
622 ( is_list(A),
623 brachylog_list_to_atom(A, AtomA)
624 ; A = _:_,
625 term_to_atom(A, AtomA)
626 ; \+ is_list(A),
627 A \= _:_,
628 AtomA = A
629 ),
630 brachylog_list_to_atom_([B|T], T2),
631 atomic_list_concat([AtomA,',',T2], Atom).
632
633
634 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
635 WRITE_TO_FILE
636 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
637 write_to_file(File, []) :-
638 write(File, '\n\n').
639 write_to_file(File, [H|T]) :-
640 write(File, H),
641 write_to_file(File, T).