19
20:- module(dcg_julia,
21 [ term_jlstring/2 22 , op(200,xfx,::) 23 , op(150,fx,:) 24 , op(160,yf,'`') 25 , op(800,xfy,:>:)
26 , op(210,xfy,.^) 27 , op(410,yfx,.*) 28 , op(410,yfx,./) 29 , op(410,xfy,.\) 30 , op(400,xfy,\) 31 , op(100,yfx,'`') 32 , op(750,xfy,\\) 33 , op(200,yf,[]) 34 , op(160,fx,.) 35 , op(200,yfx,@) 36 , op(200,yfx,.@) 37 , op(300,yf,...) 38 , op(700,xfy,=>) 39 ]). 40
41
42:- multifile dcg_julia:pl2jl_hook/2.
128:- use_module(library(dcg_core)). 129:- use_module(library(dcg_codes)). 130
131:- set_prolog_flag(back_quotes,symbol_char). 132:- set_prolog_flag(double_quotes,codes).
142expr(A:>:B) --> !, "(", expr(A), ";", expr(B), ")".
143expr(A=B) --> !, "(", expr(A), " = ", expr(B), ")".
144expr(A::B) --> !, "(", expr(A), ")::", expr(B). 145expr(if(A,B)) --> !, "if ",expr(A), " ", expr(B), " end".
146expr(if(A,B,C)) --> !, "if ",expr(A), " ", expr(B), " else ", expr(C), " end".
147expr(using(P)) --> !, "using ", atm(P).
148
149expr(\X) --> !, phrase(X).
150expr($X) --> !, {pl2jl_hook(X,Y)}, expr(Y).
151expr(q(X)) --> !, q(expr(X)).
152expr(qq(X)) --> !, qq(expr(X)).
153expr(noeval(_)) --> !, {fail}. 154
155expr(A>=B)--> !, ">=",args(A,B).
156expr(A=<B)--> !, "<=",args(A,B).
157expr(A\=B)--> !, "!=",args(A,B).
158expr(\+A) --> !, "!",args(A).
159expr(A:B:C) --> !, expr(colon(A,B,C)).
160expr(A:B) --> !, expr(colon(A,B)).
161expr(rdiv(A,B)) --> !, "//", args(A,B).
162expr(<<(A,B)) --> !, "∘", args(A,B). 163
164expr([]) --> !, "[]".
165expr([X|Xs]) --> !, "[", seqmap_with_sep(",",expr,[X|Xs]), "]".
166
167expr(:B) --> !, ":", {atomic(B)} -> atm(B); ":(", expr(B), ")".
168expr(A`B) --> !, expr(A), ".", atm(B).
169expr(B`) --> !, "ctranspose", args(B).
170expr(B...) --> !, expr(B), "...".
171expr(A\\B) --> !, { term_variables(A,V), varnames(V) },
172 "((", arglist(A), ") -> ", expr(B), ")".
173
174expr([](Xs,'`')) --> !, "[", slist(Xs), "]".
175expr([](Is,X)) --> !, expr(X), "[", clist(Is), "]".
176expr(A@B) --> !, expr(A), arglist(B).
177expr(A.@B) --> !, expr(.A), arglist(B).
178expr(.A) --> !, "(", expr(A), ")", ".".
179expr(#()) --> !, "()".
180expr(#(A)) --> !, "(", expr(A), ",)".
181expr(#(A,B)) --> !, arglist([A,B]).
182
183expr(int64([_],L)) --> !, "Int64[", clist(L), "]".
184expr(float64([_],L)) --> !, "Float64[", clist(L), "]".
185expr(int64(S,L)) --> !, "reshape(Int64[", flatten(S,L), "],reverse(", arglist(S), "))".
186expr(float64(S,L)) --> !, "reshape(Float64[", flatten(S,L), "],reverse(", arglist(S), "))".
187
188expr(arr($X)) --> !, { pl2jl_hook(X,L) }, expr(arr(L)).
189expr(arr(L)) --> !, { array_dims(L,D) }, array(D,L).
190expr(arr(D,L)) --> !, array(D,L).
191expr(arr(D,L,P)) --> !, array(D,P,L).
192expr('$VAR'(N)) --> !, "p_", atm(N).
193
195expr(A) --> {string(A)}, !, qq(str(A)).
196expr(A) --> {atomic(A)}, !, atm(A).
197expr(F) --> {compound_name_arity(F,H,0)}, !, atm(H), "()".
198expr(A) --> {is_dict(A)}, !, {dict_pairs(A,_,Ps), maplist(pair_to_jl,Ps,Ps1)}, "Dict", arglist(Ps1).
199expr(F) --> {F=..[H|AX]}, ({H='#'} -> []; atm(H)), arglist(AX).
200
201expr_with(Lambda,Y) --> {copy_term(Lambda,Y\\PY)}, expr(PY).
202pair_to_jl(K-V, KK=>V) :- atom(K) -> KK= :K; KK=K.
203
204
206array_dims([X|_],M) :- !, array_dims(X,N), M is N+1.
207array_dims(_,0).
208
209flatten([], X) --> expr(X).
210flatten([_|D], L) --> seqmap_with_sep(",", flatten(D), L).
218array(0,X) --> !, expr(X).
219array(1,L) --> !, "[", seqmap_with_sep(";",expr,L), "]".
220array(2,L) --> !, "[", seqmap_with_sep(" ",array(1),L), "]".
221array(N,L) --> {succ(M,N)}, "cat(", atm(N), ",", seqmap_with_sep(",",array(M),L), ")".
222
223array(0,P,X) --> !, expr_with(P,X).
224array(1,P,L) --> !, "[", seqmap_with_sep(";",expr_with(P),L), "]".
225array(2,P,L) --> !, "[", seqmap_with_sep(" ",array(1,P),L), "]".
226array(N,P,L) --> {succ(M,N)}, "cat(", atm(N), ",", seqmap_with_sep(",",array(M,P),L), ")".
230clist([]) --> [].
231clist([L1|LX]) --> expr(L1), seqmap(do_then_call(",",expr),LX).
232
233slist([]) --> [].
234slist([L1|LX]) --> expr(L1), seqmap(do_then_call(" ",expr),LX).
239arglist(X) --> "(", clist(X), ")".
246args(X,Y) --> "(", expr(X), ",", expr(Y), ")".
247args(X) --> "(", expr(X), ")".
251atm(A,C,T) :- format(codes(C,T),'~w',[A]).
252
253varnames(L) :- varnames(1,L).
254varnames(_,[]).
255varnames(N,[TN|Rest]) :-
256 atom_concat(p_,N,TN), succ(N,M),
257 varnames(M,Rest).
262term_jlstring(Term,String) :- phrase(expr(Term),String), !
Julia DCG
TODO
@ for macros? ; for keyword arguments
REVIEW \\ for lambda
Julia expression syntax
The expression syntax adopted by this module allows Prolog terms to represent or denote Julia expressions. Let T be the domain of recognised Prolog terms (denoted by type expr), and M be the domain of Julia expressions written in Julia syntax. Then V : T->M is the valuation function which maps Prolog term X to Julia expression V[X]. These are some of the constructs it recognises:
Things to bypass default formatting
All other Prolog atoms are written using write/1. Prolog dictionaries are written as Julia dictionaries. Dictionary keys can be atoms (written as Julia symbols) or small integers (written as Julia integers). Other Prolog terms are assumed to be calls to functions named according to the head functor. Thus V[ <head>( <arg1>, <arg2>, ...) ] = <head>(V[<arg1>, V[<arg2>], ...).
arr(Vals,Shape,InnerFunctor)
- allows efficient representation of arrays of arbitrary things. Will require more strict nested list form. */