author | haftmann |
Fri, 04 Jun 2010 19:36:41 +0200 | |
changeset 37337 | c0cf8b6c2c26 |
parent 37243 | 6e2ac5358d6e |
child 37384 | 5aba26803073 |
permissions | -rw-r--r-- |
34294 | 1 |
(* Author: Florian Haftmann, TU Muenchen |
2 |
||
3 |
Serializer for Scala. |
|
4 |
*) |
|
5 |
||
6 |
signature CODE_SCALA = |
|
7 |
sig |
|
8 |
val setup: theory -> theory |
|
9 |
end; |
|
10 |
||
11 |
structure Code_Scala : CODE_SCALA = |
|
12 |
struct |
|
13 |
||
14 |
val target = "Scala"; |
|
15 |
||
16 |
open Basic_Code_Thingol; |
|
17 |
open Code_Printer; |
|
18 |
||
19 |
infixr 5 @@; |
|
20 |
infixr 5 @|; |
|
21 |
||
22 |
||
23 |
(** Scala serializer **) |
|
24 |
||
25 |
fun print_scala_stmt labelled_name syntax_tyco syntax_const reserved args_num is_singleton deresolve = |
|
26 |
let |
|
27 |
val deresolve_base = Long_Name.base_name o deresolve; |
|
37243
6e2ac5358d6e
capitalized type variables; added yield as keyword
haftmann
parents:
37224
diff
changeset
|
28 |
val lookup_tyvar = first_upper oo lookup_var; |
34294 | 29 |
fun print_typ tyvars fxy (tycoexpr as tyco `%% tys) = (case syntax_tyco tyco |
30 |
of NONE => applify "[" "]" fxy |
|
31 |
((str o deresolve) tyco) (map (print_typ tyvars NOBR) tys) |
|
32 |
| SOME (i, print) => print (print_typ tyvars) fxy tys) |
|
37243
6e2ac5358d6e
capitalized type variables; added yield as keyword
haftmann
parents:
37224
diff
changeset
|
33 |
| print_typ tyvars fxy (ITyVar v) = (str o lookup_tyvar tyvars) v; |
34294 | 34 |
fun print_typed tyvars p ty = |
35 |
Pretty.block [p, str ":", Pretty.brk 1, print_typ tyvars NOBR ty] |
|
36 |
fun print_var vars NONE = str "_" |
|
37 |
| print_var vars (SOME v) = (str o lookup_var vars) v |
|
35228 | 38 |
fun print_term tyvars is_pat some_thm vars fxy (IConst c) = |
39 |
print_app tyvars is_pat some_thm vars fxy (c, []) |
|
40 |
| print_term tyvars is_pat some_thm vars fxy (t as (t1 `$ t2)) = |
|
34294 | 41 |
(case Code_Thingol.unfold_const_app t |
35228 | 42 |
of SOME app => print_app tyvars is_pat some_thm vars fxy app |
34294 | 43 |
| _ => applify "(" ")" fxy |
35228 | 44 |
(print_term tyvars is_pat some_thm vars BR t1) |
45 |
[print_term tyvars is_pat some_thm vars NOBR t2]) |
|
46 |
| print_term tyvars is_pat some_thm vars fxy (IVar v) = |
|
34294 | 47 |
print_var vars v |
35228 | 48 |
| print_term tyvars is_pat some_thm vars fxy ((v, ty) `|=> t) = |
34294 | 49 |
let |
50 |
val vars' = intro_vars (the_list v) vars; |
|
51 |
in |
|
52 |
concat [ |
|
53 |
Pretty.block [str "(", print_typed tyvars (print_var vars' v) ty, str ")"], |
|
54 |
str "=>", |
|
35228 | 55 |
print_term tyvars false some_thm vars' NOBR t |
34294 | 56 |
] |
57 |
end |
|
35228 | 58 |
| print_term tyvars is_pat some_thm vars fxy (ICase (cases as (_, t0))) = |
34294 | 59 |
(case Code_Thingol.unfold_const_app t0 |
60 |
of SOME (c_ts as ((c, _), _)) => if is_none (syntax_const c) |
|
35228 | 61 |
then print_case tyvars some_thm vars fxy cases |
62 |
else print_app tyvars is_pat some_thm vars fxy c_ts |
|
63 |
| NONE => print_case tyvars some_thm vars fxy cases) |
|
64 |
and print_app tyvars is_pat some_thm vars fxy (app as ((c, ((tys, _), tys_args)), ts)) = |
|
34294 | 65 |
let |
66 |
val k = length ts; |
|
67 |
val l = case syntax_const c of NONE => args_num c | SOME (l, _) => l; |
|
68 |
val tys' = if is_pat orelse |
|
69 |
(is_none (syntax_const c) andalso is_singleton c) then [] else tys; |
|
70 |
val (no_syntax, print') = case syntax_const c |
|
71 |
of NONE => (true, fn ts => applify "(" ")" fxy |
|
72 |
(applify "[" "]" NOBR ((str o deresolve) c) (map (print_typ tyvars NOBR) tys')) |
|
35228 | 73 |
(map (print_term tyvars is_pat some_thm vars NOBR) ts)) |
34294 | 74 |
| SOME (_, print) => (false, fn ts => |
35228 | 75 |
print (print_term tyvars is_pat some_thm) some_thm vars fxy (ts ~~ take l tys_args)); |
34294 | 76 |
in if k = l then print' ts |
77 |
else if k < l then |
|
35228 | 78 |
print_term tyvars is_pat some_thm vars fxy (Code_Thingol.eta_expand l app) |
34294 | 79 |
else let |
80 |
val (ts1, ts23) = chop l ts; |
|
81 |
in |
|
82 |
Pretty.block (print' ts1 :: map (fn t => Pretty.block |
|
35228 | 83 |
[str ".apply(", print_term tyvars is_pat some_thm vars NOBR t, str ")"]) ts23) |
34294 | 84 |
end end |
35228 | 85 |
and print_bind tyvars some_thm fxy p = gen_print_bind (print_term tyvars true) some_thm fxy p |
86 |
and print_case tyvars some_thm vars fxy (cases as ((_, [_]), _)) = |
|
34294 | 87 |
let |
88 |
val (binds, body) = Code_Thingol.unfold_let (ICase cases); |
|
89 |
fun print_match ((pat, ty), t) vars = |
|
90 |
vars |
|
35228 | 91 |
|> print_bind tyvars some_thm BR pat |
34294 | 92 |
|>> (fn p => semicolon [Pretty.block [str "val", Pretty.brk 1, p, |
93 |
str ":", Pretty.brk 1, print_typ tyvars NOBR ty], |
|
35228 | 94 |
str "=", print_term tyvars false some_thm vars NOBR t]) |
34294 | 95 |
val (ps, vars') = fold_map print_match binds vars; |
96 |
in |
|
97 |
brackify_block fxy |
|
98 |
(str "{") |
|
35228 | 99 |
(ps @| print_term tyvars false some_thm vars' NOBR body) |
34294 | 100 |
(str "}") |
101 |
end |
|
35228 | 102 |
| print_case tyvars some_thm vars fxy (((t, ty), clauses as _ :: _), _) = |
34294 | 103 |
let |
104 |
fun print_select (pat, body) = |
|
105 |
let |
|
35228 | 106 |
val (p, vars') = print_bind tyvars some_thm NOBR pat vars; |
107 |
in concat [str "case", p, str "=>", print_term tyvars false some_thm vars' NOBR body] end; |
|
34294 | 108 |
in brackify_block fxy |
35228 | 109 |
(concat [print_term tyvars false some_thm vars NOBR t, str "match", str "{"]) |
34294 | 110 |
(map print_select clauses) |
111 |
(str "}") |
|
112 |
end |
|
35228 | 113 |
| print_case tyvars some_thm vars fxy ((_, []), _) = |
34294 | 114 |
(brackify fxy o Pretty.breaks o map str) ["error(\"empty case\")"]; |
115 |
fun implicit_arguments tyvars vs vars = |
|
116 |
let |
|
117 |
val implicit_typ_ps = maps (fn (v, sort) => map (fn class => Pretty.block |
|
37243
6e2ac5358d6e
capitalized type variables; added yield as keyword
haftmann
parents:
37224
diff
changeset
|
118 |
[(str o deresolve) class, str "[", (str o lookup_tyvar tyvars) v, str "]"]) sort) vs; |
6e2ac5358d6e
capitalized type variables; added yield as keyword
haftmann
parents:
37224
diff
changeset
|
119 |
val implicit_names = Name.variant_list [] (maps (fn (v, sort) => map (fn class => |
6e2ac5358d6e
capitalized type variables; added yield as keyword
haftmann
parents:
37224
diff
changeset
|
120 |
lookup_tyvar tyvars v ^ "_" ^ (Long_Name.base_name o deresolve) class) sort) vs); |
34294 | 121 |
val vars' = intro_vars implicit_names vars; |
122 |
val implicit_ps = map2 (fn v => fn p => concat [str (v ^ ":"), p]) |
|
123 |
implicit_names implicit_typ_ps; |
|
124 |
in ((implicit_names, implicit_ps), vars') end; |
|
125 |
fun print_defhead tyvars vars p vs params tys implicits ty = |
|
37243
6e2ac5358d6e
capitalized type variables; added yield as keyword
haftmann
parents:
37224
diff
changeset
|
126 |
Pretty.block [str "def ", print_typed tyvars (applify "(implicit " ")" NOBR |
34294 | 127 |
(applify "(" ")" NOBR |
37243
6e2ac5358d6e
capitalized type variables; added yield as keyword
haftmann
parents:
37224
diff
changeset
|
128 |
(applify "[" "]" NOBR p (map (str o lookup_tyvar tyvars o fst) vs)) |
34294 | 129 |
(map2 (fn param => fn ty => print_typed tyvars |
130 |
((str o lookup_var vars) param) ty) |
|
37243
6e2ac5358d6e
capitalized type variables; added yield as keyword
haftmann
parents:
37224
diff
changeset
|
131 |
params tys)) implicits) ty, str " ="] |
34294 | 132 |
fun print_stmt (name, Code_Thingol.Fun (_, ((vs, ty), raw_eqs))) = (case filter (snd o snd) raw_eqs |
133 |
of [] => |
|
134 |
let |
|
135 |
val (tys, ty') = Code_Thingol.unfold_fun ty; |
|
136 |
val params = Name.invents (snd reserved) "a" (length tys); |
|
137 |
val tyvars = intro_vars (map fst vs) reserved; |
|
138 |
val vars = intro_vars params reserved; |
|
139 |
in |
|
140 |
concat [print_defhead tyvars vars ((str o deresolve) name) vs params tys [] ty', |
|
141 |
str ("error(\"" ^ name ^ "\")")] |
|
142 |
end |
|
143 |
| eqs => |
|
144 |
let |
|
35228 | 145 |
val tycos = fold (fn ((ts, t), _) => |
34294 | 146 |
fold Code_Thingol.add_tyconames (t :: ts)) eqs []; |
147 |
val tyvars = reserved |
|
148 |
|> intro_base_names |
|
149 |
(is_none o syntax_tyco) deresolve tycos |
|
150 |
|> intro_vars (map fst vs); |
|
151 |
val simple = case eqs |
|
152 |
of [((ts, _), _)] => forall Code_Thingol.is_IVar ts |
|
153 |
| _ => false; |
|
154 |
val consts = fold Code_Thingol.add_constnames |
|
155 |
(map (snd o fst) eqs) []; |
|
156 |
val vars1 = reserved |
|
157 |
|> intro_base_names |
|
158 |
(is_none o syntax_const) deresolve consts |
|
159 |
val ((_, implicit_ps), vars2) = implicit_arguments tyvars vs vars1; |
|
160 |
val params = if simple then (map (fn IVar (SOME x) => x) o fst o fst o hd) eqs |
|
161 |
else aux_params vars2 (map (fst o fst) eqs); |
|
162 |
val vars3 = intro_vars params vars2; |
|
163 |
val (tys, ty1) = Code_Thingol.unfold_fun ty; |
|
164 |
val (tys1, tys2) = chop (length params) tys; |
|
165 |
val ty2 = Library.foldr |
|
166 |
(fn (ty1, ty2) => Code_Thingol.fun_tyco `%% [ty1, ty2]) (tys2, ty1); |
|
167 |
fun print_tuple [p] = p |
|
168 |
| print_tuple ps = enum "," "(" ")" ps; |
|
35228 | 169 |
fun print_rhs vars' ((_, t), (some_thm, _)) = print_term tyvars false some_thm vars' NOBR t; |
170 |
fun print_clause (eq as ((ts, _), (some_thm, _))) = |
|
34294 | 171 |
let |
172 |
val vars' = intro_vars ((fold o Code_Thingol.fold_varnames) (insert (op =)) ts []) vars2; |
|
173 |
in |
|
35228 | 174 |
concat [str "case", print_tuple (map (print_term tyvars true some_thm vars' NOBR) ts), |
34294 | 175 |
str "=>", print_rhs vars' eq] |
176 |
end; |
|
177 |
val head = print_defhead tyvars vars3 ((str o deresolve) name) vs params tys1 implicit_ps ty2; |
|
178 |
in if simple then |
|
179 |
concat [head, print_rhs vars3 (hd eqs)] |
|
180 |
else |
|
181 |
Pretty.block_enclose |
|
182 |
(concat [head, print_tuple (map (str o lookup_var vars3) params), |
|
183 |
str "match", str "{"], str "}") |
|
184 |
(map print_clause eqs) |
|
185 |
end) |
|
186 |
| print_stmt (name, Code_Thingol.Datatype (_, (vs, cos))) = |
|
187 |
let |
|
188 |
val tyvars = intro_vars (map fst vs) reserved; |
|
189 |
fun print_co (co, []) = |
|
190 |
concat [str "final", str "case", str "object", (str o deresolve_base) co, |
|
191 |
str "extends", applify "[" "]" NOBR ((str o deresolve_base) name) |
|
192 |
(replicate (length vs) (str "Nothing"))] |
|
193 |
| print_co (co, tys) = |
|
194 |
let |
|
195 |
val fields = Name.names (snd reserved) "a" tys; |
|
196 |
val vars = intro_vars (map fst fields) reserved; |
|
197 |
fun add_typargs p = applify "[" "]" NOBR p |
|
37243
6e2ac5358d6e
capitalized type variables; added yield as keyword
haftmann
parents:
37224
diff
changeset
|
198 |
(map (str o lookup_tyvar tyvars o fst) vs); |
34294 | 199 |
in |
200 |
concat [ |
|
201 |
applify "(" ")" NOBR |
|
202 |
(add_typargs ((concat o map str) ["final", "case", "class", deresolve_base co])) |
|
203 |
(map (uncurry (print_typed tyvars) o apfst str) fields), |
|
204 |
str "extends", |
|
205 |
add_typargs ((str o deresolve_base) name) |
|
206 |
] |
|
207 |
end |
|
208 |
in |
|
209 |
Pretty.chunks ( |
|
210 |
applify "[" "]" NOBR ((concat o map str) ["sealed", "class", deresolve_base name]) |
|
37243
6e2ac5358d6e
capitalized type variables; added yield as keyword
haftmann
parents:
37224
diff
changeset
|
211 |
(map (str o prefix "+" o lookup_tyvar tyvars o fst) vs) |
34294 | 212 |
:: map print_co cos |
213 |
) |
|
214 |
end |
|
215 |
| print_stmt (name, Code_Thingol.Class (_, (v, (superclasses, classparams)))) = |
|
216 |
let |
|
217 |
val tyvars = intro_vars [v] reserved; |
|
218 |
val vs = [(v, [name])]; |
|
37243
6e2ac5358d6e
capitalized type variables; added yield as keyword
haftmann
parents:
37224
diff
changeset
|
219 |
fun add_typarg p = applify "[" "]" NOBR p [(str o lookup_tyvar tyvars) v]; |
34294 | 220 |
fun print_superclasses [] = NONE |
221 |
| print_superclasses classes = SOME (concat (str "extends" |
|
222 |
:: separate (str "with") (map (add_typarg o str o deresolve o fst) classes))); |
|
223 |
fun print_tupled_typ ([], ty) = |
|
224 |
print_typ tyvars NOBR ty |
|
225 |
| print_tupled_typ ([ty1], ty2) = |
|
226 |
concat [print_typ tyvars BR ty1, str "=>", print_typ tyvars NOBR ty2] |
|
227 |
| print_tupled_typ (tys, ty) = |
|
228 |
concat [enum "," "(" ")" (map (print_typ tyvars NOBR) tys), |
|
229 |
str "=>", print_typ tyvars NOBR ty]; |
|
230 |
fun print_classparam_val (classparam, ty) = |
|
37337 | 231 |
concat [str "val", (str o Library.enclose "`" "+`:" o deresolve_base) classparam, |
34294 | 232 |
(print_tupled_typ o Code_Thingol.unfold_fun) ty] |
233 |
fun print_classparam_def (classparam, ty) = |
|
234 |
let |
|
235 |
val (tys, ty) = Code_Thingol.unfold_fun ty; |
|
236 |
val params = Name.invents (snd reserved) "a" (length tys); |
|
237 |
val vars = intro_vars params reserved; |
|
238 |
val (([implicit], [p_implicit]), vars') = implicit_arguments tyvars vs vars; |
|
239 |
val head = print_defhead tyvars vars' ((str o deresolve) classparam) vs params tys [p_implicit] ty; |
|
240 |
in |
|
241 |
concat [head, applify "(" ")" NOBR |
|
37337 | 242 |
(Pretty.block [str implicit, str ".", (str o Library.enclose "`" "+`" o deresolve_base) classparam]) |
34294 | 243 |
(map (str o lookup_var vars') params)] |
244 |
end; |
|
245 |
in |
|
246 |
Pretty.chunks ( |
|
247 |
(Pretty.block_enclose |
|
248 |
(concat ([str "trait", add_typarg ((str o deresolve_base) name)] |
|
249 |
@ the_list (print_superclasses superclasses) @ [str "{"]), str "}") |
|
250 |
(map print_classparam_val classparams)) |
|
251 |
:: map print_classparam_def classparams |
|
252 |
) |
|
253 |
end |
|
254 |
| print_stmt (name, Code_Thingol.Classinst ((class, (tyco, vs)), |
|
255 |
(super_instances, classparam_insts))) = |
|
256 |
let |
|
257 |
val tyvars = intro_vars (map fst vs) reserved; |
|
258 |
val insttyp = tyco `%% map (ITyVar o fst) vs; |
|
259 |
val p_inst_typ = print_typ tyvars NOBR insttyp; |
|
37243
6e2ac5358d6e
capitalized type variables; added yield as keyword
haftmann
parents:
37224
diff
changeset
|
260 |
fun add_typ_params p = applify "[" "]" NOBR p (map (str o lookup_tyvar tyvars o fst) vs); |
34294 | 261 |
fun add_inst_typ p = Pretty.block [p, str "[", p_inst_typ, str "]"]; |
262 |
val ((implicit_names, implicit_ps), vars) = implicit_arguments tyvars vs reserved; |
|
263 |
fun print_classparam_inst ((classparam, const as (_, (_, tys))), (thm, _)) = |
|
264 |
let |
|
265 |
val auxs = Name.invents (snd reserved) "a" (length tys); |
|
266 |
val vars = intro_vars auxs reserved; |
|
267 |
val args = if null auxs then [] else |
|
268 |
[concat [enum "," "(" ")" (map2 (fn aux => fn ty => print_typed tyvars ((str o lookup_var vars) aux) ty) |
|
269 |
auxs tys), str "=>"]]; |
|
270 |
in |
|
37337 | 271 |
concat ([str "val", (str o Library.enclose "`" "+`" o deresolve_base) classparam, |
35228 | 272 |
str "="] @ args @ [print_app tyvars false (SOME thm) vars NOBR (const, map (IVar o SOME) auxs)]) |
34294 | 273 |
end; |
274 |
in |
|
275 |
Pretty.chunks [ |
|
276 |
Pretty.block_enclose |
|
277 |
(concat ([str "trait", |
|
278 |
add_typ_params ((str o deresolve_base) name), |
|
279 |
str "extends", |
|
280 |
Pretty.block [(str o deresolve) class, str "[", p_inst_typ, str "]"]] |
|
281 |
@ map (fn (_, (_, (superinst, _))) => add_typ_params (str ("with " ^ deresolve superinst))) |
|
282 |
super_instances @| str "{"), str "}") |
|
283 |
(map (fn p => Pretty.block [str "implicit val arg$", p]) implicit_ps |
|
284 |
@ map print_classparam_inst classparam_insts), |
|
285 |
concat [str "implicit", str (if null vs then "val" else "def"), |
|
286 |
applify "(implicit " ")" NOBR (applify "[" "]" NOBR |
|
37243
6e2ac5358d6e
capitalized type variables; added yield as keyword
haftmann
parents:
37224
diff
changeset
|
287 |
((str o deresolve_base) name) (map (str o lookup_tyvar tyvars o fst) vs)) |
34294 | 288 |
implicit_ps, |
289 |
str "=", str "new", applify "[" "]" NOBR ((str o deresolve_base) name) |
|
37243
6e2ac5358d6e
capitalized type variables; added yield as keyword
haftmann
parents:
37224
diff
changeset
|
290 |
(map (str o lookup_tyvar tyvars o fst) vs), |
34294 | 291 |
Pretty.enum ";" "{ " " }" (map (str o (fn v => "val arg$" ^ v ^ " = " ^ v) o lookup_var vars) |
292 |
implicit_names)] |
|
293 |
] |
|
294 |
end; |
|
295 |
in print_stmt end; |
|
296 |
||
297 |
fun scala_program_of_program labelled_name module_name reserved raw_module_alias program = |
|
298 |
let |
|
299 |
val the_module_name = the_default "Program" module_name; |
|
300 |
val module_alias = K (SOME the_module_name); |
|
301 |
val reserved = Name.make_context reserved; |
|
302 |
fun prepare_stmt (name, stmt) (nsps, stmts) = |
|
303 |
let |
|
304 |
val (_, base) = Code_Printer.dest_name name; |
|
305 |
val mk_name_stmt = yield_singleton Name.variants; |
|
306 |
fun add_class ((nsp_class, nsp_object), nsp_common) = |
|
307 |
let |
|
308 |
val (base', nsp_class') = mk_name_stmt base nsp_class |
|
309 |
in (base', ((nsp_class', nsp_object), Name.declare base' nsp_common)) end; |
|
310 |
fun add_object ((nsp_class, nsp_object), nsp_common) = |
|
311 |
let |
|
312 |
val (base', nsp_object') = mk_name_stmt base nsp_object |
|
313 |
in (base', ((nsp_class, nsp_object'), Name.declare base' nsp_common)) end; |
|
314 |
fun add_common upper ((nsp_class, nsp_object), nsp_common) = |
|
315 |
let |
|
316 |
val (base', nsp_common') = |
|
317 |
mk_name_stmt (if upper then first_upper base else base) nsp_common |
|
318 |
in (base', ((Name.declare base' nsp_class, Name.declare base' nsp_object), nsp_common')) end; |
|
319 |
val add_name = case stmt |
|
320 |
of Code_Thingol.Fun _ => add_object |
|
321 |
| Code_Thingol.Datatype _ => add_class |
|
322 |
| Code_Thingol.Datatypecons _ => add_common true |
|
323 |
| Code_Thingol.Class _ => add_class |
|
324 |
| Code_Thingol.Classrel _ => add_object |
|
325 |
| Code_Thingol.Classparam _ => add_object |
|
326 |
| Code_Thingol.Classinst _ => add_common false; |
|
327 |
fun add_stmt base' = case stmt |
|
328 |
of Code_Thingol.Datatypecons _ => cons (name, (base', NONE)) |
|
329 |
| Code_Thingol.Classrel _ => cons (name, (base', NONE)) |
|
330 |
| Code_Thingol.Classparam _ => cons (name, (base', NONE)) |
|
331 |
| _ => cons (name, (base', SOME stmt)); |
|
332 |
in |
|
333 |
nsps |
|
334 |
|> add_name |
|
335 |
|-> (fn base' => rpair (add_stmt base' stmts)) |
|
336 |
end; |
|
337 |
val (_, sca_program) = fold prepare_stmt (AList.make (fn name => Graph.get_node program name) |
|
338 |
(Graph.strong_conn program |> flat)) (((reserved, reserved), reserved), []); |
|
339 |
fun deresolver name = (fst o the o AList.lookup (op =) sca_program) name |
|
340 |
handle Option => error ("Unknown statement name: " ^ labelled_name name); |
|
341 |
in (deresolver, (the_module_name, sca_program)) end; |
|
342 |
||
343 |
fun serialize_scala raw_module_name labelled_name |
|
344 |
raw_reserved includes raw_module_alias |
|
36535 | 345 |
_ syntax_tyco syntax_const (code_of_pretty, code_writeln) program stmt_names destination = |
34294 | 346 |
let |
36535 | 347 |
val presentation_stmt_names = Code_Target.stmt_names_of_destination destination; |
348 |
val module_name = if null presentation_stmt_names then raw_module_name else SOME "Code"; |
|
34294 | 349 |
val reserved = fold (insert (op =) o fst) includes raw_reserved; |
350 |
val (deresolver, (the_module_name, sca_program)) = scala_program_of_program labelled_name |
|
351 |
module_name reserved raw_module_alias program; |
|
352 |
val reserved = make_vars reserved; |
|
353 |
fun args_num c = case Graph.get_node program c |
|
354 |
of Code_Thingol.Fun (_, ((_, ty), [])) => (length o fst o Code_Thingol.unfold_fun) ty |
|
355 |
| Code_Thingol.Fun (_, (_, ((ts, _), _) :: _)) => length ts |
|
356 |
| Code_Thingol.Datatypecons (_, tyco) => |
|
35228 | 357 |
let val Code_Thingol.Datatype (_, (_, constrs)) = Graph.get_node program tyco |
358 |
in (length o the o AList.lookup (op =) constrs) c end |
|
34294 | 359 |
| Code_Thingol.Classparam (_, class) => |
360 |
let val Code_Thingol.Class (_, (_, (_, classparams))) = Graph.get_node program class |
|
361 |
in (length o fst o Code_Thingol.unfold_fun o the o AList.lookup (op =) classparams) c end; |
|
362 |
fun is_singleton c = case Graph.get_node program c |
|
363 |
of Code_Thingol.Datatypecons (_, tyco) => |
|
35228 | 364 |
let val Code_Thingol.Datatype (_, (_, constrs)) = Graph.get_node program tyco |
365 |
in (null o the o AList.lookup (op =) constrs) c end |
|
34294 | 366 |
| _ => false; |
367 |
val print_stmt = print_scala_stmt labelled_name syntax_tyco syntax_const |
|
368 |
reserved args_num is_singleton deresolver; |
|
369 |
fun print_module name content = |
|
370 |
(name, Pretty.chunks [ |
|
371 |
str ("object " ^ name ^ " {"), |
|
372 |
str "", |
|
373 |
content, |
|
374 |
str "", |
|
375 |
str "}" |
|
376 |
]); |
|
377 |
fun serialize_module the_module_name sca_program = |
|
378 |
let |
|
379 |
val content = Pretty.chunks2 (map_filter |
|
380 |
(fn (name, (_, SOME stmt)) => SOME (print_stmt (name, stmt)) |
|
381 |
| (_, (_, NONE)) => NONE) sca_program); |
|
382 |
in print_module the_module_name content end; |
|
383 |
fun check_destination destination = |
|
384 |
(File.check destination; destination); |
|
385 |
fun write_module destination (modlname, content) = |
|
386 |
let |
|
387 |
val filename = case modlname |
|
388 |
of "" => Path.explode "Main.scala" |
|
389 |
| _ => (Path.ext "scala" o Path.explode o implode o separate "/" |
|
390 |
o Long_Name.explode) modlname; |
|
391 |
val pathname = Path.append destination filename; |
|
392 |
val _ = File.mkdir (Path.dir pathname); |
|
393 |
in File.write pathname (code_of_pretty content) end |
|
394 |
in |
|
395 |
Code_Target.mk_serialization target NONE |
|
396 |
(fn NONE => K () o map (code_writeln o snd) | SOME file => K () o map |
|
397 |
(write_module (check_destination file))) |
|
398 |
(rpair [] o cat_lines o map (code_of_pretty o snd)) |
|
399 |
(map (uncurry print_module) includes |
|
400 |
@| serialize_module the_module_name sca_program) |
|
401 |
destination |
|
402 |
end; |
|
403 |
||
404 |
val literals = let |
|
37224 | 405 |
fun char_scala c = if c = "'" then "\\'" |
406 |
else if c = "\"" then "\\\"" |
|
407 |
else if c = "\\" then "\\\\" |
|
408 |
else let val k = ord c |
|
409 |
in if k < 32 orelse k > 126 then "\\" ^ radixstring (8, "0", k) else c end |
|
34944
970e1466028d
code literals: distinguish numeral classes by different entries
haftmann
parents:
34900
diff
changeset
|
410 |
fun numeral_scala k = if k < 0 |
970e1466028d
code literals: distinguish numeral classes by different entries
haftmann
parents:
34900
diff
changeset
|
411 |
then if k <= 2147483647 then "- " ^ string_of_int (~ k) |
970e1466028d
code literals: distinguish numeral classes by different entries
haftmann
parents:
34900
diff
changeset
|
412 |
else quote ("- " ^ string_of_int (~ k)) |
970e1466028d
code literals: distinguish numeral classes by different entries
haftmann
parents:
34900
diff
changeset
|
413 |
else if k <= 2147483647 then string_of_int k |
970e1466028d
code literals: distinguish numeral classes by different entries
haftmann
parents:
34900
diff
changeset
|
414 |
else quote (string_of_int k) |
34294 | 415 |
in Literals { |
416 |
literal_char = Library.enclose "'" "'" o char_scala, |
|
417 |
literal_string = quote o translate_string char_scala, |
|
34944
970e1466028d
code literals: distinguish numeral classes by different entries
haftmann
parents:
34900
diff
changeset
|
418 |
literal_numeral = fn k => "BigInt(" ^ numeral_scala k ^ ")", |
970e1466028d
code literals: distinguish numeral classes by different entries
haftmann
parents:
34900
diff
changeset
|
419 |
literal_positive_numeral = fn k => "Nat.Nat(" ^ numeral_scala k ^ ")", |
970e1466028d
code literals: distinguish numeral classes by different entries
haftmann
parents:
34900
diff
changeset
|
420 |
literal_naive_numeral = fn k => if k >= 0 |
970e1466028d
code literals: distinguish numeral classes by different entries
haftmann
parents:
34900
diff
changeset
|
421 |
then string_of_int k else "(- " ^ string_of_int (~ k) ^ ")", |
34888 | 422 |
literal_list = fn [] => str "Nil" | ps => Pretty.block [str "List", enum "," "(" ")" ps], |
34294 | 423 |
infix_cons = (6, "::") |
424 |
} end; |
|
425 |
||
426 |
||
427 |
(** Isar setup **) |
|
428 |
||
429 |
fun isar_seri_scala module_name = |
|
430 |
Code_Target.parse_args (Scan.succeed ()) |
|
431 |
#> (fn () => serialize_scala module_name); |
|
432 |
||
433 |
val setup = |
|
434 |
Code_Target.add_target (target, (isar_seri_scala, literals)) |
|
435 |
#> Code_Target.add_syntax_tyco target "fun" (SOME (2, fn print_typ => fn fxy => fn [ty1, ty2] => |
|
37243
6e2ac5358d6e
capitalized type variables; added yield as keyword
haftmann
parents:
37224
diff
changeset
|
436 |
brackify_infix (1, R) fxy ( |
34900 | 437 |
print_typ BR ty1 (*product type vs. tupled arguments!*), |
34294 | 438 |
str "=>", |
439 |
print_typ (INFX (1, R)) ty2 |
|
37243
6e2ac5358d6e
capitalized type variables; added yield as keyword
haftmann
parents:
37224
diff
changeset
|
440 |
))) |
34294 | 441 |
#> fold (Code_Target.add_reserved target) [ |
442 |
"abstract", "case", "catch", "class", "def", "do", "else", "extends", "false", |
|
443 |
"final", "finally", "for", "forSome", "if", "implicit", "import", "lazy", |
|
444 |
"match", "new", "null", "object", "override", "package", "private", "protected", |
|
445 |
"requires", "return", "sealed", "super", "this", "throw", "trait", "try", |
|
37243
6e2ac5358d6e
capitalized type variables; added yield as keyword
haftmann
parents:
37224
diff
changeset
|
446 |
"true", "type", "val", "var", "while", "with", "yield" |
34294 | 447 |
] |
448 |
#> fold (Code_Target.add_reserved target) [ |
|
34944
970e1466028d
code literals: distinguish numeral classes by different entries
haftmann
parents:
34900
diff
changeset
|
449 |
"error", "apply", "List", "Nil", "BigInt" |
34294 | 450 |
]; |
451 |
||
452 |
end; (*struct*) |