author | wenzelm |
Fri, 06 Jan 2006 18:18:13 +0100 | |
changeset 18595 | a52907967bae |
parent 18517 | 788fa99aba33 |
child 18702 | 7dc7dcd63224 |
permissions | -rw-r--r-- |
18169
45def66f86cb
added modules for code generator generation two, not operational yet
haftmann
parents:
diff
changeset
|
1 |
(* Title: Pure/Tools/codegen_package.ML |
45def66f86cb
added modules for code generator generation two, not operational yet
haftmann
parents:
diff
changeset
|
2 |
ID: $Id$ |
45def66f86cb
added modules for code generator generation two, not operational yet
haftmann
parents:
diff
changeset
|
3 |
Author: Florian Haftmann, TU Muenchen |
45def66f86cb
added modules for code generator generation two, not operational yet
haftmann
parents:
diff
changeset
|
4 |
|
18217 | 5 |
Code generator from Isabelle theories to |
18169
45def66f86cb
added modules for code generator generation two, not operational yet
haftmann
parents:
diff
changeset
|
6 |
intermediate language ("Thin-gol"). |
45def66f86cb
added modules for code generator generation two, not operational yet
haftmann
parents:
diff
changeset
|
7 |
*) |
45def66f86cb
added modules for code generator generation two, not operational yet
haftmann
parents:
diff
changeset
|
8 |
|
18282 | 9 |
(*NOTE: for simplifying developement, this package contains |
18169
45def66f86cb
added modules for code generator generation two, not operational yet
haftmann
parents:
diff
changeset
|
10 |
some stuff which will finally be moved upwards to HOL*) |
45def66f86cb
added modules for code generator generation two, not operational yet
haftmann
parents:
diff
changeset
|
11 |
|
45def66f86cb
added modules for code generator generation two, not operational yet
haftmann
parents:
diff
changeset
|
12 |
signature CODEGEN_PACKAGE = |
45def66f86cb
added modules for code generator generation two, not operational yet
haftmann
parents:
diff
changeset
|
13 |
sig |
18454 | 14 |
type auxtab; |
18335 | 15 |
type appgen; |
18217 | 16 |
type defgen; |
18516 | 17 |
val add_appconst: string * ((int * int) * appgen) -> theory -> theory; |
18517 | 18 |
val add_appconst_i: xstring * ((int * int) * appgen) -> theory -> theory; |
18217 | 19 |
val add_defgen: string * defgen -> theory -> theory; |
18517 | 20 |
val add_prim_class: xstring -> string list -> (string * string) |
21 |
-> theory -> theory; |
|
22 |
val add_prim_tyco: xstring -> string list -> (string * string) |
|
23 |
-> theory -> theory; |
|
24 |
val add_prim_const: xstring * string option -> string list -> (string * string) |
|
25 |
-> theory -> theory; |
|
26 |
val add_prim_i: string -> string list -> (string * Pretty.T) |
|
27 |
-> theory -> theory; |
|
28 |
val add_syntax_tyco: xstring -> (string * (string * CodegenSerializer.fixity)) |
|
29 |
-> theory -> theory; |
|
30 |
val add_syntax_tyco_i: string -> (string * (CodegenThingol.itype Codegen.mixfix list * CodegenSerializer.fixity)) |
|
31 |
-> theory -> theory; |
|
32 |
val add_syntax_const: (xstring * string option) -> (string * (string * CodegenSerializer.fixity)) |
|
33 |
-> theory -> theory; |
|
34 |
val add_syntax_const_i: string -> (string * (CodegenThingol.iexpr Codegen.mixfix list * CodegenSerializer.fixity)) |
|
35 |
-> theory -> theory; |
|
18217 | 36 |
val add_lookup_tyco: string * string -> theory -> theory; |
37 |
val add_lookup_const: (string * typ) * CodegenThingol.iexpr -> theory -> theory; |
|
38 |
val add_alias: string * string -> theory -> theory; |
|
39 |
val set_is_datatype: (theory -> string -> bool) -> theory -> theory; |
|
18455 | 40 |
val set_get_all_datatype_cons : (theory -> (string * string) list) |
18454 | 41 |
-> theory -> theory; |
18217 | 42 |
|
18516 | 43 |
val exprgen_type: theory -> auxtab |
18217 | 44 |
-> typ -> CodegenThingol.transact -> CodegenThingol.itype * CodegenThingol.transact; |
18516 | 45 |
val exprgen_term: theory -> auxtab |
18217 | 46 |
-> term -> CodegenThingol.transact -> CodegenThingol.iexpr * CodegenThingol.transact; |
18454 | 47 |
val ensure_def_tyco: theory -> auxtab |
18217 | 48 |
-> string -> CodegenThingol.transact -> string * CodegenThingol.transact; |
18454 | 49 |
val ensure_def_const: theory -> auxtab |
50 |
-> string * typ -> CodegenThingol.transact -> string * CodegenThingol.transact; |
|
18217 | 51 |
|
18335 | 52 |
val appgen_let: (int -> term -> term list * term) |
53 |
-> appgen; |
|
54 |
val appgen_split: (int -> term -> term list * term) |
|
55 |
-> appgen; |
|
56 |
val appgen_number_of: (term -> IntInf.int) -> (term -> term) |
|
57 |
-> appgen; |
|
18517 | 58 |
val appgen_datatype_case: (string * int) list |
18335 | 59 |
-> appgen; |
18517 | 60 |
val add_cg_case_const: (theory -> string -> (string * int) list option) -> xstring |
61 |
-> theory -> theory; |
|
62 |
val add_cg_case_const_i: (theory -> string -> (string * int) list option) -> string |
|
63 |
-> theory -> theory; |
|
18380
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
64 |
val defgen_datatype: (theory -> string -> ((string * sort) list * string list) option) |
18335 | 65 |
-> (theory -> string * string -> typ list option) |
18217 | 66 |
-> defgen; |
67 |
val defgen_datacons: (theory -> string * string -> typ list option) |
|
68 |
-> defgen; |
|
69 |
val defgen_recfun: (theory -> string * typ -> (term list * term) list * typ) |
|
70 |
-> defgen; |
|
71 |
||
18247
b17724cae935
code generator: case expressions, improved name resolving
haftmann
parents:
18231
diff
changeset
|
72 |
val print_codegen_generated: theory -> unit; |
18454 | 73 |
val rename_inconsistent: theory -> theory; |
18517 | 74 |
val ensure_datatype_case_consts: (theory -> string list) |
75 |
-> (theory -> string -> (string * int) list option) |
|
76 |
-> theory -> theory; |
|
18515 | 77 |
|
78 |
(*debugging purpose only*) |
|
18454 | 79 |
structure InstNameMangler: NAME_MANGLER; |
80 |
structure ConstNameMangler: NAME_MANGLER; |
|
81 |
structure DatatypeconsNameMangler: NAME_MANGLER; |
|
18231 | 82 |
structure CodegenData: THEORY_DATA; |
18454 | 83 |
val mk_tabs: theory -> auxtab; |
84 |
val alias_get: theory -> string -> string; |
|
18515 | 85 |
val idf_of_name: theory -> string -> string -> string; |
86 |
val idf_of_const: theory -> auxtab -> string * typ -> string; |
|
18169
45def66f86cb
added modules for code generator generation two, not operational yet
haftmann
parents:
diff
changeset
|
87 |
end; |
45def66f86cb
added modules for code generator generation two, not operational yet
haftmann
parents:
diff
changeset
|
88 |
|
18217 | 89 |
structure CodegenPackage : CODEGEN_PACKAGE = |
18169
45def66f86cb
added modules for code generator generation two, not operational yet
haftmann
parents:
diff
changeset
|
90 |
struct |
45def66f86cb
added modules for code generator generation two, not operational yet
haftmann
parents:
diff
changeset
|
91 |
|
18385 | 92 |
open CodegenThingolOp; |
93 |
infix 8 `%%; |
|
94 |
infixr 6 `->; |
|
95 |
infixr 6 `-->; |
|
96 |
infix 4 `$; |
|
97 |
infix 4 `$$; |
|
98 |
infixr 5 `|->; |
|
99 |
infixr 5 `|-->; |
|
18217 | 100 |
|
101 |
(* auxiliary *) |
|
102 |
||
18454 | 103 |
fun devarify_type ty = (fst o Type.freeze_thaw_type) ty; |
18335 | 104 |
fun devarify_term t = (fst o Type.freeze_thaw) t; |
18454 | 105 |
|
106 |
val is_number = is_some o Int.fromString; |
|
18217 | 107 |
|
18361 | 108 |
fun newline_correct s = |
109 |
s |
|
110 |
|> space_explode "\n" |
|
111 |
|> map (implode o (fn [] => [] |
|
112 |
| (" "::xs) => xs |
|
113 |
| xs => xs) o explode) |
|
114 |
|> space_implode "\n"; |
|
18217 | 115 |
|
116 |
||
18454 | 117 |
(* shallo name spaces *) |
18217 | 118 |
|
119 |
val nsp_class = "class"; |
|
18454 | 120 |
val nsp_tyco = "tyco"; |
18217 | 121 |
val nsp_const = "const"; |
18454 | 122 |
val nsp_overl = "overl"; |
123 |
val nsp_dtcon = "dtcon"; |
|
18217 | 124 |
val nsp_mem = "mem"; |
125 |
val nsp_inst = "inst"; |
|
18385 | 126 |
val nsp_eq_inst = "eq_inst"; |
127 |
val nsp_eq_pred = "eq"; |
|
18217 | 128 |
|
129 |
||
18454 | 130 |
(* code generator data types *) |
131 |
||
132 |
structure InstNameMangler = NameManglerFun ( |
|
133 |
type ctxt = theory; |
|
134 |
type src = string * (class * string); |
|
135 |
val ord = prod_ord string_ord (prod_ord string_ord string_ord); |
|
136 |
fun mk thy ((thyname, (cls, tyco)), i) = |
|
137 |
NameSpace.base cls ^ "_" ^ NameSpace.base tyco ^ implode (replicate i "'") |
|
138 |
|> NameSpace.append thyname; |
|
139 |
fun is_valid _ _ = true; |
|
140 |
fun maybe_unique _ _ = NONE; |
|
141 |
fun re_mangle _ dst = error ("no such instance: " ^ quote dst); |
|
142 |
); |
|
143 |
||
144 |
structure ConstNameMangler = NameManglerFun ( |
|
145 |
type ctxt = theory; |
|
146 |
type src = string * (typ * typ); |
|
147 |
val ord = prod_ord string_ord (prod_ord Term.typ_ord Term.typ_ord); |
|
148 |
fun mk thy ((c, (ty_decl, ty)), i) = |
|
149 |
let |
|
150 |
fun mangle (Type (tyco, tys)) = |
|
151 |
NameSpace.base tyco :: Library.flat (List.mapPartial mangle tys) |> SOME |
|
152 |
| mangle _ = |
|
153 |
NONE |
|
154 |
in |
|
155 |
Vartab.empty |
|
156 |
|> Sign.typ_match thy (ty_decl, ty) |
|
157 |
|> map (snd o snd) o Vartab.dest |
|
158 |
|> List.mapPartial mangle |
|
159 |
|> Library.flat |
|
160 |
|> null ? K ["x"] |
|
161 |
|> cons c |
|
162 |
|> space_implode "_" |
|
163 |
|> curry (op ^ o swap) ((implode oo replicate) i "'") |
|
164 |
end; |
|
165 |
fun is_valid _ _ = true; |
|
166 |
fun maybe_unique _ _ = NONE; |
|
167 |
fun re_mangle _ dst = error ("no such constant: " ^ quote dst); |
|
168 |
); |
|
169 |
||
170 |
structure DatatypeconsNameMangler = NameManglerFun ( |
|
171 |
type ctxt = theory; |
|
172 |
type src = string * string; |
|
173 |
val ord = prod_ord string_ord string_ord; |
|
174 |
fun mk thy (("0", "nat"), _) = |
|
175 |
"Nat.Zero" |
|
176 |
| mk thy ((co, dtco), i) = |
|
177 |
let |
|
178 |
fun basename 0 = NameSpace.base co |
|
18455 | 179 |
| basename 1 = NameSpace.base dtco ^ "_" ^ NameSpace.base co |
18454 | 180 |
| basename i = NameSpace.base dtco ^ "_" ^ NameSpace.base co ^ "_" ^ (implode oo replicate) (i-1) "'"; |
181 |
fun strip_dtco name = |
|
182 |
case (rev o NameSpace.unpack) name |
|
183 |
of x1::x2::xs => |
|
184 |
if x2 = NameSpace.base dtco |
|
185 |
then NameSpace.pack (x1::xs) |
|
186 |
else name |
|
187 |
| _ => name; |
|
188 |
in |
|
189 |
NameSpace.append (NameSpace.drop_base dtco) (basename i) |
|
190 |
|> strip_dtco |
|
191 |
end; |
|
192 |
fun is_valid _ _ = true; |
|
193 |
fun maybe_unique _ _ = NONE; |
|
194 |
fun re_mangle _ dst = error ("no such datatype constructor: " ^ quote dst); |
|
195 |
); |
|
196 |
||
197 |
type auxtab = ((typ * (term list * term)) Symtab.table * string Symtab.table) |
|
198 |
* (InstNameMangler.T * ((typ * typ list) Symtab.table * ConstNameMangler.T) * DatatypeconsNameMangler.T); |
|
199 |
||
200 |
type appgen = theory -> auxtab -> ((string * typ) * term list, iexpr) gen_exprgen; |
|
201 |
type defgen = theory -> auxtab -> gen_defgen; |
|
202 |
||
203 |
||
18217 | 204 |
(* serializer *) |
205 |
||
206 |
val serializer_ml = |
|
207 |
let |
|
18247
b17724cae935
code generator: case expressions, improved name resolving
haftmann
parents:
18231
diff
changeset
|
208 |
val name_root = "Generated"; |
18282 | 209 |
val nsp_conn = [ |
18454 | 210 |
[nsp_class, nsp_tyco], [nsp_const, nsp_overl, nsp_dtcon, nsp_mem, nsp_inst, nsp_eq_inst, nsp_eq_pred] |
18217 | 211 |
]; |
18516 | 212 |
in CodegenSerializer.ml_from_thingol nsp_conn nsp_class name_root end; |
18217 | 213 |
|
18282 | 214 |
val serializer_hs = |
215 |
let |
|
216 |
val name_root = "Generated"; |
|
217 |
val nsp_conn = [ |
|
18454 | 218 |
[nsp_class], [nsp_tyco], [nsp_const, nsp_overl, nsp_mem, nsp_eq_pred], [nsp_dtcon], [nsp_inst, nsp_eq_inst] |
18282 | 219 |
]; |
18516 | 220 |
in CodegenSerializer.haskell_from_thingol nsp_conn nsp_dtcon name_root end; |
18217 | 221 |
|
222 |
||
18454 | 223 |
(* theory data for code generator *) |
18217 | 224 |
|
225 |
type gens = { |
|
18516 | 226 |
appconst: ((int * int) * (appgen * stamp)) Symtab.table, |
18217 | 227 |
defgens: (string * (defgen * stamp)) list |
228 |
}; |
|
229 |
||
18517 | 230 |
fun map_gens f { appconst, defgens } = |
18217 | 231 |
let |
18517 | 232 |
val (appconst, defgens) = |
233 |
f (appconst, defgens) |
|
234 |
in { appconst = appconst, defgens = defgens } : gens end; |
|
18217 | 235 |
|
236 |
fun merge_gens |
|
18517 | 237 |
({ appconst = appconst1 , defgens = defgens1 }, |
238 |
{ appconst = appconst2 , defgens = defgens2 }) = |
|
18516 | 239 |
{ appconst = Symtab.merge |
240 |
(fn ((bounds1, (_, stamp1)), (bounds2, (_, stamp2))) => bounds1 = bounds2 andalso stamp1 = stamp2) |
|
241 |
(appconst1, appconst2), |
|
18304 | 242 |
defgens = AList.merge (op =) (eq_snd (op =)) (defgens1, defgens2) } : gens; |
18217 | 243 |
|
244 |
type lookups = { |
|
245 |
lookups_tyco: string Symtab.table, |
|
246 |
lookups_const: (typ * iexpr) list Symtab.table |
|
247 |
} |
|
248 |
||
249 |
fun map_lookups f { lookups_tyco, lookups_const } = |
|
250 |
let |
|
251 |
val (lookups_tyco, lookups_const) = |
|
252 |
f (lookups_tyco, lookups_const) |
|
18454 | 253 |
in { lookups_tyco = lookups_tyco, lookups_const = lookups_const } : lookups end; |
18217 | 254 |
|
255 |
fun merge_lookups |
|
256 |
({ lookups_tyco = lookups_tyco1, lookups_const = lookups_const1 }, |
|
257 |
{ lookups_tyco = lookups_tyco2, lookups_const = lookups_const2 }) = |
|
258 |
{ lookups_tyco = Symtab.merge (op =) (lookups_tyco1, lookups_tyco2), |
|
18304 | 259 |
lookups_const = Symtab.merge (op =) (lookups_const1, lookups_const2) } : lookups; |
18217 | 260 |
|
261 |
type logic_data = { |
|
262 |
is_datatype: ((theory -> string -> bool) * stamp) option, |
|
18455 | 263 |
get_all_datatype_cons: ((theory -> (string * string) list) * stamp) option, |
18217 | 264 |
alias: string Symtab.table * string Symtab.table |
265 |
}; |
|
266 |
||
18454 | 267 |
fun map_logic_data f { is_datatype, get_all_datatype_cons, alias } = |
18217 | 268 |
let |
18454 | 269 |
val ((is_datatype, get_all_datatype_cons), alias) = |
270 |
f ((is_datatype, get_all_datatype_cons), alias) |
|
271 |
in { is_datatype = is_datatype, get_all_datatype_cons = get_all_datatype_cons, alias = alias } : logic_data end; |
|
18217 | 272 |
|
273 |
fun merge_logic_data |
|
18454 | 274 |
({ is_datatype = is_datatype1, get_all_datatype_cons = get_all_datatype_cons1, alias = alias1 }, |
275 |
{ is_datatype = is_datatype2, get_all_datatype_cons = get_all_datatype_cons2, alias = alias2 }) = |
|
18217 | 276 |
let |
277 |
fun merge_opt _ (x1, NONE) = x1 |
|
278 |
| merge_opt _ (NONE, x2) = x2 |
|
279 |
| merge_opt eq (SOME x1, SOME x2) = |
|
280 |
if eq (x1, x2) then SOME x1 else error ("incompatible options during merge"); |
|
281 |
in |
|
282 |
{ is_datatype = merge_opt (eq_snd (op =)) (is_datatype1, is_datatype2), |
|
18454 | 283 |
get_all_datatype_cons = merge_opt (eq_snd (op =)) (get_all_datatype_cons1, get_all_datatype_cons2), |
18217 | 284 |
alias = (Symtab.merge (op =) (fst alias1, fst alias2), |
18304 | 285 |
Symtab.merge (op =) (snd alias1, snd alias2)) } : logic_data |
18217 | 286 |
end; |
287 |
||
288 |
type serialize_data = { |
|
289 |
serializer: CodegenSerializer.serializer, |
|
18516 | 290 |
syntax_tyco: (itype CodegenSerializer.pretty_syntax * stamp) Symtab.table, |
291 |
syntax_const: (iexpr CodegenSerializer.pretty_syntax * stamp) Symtab.table |
|
18217 | 292 |
}; |
293 |
||
18517 | 294 |
fun map_serialize_data f { serializer, syntax_tyco, syntax_const } = |
18217 | 295 |
let |
18517 | 296 |
val (syntax_tyco, syntax_const) = |
297 |
f (syntax_tyco, syntax_const) |
|
298 |
in { serializer = serializer, |
|
18454 | 299 |
syntax_tyco = syntax_tyco, syntax_const = syntax_const } : serialize_data |
300 |
end; |
|
18217 | 301 |
|
302 |
fun merge_serialize_data |
|
18517 | 303 |
({ serializer = serializer, |
18217 | 304 |
syntax_tyco = syntax_tyco1, syntax_const = syntax_const1 }, |
18517 | 305 |
{serializer = _, |
18217 | 306 |
syntax_tyco = syntax_tyco2, syntax_const = syntax_const2 }) = |
307 |
{ serializer = serializer, |
|
18516 | 308 |
syntax_tyco = Symtab.merge (eq_snd (op =)) (syntax_tyco1, syntax_tyco2), |
309 |
syntax_const = Symtab.merge (eq_snd (op =)) (syntax_const1, syntax_const2) } : serialize_data; |
|
18217 | 310 |
|
311 |
structure CodegenData = TheoryDataFun |
|
312 |
(struct |
|
313 |
val name = "Pure/codegen_package"; |
|
314 |
type T = { |
|
315 |
modl: module, |
|
316 |
gens: gens, |
|
317 |
lookups: lookups, |
|
318 |
logic_data: logic_data, |
|
319 |
serialize_data: serialize_data Symtab.table |
|
320 |
}; |
|
321 |
val empty = { |
|
322 |
modl = empty_module, |
|
18517 | 323 |
gens = { appconst = Symtab.empty, defgens = [] } : gens, |
18217 | 324 |
lookups = { lookups_tyco = Symtab.empty, lookups_const = Symtab.empty } : lookups, |
18454 | 325 |
logic_data = { is_datatype = NONE, get_all_datatype_cons = NONE, |
326 |
alias = (Symtab.empty, Symtab.empty) } : logic_data, |
|
18217 | 327 |
serialize_data = |
328 |
Symtab.empty |
|
329 |
|> Symtab.update ("ml", |
|
18231 | 330 |
{ serializer = serializer_ml : CodegenSerializer.serializer, |
18217 | 331 |
syntax_tyco = Symtab.empty, syntax_const = Symtab.empty }) |
332 |
|> Symtab.update ("haskell", |
|
18335 | 333 |
{ serializer = serializer_hs : CodegenSerializer.serializer, |
18217 | 334 |
syntax_tyco = Symtab.empty, syntax_const = Symtab.empty }) |
335 |
} : T; |
|
336 |
val copy = I; |
|
337 |
val extend = I; |
|
338 |
fun merge _ ( |
|
339 |
{ modl = modl1, gens = gens1, lookups = lookups1, |
|
340 |
serialize_data = serialize_data1, logic_data = logic_data1 }, |
|
341 |
{ modl = modl2, gens = gens2, lookups = lookups2, |
|
342 |
serialize_data = serialize_data2, logic_data = logic_data2 } |
|
343 |
) = { |
|
344 |
modl = merge_module (modl1, modl2), |
|
345 |
gens = merge_gens (gens1, gens2), |
|
346 |
lookups = merge_lookups (lookups1, lookups2), |
|
347 |
logic_data = merge_logic_data (logic_data1, logic_data2), |
|
348 |
serialize_data = Symtab.join (K (merge_serialize_data #> SOME)) |
|
349 |
(serialize_data1, serialize_data2) |
|
350 |
}; |
|
351 |
fun print thy _ = writeln "sorry, this stuff is too complicated..."; |
|
352 |
end); |
|
353 |
||
354 |
fun map_codegen_data f thy = |
|
355 |
case CodegenData.get thy |
|
356 |
of { modl, gens, lookups, serialize_data, logic_data } => |
|
357 |
let val (modl, gens, lookups, serialize_data, logic_data) = |
|
358 |
f (modl, gens, lookups, serialize_data, logic_data) |
|
359 |
in CodegenData.put { modl = modl, gens = gens, lookups = lookups, |
|
360 |
serialize_data = serialize_data, logic_data = logic_data } thy end; |
|
361 |
||
18517 | 362 |
fun print_codegen_generated thy = |
363 |
let |
|
364 |
val module = (#modl o CodegenData.get) thy; |
|
365 |
in |
|
366 |
(writeln o Pretty.output o Pretty.chunks) [pretty_module module, pretty_deps module] |
|
367 |
end; |
|
18217 | 368 |
|
18516 | 369 |
fun gen_add_appconst prep_const (raw_c, (bounds, ag)) thy = |
370 |
let |
|
371 |
val c = prep_const thy raw_c; |
|
372 |
in map_codegen_data |
|
18217 | 373 |
(fn (modl, gens, lookups, serialize_data, logic_data) => |
374 |
(modl, |
|
375 |
gens |> map_gens |
|
18517 | 376 |
(fn (appconst, defgens) => |
18516 | 377 |
(appconst |
378 |
|> Symtab.update (c, (bounds, (ag, stamp ()))), |
|
18517 | 379 |
defgens)), lookups, serialize_data, logic_data)) thy |
18516 | 380 |
end; |
18217 | 381 |
|
18516 | 382 |
val add_appconst = gen_add_appconst Sign.intern_const; |
383 |
val add_appconst_i = gen_add_appconst (K I); |
|
18217 | 384 |
|
385 |
fun add_defgen (name, dg) = |
|
386 |
map_codegen_data |
|
387 |
(fn (modl, gens, lookups, serialize_data, logic_data) => |
|
388 |
(modl, |
|
389 |
gens |> map_gens |
|
18517 | 390 |
(fn (appconst, defgens) => |
391 |
(appconst, defgens |
|
18335 | 392 |
|> Output.update_warn (op =) ("overwriting existing definition definition generator " ^ name) (name, (dg, stamp ())))), |
18217 | 393 |
lookups, serialize_data, logic_data)); |
394 |
||
18454 | 395 |
fun get_defgens thy tabs = |
396 |
(map (apsnd (fn (dg, _) => dg thy tabs)) o #defgens o #gens o CodegenData.get) thy; |
|
18217 | 397 |
|
398 |
fun add_lookup_tyco (src, dst) = |
|
399 |
map_codegen_data |
|
400 |
(fn (modl, gens, lookups, serialize_data, logic_data) => |
|
401 |
(modl, gens, |
|
402 |
lookups |> map_lookups |
|
403 |
(fn (lookups_tyco, lookups_const) => |
|
404 |
(lookups_tyco |> Symtab.update_new (src, dst), |
|
18282 | 405 |
lookups_const)), |
18217 | 406 |
serialize_data, logic_data)); |
407 |
||
18454 | 408 |
val lookup_tyco = Symtab.lookup o #lookups_tyco o #lookups o CodegenData.get; |
409 |
||
18217 | 410 |
fun add_lookup_const ((src, ty), dst) = |
411 |
map_codegen_data |
|
412 |
(fn (modl, gens, lookups, serialize_data, logic_data) => |
|
413 |
(modl, gens, |
|
414 |
lookups |> map_lookups |
|
415 |
(fn (lookups_tyco, lookups_const) => |
|
416 |
(lookups_tyco, |
|
18282 | 417 |
lookups_const |> Symtab.update_multi (src, (ty, dst)))), |
18217 | 418 |
serialize_data, logic_data)); |
419 |
||
18454 | 420 |
fun lookup_const thy (f, ty) = |
421 |
(Symtab.lookup_multi o #lookups_const o #lookups o CodegenData.get) thy f |
|
422 |
|> (fn tab => AList.lookup (Sign.typ_instance thy) tab ty); |
|
423 |
||
18217 | 424 |
fun set_is_datatype f = |
425 |
map_codegen_data |
|
426 |
(fn (modl, gens, lookups, serialize_data, logic_data) => |
|
427 |
(modl, gens, lookups, serialize_data, |
|
428 |
logic_data |
|
18454 | 429 |
|> map_logic_data ((apfst o apfst) (K (SOME (f, stamp ())))))); |
430 |
||
431 |
fun is_datatype thy = |
|
432 |
case (#is_datatype o #logic_data o CodegenData.get) thy |
|
433 |
of NONE => K false |
|
434 |
| SOME (f, _) => f thy; |
|
435 |
||
436 |
fun set_get_all_datatype_cons f = |
|
437 |
map_codegen_data |
|
438 |
(fn (modl, gens, lookups, serialize_data, logic_data) => |
|
439 |
(modl, gens, lookups, serialize_data, |
|
440 |
logic_data |
|
441 |
|> map_logic_data ((apfst o apsnd) (K (SOME (f, stamp ())))))); |
|
442 |
||
443 |
fun get_all_datatype_cons thy = |
|
444 |
case (#get_all_datatype_cons o #logic_data o CodegenData.get) thy |
|
445 |
of NONE => [] |
|
446 |
| SOME (f, _) => f thy; |
|
18217 | 447 |
|
448 |
fun add_alias (src, dst) = |
|
449 |
map_codegen_data |
|
450 |
(fn (modl, gens, lookups, serialize_data, logic_data) => |
|
451 |
(modl, gens, lookups, serialize_data, |
|
452 |
logic_data |> map_logic_data |
|
453 |
(apsnd (fn (tab, tab_rev) => |
|
454 |
(tab |> Symtab.update (src, dst), |
|
455 |
tab_rev |> Symtab.update (dst, src)))))); |
|
456 |
||
457 |
||
18454 | 458 |
(* name handling *) |
18217 | 459 |
|
18454 | 460 |
val nsp_class = "class"; |
461 |
val nsp_tyco = "tyco"; |
|
462 |
val nsp_const = "const"; |
|
463 |
val nsp_overl = "overl"; |
|
464 |
val nsp_dtcon = "dtcon"; |
|
465 |
val nsp_mem = "mem"; |
|
466 |
val nsp_inst = "inst"; |
|
467 |
val nsp_eq_inst = "eq_inst"; |
|
468 |
val nsp_eq_pred = "eq"; |
|
18217 | 469 |
|
18454 | 470 |
val alias_get = perhaps o Symtab.lookup o fst o #alias o #logic_data o CodegenData.get; |
471 |
val alias_rev = perhaps o Symtab.lookup o snd o #alias o #logic_data o CodegenData.get; |
|
18217 | 472 |
|
18454 | 473 |
fun add_nsp shallow name = |
474 |
name |
|
475 |
|> NameSpace.unpack |
|
476 |
|> split_last |
|
477 |
|> apsnd (single #> cons shallow) |
|
478 |
|> (op @) |
|
479 |
|> NameSpace.pack; |
|
480 |
fun dest_nsp nsp idf = |
|
18217 | 481 |
let |
482 |
val idf' = NameSpace.unpack idf; |
|
483 |
val (idf'', idf_base) = split_last idf'; |
|
484 |
val (modl, shallow) = split_last idf''; |
|
485 |
in |
|
486 |
if nsp = shallow |
|
18454 | 487 |
then (SOME o NameSpace.pack) (modl @ [idf_base]) |
18217 | 488 |
else NONE |
489 |
end; |
|
490 |
||
18454 | 491 |
fun idf_of_name thy shallow name = |
492 |
if is_number name |
|
493 |
then name |
|
18217 | 494 |
else |
18454 | 495 |
name |
496 |
|> alias_get thy |
|
497 |
|> add_nsp shallow; |
|
498 |
fun name_of_idf thy shallow idf = |
|
499 |
idf |
|
500 |
|> dest_nsp shallow |
|
501 |
|> Option.map (alias_rev thy); |
|
18217 | 502 |
|
18516 | 503 |
|
18454 | 504 |
(* code generator instantiation *) |
18217 | 505 |
|
18454 | 506 |
fun ensure_def_class thy tabs cls trns = |
507 |
let |
|
508 |
val cls' = idf_of_name thy nsp_class cls; |
|
509 |
in |
|
510 |
trns |
|
511 |
|> debug 4 (fn _ => "generating class " ^ quote cls) |
|
512 |
|> gen_ensure_def (get_defgens thy tabs) ("generating class " ^ quote cls) cls' |
|
513 |
|> pair cls' |
|
514 |
end; |
|
18217 | 515 |
|
18454 | 516 |
fun ensure_def_inst thy (tabs as (_, (insttab, _, _))) (cls, tyco) trns = |
517 |
let |
|
518 |
val thyname = (the o AList.lookup (op =) (ClassPackage.the_tycos thy cls)) tyco; |
|
519 |
val inst = idf_of_name thy nsp_inst (InstNameMangler.get thy insttab (thyname, (cls, tyco))); |
|
520 |
in |
|
521 |
trns |
|
522 |
|> debug 4 (fn _ => "generating instance " ^ quote cls ^ " / " ^ quote tyco) |
|
523 |
|> gen_ensure_def (get_defgens thy tabs) ("generating instance " ^ quote cls ^ " / " ^ quote tyco) inst |
|
524 |
|> pair inst |
|
525 |
end; |
|
18335 | 526 |
|
18454 | 527 |
fun ensure_def_tyco thy tabs tyco trns = |
528 |
let |
|
529 |
val tyco' = idf_of_name thy nsp_tyco tyco; |
|
530 |
in case lookup_tyco thy tyco |
|
18217 | 531 |
of NONE => |
532 |
trns |
|
18231 | 533 |
|> debug 4 (fn _ => "generating type constructor " ^ quote tyco) |
18454 | 534 |
|> gen_ensure_def (get_defgens thy tabs) ("generating type constructor " ^ quote tyco) tyco' |
535 |
|> pair tyco' |
|
18217 | 536 |
| SOME tyco => |
537 |
trns |
|
538 |
|> pair tyco |
|
18454 | 539 |
end; |
540 |
||
541 |
fun idf_of_const thy (tabs as ((_, clsmemtab), (_, (overltab1, overltab2), dtcontab))) (c, ty) = |
|
542 |
let |
|
18515 | 543 |
fun get_overloaded (c, ty) = |
544 |
case Symtab.lookup overltab1 c |
|
545 |
of SOME (ty_decl, tys) => |
|
546 |
(case find_first (curry (Sign.typ_instance thy) ty) tys |
|
547 |
of SOME ty' => ConstNameMangler.get thy overltab2 |
|
548 |
(idf_of_name thy nsp_overl c, (ty_decl, ty')) |> SOME |
|
549 |
| _ => NONE) |
|
550 |
| _ => NONE |
|
551 |
fun get_datatypecons (c, ty) = |
|
552 |
case (snd o strip_type) ty |
|
553 |
of Type (tyco, _) => |
|
554 |
try (DatatypeconsNameMangler.get thy dtcontab) (c, tyco) |
|
555 |
| _ => NONE; |
|
556 |
in case get_overloaded (c, ty) |
|
557 |
of SOME idf => idf |
|
558 |
| NONE => case get_datatypecons (c, ty) |
|
559 |
of SOME c' => idf_of_name thy nsp_dtcon c' |
|
560 |
| NONE => case Symtab.lookup clsmemtab c |
|
561 |
of SOME _ => idf_of_name thy nsp_mem c |
|
562 |
| NONE => idf_of_name thy nsp_const c |
|
563 |
end; |
|
18217 | 564 |
|
18454 | 565 |
fun recconst_of_idf thy (_, (_, (_, overltab2), _)) idf = |
566 |
case name_of_idf thy nsp_const idf |
|
567 |
of SOME c => SOME (c, Sign.the_const_constraint thy c) |
|
568 |
| NONE => ( |
|
569 |
case dest_nsp nsp_overl idf |
|
570 |
of SOME _ => |
|
571 |
idf |
|
572 |
|> ConstNameMangler.rev thy overltab2 |
|
573 |
|> apfst (the o name_of_idf thy nsp_overl) |
|
574 |
|> apsnd snd |
|
575 |
|> SOME |
|
576 |
| NONE => NONE |
|
577 |
); |
|
578 |
||
579 |
fun ensure_def_const thy (tabs as ((_, clsmemtab), (_, overltab, dtcontab))) (c, ty) trns = |
|
580 |
let |
|
581 |
val c' = idf_of_const thy tabs (c, ty); |
|
582 |
in case lookup_const thy (c, ty) |
|
18217 | 583 |
of NONE => |
584 |
trns |
|
18454 | 585 |
|> debug 4 (fn _ => "generating constant " ^ quote c) |
18516 | 586 |
|> gen_ensure_def (get_defgens thy tabs) ("generating constant " ^ quote c) c' |
587 |
|> pair c' |
|
18454 | 588 |
| SOME (IConst (c, ty)) => |
18217 | 589 |
trns |
18454 | 590 |
|> pair c |
591 |
end; |
|
18217 | 592 |
|
18454 | 593 |
fun ensure_def_eq thy tabs (dtco, (eqpred, arity)) trns = |
594 |
let |
|
595 |
val name_dtco = (the ooo name_of_idf) thy nsp_tyco dtco; |
|
596 |
val idf_eqinst = idf_of_name thy nsp_eq_inst name_dtco; |
|
597 |
val idf_eqpred = idf_of_name thy nsp_eq_pred name_dtco; |
|
18515 | 598 |
val inst_sortlookup = map (fn (v, _) => [ClassPackage.Lookup ([], (v, 0))]) arity; |
18454 | 599 |
fun mk_eq_pred _ trns = |
600 |
trns |
|
601 |
|> succeed (eqpred, []) |
|
602 |
fun mk_eq_inst _ trns = |
|
603 |
trns |
|
604 |
|> gen_ensure_def [("eqpred", mk_eq_pred)] ("generating equality predicate for " ^ quote dtco) idf_eqpred |
|
18515 | 605 |
|> succeed (Classinst ((class_eq, (dtco, arity)), ([], [(fun_eq, (idf_eqpred, inst_sortlookup))])), []); |
18454 | 606 |
in |
607 |
trns |
|
608 |
|> gen_ensure_def [("eqinst", mk_eq_inst)] ("generating equality instance for " ^ quote dtco) idf_eqinst |
|
609 |
end; |
|
610 |
||
18516 | 611 |
|
612 |
(* expression generators *) |
|
613 |
||
614 |
fun exprgen_sort thy tabs sort trns = |
|
615 |
trns |
|
616 |
|> fold_map (ensure_def_class thy tabs) (ClassPackage.syntactic_sort_of thy sort) |
|
617 |
|-> (fn sort => pair sort); |
|
618 |
||
619 |
fun exprgen_type thy tabs (TVar _) trns = |
|
620 |
error "TVar encountered during code generation" |
|
621 |
| exprgen_type thy tabs (TFree (v, sort)) trns = |
|
622 |
trns |
|
623 |
|> exprgen_sort thy tabs sort |
|
624 |
|-> (fn sort => pair (IVarT (v |> unprefix "'", sort))) |
|
625 |
| exprgen_type thy tabs (Type ("fun", [t1, t2])) trns = |
|
626 |
trns |
|
627 |
|> exprgen_type thy tabs t1 |
|
628 |
||>> exprgen_type thy tabs t2 |
|
629 |
|-> (fn (t1', t2') => pair (t1' `-> t2')) |
|
630 |
| exprgen_type thy tabs (Type (tyco, tys)) trns = |
|
631 |
trns |
|
632 |
|> ensure_def_tyco thy tabs tyco |
|
633 |
||>> fold_map (exprgen_type thy tabs) tys |
|
634 |
|-> (fn (tyco, tys) => pair (tyco `%% tys)); |
|
635 |
||
18517 | 636 |
fun mk_lookup thy tabs (ClassPackage.Instance (inst as (cls, tyco), ls)) trns = |
637 |
trns |
|
638 |
|> ensure_def_class thy tabs cls |
|
639 |
||>> ensure_def_inst thy tabs inst |
|
640 |
||>> (fold_map o fold_map) (mk_lookup thy tabs) ls |
|
641 |
|-> (fn ((cls, i), ls) => pair (ClassPackage.Instance ((cls, i), ls))) |
|
642 |
| mk_lookup thy tabs (ClassPackage.Lookup (clss, (v, i))) trns = |
|
18516 | 643 |
trns |
18517 | 644 |
|> fold_map (ensure_def_class thy tabs) clss |
645 |
|-> (fn clss => pair (ClassPackage.Lookup (clss, (v |> unprefix "'", i)))); |
|
646 |
||
647 |
fun mk_itapp e [] = e |
|
648 |
| mk_itapp e lookup = IInst (e, lookup); |
|
649 |
||
650 |
fun appgen thy tabs ((f, ty), ts) trns = |
|
651 |
case Symtab.lookup ((#appconst o #gens o CodegenData.get) thy) f |
|
652 |
of SOME ((imin, imax), (ag, _)) => |
|
653 |
let |
|
654 |
fun invoke ts trns = |
|
655 |
trns |
|
656 |
|> gen_invoke [("const application", ag thy tabs)] ("generating application " ^ f ^ "::" ^ (Sign.string_of_typ thy) ty |
|
657 |
^ " " ^ enclose "(" ")" (commas (map (Sign.string_of_term thy) ts))) |
|
658 |
((f, ty), ts) |
|
659 |
in if length ts < imin then |
|
660 |
let |
|
661 |
val d = imin - length ts; |
|
662 |
val vs = Term.invent_names (add_term_names (Const (f, ty), [])) "x" d; |
|
663 |
val tys = Library.take (d, ((fst o strip_type) ty)); |
|
664 |
in |
|
665 |
trns |
|
666 |
|> debug 10 (fn _ => "eta-expanding") |
|
667 |
|> fold_map (exprgen_type thy tabs) tys |
|
668 |
||>> invoke (ts @ map2 (curry Free) vs tys) |
|
669 |
|-> (fn (tys, e) => pair ((vs ~~ tys) `|--> e)) |
|
670 |
end |
|
671 |
else if length ts > imax then |
|
672 |
trns |
|
673 |
|> debug 10 (fn _ => "splitting arguments (" ^ string_of_int imax ^ ", " ^ string_of_int (length ts) ^ ")") |
|
674 |
|> invoke (Library.take (imax, ts)) |
|
675 |
||>> fold_map (exprgen_term thy tabs) (Library.drop (imax, ts)) |
|
676 |
|-> (fn es => pair (mk_apps es)) |
|
677 |
else |
|
678 |
trns |
|
679 |
|> debug 10 (fn _ => "keeping arguments") |
|
680 |
|> invoke ts |
|
681 |
end |
|
682 |
| NONE => |
|
683 |
trns |
|
684 |
|> ensure_def_const thy tabs (f, ty) |
|
685 |
||>> (fold_map o fold_map) (mk_lookup thy tabs) |
|
686 |
(ClassPackage.extract_sortlookup thy (Sign.the_const_constraint thy f, ty)) |
|
687 |
||>> exprgen_type thy tabs ty |
|
688 |
||>> fold_map (exprgen_term thy tabs) ts |
|
689 |
|-> (fn (((f, lookup), ty), es) => |
|
690 |
pair (mk_itapp (IConst (f, ty)) lookup `$$ es)) |
|
691 |
and exprgen_term thy tabs (Const (f, ty)) trns = |
|
692 |
trns |
|
693 |
|> appgen thy tabs ((f, ty), []) |
|
18516 | 694 |
|-> (fn e => pair e) |
695 |
| exprgen_term thy tabs (Var ((v, i), ty)) trns = |
|
696 |
trns |
|
697 |
|> exprgen_type thy tabs ty |
|
698 |
|-> (fn ty => pair (IVarE (if i = 0 then v else v ^ "_" ^ string_of_int i, ty))) |
|
699 |
| exprgen_term thy tabs (Free (v, ty)) trns = |
|
700 |
trns |
|
701 |
|> exprgen_type thy tabs ty |
|
702 |
|-> (fn ty => pair (IVarE (v, ty))) |
|
703 |
| exprgen_term thy tabs (Abs (v, ty, t)) trns = |
|
704 |
trns |
|
705 |
|> exprgen_type thy tabs ty |
|
706 |
||>> exprgen_term thy tabs (subst_bound (Free (v, ty), t)) |
|
707 |
|-> (fn (ty, e) => pair ((v, ty) `|-> e)) |
|
708 |
| exprgen_term thy tabs (t as t1 $ t2) trns = |
|
709 |
let |
|
710 |
val (t', ts) = strip_comb t |
|
711 |
in case t' |
|
712 |
of Const (f, ty) => |
|
713 |
trns |
|
18517 | 714 |
|> appgen thy tabs ((f, ty), ts) |
18516 | 715 |
|-> (fn e => pair e) |
716 |
| _ => |
|
717 |
trns |
|
718 |
|> exprgen_term thy tabs t' |
|
719 |
||>> fold_map (exprgen_term thy tabs) ts |
|
720 |
|-> (fn (e, es) => pair (e `$$ es)) |
|
721 |
end; |
|
722 |
||
18454 | 723 |
|
18517 | 724 |
(* application generators *) |
725 |
||
726 |
fun appgen_neg thy tabs (("neg", Type ("fun", [ty, _])), ts) trns = |
|
727 |
trns |
|
728 |
|> exprgen_term thy tabs (Const ("op >", ty --> ty --> Type ("bool", [])) $ Const ("0", ty)) |
|
729 |
|-> succeed; |
|
730 |
||
731 |
fun appgen_eq thy tabs (("op =", Type ("fun", [ty, _])), [t1, t2]) trns = |
|
732 |
trns |
|
733 |
|> invoke_eq (exprgen_type thy tabs) (ensure_def_eq thy tabs) ty |
|
734 |
|-> (fn false => error ("could not derive equality for " ^ Sign.string_of_typ thy ty) |
|
735 |
| true => fn trns => trns |
|
736 |
|> exprgen_term thy tabs t1 |
|
737 |
||>> exprgen_term thy tabs t2 |
|
738 |
|-> (fn (e1, e2) => succeed (Fun_eq `$ e1 `$ e2))); |
|
739 |
||
740 |
||
741 |
(* definition generators *) |
|
18454 | 742 |
|
743 |
fun mk_fun thy tabs eqs ty trns = |
|
18217 | 744 |
let |
745 |
val sortctxt = ClassPackage.extract_sortctxt thy ty; |
|
746 |
fun mk_sortvar (v, sort) trns = |
|
747 |
trns |
|
18516 | 748 |
|> exprgen_sort thy tabs sort |
18217 | 749 |
|-> (fn sort => pair (unprefix "'" v, sort)) |
750 |
fun mk_eq (args, rhs) trns = |
|
751 |
trns |
|
18516 | 752 |
|> fold_map (exprgen_term thy tabs o devarify_term) args |
753 |
||>> (exprgen_term thy tabs o devarify_term) rhs |
|
18217 | 754 |
|-> (fn (args, rhs) => pair (map ipat_of_iexpr args, rhs)) |
755 |
in |
|
756 |
trns |
|
757 |
|> fold_map mk_eq eqs |
|
18516 | 758 |
||>> exprgen_type thy tabs (devarify_type ty) |
18217 | 759 |
||>> fold_map mk_sortvar sortctxt |
760 |
|-> (fn ((eqs, ty), sortctxt) => pair (Fun (eqs, (sortctxt, ty)))) |
|
761 |
end; |
|
762 |
||
18454 | 763 |
fun defgen_tyco_fallback thy tabs tyco trns = |
18217 | 764 |
if Symtab.fold (fn (_, { syntax_tyco, ... }) => fn b => b orelse Symtab.defined syntax_tyco tyco) |
18282 | 765 |
((#serialize_data o CodegenData.get) thy) false |
18217 | 766 |
then |
767 |
trns |
|
18231 | 768 |
|> debug 5 (fn _ => "trying defgen tyco fallback for " ^ quote tyco) |
18217 | 769 |
|> succeed (Nop, []) |
770 |
else |
|
771 |
trns |
|
772 |
|> fail ("no code generation fallback for " ^ quote tyco) |
|
773 |
||
18454 | 774 |
fun defgen_const_fallback thy tabs c trns = |
775 |
if Symtab.fold (fn (_, { syntax_const, ... }) => fn b => b orelse Symtab.defined syntax_const c) |
|
18282 | 776 |
((#serialize_data o CodegenData.get) thy) false |
18217 | 777 |
then |
778 |
trns |
|
18454 | 779 |
|> debug 5 (fn _ => "trying defgen const fallback for " ^ quote c) |
18217 | 780 |
|> succeed (Nop, []) |
781 |
else |
|
782 |
trns |
|
18454 | 783 |
|> fail ("no code generation fallback for " ^ quote c) |
18217 | 784 |
|
18454 | 785 |
fun defgen_defs thy (tabs as ((deftab, _), _)) c trns = |
786 |
case Symtab.lookup deftab c |
|
787 |
of SOME (ty, (args, rhs)) => |
|
18217 | 788 |
trns |
18454 | 789 |
|> debug 5 (fn _ => "trying defgen def for " ^ quote c) |
790 |
|> mk_fun thy tabs [(args, rhs)] (devarify_type ty) |
|
18217 | 791 |
|-> (fn def => succeed (def, [])) |
18454 | 792 |
| _ => trns |> fail ("no definition found for " ^ quote c); |
18217 | 793 |
|
18454 | 794 |
fun defgen_clsdecl thy (tabs as (_, (insttab, _, _))) (cls : string) trns = |
18217 | 795 |
case name_of_idf thy nsp_class cls |
796 |
of SOME cls => |
|
18380
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
797 |
let |
18454 | 798 |
val memnames = ClassPackage.the_consts thy (cls : string); |
18380
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
799 |
val memtypes = map (devarify_type o ClassPackage.get_const_sign thy "'a") memnames; |
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
800 |
val memctxt = map (ClassPackage.extract_sortctxt thy) memtypes; |
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
801 |
val memidfs = map (idf_of_name thy nsp_mem) memnames; |
18454 | 802 |
fun mk_instname (tyco, thyname) = idf_of_name thy nsp_inst (InstNameMangler.get thy insttab (thyname, (cls, tyco))) |
803 |
val instnames = map mk_instname (ClassPackage.the_tycos thy cls); |
|
18380
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
804 |
in |
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
805 |
trns |
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
806 |
|> debug 5 (fn _ => "trying defgen class declaration for " ^ quote cls) |
18454 | 807 |
|> fold_map (ensure_def_class thy tabs) (ClassPackage.get_superclasses thy cls) |
18516 | 808 |
||>> fold_map (exprgen_type thy tabs) memtypes |
18380
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
809 |
|-> (fn (supcls, memtypes) => succeed (Class (supcls, "a", memidfs ~~ (memctxt ~~ memtypes), []), |
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
810 |
memidfs @ instnames)) |
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
811 |
end |
18217 | 812 |
| _ => |
813 |
trns |
|
814 |
|> fail ("no class definition found for " ^ quote cls); |
|
815 |
||
18454 | 816 |
fun defgen_clsmem thy tabs m trns = |
817 |
case name_of_idf thy nsp_mem m |
|
818 |
of SOME m => |
|
18360 | 819 |
trns |
18454 | 820 |
|> debug 5 (fn _ => "trying defgen class member for " ^ quote m) |
821 |
|> ensure_def_class thy tabs ((the o ClassPackage.lookup_const_class thy) m) |
|
18380
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
822 |
|-> (fn cls => succeed (Classmember cls, [])) |
18217 | 823 |
| _ => |
18454 | 824 |
trns |> fail ("no class member found for " ^ quote m) |
18217 | 825 |
|
18454 | 826 |
fun defgen_clsinst thy (tabs as (_, (insttab, _, _))) inst trns = |
827 |
case Option.map (InstNameMangler.rev thy insttab) (name_of_idf thy nsp_inst inst) |
|
828 |
of SOME (_, (cls, tyco)) => |
|
18217 | 829 |
let |
18454 | 830 |
val arity = ClassPackage.get_arities thy [cls] tyco; |
831 |
val ms = map (fn m => (m, Sign.the_const_constraint thy m)) (ClassPackage.the_consts thy cls); |
|
832 |
val instmem_idfs = ClassPackage.get_inst_consts_sign thy (tyco, cls); |
|
18515 | 833 |
val supclss = ClassPackage.get_superclasses thy cls; |
18335 | 834 |
fun add_vars arity clsmems (trns as (_, modl)) = |
18380
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
835 |
case get_def modl (idf_of_name thy nsp_class cls) |
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
836 |
of Class (_, _, members, _) => ((Term.invent_names |
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
837 |
(tvars_of_itypes ((map (snd o snd)) members)) "a" (length arity) ~~ arity, clsmems), trns) |
18515 | 838 |
val ad_hoc_arity = map (fn (v, sort) => map_index (fn (i, _) => (ClassPackage.Lookup ([], (v, i)))) sort); |
839 |
(*! THIS IS ACTUALLY VERY AD-HOC... !*) |
|
18217 | 840 |
in |
18515 | 841 |
(trns |
18231 | 842 |
|> debug 5 (fn _ => "trying defgen class instance for (" ^ quote cls ^ ", " ^ quote tyco ^ ")") |
18454 | 843 |
|> (fold_map o fold_map) (ensure_def_class thy tabs) arity |
844 |
||>> fold_map (ensure_def_const thy tabs) ms |
|
845 |
|-> (fn (arity, ms) => add_vars arity ms) |
|
846 |
||>> ensure_def_class thy tabs cls |
|
847 |
||>> ensure_def_tyco thy tabs tyco |
|
18515 | 848 |
||>> fold_map (fn supcls => ensure_def_inst thy tabs (supcls, tyco)) supclss |
849 |
||>> fold_map (fn supcls => (fold_map o fold_map) (mk_lookup thy tabs) |
|
850 |
(ClassPackage.extract_sortlookup thy |
|
851 |
(Type (tyco, map_index (fn (i, _) => TVar (("'a", i), [])) (ClassPackage.get_arities thy [supcls] tyco)), |
|
852 |
Type (tyco, map_index (fn (i, sort) => TFree (string_of_int i, sort)) arity)))) supclss |
|
853 |
||>> fold_map (ensure_def_const thy tabs) instmem_idfs) |
|
854 |
|-> (fn ((((((arity, ms), cls), tyco), supinsts), supinstlookup), instmem_idfs) |
|
855 |
: ((((((string * string list) list * string list) * string) * string) |
|
856 |
* string list) * ClassPackage.sortlookup list list list) * string list |
|
857 |
=> |
|
858 |
succeed (Classinst ((cls, (tyco, arity)), (supclss ~~ (supinsts ~~ supinstlookup), ms ~~ map (rpair (ad_hoc_arity arity)) instmem_idfs)), [])) |
|
18217 | 859 |
end |
860 |
| _ => |
|
18454 | 861 |
trns |> fail ("no class instance found for " ^ quote inst); |
18217 | 862 |
|
863 |
||
18515 | 864 |
(* trns |
865 |
|> ensure_def_const thy tabs (f, ty) |
|
866 |
||
18516 | 867 |
||>> exprgen_type thy tabs ty |
868 |
||>> fold_map (exprgen_term thy tabs) ts |
|
18515 | 869 |
|-> (fn (((f, lookup), ty), es) => |
870 |
succeed (mk_itapp (IConst (f, ty)) lookup `$$ es))*) |
|
871 |
||
872 |
||
18217 | 873 |
(* parametrized generators, for instantiation in HOL *) |
874 |
||
18517 | 875 |
fun appgen_let strip_abs thy tabs (c, [t2, t3]) trns = |
876 |
let |
|
877 |
fun dest_let (l as Const ("Let", _) $ t $ u) = |
|
878 |
(case strip_abs 1 u |
|
879 |
of ([p], u') => apfst (cons (p, t)) (dest_let u') |
|
880 |
| _ => ([], l)) |
|
881 |
| dest_let t = ([], t); |
|
882 |
fun mk_let (l, r) trns = |
|
18335 | 883 |
trns |
18517 | 884 |
|> exprgen_term thy tabs l |
885 |
||>> exprgen_term thy tabs r |
|
886 |
|-> (fn (l, r) => pair (r, ipat_of_iexpr l)); |
|
887 |
val (lets, body) = dest_let (Const c $ t2 $ t3) |
|
888 |
in |
|
889 |
trns |
|
890 |
|> fold_map mk_let lets |
|
891 |
||>> exprgen_term thy tabs body |
|
892 |
|-> (fn (lets, body) => |
|
893 |
succeed (Library.foldr (fn ((e, p), body) => ICase (e, [(p, body)])) (lets, body))) |
|
894 |
end |
|
18217 | 895 |
|
18517 | 896 |
fun appgen_split strip_abs thy tabs (c, [t2]) trns = |
897 |
let |
|
898 |
val ([p], body) = strip_abs 1 (Const c $ t2) |
|
899 |
in |
|
900 |
trns |
|
901 |
|> exprgen_term thy tabs p |
|
902 |
||>> exprgen_term thy tabs body |
|
903 |
|-> (fn (IVarE v, body) => succeed (IAbs (v, body))) |
|
904 |
end; |
|
18335 | 905 |
|
18517 | 906 |
fun appgen_number_of dest_binum mk_int_to_nat thy tabs (("Numeral.number_of", |
907 |
Type ("fun", [_, Type ("IntDef.int", [])])), [bin]) trns = |
|
908 |
trns |
|
909 |
|> (succeed (IConst ((IntInf.toString o dest_binum) bin, Type_integer)) |
|
910 |
handle TERM _ |
|
911 |
=> error ("not a number: " ^ Sign.string_of_term thy bin)) |
|
912 |
| appgen_number_of dest_binum mk_int_to_nat thy tabs (("Numeral.number_of", |
|
913 |
Type ("fun", [_, Type ("nat", [])])), [bin]) trns = |
|
18335 | 914 |
trns |
18517 | 915 |
|> exprgen_term thy tabs (mk_int_to_nat bin) |
916 |
|-> succeed; |
|
18217 | 917 |
|
18517 | 918 |
fun appgen_datatype_case cos thy tabs ((_, ty), ts) trns = |
18247
b17724cae935
code generator: case expressions, improved name resolving
haftmann
parents:
18231
diff
changeset
|
919 |
let |
18517 | 920 |
val (ts', t) = split_last ts; |
921 |
val (tys, dty) = (split_last o fst o strip_type) ty; |
|
922 |
fun gen_names i = |
|
923 |
variantlist (replicate i "x", foldr add_term_names |
|
924 |
(map (fst o fst o dest_Var) (foldr add_term_vars [] ts)) ts); |
|
925 |
fun cg_case_d (((cname, i), ty), t) trns = |
|
18247
b17724cae935
code generator: case expressions, improved name resolving
haftmann
parents:
18231
diff
changeset
|
926 |
let |
b17724cae935
code generator: case expressions, improved name resolving
haftmann
parents:
18231
diff
changeset
|
927 |
val vs = gen_names i; |
b17724cae935
code generator: case expressions, improved name resolving
haftmann
parents:
18231
diff
changeset
|
928 |
val tys = Library.take (i, (fst o strip_type) ty); |
18330 | 929 |
val frees = map2 (curry Free) vs tys; |
18247
b17724cae935
code generator: case expressions, improved name resolving
haftmann
parents:
18231
diff
changeset
|
930 |
val t' = Envir.beta_norm (list_comb (t, frees)); |
b17724cae935
code generator: case expressions, improved name resolving
haftmann
parents:
18231
diff
changeset
|
931 |
in |
b17724cae935
code generator: case expressions, improved name resolving
haftmann
parents:
18231
diff
changeset
|
932 |
trns |
18516 | 933 |
|> exprgen_term thy tabs (list_comb (Const (cname, tys ---> dty), frees)) |
934 |
||>> exprgen_term thy tabs t' |
|
18247
b17724cae935
code generator: case expressions, improved name resolving
haftmann
parents:
18231
diff
changeset
|
935 |
|-> (fn (ep, e) => pair (ipat_of_iexpr ep, e)) |
b17724cae935
code generator: case expressions, improved name resolving
haftmann
parents:
18231
diff
changeset
|
936 |
end; |
18517 | 937 |
in |
938 |
trns |
|
939 |
|> exprgen_term thy tabs t |
|
940 |
||>> fold_map cg_case_d ((cos ~~ tys) ~~ ts') |
|
941 |
|-> (fn (t, ds) => succeed (ICase (t, ds))) |
|
18247
b17724cae935
code generator: case expressions, improved name resolving
haftmann
parents:
18231
diff
changeset
|
942 |
end; |
b17724cae935
code generator: case expressions, improved name resolving
haftmann
parents:
18231
diff
changeset
|
943 |
|
18517 | 944 |
fun gen_add_cg_case_const prep_c get_case_const_data raw_c thy = |
945 |
let |
|
946 |
val c = prep_c thy raw_c; |
|
947 |
val (tys, dty) = (split_last o fst o strip_type o Sign.the_const_constraint thy) c; |
|
948 |
val cos = (the o get_case_const_data thy) c; |
|
949 |
val n_eta = length cos + 1; |
|
950 |
in |
|
951 |
thy |
|
952 |
|> add_appconst_i (c, ((n_eta, n_eta), appgen_datatype_case cos)) |
|
953 |
end; |
|
954 |
||
955 |
val add_cg_case_const = gen_add_cg_case_const Sign.intern_const; |
|
956 |
val add_cg_case_const_i = gen_add_cg_case_const (K I); |
|
957 |
||
18454 | 958 |
fun defgen_datatype get_datatype get_datacons thy (tabs as (_, (_, _, dtcontab))) dtco trns = |
959 |
case name_of_idf thy nsp_tyco dtco |
|
18380
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
960 |
of SOME dtco => |
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
961 |
(case get_datatype thy dtco |
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
962 |
of SOME (vars, cos) => |
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
963 |
let |
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
964 |
val cotys = map (the o get_datacons thy o rpair dtco) cos; |
18454 | 965 |
val coidfs = map (fn co => (DatatypeconsNameMangler.get thy dtcontab (co, dtco)) |> |
966 |
idf_of_name thy nsp_dtcon) cos; |
|
18380
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
967 |
in |
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
968 |
trns |
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
969 |
|> debug 5 (fn _ => "trying defgen datatype for " ^ quote dtco) |
18516 | 970 |
|> fold_map (exprgen_sort thy tabs) (map snd vars) |
971 |
||>> (fold_map o fold_map) (exprgen_type thy tabs o devarify_type) cotys |
|
18380
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
972 |
|-> (fn (sorts, tys) => succeed (Datatype |
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
973 |
(map2 (fn (v, _) => fn sort => (unprefix "'" v, sort)) vars sorts, coidfs ~~ tys, []), |
18454 | 974 |
coidfs)) |
18380
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
975 |
end |
18217 | 976 |
| NONE => |
977 |
trns |
|
18380
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
978 |
|> fail ("no datatype found for " ^ quote dtco)) |
18217 | 979 |
| NONE => |
980 |
trns |
|
18454 | 981 |
|> fail ("not a type constructor: " ^ quote dtco) |
18335 | 982 |
|
18454 | 983 |
fun defgen_datacons get_datacons thy (tabs as (_, (_, _, dtcontab))) co trns = |
984 |
case Option.map (DatatypeconsNameMangler.rev thy dtcontab) (name_of_idf thy nsp_dtcon co) |
|
985 |
of SOME (co, dtco) => |
|
986 |
trns |
|
987 |
|> debug 5 (fn _ => "trying defgen datatype constructor for " ^ quote co) |
|
988 |
|> ensure_def_tyco thy tabs dtco |
|
18517 | 989 |
||>> fold_map (exprgen_type thy tabs) ((the o get_datacons thy) (co, dtco)) |
990 |
|-> (fn (tyco, _) => succeed (Datatypecons tyco, [])) |
|
18454 | 991 |
| _ => |
992 |
trns |
|
993 |
|> fail ("not a datatype constructor: " ^ quote co); |
|
18217 | 994 |
|
18454 | 995 |
fun defgen_recfun get_equations thy tabs c trns = |
996 |
case recconst_of_idf thy tabs c |
|
997 |
of SOME (c, ty) => |
|
18217 | 998 |
let |
18454 | 999 |
val (eqs, ty) = get_equations thy (c, ty); |
18217 | 1000 |
in |
1001 |
case eqs |
|
1002 |
of (_::_) => |
|
1003 |
trns |
|
18454 | 1004 |
|> debug 5 (fn _ => "trying defgen recfun for " ^ quote c) |
1005 |
|> mk_fun thy tabs eqs (devarify_type ty) |
|
18217 | 1006 |
|-> (fn def => succeed (def, [])) |
1007 |
| _ => |
|
1008 |
trns |
|
18454 | 1009 |
|> fail ("no recursive definition found for " ^ quote c) |
18217 | 1010 |
end |
1011 |
| NONE => |
|
1012 |
trns |
|
18454 | 1013 |
|> fail ("not a constant: " ^ quote c); |
18217 | 1014 |
|
1015 |
||
18516 | 1016 |
|
1017 |
(** theory interface **) |
|
18217 | 1018 |
|
18454 | 1019 |
fun mk_tabs thy = |
18217 | 1020 |
let |
18454 | 1021 |
fun extract_defs thy = |
18217 | 1022 |
let |
18454 | 1023 |
fun dest t = |
1024 |
let |
|
1025 |
val (lhs, rhs) = Logic.dest_equals t; |
|
1026 |
val (c, args) = strip_comb lhs; |
|
1027 |
val (s, T) = dest_Const c |
|
1028 |
in if forall is_Var args then SOME (s, (T, (args, rhs))) else NONE |
|
1029 |
end handle TERM _ => NONE; |
|
1030 |
fun prep_def def = (case Codegen.preprocess thy [def] of |
|
1031 |
[def'] => prop_of def' | _ => error "mk_auxtab: bad preprocessor"); |
|
1032 |
fun add_def (name, t) defs = (case dest t of |
|
1033 |
NONE => defs |
|
1034 |
| SOME _ => (case (dest o prep_def oo Thm.get_axiom) thy name of |
|
1035 |
NONE => defs |
|
1036 |
| SOME (s, (T, (args, rhs))) => Symtab.update |
|
1037 |
(s, (T, (split_last (args @ [rhs]))) :: |
|
1038 |
if_none (Symtab.lookup defs s) []) defs)) |
|
18217 | 1039 |
in |
18454 | 1040 |
Symtab.empty |
1041 |
|> fold (Symtab.fold add_def) (map |
|
1042 |
(snd o #axioms o Theory.rep_theory) (thy :: Theory.ancestors_of thy)) |
|
18217 | 1043 |
end; |
18454 | 1044 |
fun mk_insttab thy = |
1045 |
InstNameMangler.empty |
|
1046 |
|> Symtab.fold_map |
|
1047 |
(fn (cls, (_, clsinsts)) => fold_map |
|
1048 |
(fn (tyco, thyname) => InstNameMangler.declare thy (thyname, (cls, tyco))) clsinsts) |
|
1049 |
(ClassPackage.get_classtab thy) |
|
1050 |
|-> (fn _ => I); |
|
1051 |
fun mk_overltabs thy defs = |
|
1052 |
(Symtab.empty, ConstNameMangler.empty) |
|
1053 |
|> Symtab.fold |
|
1054 |
(fn (c, [_]) => I |
|
1055 |
| ("0", _) => I |
|
1056 |
| (c, tytab) => |
|
1057 |
(fn (overltab1, overltab2) => ( |
|
1058 |
overltab1 |
|
1059 |
|> Symtab.update_new (c, (Sign.the_const_constraint thy c, map fst tytab)), |
|
1060 |
overltab2 |
|
1061 |
|> fold (fn (ty, _) => ConstNameMangler.declare thy (idf_of_name thy nsp_overl c, (Sign.the_const_constraint thy c, ty)) #> snd) tytab |
|
1062 |
))) defs; |
|
1063 |
fun mk_dtcontab thy = |
|
1064 |
DatatypeconsNameMangler.empty |
|
1065 |
|> fold_map |
|
18455 | 1066 |
(fn (_, co_dtco) => DatatypeconsNameMangler.declare_multi thy co_dtco) |
1067 |
(fold (fn (co, dtco) => |
|
1068 |
let |
|
1069 |
val key = ((NameSpace.drop_base o NameSpace.drop_base) co, NameSpace.base co) |
|
1070 |
in AList.default (op =) (key, []) #> AList.map_entry (op =) key (cons (co, dtco)) end |
|
1071 |
) (get_all_datatype_cons thy) []) |
|
18454 | 1072 |
|-> (fn _ => I); |
1073 |
fun mk_deftab thy defs overltab = |
|
1074 |
Symtab.empty |
|
1075 |
|> Symtab.fold |
|
1076 |
(fn (c, [ty_cdef]) => |
|
1077 |
Symtab.update_new (idf_of_name thy nsp_const c, ty_cdef) |
|
1078 |
| ("0", _) => I |
|
1079 |
| (c, cdefs) => fold (fn (ty, cdef) => |
|
1080 |
let |
|
1081 |
val c' = ConstNameMangler.get thy overltab |
|
1082 |
(idf_of_name thy nsp_overl c, (Sign.the_const_constraint thy c, ty)) |
|
1083 |
in Symtab.update_new (c', (ty, cdef)) end) cdefs) defs; |
|
1084 |
fun mk_clsmemtab thy = |
|
1085 |
Symtab.empty |
|
1086 |
|> Symtab.fold |
|
1087 |
(fn (class, (clsmems, _)) => fold |
|
1088 |
(fn clsmem => Symtab.update (clsmem, class)) clsmems) |
|
1089 |
(ClassPackage.get_classtab thy); |
|
1090 |
val defs = extract_defs thy; |
|
1091 |
val insttab = mk_insttab thy; |
|
1092 |
val overltabs = mk_overltabs thy defs; |
|
1093 |
val dtcontab = mk_dtcontab thy; |
|
1094 |
val deftab = mk_deftab thy defs (snd overltabs); |
|
1095 |
val clsmemtab = mk_clsmemtab thy; |
|
1096 |
in ((deftab, clsmemtab), (insttab, overltabs, dtcontab)) end; |
|
18217 | 1097 |
|
18335 | 1098 |
fun check_for_serializer serial_name serialize_data = |
1099 |
if Symtab.defined serialize_data serial_name |
|
1100 |
then serialize_data |
|
1101 |
else error ("unknown code serializer: " ^ quote serial_name); |
|
1102 |
||
18516 | 1103 |
fun map_module f = |
1104 |
map_codegen_data (fn (modl, gens, lookups, serialize_data, logic_data) => |
|
1105 |
(f modl, gens, lookups, serialize_data, logic_data)); |
|
1106 |
||
18231 | 1107 |
fun expand_module defs gen thy = |
18516 | 1108 |
(#modl o CodegenData.get) thy |
1109 |
|> start_transact (gen thy defs) |
|
1110 |
|-> (fn x:'a => fn modl => (x, map_module (K modl) thy)); |
|
1111 |
||
1112 |
fun rename_inconsistent thy = |
|
18217 | 1113 |
let |
18516 | 1114 |
fun get_inconsistent thyname = |
1115 |
let |
|
1116 |
val thy = theory thyname; |
|
1117 |
fun own_tables get = |
|
1118 |
(get thy) |
|
1119 |
|> fold (Symtab.fold (Symtab.remove (K true)) o get) (Theory.parents_of thy) |
|
1120 |
|> Symtab.keys; |
|
1121 |
val names = own_tables (#2 o #types o Type.rep_tsig o Sign.tsig_of) |
|
1122 |
@ own_tables (#2 o #declarations o Consts.dest o #consts o Sign.rep_sg); |
|
1123 |
fun diff names = |
|
1124 |
fold (fn name => |
|
1125 |
if is_prefix (op =) (NameSpace.unpack thyname) (NameSpace.unpack name) |
|
1126 |
then I |
|
1127 |
else cons (name, NameSpace.append thyname (NameSpace.base name))) names []; |
|
1128 |
in diff names end; |
|
1129 |
val inconsistent = map get_inconsistent (ThyInfo.names ()) |> Library.flat; |
|
1130 |
fun add (src, dst) thy = |
|
1131 |
if (is_some oo Symtab.lookup o fst o #alias o #logic_data o CodegenData.get) thy src |
|
1132 |
then (warning ("code generator alias already defined for " ^ quote src ^ ", will not overwrite"); thy) |
|
1133 |
else add_alias (src, dst) thy |
|
1134 |
in fold add inconsistent thy end; |
|
1135 |
||
18517 | 1136 |
fun ensure_datatype_case_consts get_datatype_case_consts get_case_const_data thy = |
1137 |
let |
|
1138 |
fun ensure case_c thy = |
|
1139 |
if |
|
1140 |
Symtab.defined ((#appconst o #gens o CodegenData.get) thy) case_c |
|
1141 |
then |
|
1142 |
(warning ("case constant " ^ quote case_c ^ " already present in application table, will not overwrite"); thy) |
|
1143 |
else |
|
1144 |
add_cg_case_const_i get_case_const_data case_c thy; |
|
1145 |
in |
|
1146 |
fold ensure (get_datatype_case_consts thy) thy |
|
1147 |
end; |
|
1148 |
||
18516 | 1149 |
|
1150 |
||
1151 |
(** target languages **) |
|
1152 |
||
1153 |
(* primitive definitions *) |
|
1154 |
||
18517 | 1155 |
fun read_const thy (raw_c, raw_ty) = |
1156 |
let |
|
1157 |
val c = Sign.intern_const thy raw_c; |
|
1158 |
val ty = case raw_ty |
|
1159 |
of NONE => Sign.the_const_constraint thy c |
|
1160 |
| SOME raw_ty => Sign.read_typ (thy, K NONE) raw_ty; |
|
1161 |
in (c, ty) end; |
|
1162 |
||
1163 |
fun gen_add_prim prep_name prep_primdef raw_name deps (target, raw_primdef) thy = |
|
18516 | 1164 |
let |
1165 |
val _ = if Symtab.defined ((#serialize_data o CodegenData.get) thy) target |
|
1166 |
then () else error ("unknown target language: " ^ quote target); |
|
1167 |
val tabs = mk_tabs thy; |
|
1168 |
val name = prep_name thy tabs raw_name; |
|
1169 |
val primdef = prep_primdef raw_primdef; |
|
18217 | 1170 |
in |
18516 | 1171 |
thy |
18517 | 1172 |
|> map_module (CodegenThingol.add_prim name deps (target, primdef)) |
18217 | 1173 |
end; |
1174 |
||
18516 | 1175 |
val add_prim_i = gen_add_prim ((K o K) I) I; |
1176 |
val add_prim_class = gen_add_prim |
|
1177 |
(fn thy => K (idf_of_name thy nsp_class o Sign.intern_class thy)) |
|
1178 |
(Pretty.str o newline_correct o Symbol.strip_blanks); |
|
1179 |
val add_prim_tyco = gen_add_prim |
|
1180 |
(fn thy => K (idf_of_name thy nsp_tyco o Sign.intern_type thy)) |
|
1181 |
(Pretty.str o newline_correct o Symbol.strip_blanks); |
|
1182 |
val add_prim_const = gen_add_prim |
|
18517 | 1183 |
(fn thy => fn tabs => idf_of_const thy tabs o read_const thy) |
18516 | 1184 |
(Pretty.str o newline_correct o Symbol.strip_blanks); |
1185 |
||
1186 |
val ensure_prim = (map_module o CodegenThingol.ensure_prim); |
|
18217 | 1187 |
|
18517 | 1188 |
|
18217 | 1189 |
(* syntax *) |
1190 |
||
18517 | 1191 |
fun gen_prep_mfx read_quote mk_quote tabs mfx thy = |
1192 |
let |
|
1193 |
val proto_mfx = Codegen.parse_mixfix (read_quote thy) mfx; |
|
1194 |
fun generate thy tabs = fold_map (mk_quote thy tabs) |
|
1195 |
(Codegen.quotes_of proto_mfx); |
|
1196 |
in |
|
1197 |
thy |
|
1198 |
|> expand_module tabs generate |
|
1199 |
|-> (fn tys => pair (Codegen.replace_quotes tys proto_mfx)) |
|
1200 |
end; |
|
1201 |
||
1202 |
fun gen_add_syntax_tyco prep_tyco prep_mfx raw_tyco (serial_name, (raw_mfx, fixity)) thy = |
|
18217 | 1203 |
let |
1204 |
val tyco = prep_tyco thy raw_tyco; |
|
18517 | 1205 |
val tabs = mk_tabs thy; |
18217 | 1206 |
in |
1207 |
thy |
|
18517 | 1208 |
|> ensure_prim tyco |
1209 |
|> prep_mfx tabs raw_mfx |
|
18217 | 1210 |
|-> (fn mfx => map_codegen_data |
1211 |
(fn (modl, gens, lookups, serialize_data, logic_data) => |
|
1212 |
(modl, gens, lookups, |
|
18335 | 1213 |
serialize_data |> check_for_serializer serial_name |> Symtab.map_entry serial_name |
18217 | 1214 |
(map_serialize_data |
18517 | 1215 |
(fn (syntax_tyco, syntax_const) => |
1216 |
(syntax_tyco |> Symtab.update_new |
|
1217 |
(tyco, |
|
18516 | 1218 |
(((Codegen.num_args_of mfx, fixity), Codegen.fillin_mixfix mfx), stamp ())), |
18217 | 1219 |
syntax_const))), |
1220 |
logic_data))) |
|
1221 |
end; |
|
1222 |
||
18517 | 1223 |
val add_syntax_tyco_i = gen_add_syntax_tyco (K I) (K pair); |
1224 |
val add_syntax_tyco = gen_add_syntax_tyco |
|
1225 |
(fn thy => idf_of_name thy nsp_tyco o Sign.intern_type thy) |
|
1226 |
(gen_prep_mfx (fn thy => typ_of o read_ctyp thy) |
|
1227 |
(fn thy => fn tabs => exprgen_type thy tabs o devarify_type)); |
|
1228 |
||
1229 |
fun gen_add_syntax_const prep_const prep_mfx raw_c (serial_name, (raw_mfx, fixity)) thy = |
|
18217 | 1230 |
let |
18454 | 1231 |
val tabs = mk_tabs thy; |
18517 | 1232 |
val c = prep_const thy tabs raw_c; |
18217 | 1233 |
in |
1234 |
thy |
|
18517 | 1235 |
|> ensure_prim c |
1236 |
|> prep_mfx tabs raw_mfx |
|
18217 | 1237 |
|-> (fn mfx => map_codegen_data |
1238 |
(fn (modl, gens, lookups, serialize_data, logic_data) => |
|
1239 |
(modl, gens, lookups, |
|
18335 | 1240 |
serialize_data |> check_for_serializer serial_name |> Symtab.map_entry serial_name |
18217 | 1241 |
(map_serialize_data |
18517 | 1242 |
(fn (syntax_tyco, syntax_const) => |
1243 |
(syntax_tyco, |
|
18516 | 1244 |
syntax_const |> Symtab.update_new |
18517 | 1245 |
(c, |
18516 | 1246 |
(((Codegen.num_args_of mfx, fixity), Codegen.fillin_mixfix mfx), stamp ()))))), |
18217 | 1247 |
logic_data))) |
1248 |
end; |
|
1249 |
||
18517 | 1250 |
val add_syntax_const_i = gen_add_syntax_const ((K o K) I) (K pair); |
1251 |
val add_syntax_const = gen_add_syntax_const |
|
1252 |
(fn thy => fn tabs => idf_of_const thy tabs o read_const thy) |
|
1253 |
(gen_prep_mfx (fn thy => term_of o read_cterm thy o rpair TypeInfer.logicT) |
|
1254 |
(fn thy => fn tabs => exprgen_term thy tabs o devarify_term)); |
|
18217 | 1255 |
|
1256 |
||
18516 | 1257 |
|
1258 |
(** code generation **) |
|
18217 | 1259 |
|
18231 | 1260 |
fun get_serializer thy serial_name = |
1261 |
(#serializer o (fn data => (the oo Symtab.lookup) data serial_name) |
|
1262 |
o #serialize_data o CodegenData.get) thy; |
|
1263 |
||
18247
b17724cae935
code generator: case expressions, improved name resolving
haftmann
parents:
18231
diff
changeset
|
1264 |
fun mk_const thy (f, s_ty) = |
18217 | 1265 |
let |
18231 | 1266 |
val f' = Sign.intern_const thy f; |
18247
b17724cae935
code generator: case expressions, improved name resolving
haftmann
parents:
18231
diff
changeset
|
1267 |
val ty = case s_ty |
b17724cae935
code generator: case expressions, improved name resolving
haftmann
parents:
18231
diff
changeset
|
1268 |
of NONE => Sign.the_const_constraint thy f' |
b17724cae935
code generator: case expressions, improved name resolving
haftmann
parents:
18231
diff
changeset
|
1269 |
| SOME s => Sign.read_typ (thy, K NONE) s; |
b17724cae935
code generator: case expressions, improved name resolving
haftmann
parents:
18231
diff
changeset
|
1270 |
in (f', ty) end; |
18231 | 1271 |
|
18247
b17724cae935
code generator: case expressions, improved name resolving
haftmann
parents:
18231
diff
changeset
|
1272 |
fun generate_code consts thy = |
18231 | 1273 |
let |
18454 | 1274 |
val tabs = mk_tabs thy; |
1275 |
val consts' = map (mk_const thy) consts; |
|
1276 |
fun generate thy tabs = fold_map (ensure_def_const thy tabs) consts' |
|
18217 | 1277 |
in |
1278 |
thy |
|
18454 | 1279 |
|> expand_module tabs generate |
1280 |
|-> (fn consts => pair consts) |
|
18217 | 1281 |
end; |
1282 |
||
1283 |
fun serialize_code serial_name filename consts thy = |
|
1284 |
let |
|
1285 |
val serialize_data = |
|
1286 |
thy |
|
1287 |
|> CodegenData.get |
|
1288 |
|> #serialize_data |
|
18335 | 1289 |
|> check_for_serializer serial_name |
18217 | 1290 |
|> (fn data => (the oo Symtab.lookup) data serial_name) |
18516 | 1291 |
val serializer' = (get_serializer thy serial_name) serial_name |
1292 |
((Option.map fst oo Symtab.lookup o #syntax_tyco) serialize_data) |
|
18517 | 1293 |
((Option.map fst oo Symtab.lookup o #syntax_const) serialize_data); |
18217 | 1294 |
val compile_it = serial_name = "ml" andalso filename = "-"; |
18282 | 1295 |
fun use_code code = |
18217 | 1296 |
if compile_it |
1297 |
then use_text Context.ml_output false code |
|
1298 |
else File.write (Path.unpack filename) (code ^ "\n"); |
|
1299 |
in |
|
1300 |
thy |
|
18247
b17724cae935
code generator: case expressions, improved name resolving
haftmann
parents:
18231
diff
changeset
|
1301 |
|> (if is_some consts then generate_code (the consts) else pair []) |
18231 | 1302 |
|-> (fn [] => `(serializer' NONE o #modl o CodegenData.get) |
1303 |
| consts => `(serializer' (SOME consts) o #modl o CodegenData.get)) |
|
18360 | 1304 |
|-> (fn code => ((use_code o Pretty.output) code; I)) |
18217 | 1305 |
end; |
1306 |
||
1307 |
||
18454 | 1308 |
|
18516 | 1309 |
(** toplevel interface **) |
18217 | 1310 |
|
1311 |
local |
|
1312 |
||
1313 |
structure P = OuterParse |
|
1314 |
and K = OuterKeyword |
|
1315 |
||
1316 |
in |
|
1317 |
||
18517 | 1318 |
val (classK, generateK, serializeK, |
1319 |
primclassK, primtycoK, primconstK, |
|
1320 |
syntax_tycoK, syntax_constK, aliasK) = |
|
1321 |
("code_class", "code_generate", "code_serialize", |
|
1322 |
"code_primclass", "code_primtyco", "code_primconst", |
|
1323 |
"code_syntax_tyco", "code_syntax_const", "code_alias"); |
|
1324 |
val (constantsK, dependingK) = |
|
1325 |
("constants", "depending_on"); |
|
18335 | 1326 |
|
1327 |
val classP = |
|
1328 |
OuterSyntax.command classK "codegen data for classes" K.thy_decl ( |
|
1329 |
P.xname |
|
1330 |
-- ((P.$$$ "\\<Rightarrow>" || P.$$$ "=>") |-- (P.list1 P.name)) |
|
1331 |
-- (Scan.optional ((P.$$$ "\\<Rightarrow>" || P.$$$ "=>") |-- (P.list1 P.name)) []) |
|
1332 |
>> (fn ((name, tycos), consts) => (Toplevel.theory (ClassPackage.add_classentry name consts tycos))) |
|
1333 |
) |
|
18217 | 1334 |
|
1335 |
val generateP = |
|
18282 | 1336 |
OuterSyntax.command generateK "generate executable code for constants" K.thy_decl ( |
18247
b17724cae935
code generator: case expressions, improved name resolving
haftmann
parents:
18231
diff
changeset
|
1337 |
Scan.repeat1 (P.name -- Scan.option (P.$$$ "::" |-- P.typ)) |
18217 | 1338 |
>> (fn consts => |
18231 | 1339 |
Toplevel.theory (generate_code consts #> snd)) |
18217 | 1340 |
); |
1341 |
||
1342 |
val serializeP = |
|
18282 | 1343 |
OuterSyntax.command serializeK "serialize executable code for constants" K.thy_decl ( |
18217 | 1344 |
P.name |
1345 |
-- P.name |
|
1346 |
-- Scan.option ( |
|
18380
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
1347 |
P.$$$ constantsK |
18247
b17724cae935
code generator: case expressions, improved name resolving
haftmann
parents:
18231
diff
changeset
|
1348 |
|-- Scan.repeat1 (P.name -- Scan.option (P.$$$ "::" |-- P.typ)) |
18217 | 1349 |
) |
1350 |
>> (fn ((serial_name, filename), consts) => |
|
1351 |
Toplevel.theory (serialize_code serial_name filename consts)) |
|
1352 |
); |
|
1353 |
||
1354 |
val aliasP = |
|
18282 | 1355 |
OuterSyntax.command aliasK "declare an alias for a theory identifier" K.thy_decl ( |
18517 | 1356 |
P.xname |
1357 |
-- P.xname |
|
18217 | 1358 |
>> (fn (src, dst) => Toplevel.theory (add_alias (src, dst))) |
1359 |
); |
|
1360 |
||
18517 | 1361 |
val primclassP = |
1362 |
OuterSyntax.command primclassK "define target-lanugage specific class" K.thy_decl ( |
|
1363 |
P.xname |
|
1364 |
-- Scan.repeat1 (P.name -- P.text) |
|
1365 |
-- Scan.optional (P.$$$ dependingK |-- Scan.repeat1 P.name) [] |
|
1366 |
>> (fn ((raw_class, primdefs), depends) => |
|
1367 |
(Toplevel.theory oo fold) (add_prim_class raw_class depends) primdefs) |
|
1368 |
); |
|
1369 |
||
1370 |
val primtycoP = |
|
1371 |
OuterSyntax.command primtycoK "define target-lanugage specific type constructor" K.thy_decl ( |
|
1372 |
P.xname |
|
1373 |
-- Scan.repeat1 (P.name -- P.text) |
|
1374 |
-- Scan.optional (P.$$$ dependingK |-- Scan.repeat1 P.name) [] |
|
1375 |
>> (fn ((raw_tyco, primdefs), depends) => |
|
1376 |
(Toplevel.theory oo fold) (add_prim_tyco raw_tyco depends) primdefs) |
|
1377 |
); |
|
1378 |
||
1379 |
val primconstP = |
|
1380 |
OuterSyntax.command primconstK "define target-lanugage specific constant" K.thy_decl ( |
|
1381 |
(P.xname -- Scan.option P.typ) |
|
1382 |
-- Scan.repeat1 (P.name -- P.text) |
|
1383 |
-- Scan.optional (P.$$$ dependingK |-- Scan.repeat1 P.name) [] |
|
1384 |
>> (fn ((raw_const, primdefs), depends) => |
|
1385 |
(Toplevel.theory oo fold) (add_prim_const raw_const depends) primdefs) |
|
1386 |
); |
|
1387 |
||
18217 | 1388 |
val syntax_tycoP = |
1389 |
OuterSyntax.command syntax_tycoK "define code syntax for type constructor" K.thy_decl ( |
|
18517 | 1390 |
P.xname |
18217 | 1391 |
-- Scan.repeat1 ( |
18517 | 1392 |
P.name -- (P.$$$ "(" |-- P.string --| P.$$$ ")") |
18516 | 1393 |
-- CodegenSerializer.parse_fixity |
18217 | 1394 |
) |
18517 | 1395 |
>> (fn (raw_tyco, stxs) => |
18217 | 1396 |
(Toplevel.theory oo fold) |
18517 | 1397 |
(fn ((target, raw_mfx), fixity) => |
1398 |
add_syntax_tyco raw_tyco (target, (raw_mfx, fixity))) stxs) |
|
18217 | 1399 |
); |
1400 |
||
1401 |
val syntax_constP = |
|
1402 |
OuterSyntax.command syntax_constK "define code syntax for constant" K.thy_decl ( |
|
18517 | 1403 |
(P.xname -- Scan.option (P.$$$ "::" |-- P.typ)) |
18217 | 1404 |
-- Scan.repeat1 ( |
18517 | 1405 |
P.name -- (P.$$$ "(" |-- P.string --| P.$$$ ")") |
18516 | 1406 |
-- CodegenSerializer.parse_fixity |
18217 | 1407 |
) |
18517 | 1408 |
>> (fn (raw_c, stxs) => |
18217 | 1409 |
(Toplevel.theory oo fold) |
18517 | 1410 |
(fn ((target, raw_mfx), fixity) => |
1411 |
add_syntax_const raw_c (target, (raw_mfx, fixity))) stxs) |
|
18217 | 1412 |
); |
1413 |
||
18517 | 1414 |
val _ = OuterSyntax.add_parsers [classP, generateP, serializeP, aliasP, |
1415 |
primclassP, primtycoP, primconstP, syntax_tycoP, syntax_constP]; |
|
1416 |
val _ = OuterSyntax.add_keywords ["\\<Rightarrow>", "=>", constantsK, dependingK]; |
|
18217 | 1417 |
|
1418 |
||
18516 | 1419 |
|
1420 |
(** setup **) |
|
1421 |
||
18217 | 1422 |
val _ = |
1423 |
let |
|
1424 |
val bool = Type ("bool", []); |
|
1425 |
val nat = Type ("nat", []); |
|
1426 |
val int = Type ("IntDef.int", []); |
|
1427 |
fun list t = Type ("List.list", [t]); |
|
1428 |
fun pair t1 t2 = Type ("*", [t1, t2]); |
|
1429 |
val A = TVar (("'a", 0), []); |
|
1430 |
val B = TVar (("'b", 0), []); |
|
1431 |
in Context.add_setup [ |
|
1432 |
CodegenData.init, |
|
18516 | 1433 |
add_appconst_i ("neg", ((0, 0), appgen_neg)), |
1434 |
add_appconst_i ("op =", ((2, 2), appgen_eq)), |
|
18217 | 1435 |
add_defgen ("clsdecl", defgen_clsdecl), |
18231 | 1436 |
add_defgen ("tyco_fallback", defgen_tyco_fallback), |
1437 |
add_defgen ("const_fallback", defgen_const_fallback), |
|
18217 | 1438 |
add_defgen ("defs", defgen_defs), |
1439 |
add_defgen ("clsmem", defgen_clsmem), |
|
1440 |
add_defgen ("clsinst", defgen_clsinst), |
|
18454 | 1441 |
add_alias ("op -->", "HOL.op_implies"), |
1442 |
add_alias ("op +", "HOL.op_add"), |
|
1443 |
add_alias ("op -", "HOL.op_minus"), |
|
1444 |
add_alias ("op *", "HOL.op_times"), |
|
18455 | 1445 |
add_alias ("op <=", "Orderings.op_le"), |
1446 |
add_alias ("op <", "Orderings.op_lt"), |
|
18454 | 1447 |
add_alias ("List.op @", "List.append"), |
1448 |
add_alias ("List.op mem", "List.member"), |
|
1449 |
add_alias ("Divides.op div", "Divides.div"), |
|
1450 |
add_alias ("Divides.op dvd", "Divides.dvd"), |
|
1451 |
add_alias ("Divides.op mod", "Divides.mod"), |
|
18217 | 1452 |
add_lookup_tyco ("bool", type_bool), |
18454 | 1453 |
add_lookup_tyco ("*", type_pair), |
18217 | 1454 |
add_lookup_tyco ("IntDef.int", type_integer), |
1455 |
add_lookup_tyco ("List.list", type_list), |
|
18231 | 1456 |
add_lookup_const (("True", bool), Cons_true), |
18217 | 1457 |
add_lookup_const (("False", bool), Cons_false), |
1458 |
add_lookup_const (("Not", bool --> bool), Fun_not), |
|
1459 |
add_lookup_const (("op &", bool --> bool --> bool), Fun_and), |
|
1460 |
add_lookup_const (("op |", bool --> bool --> bool), Fun_or), |
|
1461 |
add_lookup_const (("HOL.If", bool --> A --> A --> A), Fun_if), |
|
1462 |
add_lookup_const (("Pair", A --> B --> pair A B), Cons_pair), |
|
1463 |
add_lookup_const (("fst", pair A B --> A), Fun_fst), |
|
1464 |
add_lookup_const (("snd", pair A B --> B), Fun_snd), |
|
18454 | 1465 |
add_lookup_const (("List.list.Cons", A --> list A --> list A), Cons_cons), |
1466 |
add_lookup_const (("List.list.Nil", list A), Cons_nil), |
|
18217 | 1467 |
add_lookup_const (("1", nat), |
1468 |
IApp ( |
|
1469 |
IConst ("const.Suc", IFun (IType ("type.nat", []), IFun (IType ("type.nat", []), IType ("type.nat", [])))), |
|
1470 |
IConst ("const.Zero", IType ("type.nat", [])) |
|
1471 |
)), |
|
1472 |
add_lookup_const (("0", int), Fun_0), |
|
1473 |
add_lookup_const (("1", int), Fun_1), |
|
1474 |
add_lookup_const (("op +", int --> int --> int), Fun_add), |
|
1475 |
add_lookup_const (("op *", int --> int --> int), Fun_mult), |
|
1476 |
add_lookup_const (("uminus", int --> int), Fun_minus), |
|
1477 |
add_lookup_const (("op <", int --> int --> bool), Fun_lt), |
|
1478 |
add_lookup_const (("op <=", int --> int --> bool), Fun_le), |
|
18454 | 1479 |
add_lookup_const (("Wellfounded_Recursion.wfrec", ((A --> B) --> A --> B) --> A --> B), Fun_wfrec) |
18217 | 1480 |
] end; |
1481 |
||
1482 |
(* "op /" ??? *) |
|
1483 |
||
1484 |
end; (* local *) |
|
1485 |
||
1486 |
end; (* struct *) |