author | haftmann |
Tue, 31 Jan 2006 16:14:37 +0100 | |
changeset 18865 | 31aed965135c |
parent 18850 | 92ef83e5eaea |
child 18885 | ee8b5c36ba2b |
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 |
|
45def66f86cb
added modules for code generator generation two, not operational yet
haftmann
parents:
diff
changeset
|
9 |
signature CODEGEN_PACKAGE = |
45def66f86cb
added modules for code generator generation two, not operational yet
haftmann
parents:
diff
changeset
|
10 |
sig |
18454 | 11 |
type auxtab; |
18702 | 12 |
type eqextr = theory -> auxtab |
13 |
-> (string * typ) -> (thm list * typ) option; |
|
18217 | 14 |
type defgen; |
18702 | 15 |
type appgen = theory -> auxtab |
18756 | 16 |
-> (string * typ) * term list -> CodegenThingol.transact |
17 |
-> CodegenThingol.iexpr * CodegenThingol.transact; |
|
18702 | 18 |
|
18516 | 19 |
val add_appconst: string * ((int * int) * appgen) -> theory -> theory; |
18517 | 20 |
val add_appconst_i: xstring * ((int * int) * appgen) -> theory -> theory; |
18702 | 21 |
val add_eqextr: string * eqextr -> theory -> theory; |
18517 | 22 |
val add_prim_class: xstring -> string list -> (string * string) |
23 |
-> theory -> theory; |
|
24 |
val add_prim_tyco: xstring -> string list -> (string * string) |
|
25 |
-> theory -> theory; |
|
26 |
val add_prim_const: xstring * string option -> string list -> (string * string) |
|
27 |
-> theory -> theory; |
|
28 |
val add_prim_i: string -> string list -> (string * Pretty.T) |
|
29 |
-> theory -> theory; |
|
18704
2c86ced392a8
substantial improvement in serialization handling
haftmann
parents:
18702
diff
changeset
|
30 |
val add_pretty_list: string -> string -> string * (int * string) |
2c86ced392a8
substantial improvement in serialization handling
haftmann
parents:
18702
diff
changeset
|
31 |
-> theory -> theory; |
18217 | 32 |
val add_alias: string * string -> theory -> theory; |
33 |
val set_is_datatype: (theory -> string -> bool) -> theory -> theory; |
|
18455 | 34 |
val set_get_all_datatype_cons : (theory -> (string * string) list) |
18454 | 35 |
-> theory -> theory; |
18865 | 36 |
val set_defgen_datatype: defgen -> theory -> theory; |
18702 | 37 |
val set_int_tyco: string -> theory -> theory; |
18217 | 38 |
|
18516 | 39 |
val exprgen_type: theory -> auxtab |
18217 | 40 |
-> typ -> CodegenThingol.transact -> CodegenThingol.itype * CodegenThingol.transact; |
18516 | 41 |
val exprgen_term: theory -> auxtab |
18217 | 42 |
-> term -> CodegenThingol.transact -> CodegenThingol.iexpr * CodegenThingol.transact; |
18702 | 43 |
val appgen_default: appgen; |
18217 | 44 |
|
18335 | 45 |
val appgen_let: (int -> term -> term list * term) |
46 |
-> appgen; |
|
47 |
val appgen_split: (int -> term -> term list * term) |
|
48 |
-> appgen; |
|
18702 | 49 |
val appgen_number_of: (term -> term) -> (term -> IntInf.int) -> string -> string |
18335 | 50 |
-> appgen; |
18702 | 51 |
val add_case_const: (theory -> string -> (string * int) list option) -> xstring |
18517 | 52 |
-> theory -> theory; |
18702 | 53 |
val add_case_const_i: (theory -> string -> (string * int) list option) -> string |
18517 | 54 |
-> theory -> theory; |
18865 | 55 |
val defgen_datatype_proto: (theory -> string -> ((string * sort) list * string list) option) |
18335 | 56 |
-> (theory -> string * string -> typ list option) |
18217 | 57 |
-> defgen; |
58 |
||
18247
b17724cae935
code generator: case expressions, improved name resolving
haftmann
parents:
18231
diff
changeset
|
59 |
val print_codegen_generated: theory -> unit; |
18454 | 60 |
val rename_inconsistent: theory -> theory; |
18517 | 61 |
val ensure_datatype_case_consts: (theory -> string list) |
62 |
-> (theory -> string -> (string * int) list option) |
|
63 |
-> theory -> theory; |
|
18515 | 64 |
|
65 |
(*debugging purpose only*) |
|
18454 | 66 |
structure InstNameMangler: NAME_MANGLER; |
67 |
structure ConstNameMangler: NAME_MANGLER; |
|
68 |
structure DatatypeconsNameMangler: NAME_MANGLER; |
|
18231 | 69 |
structure CodegenData: THEORY_DATA; |
18454 | 70 |
val mk_tabs: theory -> auxtab; |
71 |
val alias_get: theory -> string -> string; |
|
18515 | 72 |
val idf_of_name: theory -> string -> string -> string; |
73 |
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
|
74 |
end; |
45def66f86cb
added modules for code generator generation two, not operational yet
haftmann
parents:
diff
changeset
|
75 |
|
18217 | 76 |
structure CodegenPackage : CODEGEN_PACKAGE = |
18169
45def66f86cb
added modules for code generator generation two, not operational yet
haftmann
parents:
diff
changeset
|
77 |
struct |
45def66f86cb
added modules for code generator generation two, not operational yet
haftmann
parents:
diff
changeset
|
78 |
|
18850 | 79 |
open CodegenThingol; |
18385 | 80 |
infix 8 `%%; |
81 |
infixr 6 `->; |
|
82 |
infixr 6 `-->; |
|
83 |
infix 4 `$; |
|
84 |
infix 4 `$$; |
|
85 |
infixr 5 `|->; |
|
86 |
infixr 5 `|-->; |
|
18217 | 87 |
|
88 |
(* auxiliary *) |
|
89 |
||
18865 | 90 |
fun devarify_type ty = (fst o Type.freeze_thaw_type o Term.zero_var_indexesT) ty; |
91 |
fun devarify_term t = (fst o Type.freeze_thaw o Term.zero_var_indexes) t; |
|
18454 | 92 |
|
93 |
val is_number = is_some o Int.fromString; |
|
18217 | 94 |
|
18702 | 95 |
fun merge_opt _ (x1, NONE) = x1 |
96 |
| merge_opt _ (NONE, x2) = x2 |
|
97 |
| merge_opt eq (SOME x1, SOME x2) = |
|
98 |
if eq (x1, x2) then SOME x1 else error ("incompatible options during merge"); |
|
18217 | 99 |
|
100 |
||
18702 | 101 |
(* shallow name spaces *) |
18217 | 102 |
|
103 |
val nsp_class = "class"; |
|
18454 | 104 |
val nsp_tyco = "tyco"; |
18217 | 105 |
val nsp_const = "const"; |
18454 | 106 |
val nsp_overl = "overl"; |
107 |
val nsp_dtcon = "dtcon"; |
|
18217 | 108 |
val nsp_mem = "mem"; |
109 |
val nsp_inst = "inst"; |
|
110 |
||
111 |
||
18702 | 112 |
(* code generator basics *) |
18454 | 113 |
|
114 |
structure InstNameMangler = NameManglerFun ( |
|
115 |
type ctxt = theory; |
|
116 |
type src = string * (class * string); |
|
117 |
val ord = prod_ord string_ord (prod_ord string_ord string_ord); |
|
118 |
fun mk thy ((thyname, (cls, tyco)), i) = |
|
119 |
NameSpace.base cls ^ "_" ^ NameSpace.base tyco ^ implode (replicate i "'") |
|
120 |
|> NameSpace.append thyname; |
|
121 |
fun is_valid _ _ = true; |
|
122 |
fun maybe_unique _ _ = NONE; |
|
123 |
fun re_mangle _ dst = error ("no such instance: " ^ quote dst); |
|
124 |
); |
|
125 |
||
126 |
structure ConstNameMangler = NameManglerFun ( |
|
127 |
type ctxt = theory; |
|
128 |
type src = string * (typ * typ); |
|
129 |
val ord = prod_ord string_ord (prod_ord Term.typ_ord Term.typ_ord); |
|
130 |
fun mk thy ((c, (ty_decl, ty)), i) = |
|
131 |
let |
|
132 |
fun mangle (Type (tyco, tys)) = |
|
133 |
NameSpace.base tyco :: Library.flat (List.mapPartial mangle tys) |> SOME |
|
134 |
| mangle _ = |
|
135 |
NONE |
|
136 |
in |
|
137 |
Vartab.empty |
|
138 |
|> Sign.typ_match thy (ty_decl, ty) |
|
139 |
|> map (snd o snd) o Vartab.dest |
|
140 |
|> List.mapPartial mangle |
|
141 |
|> Library.flat |
|
142 |
|> null ? K ["x"] |
|
143 |
|> cons c |
|
144 |
|> space_implode "_" |
|
145 |
|> curry (op ^ o swap) ((implode oo replicate) i "'") |
|
146 |
end; |
|
147 |
fun is_valid _ _ = true; |
|
148 |
fun maybe_unique _ _ = NONE; |
|
149 |
fun re_mangle _ dst = error ("no such constant: " ^ quote dst); |
|
150 |
); |
|
151 |
||
152 |
structure DatatypeconsNameMangler = NameManglerFun ( |
|
153 |
type ctxt = theory; |
|
154 |
type src = string * string; |
|
155 |
val ord = prod_ord string_ord string_ord; |
|
18702 | 156 |
fun mk thy ((co, dtco), i) = |
18454 | 157 |
let |
158 |
fun basename 0 = NameSpace.base co |
|
18455 | 159 |
| basename 1 = NameSpace.base dtco ^ "_" ^ NameSpace.base co |
18454 | 160 |
| basename i = NameSpace.base dtco ^ "_" ^ NameSpace.base co ^ "_" ^ (implode oo replicate) (i-1) "'"; |
161 |
fun strip_dtco name = |
|
162 |
case (rev o NameSpace.unpack) name |
|
163 |
of x1::x2::xs => |
|
164 |
if x2 = NameSpace.base dtco |
|
165 |
then NameSpace.pack (x1::xs) |
|
166 |
else name |
|
167 |
| _ => name; |
|
168 |
in |
|
169 |
NameSpace.append (NameSpace.drop_base dtco) (basename i) |
|
170 |
|> strip_dtco |
|
171 |
end; |
|
172 |
fun is_valid _ _ = true; |
|
173 |
fun maybe_unique _ _ = NONE; |
|
174 |
fun re_mangle _ dst = error ("no such datatype constructor: " ^ quote dst); |
|
175 |
); |
|
176 |
||
18702 | 177 |
type auxtab = ((typ * thm) list Symtab.table * string Symtab.table) |
18865 | 178 |
* (InstNameMangler.T * ((typ * typ list) Symtab.table * ConstNameMangler.T) |
179 |
* DatatypeconsNameMangler.T); |
|
18702 | 180 |
type eqextr = theory -> auxtab |
181 |
-> (string * typ) -> (thm list * typ) option; |
|
18454 | 182 |
type defgen = theory -> auxtab -> gen_defgen; |
18865 | 183 |
type appgen = theory -> auxtab |
184 |
-> (string * typ) * term list -> transact -> iexpr * transact; |
|
18217 | 185 |
|
18702 | 186 |
val serializers = ref ( |
187 |
Symtab.empty |
|
188 |
|> Symtab.update ( |
|
189 |
#ml CodegenSerializer.serializers |
|
190 |
|> apsnd (fn seri => seri |
|
18865 | 191 |
(nsp_dtcon, nsp_class, K false) |
192 |
[[nsp_class, nsp_tyco], [nsp_const, nsp_overl, nsp_dtcon, nsp_class, nsp_mem, nsp_inst]] |
|
18702 | 193 |
) |
194 |
) |
|
195 |
|> Symtab.update ( |
|
196 |
#haskell CodegenSerializer.serializers |
|
197 |
|> apsnd (fn seri => seri |
|
198 |
nsp_dtcon |
|
199 |
[[nsp_class], [nsp_tyco], [nsp_const, nsp_overl, nsp_mem], [nsp_dtcon], [nsp_inst]] |
|
200 |
) |
|
201 |
) |
|
202 |
); |
|
18217 | 203 |
|
204 |
||
18454 | 205 |
(* theory data for code generator *) |
18217 | 206 |
|
207 |
type gens = { |
|
18516 | 208 |
appconst: ((int * int) * (appgen * stamp)) Symtab.table, |
18865 | 209 |
eqextrs: (string * (eqextr * stamp)) list |
18217 | 210 |
}; |
211 |
||
18865 | 212 |
fun map_gens f { appconst, eqextrs } = |
18217 | 213 |
let |
18865 | 214 |
val (appconst, eqextrs) = |
215 |
f (appconst, eqextrs) |
|
216 |
in { appconst = appconst, eqextrs = eqextrs } : gens end; |
|
18217 | 217 |
|
218 |
fun merge_gens |
|
18865 | 219 |
({ appconst = appconst1 , eqextrs = eqextrs1 }, |
220 |
{ appconst = appconst2 , eqextrs = eqextrs2 }) = |
|
18516 | 221 |
{ appconst = Symtab.merge |
18865 | 222 |
(fn ((bounds1, (_, stamp1)), (bounds2, (_, stamp2))) => bounds1 = bounds2 |
223 |
andalso stamp1 = stamp2) |
|
18516 | 224 |
(appconst1, appconst2), |
18865 | 225 |
eqextrs = AList.merge (op =) (eq_snd (op =)) (eqextrs1, eqextrs2) |
18702 | 226 |
} : gens; |
18217 | 227 |
|
228 |
type logic_data = { |
|
229 |
is_datatype: ((theory -> string -> bool) * stamp) option, |
|
18455 | 230 |
get_all_datatype_cons: ((theory -> (string * string) list) * stamp) option, |
18865 | 231 |
defgen_datatype: (defgen * stamp) option, |
18217 | 232 |
alias: string Symtab.table * string Symtab.table |
233 |
}; |
|
234 |
||
18865 | 235 |
fun map_logic_data f { is_datatype, get_all_datatype_cons, defgen_datatype, alias } = |
18217 | 236 |
let |
18865 | 237 |
val ((is_datatype, get_all_datatype_cons, defgen_datatype), alias) = |
238 |
f ((is_datatype, get_all_datatype_cons, defgen_datatype), alias) |
|
18702 | 239 |
in { is_datatype = is_datatype, get_all_datatype_cons = get_all_datatype_cons, |
18865 | 240 |
defgen_datatype = defgen_datatype, alias = alias } : logic_data end; |
18217 | 241 |
|
242 |
fun merge_logic_data |
|
18702 | 243 |
({ is_datatype = is_datatype1, get_all_datatype_cons = get_all_datatype_cons1, |
18865 | 244 |
defgen_datatype = defgen_datatype1, alias = alias1 }, |
18702 | 245 |
{ is_datatype = is_datatype2, get_all_datatype_cons = get_all_datatype_cons2, |
18865 | 246 |
defgen_datatype = defgen_datatype2, alias = alias2 }) = |
18217 | 247 |
let |
248 |
in |
|
249 |
{ is_datatype = merge_opt (eq_snd (op =)) (is_datatype1, is_datatype2), |
|
18865 | 250 |
get_all_datatype_cons = merge_opt (eq_snd (op =)) |
251 |
(get_all_datatype_cons1, get_all_datatype_cons2), |
|
252 |
defgen_datatype = merge_opt (eq_snd (op =)) (defgen_datatype1, defgen_datatype2), |
|
18217 | 253 |
alias = (Symtab.merge (op =) (fst alias1, fst alias2), |
18304 | 254 |
Symtab.merge (op =) (snd alias1, snd alias2)) } : logic_data |
18217 | 255 |
end; |
256 |
||
18702 | 257 |
type target_data = { |
18865 | 258 |
syntax_class: string Symtab.table, |
18516 | 259 |
syntax_tyco: (itype CodegenSerializer.pretty_syntax * stamp) Symtab.table, |
260 |
syntax_const: (iexpr CodegenSerializer.pretty_syntax * stamp) Symtab.table |
|
18217 | 261 |
}; |
262 |
||
18865 | 263 |
fun map_target_data f { syntax_class, syntax_tyco, syntax_const } = |
18217 | 264 |
let |
18865 | 265 |
val (syntax_class, syntax_tyco, syntax_const) = |
266 |
f (syntax_class, syntax_tyco, syntax_const) |
|
267 |
in { |
|
268 |
syntax_class = syntax_class, |
|
269 |
syntax_tyco = syntax_tyco, |
|
270 |
syntax_const = syntax_const } : target_data |
|
18454 | 271 |
end; |
18217 | 272 |
|
18702 | 273 |
fun merge_target_data |
18865 | 274 |
({ syntax_class = syntax_class1, syntax_tyco = syntax_tyco1, syntax_const = syntax_const1 }, |
275 |
{ syntax_class = syntax_class2, syntax_tyco = syntax_tyco2, syntax_const = syntax_const2 }) = |
|
276 |
{ syntax_class = Symtab.merge (op =) (syntax_class1, syntax_class2), |
|
277 |
syntax_tyco = Symtab.merge (eq_snd (op =)) (syntax_tyco1, syntax_tyco2), |
|
18702 | 278 |
syntax_const = Symtab.merge (eq_snd (op =)) (syntax_const1, syntax_const2) } : target_data; |
18217 | 279 |
|
280 |
structure CodegenData = TheoryDataFun |
|
281 |
(struct |
|
282 |
val name = "Pure/codegen_package"; |
|
283 |
type T = { |
|
284 |
modl: module, |
|
285 |
gens: gens, |
|
286 |
logic_data: logic_data, |
|
18702 | 287 |
target_data: target_data Symtab.table |
18217 | 288 |
}; |
289 |
val empty = { |
|
290 |
modl = empty_module, |
|
18865 | 291 |
gens = { appconst = Symtab.empty, eqextrs = [] } : gens, |
18454 | 292 |
logic_data = { is_datatype = NONE, get_all_datatype_cons = NONE, |
18865 | 293 |
defgen_datatype = NONE, |
18454 | 294 |
alias = (Symtab.empty, Symtab.empty) } : logic_data, |
18702 | 295 |
target_data = |
18217 | 296 |
Symtab.empty |
18702 | 297 |
|> Symtab.fold (fn (target, _) => |
18865 | 298 |
Symtab.update (target, |
299 |
{ syntax_class = Symtab.empty, syntax_tyco = Symtab.empty, syntax_const = Symtab.empty }) |
|
18702 | 300 |
) (! serializers) |
18217 | 301 |
} : T; |
302 |
val copy = I; |
|
303 |
val extend = I; |
|
304 |
fun merge _ ( |
|
18702 | 305 |
{ modl = modl1, gens = gens1, |
306 |
target_data = target_data1, logic_data = logic_data1 }, |
|
307 |
{ modl = modl2, gens = gens2, |
|
308 |
target_data = target_data2, logic_data = logic_data2 } |
|
18217 | 309 |
) = { |
310 |
modl = merge_module (modl1, modl2), |
|
311 |
gens = merge_gens (gens1, gens2), |
|
312 |
logic_data = merge_logic_data (logic_data1, logic_data2), |
|
18702 | 313 |
target_data = Symtab.join (K (merge_target_data #> SOME)) |
314 |
(target_data1, target_data2) |
|
18217 | 315 |
}; |
18708 | 316 |
fun print _ _ = (); |
18217 | 317 |
end); |
318 |
||
18708 | 319 |
val _ = Context.add_setup CodegenData.init; |
320 |
||
18217 | 321 |
fun map_codegen_data f thy = |
322 |
case CodegenData.get thy |
|
18702 | 323 |
of { modl, gens, target_data, logic_data } => |
324 |
let val (modl, gens, target_data, logic_data) = |
|
325 |
f (modl, gens, target_data, logic_data) |
|
326 |
in CodegenData.put { modl = modl, gens = gens, |
|
327 |
target_data = target_data, logic_data = logic_data } thy end; |
|
18217 | 328 |
|
18517 | 329 |
fun print_codegen_generated thy = |
330 |
let |
|
331 |
val module = (#modl o CodegenData.get) thy; |
|
332 |
in |
|
333 |
(writeln o Pretty.output o Pretty.chunks) [pretty_module module, pretty_deps module] |
|
334 |
end; |
|
18217 | 335 |
|
336 |
||
18865 | 337 |
(* name handling *) |
18217 | 338 |
|
339 |
fun add_alias (src, dst) = |
|
340 |
map_codegen_data |
|
18702 | 341 |
(fn (modl, gens, target_data, logic_data) => |
342 |
(modl, gens, target_data, |
|
18217 | 343 |
logic_data |> map_logic_data |
344 |
(apsnd (fn (tab, tab_rev) => |
|
345 |
(tab |> Symtab.update (src, dst), |
|
346 |
tab_rev |> Symtab.update (dst, src)))))); |
|
347 |
||
18454 | 348 |
val alias_get = perhaps o Symtab.lookup o fst o #alias o #logic_data o CodegenData.get; |
349 |
val alias_rev = perhaps o Symtab.lookup o snd o #alias o #logic_data o CodegenData.get; |
|
18217 | 350 |
|
18454 | 351 |
fun add_nsp shallow name = |
352 |
name |
|
353 |
|> NameSpace.unpack |
|
354 |
|> split_last |
|
355 |
|> apsnd (single #> cons shallow) |
|
356 |
|> (op @) |
|
357 |
|> NameSpace.pack; |
|
18702 | 358 |
|
18454 | 359 |
fun dest_nsp nsp idf = |
18217 | 360 |
let |
361 |
val idf' = NameSpace.unpack idf; |
|
362 |
val (idf'', idf_base) = split_last idf'; |
|
363 |
val (modl, shallow) = split_last idf''; |
|
364 |
in |
|
365 |
if nsp = shallow |
|
18454 | 366 |
then (SOME o NameSpace.pack) (modl @ [idf_base]) |
18217 | 367 |
else NONE |
368 |
end; |
|
369 |
||
18454 | 370 |
fun idf_of_name thy shallow name = |
18702 | 371 |
name |
372 |
|> alias_get thy |
|
373 |
|> add_nsp shallow; |
|
374 |
||
18454 | 375 |
fun name_of_idf thy shallow idf = |
376 |
idf |
|
377 |
|> dest_nsp shallow |
|
378 |
|> Option.map (alias_rev thy); |
|
18217 | 379 |
|
18865 | 380 |
fun idf_of_const thy (tabs as ((_, clsmemtab), (_, (overltab1, overltab2), dtcontab))) |
381 |
(c, ty) = |
|
18454 | 382 |
let |
18515 | 383 |
fun get_overloaded (c, ty) = |
384 |
case Symtab.lookup overltab1 c |
|
385 |
of SOME (ty_decl, tys) => |
|
386 |
(case find_first (curry (Sign.typ_instance thy) ty) tys |
|
387 |
of SOME ty' => ConstNameMangler.get thy overltab2 |
|
388 |
(idf_of_name thy nsp_overl c, (ty_decl, ty')) |> SOME |
|
389 |
| _ => NONE) |
|
390 |
| _ => NONE |
|
391 |
fun get_datatypecons (c, ty) = |
|
392 |
case (snd o strip_type) ty |
|
393 |
of Type (tyco, _) => |
|
394 |
try (DatatypeconsNameMangler.get thy dtcontab) (c, tyco) |
|
395 |
| _ => NONE; |
|
18702 | 396 |
in case get_datatypecons (c, ty) |
397 |
of SOME c' => idf_of_name thy nsp_dtcon c' |
|
398 |
| NONE => case get_overloaded (c, ty) |
|
18515 | 399 |
of SOME idf => idf |
400 |
| NONE => case Symtab.lookup clsmemtab c |
|
401 |
of SOME _ => idf_of_name thy nsp_mem c |
|
402 |
| NONE => idf_of_name thy nsp_const c |
|
403 |
end; |
|
18217 | 404 |
|
18454 | 405 |
fun recconst_of_idf thy (_, (_, (_, overltab2), _)) idf = |
406 |
case name_of_idf thy nsp_const idf |
|
18702 | 407 |
of SOME c => SOME (c, Sign.the_const_type thy c) |
18454 | 408 |
| NONE => ( |
409 |
case dest_nsp nsp_overl idf |
|
410 |
of SOME _ => |
|
411 |
idf |
|
412 |
|> ConstNameMangler.rev thy overltab2 |
|
413 |
|> apfst (the o name_of_idf thy nsp_overl) |
|
414 |
|> apsnd snd |
|
415 |
|> SOME |
|
416 |
| NONE => NONE |
|
417 |
); |
|
418 |
||
18865 | 419 |
|
420 |
(* further theory data accessors *) |
|
421 |
||
422 |
fun gen_add_appconst prep_const (raw_c, (bounds, ag)) thy = |
|
18454 | 423 |
let |
18865 | 424 |
val c = prep_const thy raw_c; |
425 |
in map_codegen_data |
|
426 |
(fn (modl, gens, target_data, logic_data) => |
|
427 |
(modl, |
|
428 |
gens |> map_gens |
|
429 |
(fn (appconst, eqextrs) => |
|
430 |
(appconst |
|
431 |
|> Symtab.update (c, (bounds, (ag, stamp ()))), |
|
432 |
eqextrs)), target_data, logic_data)) thy |
|
18454 | 433 |
end; |
18217 | 434 |
|
18865 | 435 |
val add_appconst = gen_add_appconst Sign.intern_const; |
436 |
val add_appconst_i = gen_add_appconst (K I); |
|
437 |
||
438 |
fun add_eqextr (name, eqx) = |
|
439 |
map_codegen_data |
|
440 |
(fn (modl, gens, target_data, logic_data) => |
|
441 |
(modl, |
|
442 |
gens |> map_gens |
|
443 |
(fn (appconst, eqextrs) => |
|
444 |
(appconst, eqextrs |
|
445 |
|> Output.update_warn (op =) ("overwriting existing equation extractor " ^ name) |
|
446 |
(name, (eqx, stamp ())))), |
|
447 |
target_data, logic_data)); |
|
448 |
||
449 |
fun get_eqextrs thy tabs = |
|
450 |
(map (fn (_, (eqx, _)) => eqx thy tabs) o #eqextrs o #gens o CodegenData.get) thy; |
|
451 |
||
452 |
fun set_is_datatype f = |
|
453 |
map_codegen_data |
|
454 |
(fn (modl, gens, target_data, logic_data) => |
|
455 |
(modl, gens, target_data, |
|
456 |
logic_data |
|
457 |
|> map_logic_data (apfst (fn (is_datatype, get_all_datatype_cons, defgen_datatype) |
|
458 |
=> (SOME (f, stamp ()), get_all_datatype_cons, defgen_datatype))))); |
|
459 |
||
460 |
fun is_datatype thy = |
|
461 |
case (#is_datatype o #logic_data o CodegenData.get) thy |
|
462 |
of NONE => K false |
|
463 |
| SOME (f, _) => f thy; |
|
464 |
||
465 |
fun set_get_all_datatype_cons f = |
|
466 |
map_codegen_data |
|
467 |
(fn (modl, gens, target_data, logic_data) => |
|
468 |
(modl, gens, target_data, |
|
469 |
logic_data |
|
470 |
|> map_logic_data ((apfst (fn (is_datatype, get_all_datatype_cons, defgen_datatype) |
|
471 |
=> (is_datatype, SOME (f, stamp ()), defgen_datatype)))))); |
|
472 |
||
473 |
fun get_all_datatype_cons thy = |
|
474 |
case (#get_all_datatype_cons o #logic_data o CodegenData.get) thy |
|
475 |
of NONE => [] |
|
476 |
| SOME (f, _) => f thy; |
|
477 |
||
478 |
fun set_defgen_datatype f = |
|
479 |
map_codegen_data |
|
480 |
(fn (modl, gens, target_data, logic_data) => |
|
481 |
(modl, gens, target_data, |
|
482 |
logic_data |
|
483 |
|> map_logic_data ((apfst (fn (is_datatype, get_all_datatype_cons, defgen_datatype) |
|
484 |
=> (is_datatype, get_all_datatype_cons, SOME (f, stamp ()))))))); |
|
485 |
||
486 |
fun defgen_datatype thy tabs dtco trns = |
|
487 |
case (#defgen_datatype o #logic_data o CodegenData.get) thy |
|
488 |
of NONE => |
|
489 |
trns |
|
490 |
|> fail ("no datatype definition generator present") |
|
491 |
| SOME (f, _) => |
|
492 |
trns |
|
493 |
|> f thy tabs dtco; |
|
494 |
||
495 |
fun set_int_tyco tyco thy = |
|
496 |
(serializers := ( |
|
497 |
! serializers |
|
498 |
|> Symtab.update ( |
|
499 |
#ml CodegenSerializer.serializers |
|
500 |
|> apsnd (fn seri => seri |
|
501 |
(nsp_dtcon, nsp_class, fn tyco' => tyco' = idf_of_name thy nsp_tyco tyco ) |
|
502 |
[[nsp_class, nsp_tyco], [nsp_const, nsp_overl, nsp_dtcon, nsp_mem, nsp_inst]] |
|
503 |
) |
|
504 |
) |
|
505 |
); thy); |
|
506 |
||
507 |
||
508 |
(* definition and expression generators *) |
|
509 |
||
510 |
fun ensure_def_class thy tabs cls trns = |
|
18454 | 511 |
let |
18865 | 512 |
fun defgen_class thy (tabs as (_, (insttab, _, _))) cls trns = |
513 |
case name_of_idf thy nsp_class cls |
|
514 |
of SOME cls => |
|
515 |
let |
|
516 |
val cs = (snd o ClassPackage.the_consts_sign thy) cls; |
|
517 |
val sortctxts = map (ClassPackage.extract_sortctxt thy o snd) cs; |
|
518 |
val idfs = map (idf_of_name thy nsp_mem o fst) cs; |
|
519 |
in |
|
520 |
trns |
|
521 |
|> debug 5 (fn _ => "trying defgen class declaration for " ^ quote cls) |
|
522 |
|> fold_map (ensure_def_class thy tabs) (ClassPackage.the_superclasses thy cls) |
|
523 |
||>> fold_map (exprgen_type thy tabs o devarify_type o snd) cs |
|
524 |
||>> (fold_map o fold_map) (exprgen_tyvar_sort thy tabs) sortctxts |
|
525 |
|-> (fn ((supcls, memtypes), sortctxts) => succeed |
|
526 |
(Class ((supcls, ("a", idfs ~~ (sortctxts ~~ memtypes))), []))) |
|
527 |
end |
|
528 |
| _ => |
|
529 |
trns |
|
530 |
|> fail ("no class definition found for " ^ quote cls); |
|
531 |
val cls' = idf_of_name thy nsp_class cls; |
|
18454 | 532 |
in |
533 |
trns |
|
18865 | 534 |
|> debug 4 (fn _ => "generating class " ^ quote cls) |
535 |
|> gen_ensure_def [("class", defgen_class thy tabs)] ("generating class " ^ quote cls) cls' |
|
536 |
|> pair cls' |
|
537 |
end |
|
538 |
and ensure_def_tyco thy tabs tyco trns = |
|
539 |
let |
|
540 |
val tyco' = idf_of_name thy nsp_tyco tyco; |
|
541 |
in |
|
542 |
trns |
|
543 |
|> debug 4 (fn _ => "generating type constructor " ^ quote tyco) |
|
544 |
|> gen_ensure_def [("datatype", defgen_datatype thy tabs)] ("generating type constructor " ^ quote tyco) tyco' |
|
545 |
|> pair tyco' |
|
546 |
end |
|
547 |
and exprgen_tyvar_sort thy tabs (v, sort) trns = |
|
18516 | 548 |
trns |
549 |
|> fold_map (ensure_def_class thy tabs) (ClassPackage.syntactic_sort_of thy sort) |
|
18865 | 550 |
|-> (fn sort => pair (unprefix "'" v, sort)) |
551 |
and exprgen_type thy tabs (TVar _) trns = |
|
18516 | 552 |
error "TVar encountered during code generation" |
18702 | 553 |
| exprgen_type thy tabs (TFree v_s) trns = |
18516 | 554 |
trns |
18702 | 555 |
|> exprgen_tyvar_sort thy tabs v_s |
556 |
|-> (fn v_s => pair (IVarT v_s)) |
|
18516 | 557 |
| exprgen_type thy tabs (Type ("fun", [t1, t2])) trns = |
558 |
trns |
|
559 |
|> exprgen_type thy tabs t1 |
|
560 |
||>> exprgen_type thy tabs t2 |
|
561 |
|-> (fn (t1', t2') => pair (t1' `-> t2')) |
|
562 |
| exprgen_type thy tabs (Type (tyco, tys)) trns = |
|
563 |
trns |
|
564 |
|> ensure_def_tyco thy tabs tyco |
|
565 |
||>> fold_map (exprgen_type thy tabs) tys |
|
566 |
|-> (fn (tyco, tys) => pair (tyco `%% tys)); |
|
567 |
||
18517 | 568 |
fun mk_lookup thy tabs (ClassPackage.Instance (inst as (cls, tyco), ls)) trns = |
569 |
trns |
|
570 |
|> ensure_def_class thy tabs cls |
|
571 |
||>> ensure_def_inst thy tabs inst |
|
572 |
||>> (fold_map o fold_map) (mk_lookup thy tabs) ls |
|
573 |
|-> (fn ((cls, i), ls) => pair (ClassPackage.Instance ((cls, i), ls))) |
|
574 |
| mk_lookup thy tabs (ClassPackage.Lookup (clss, (v, i))) trns = |
|
18516 | 575 |
trns |
18517 | 576 |
|> fold_map (ensure_def_class thy tabs) clss |
18865 | 577 |
|-> (fn clss => pair (ClassPackage.Lookup (clss, (v |> unprefix "'", i)))) |
578 |
and mk_fun thy tabs (c, ty) trns = |
|
579 |
case get_first (fn eqx => eqx (c, ty)) (get_eqextrs thy tabs) |
|
580 |
of SOME (eq_thms, ty) => |
|
581 |
let |
|
582 |
val sortctxt = ClassPackage.extract_sortctxt thy ty; |
|
583 |
fun dest_eqthm eq_thm = |
|
584 |
let |
|
585 |
val ((t, args), rhs) = |
|
586 |
(apfst strip_comb o Logic.dest_equals o prop_of o Drule.zero_var_indexes) eq_thm; |
|
587 |
in case t |
|
588 |
of Const (c', _) => if c' = c then (args, rhs) |
|
589 |
else error ("illegal function equation for " ^ quote c |
|
590 |
^ ", actually defining " ^ quote c') |
|
591 |
| _ => error ("illegal function equation for " ^ quote c) |
|
592 |
end; |
|
593 |
fun mk_eq (args, rhs) trns = |
|
18517 | 594 |
trns |
18865 | 595 |
|> fold_map (exprgen_term thy tabs o devarify_term) args |
596 |
||>> (exprgen_term thy tabs o devarify_term) rhs |
|
597 |
|-> (fn (args, rhs) => pair (args, rhs)) |
|
598 |
in |
|
18517 | 599 |
trns |
18865 | 600 |
|> debug 6 (fn _ => "(1) retrieved function equations for " ^ |
601 |
quote (c ^ "::" ^ Sign.string_of_typ thy ty)) |
|
602 |
|> fold_map (mk_eq o dest_eqthm) eq_thms |
|
603 |
|> debug 6 (fn _ => "(2) building equations") |
|
604 |
||>> (exprgen_type thy tabs o devarify_type) ty |
|
605 |
|> debug 6 (fn _ => "(3) building type") |
|
606 |
||>> fold_map (exprgen_tyvar_sort thy tabs) sortctxt |
|
607 |
|> debug 6 (fn _ => "(4) building sort context") |
|
608 |
|-> (fn ((eqs, ty), sortctxt) => (pair o SOME) (eqs, (sortctxt, ty))) |
|
609 |
end |
|
610 |
| NONE => (NONE, trns) |
|
611 |
and ensure_def_inst thy (tabs as (_, (insttab, _, _))) (cls, tyco) trns = |
|
612 |
let |
|
613 |
fun defgen_inst thy (tabs as (_, (insttab, _, _))) inst trns = |
|
614 |
case Option.map (InstNameMangler.rev thy insttab) (name_of_idf thy nsp_inst inst) |
|
615 |
of SOME (_, (cls, tyco)) => |
|
616 |
let |
|
617 |
val (arity, memdefs) = ClassPackage.the_inst_sign thy (cls, tyco); |
|
618 |
fun gen_suparity supclass trns = |
|
619 |
trns |
|
620 |
|> ensure_def_inst thy tabs (supclass, tyco) |
|
621 |
||>> (fold_map o fold_map) (mk_lookup thy tabs) |
|
622 |
(ClassPackage.extract_sortlookup_inst thy (cls, tyco) supclass) |
|
623 |
|-> (fn (inst, ls) => pair (supclass, (inst, ls))); |
|
624 |
fun gen_membr (m, ty) trns = |
|
625 |
trns |
|
626 |
|> mk_fun thy tabs (m, ty) |
|
627 |
|-> (fn SOME funn => pair (idf_of_name thy nsp_mem m, funn) |
|
628 |
| NONE => error ("could not derive definition for member " ^ quote m)); |
|
629 |
in |
|
630 |
trns |
|
631 |
|> debug 5 (fn _ => "trying defgen class instance for (" ^ quote cls |
|
632 |
^ ", " ^ quote tyco ^ ")") |
|
633 |
|> ensure_def_class thy tabs cls |
|
634 |
|> debug 5 (fn _ => "(1) got class") |
|
635 |
||>> ensure_def_tyco thy tabs tyco |
|
636 |
|> debug 5 (fn _ => "(2) got type") |
|
637 |
||>> fold_map (exprgen_tyvar_sort thy tabs) arity |
|
638 |
|> debug 5 (fn _ => "(3) got arity") |
|
639 |
||>> fold_map gen_suparity (ClassPackage.the_superclasses thy cls) |
|
640 |
|> debug 5 (fn _ => "(4) got superarities") |
|
641 |
||>> fold_map gen_membr memdefs |
|
642 |
|> debug 5 (fn _ => "(5) got members") |
|
643 |
|-> (fn ((((cls, tyco), arity), suparities), memdefs) => |
|
644 |
succeed (Classinst (((cls, (tyco, arity)), suparities), memdefs))) |
|
645 |
end |
|
646 |
| _ => |
|
647 |
trns |> fail ("no class instance found for " ^ quote inst); |
|
648 |
val thyname = (the o AList.lookup (op =) (ClassPackage.the_instances thy cls)) tyco; |
|
649 |
val inst = idf_of_name thy nsp_inst (InstNameMangler.get thy insttab (thyname, (cls, tyco))); |
|
650 |
in |
|
651 |
trns |
|
652 |
|> debug 4 (fn _ => "generating instance " ^ quote cls ^ " / " ^ quote tyco) |
|
653 |
|> gen_ensure_def [("instance", defgen_inst thy tabs)] |
|
654 |
("generating instance " ^ quote cls ^ " / " ^ quote tyco) inst |
|
655 |
|> pair inst |
|
656 |
end |
|
657 |
and ensure_def_const thy (tabs as ((_, clsmemtab), (_, overltab, dtcontab))) (c, ty) trns = |
|
658 |
let |
|
659 |
fun defgen_funs thy tabs c trns = |
|
660 |
case recconst_of_idf thy tabs c |
|
661 |
of SOME (c, ty) => |
|
662 |
trns |
|
663 |
|> mk_fun thy tabs (c, ty) |
|
664 |
|-> (fn (SOME funn) => succeed (Fun funn) |
|
665 |
| NONE => fail ("no defining equations found for " ^ quote c)) |
|
666 |
| NONE => |
|
667 |
trns |
|
668 |
|> fail ("not a constant: " ^ quote c); |
|
669 |
fun defgen_datatypecons thy (tabs as (_, (_, _, dtcontab))) co trns = |
|
670 |
case Option.map (DatatypeconsNameMangler.rev thy dtcontab) (name_of_idf thy nsp_dtcon co) |
|
671 |
of SOME (co, dtco) => |
|
672 |
trns |
|
673 |
|> debug 5 (fn _ => "trying defgen datatype constructor for " ^ quote co) |
|
674 |
|> ensure_def_tyco thy tabs dtco |
|
675 |
|-> (fn dtco => succeed Undef) |
|
676 |
| _ => |
|
677 |
trns |
|
678 |
|> fail ("not a datatype constructor: " ^ quote co); |
|
679 |
fun defgen_clsmem thy tabs m trns = |
|
680 |
case name_of_idf thy nsp_mem m |
|
681 |
of SOME m => |
|
682 |
trns |
|
683 |
|> debug 5 (fn _ => "trying defgen class member for " ^ quote m) |
|
684 |
|> ensure_def_class thy tabs ((the o ClassPackage.lookup_const_class thy) m) |
|
685 |
|-> (fn cls => succeed Undef) |
|
686 |
| _ => |
|
687 |
trns |> fail ("no class member found for " ^ quote m) |
|
688 |
val c' = idf_of_const thy tabs (c, ty); |
|
689 |
in |
|
690 |
trns |
|
691 |
|> debug 4 (fn _ => "generating constant " ^ quote c) |
|
692 |
|> gen_ensure_def |
|
693 |
[("funs", defgen_funs thy tabs), |
|
694 |
("clsmem", defgen_clsmem thy tabs), |
|
695 |
("datatypecons", defgen_datatypecons thy tabs)] |
|
696 |
("generating constant " ^ quote c) c' |
|
697 |
|> pair c' |
|
698 |
end |
|
18517 | 699 |
and exprgen_term thy tabs (Const (f, ty)) trns = |
700 |
trns |
|
701 |
|> appgen thy tabs ((f, ty), []) |
|
18516 | 702 |
|-> (fn e => pair e) |
18865 | 703 |
| exprgen_term thy tabs (Var ((v, 0), ty)) trns = |
18516 | 704 |
trns |
18865 | 705 |
|> (exprgen_type thy tabs o devarify_type) ty |
706 |
|-> (fn ty => pair (IVarE (v, ty))) |
|
707 |
| exprgen_term thy tabs (Var ((_, _), _)) trns = |
|
708 |
error "Var with index greater 0 encountered during code generation" |
|
18516 | 709 |
| exprgen_term thy tabs (Free (v, ty)) trns = |
710 |
trns |
|
18865 | 711 |
|> (exprgen_type thy tabs o devarify_type) ty |
18516 | 712 |
|-> (fn ty => pair (IVarE (v, ty))) |
713 |
| exprgen_term thy tabs (Abs (v, ty, t)) trns = |
|
714 |
trns |
|
18865 | 715 |
|> (exprgen_type thy tabs o devarify_type) ty |
18516 | 716 |
||>> exprgen_term thy tabs (subst_bound (Free (v, ty), t)) |
717 |
|-> (fn (ty, e) => pair ((v, ty) `|-> e)) |
|
718 |
| exprgen_term thy tabs (t as t1 $ t2) trns = |
|
719 |
let |
|
720 |
val (t', ts) = strip_comb t |
|
721 |
in case t' |
|
722 |
of Const (f, ty) => |
|
723 |
trns |
|
18517 | 724 |
|> appgen thy tabs ((f, ty), ts) |
18516 | 725 |
|-> (fn e => pair e) |
726 |
| _ => |
|
727 |
trns |
|
728 |
|> exprgen_term thy tabs t' |
|
729 |
||>> fold_map (exprgen_term thy tabs) ts |
|
730 |
|-> (fn (e, es) => pair (e `$$ es)) |
|
18865 | 731 |
end |
732 |
and appgen_default thy tabs ((c, ty), ts) trns = |
|
733 |
trns |
|
734 |
|> ensure_def_const thy tabs (c, ty) |
|
735 |
||>> (fold_map o fold_map) (mk_lookup thy tabs) |
|
736 |
(ClassPackage.extract_sortlookup thy (c, ty)) |
|
737 |
||>> (exprgen_type thy tabs o devarify_type) ty |
|
738 |
||>> fold_map (exprgen_term thy tabs o devarify_term) ts |
|
739 |
|-> (fn (((c, ls), ty), es) => |
|
740 |
pair (IConst ((c, ty), ls) `$$ es)) |
|
741 |
and appgen thy tabs ((f, ty), ts) trns = |
|
742 |
case Symtab.lookup ((#appconst o #gens o CodegenData.get) thy) f |
|
743 |
of SOME ((imin, imax), (ag, _)) => |
|
744 |
if length ts < imin then |
|
745 |
let |
|
746 |
val d = imin - length ts; |
|
747 |
val vs = Term.invent_names (add_term_names (Const (f, ty), [])) "x" d; |
|
748 |
val tys = Library.take (d, ((fst o strip_type) ty)); |
|
749 |
in |
|
750 |
trns |
|
751 |
|> debug 10 (fn _ => "eta-expanding") |
|
752 |
|> fold_map (exprgen_type thy tabs o devarify_type) tys |
|
753 |
||>> ag thy tabs ((f, ty), ts @ map2 (curry Free) vs tys) |
|
754 |
|-> (fn (tys, e) => pair ((vs ~~ tys) `|--> e)) |
|
755 |
end |
|
756 |
else if length ts > imax then |
|
757 |
trns |
|
758 |
|> debug 10 (fn _ => "splitting arguments (" ^ string_of_int imax ^ ", " |
|
759 |
^ string_of_int (length ts) ^ ")") |
|
760 |
|> ag thy tabs ((f, ty), Library.take (imax, ts)) |
|
761 |
||>> fold_map (exprgen_term thy tabs) (Library.drop (imax, ts)) |
|
762 |
|-> (fn es => pair (mk_apps es)) |
|
763 |
else |
|
764 |
trns |
|
765 |
|> debug 10 (fn _ => "keeping arguments") |
|
766 |
|> ag thy tabs ((f, ty), ts) |
|
767 |
| NONE => |
|
768 |
trns |
|
769 |
|> appgen_default thy tabs ((f, ty), ts); |
|
18516 | 770 |
|
18865 | 771 |
(* fun ensure_def_eq thy tabs (dtco, (eqpred, arity)) trns = |
772 |
let |
|
773 |
val name_dtco = (the ooo name_of_idf) thy nsp_tyco dtco; |
|
774 |
val idf_eqinst = idf_of_name thy nsp_eq_inst name_dtco; |
|
775 |
val idf_eqpred = idf_of_name thy nsp_eq_pred name_dtco; |
|
776 |
val inst_sortlookup = map (fn (v, _) => [ClassPackage.Lookup ([], (v, 0))]) arity; |
|
777 |
fun mk_eq_pred _ trns = |
|
778 |
trns |
|
779 |
|> succeed (eqpred) |
|
780 |
fun mk_eq_inst _ trns = |
|
781 |
trns |
|
782 |
|> gen_ensure_def [("eqpred", mk_eq_pred)] ("generating equality predicate for " ^ quote dtco) idf_eqpred |
|
783 |
|> succeed (Classinst ((class_eq, (dtco, arity)), ([], [(fun_eq, (idf_eqpred, inst_sortlookup))]))); |
|
784 |
in |
|
785 |
trns |
|
786 |
|> gen_ensure_def [("eqinst", mk_eq_inst)] ("generating equality instance for " ^ quote dtco) idf_eqinst |
|
787 |
end; *) |
|
18454 | 788 |
|
18865 | 789 |
(* expression generators *) |
18517 | 790 |
|
18702 | 791 |
(* fun appgen_eq thy tabs (("op =", Type ("fun", [ty, _])), [t1, t2]) trns = |
18517 | 792 |
trns |
793 |
|> invoke_eq (exprgen_type thy tabs) (ensure_def_eq thy tabs) ty |
|
794 |
|-> (fn false => error ("could not derive equality for " ^ Sign.string_of_typ thy ty) |
|
795 |
| true => fn trns => trns |
|
796 |
|> exprgen_term thy tabs t1 |
|
797 |
||>> exprgen_term thy tabs t2 |
|
18702 | 798 |
|-> (fn (e1, e2) => pair (Fun_eq `$ e1 `$ e2))); *) |
799 |
||
800 |
||
801 |
(* function extractors *) |
|
802 |
||
803 |
fun eqextr_defs thy ((deftab, _), _) (c, ty) = |
|
804 |
let |
|
805 |
fun eq_typ (ty1, ty2) = |
|
806 |
Sign.typ_instance thy (ty1, ty2) |
|
807 |
andalso Sign.typ_instance thy (ty2, ty1) |
|
808 |
in |
|
809 |
Option.mapPartial (get_first (fn (ty', thm) => if eq_typ (ty, ty') |
|
810 |
then SOME ([thm], ty') |
|
811 |
else NONE |
|
812 |
)) (Symtab.lookup deftab c) |
|
813 |
end; |
|
18517 | 814 |
|
815 |
||
18217 | 816 |
(* parametrized generators, for instantiation in HOL *) |
817 |
||
18702 | 818 |
fun appgen_let strip_abs thy tabs ((c, ty), [t2, t3]) trns = |
18517 | 819 |
let |
18702 | 820 |
fun dest_let (l as Const (c', _) $ t $ u) = |
821 |
if c = c' then |
|
822 |
case strip_abs 1 u |
|
823 |
of ([p], u') => apfst (cons (p, t)) (dest_let u') |
|
824 |
| _ => ([], l) |
|
825 |
else ([], t) |
|
18517 | 826 |
| dest_let t = ([], t); |
827 |
fun mk_let (l, r) trns = |
|
18335 | 828 |
trns |
18517 | 829 |
|> exprgen_term thy tabs l |
830 |
||>> exprgen_term thy tabs r |
|
18865 | 831 |
|-> (fn (l, r) => pair (r, l)); |
18702 | 832 |
val (lets, body) = dest_let (Const (c, ty) $ t2 $ t3) |
18517 | 833 |
in |
834 |
trns |
|
835 |
|> fold_map mk_let lets |
|
836 |
||>> exprgen_term thy tabs body |
|
837 |
|-> (fn (lets, body) => |
|
18702 | 838 |
pair (Library.foldr (fn ((e, p), body) => ICase (e, [(p, body)])) (lets, body))) |
18517 | 839 |
end |
18217 | 840 |
|
18517 | 841 |
fun appgen_split strip_abs thy tabs (c, [t2]) trns = |
842 |
let |
|
843 |
val ([p], body) = strip_abs 1 (Const c $ t2) |
|
844 |
in |
|
845 |
trns |
|
846 |
|> exprgen_term thy tabs p |
|
847 |
||>> exprgen_term thy tabs body |
|
18702 | 848 |
|-> (fn (IVarE v, body) => pair (IAbs (v, body))) |
18517 | 849 |
end; |
18335 | 850 |
|
18702 | 851 |
fun appgen_number_of mk_int_to_nat bin_to_int tyco_int tyco_nat thy tabs ((_, |
852 |
Type (_, [_, ty as Type (tyco, [])])), [bin]) trns = |
|
853 |
if tyco = tyco_int then |
|
854 |
trns |
|
18865 | 855 |
|> (exprgen_type thy tabs o devarify_type) ty |
856 |
|-> (fn ty => pair (CodegenThingol.IConst (((IntInf.toString o bin_to_int) bin, ty), []))) |
|
18702 | 857 |
else if tyco = tyco_nat then |
858 |
trns |
|
859 |
|> exprgen_term thy tabs (mk_int_to_nat bin) |
|
860 |
else error ("invalid type constructor for numeral: " ^ quote tyco); |
|
18217 | 861 |
|
18517 | 862 |
fun appgen_datatype_case cos thy tabs ((_, ty), ts) trns = |
18247
b17724cae935
code generator: case expressions, improved name resolving
haftmann
parents:
18231
diff
changeset
|
863 |
let |
18517 | 864 |
val (ts', t) = split_last ts; |
865 |
val (tys, dty) = (split_last o fst o strip_type) ty; |
|
866 |
fun gen_names i = |
|
867 |
variantlist (replicate i "x", foldr add_term_names |
|
868 |
(map (fst o fst o dest_Var) (foldr add_term_vars [] ts)) ts); |
|
869 |
fun cg_case_d (((cname, i), ty), t) trns = |
|
18247
b17724cae935
code generator: case expressions, improved name resolving
haftmann
parents:
18231
diff
changeset
|
870 |
let |
b17724cae935
code generator: case expressions, improved name resolving
haftmann
parents:
18231
diff
changeset
|
871 |
val vs = gen_names i; |
b17724cae935
code generator: case expressions, improved name resolving
haftmann
parents:
18231
diff
changeset
|
872 |
val tys = Library.take (i, (fst o strip_type) ty); |
18330 | 873 |
val frees = map2 (curry Free) vs tys; |
18247
b17724cae935
code generator: case expressions, improved name resolving
haftmann
parents:
18231
diff
changeset
|
874 |
val t' = Envir.beta_norm (list_comb (t, frees)); |
b17724cae935
code generator: case expressions, improved name resolving
haftmann
parents:
18231
diff
changeset
|
875 |
in |
b17724cae935
code generator: case expressions, improved name resolving
haftmann
parents:
18231
diff
changeset
|
876 |
trns |
18516 | 877 |
|> exprgen_term thy tabs (list_comb (Const (cname, tys ---> dty), frees)) |
878 |
||>> exprgen_term thy tabs t' |
|
18865 | 879 |
|-> (fn (ep, e) => pair (ep, e)) |
18247
b17724cae935
code generator: case expressions, improved name resolving
haftmann
parents:
18231
diff
changeset
|
880 |
end; |
18517 | 881 |
in |
882 |
trns |
|
883 |
|> exprgen_term thy tabs t |
|
884 |
||>> fold_map cg_case_d ((cos ~~ tys) ~~ ts') |
|
18702 | 885 |
|-> (fn (t, ds) => pair (ICase (t, ds))) |
18247
b17724cae935
code generator: case expressions, improved name resolving
haftmann
parents:
18231
diff
changeset
|
886 |
end; |
b17724cae935
code generator: case expressions, improved name resolving
haftmann
parents:
18231
diff
changeset
|
887 |
|
18702 | 888 |
fun gen_add_case_const prep_c get_case_const_data raw_c thy = |
18517 | 889 |
let |
890 |
val c = prep_c thy raw_c; |
|
18702 | 891 |
val (tys, dty) = (split_last o fst o strip_type o Sign.the_const_type thy) c; |
18517 | 892 |
val cos = (the o get_case_const_data thy) c; |
893 |
val n_eta = length cos + 1; |
|
894 |
in |
|
895 |
thy |
|
896 |
|> add_appconst_i (c, ((n_eta, n_eta), appgen_datatype_case cos)) |
|
897 |
end; |
|
898 |
||
18702 | 899 |
val add_case_const = gen_add_case_const Sign.intern_const; |
900 |
val add_case_const_i = gen_add_case_const (K I); |
|
18517 | 901 |
|
18865 | 902 |
fun defgen_datatype_proto get_datatype get_datacons thy (tabs as (_, (_, _, dtcontab))) dtco trns = |
18454 | 903 |
case name_of_idf thy nsp_tyco dtco |
18380
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
904 |
of SOME dtco => |
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
905 |
(case get_datatype thy dtco |
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
906 |
of SOME (vars, cos) => |
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
907 |
let |
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
908 |
val cotys = map (the o get_datacons thy o rpair dtco) cos; |
18454 | 909 |
val coidfs = map (fn co => (DatatypeconsNameMangler.get thy dtcontab (co, dtco)) |> |
910 |
idf_of_name thy nsp_dtcon) cos; |
|
18380
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
911 |
in |
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
912 |
trns |
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
913 |
|> debug 5 (fn _ => "trying defgen datatype for " ^ quote dtco) |
18702 | 914 |
|> fold_map (exprgen_tyvar_sort thy tabs) vars |
18516 | 915 |
||>> (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
|
916 |
|-> (fn (sorts, tys) => succeed (Datatype |
18702 | 917 |
((sorts, coidfs ~~ tys), []))) |
18380
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
918 |
end |
18217 | 919 |
| NONE => |
920 |
trns |
|
18380
9668764224a7
substantial improvements for class code generation
haftmann
parents:
18361
diff
changeset
|
921 |
|> fail ("no datatype found for " ^ quote dtco)) |
18217 | 922 |
| NONE => |
923 |
trns |
|
18454 | 924 |
|> fail ("not a type constructor: " ^ quote dtco) |
18335 | 925 |
|
18217 | 926 |
|
18516 | 927 |
|
928 |
(** theory interface **) |
|
18217 | 929 |
|
18454 | 930 |
fun mk_tabs thy = |
18217 | 931 |
let |
18454 | 932 |
fun extract_defs thy = |
18217 | 933 |
let |
18702 | 934 |
fun dest tm = |
18454 | 935 |
let |
18702 | 936 |
val (lhs, rhs) = Logic.dest_equals (prop_of tm); |
937 |
val (t, args) = strip_comb lhs; |
|
938 |
val (c, ty) = dest_Const t |
|
939 |
in if forall is_Var args then SOME ((c, ty), tm) else NONE |
|
18454 | 940 |
end handle TERM _ => NONE; |
941 |
fun prep_def def = (case Codegen.preprocess thy [def] of |
|
18702 | 942 |
[def'] => def' | _ => error "mk_auxtab: bad preprocessor"); |
943 |
fun add_def (name, _) = |
|
944 |
case (dest o prep_def o Thm.get_axiom thy) name |
|
945 |
of SOME ((c, ty), tm) => |
|
946 |
Symtab.default (c, []) #> Symtab.map_entry c (cons (ty, tm)) |
|
947 |
| NONE => I |
|
18217 | 948 |
in |
18454 | 949 |
Symtab.empty |
18702 | 950 |
|> fold (Symtab.fold add_def o snd o #axioms o Theory.rep_theory) |
951 |
(thy :: Theory.ancestors_of thy) |
|
18217 | 952 |
end; |
18454 | 953 |
fun mk_insttab thy = |
954 |
InstNameMangler.empty |
|
955 |
|> Symtab.fold_map |
|
18702 | 956 |
(fn (cls, (clsmems, clsinsts)) => fold_map |
18454 | 957 |
(fn (tyco, thyname) => InstNameMangler.declare thy (thyname, (cls, tyco))) clsinsts) |
958 |
(ClassPackage.get_classtab thy) |
|
959 |
|-> (fn _ => I); |
|
18702 | 960 |
fun mk_overltabs thy deftab = |
18454 | 961 |
(Symtab.empty, ConstNameMangler.empty) |
962 |
|> Symtab.fold |
|
963 |
(fn (c, [_]) => I |
|
964 |
| (c, tytab) => |
|
18865 | 965 |
if (is_none o ClassPackage.lookup_const_class thy) c |
966 |
then (fn (overltab1, overltab2) => ( |
|
967 |
overltab1 |
|
968 |
|> Symtab.update_new (c, (Sign.the_const_constraint thy c, map fst tytab)), |
|
969 |
overltab2 |
|
970 |
|> fold (fn (ty, _) => ConstNameMangler.declare thy |
|
971 |
(idf_of_name thy nsp_overl c, (Sign.the_const_constraint thy c, ty)) #> snd) tytab)) |
|
972 |
else I |
|
973 |
) deftab; |
|
18454 | 974 |
fun mk_dtcontab thy = |
975 |
DatatypeconsNameMangler.empty |
|
976 |
|> fold_map |
|
18455 | 977 |
(fn (_, co_dtco) => DatatypeconsNameMangler.declare_multi thy co_dtco) |
978 |
(fold (fn (co, dtco) => |
|
979 |
let |
|
980 |
val key = ((NameSpace.drop_base o NameSpace.drop_base) co, NameSpace.base co) |
|
981 |
in AList.default (op =) (key, []) #> AList.map_entry (op =) key (cons (co, dtco)) end |
|
982 |
) (get_all_datatype_cons thy) []) |
|
18454 | 983 |
|-> (fn _ => I); |
984 |
fun mk_clsmemtab thy = |
|
985 |
Symtab.empty |
|
986 |
|> Symtab.fold |
|
987 |
(fn (class, (clsmems, _)) => fold |
|
988 |
(fn clsmem => Symtab.update (clsmem, class)) clsmems) |
|
989 |
(ClassPackage.get_classtab thy); |
|
18702 | 990 |
val deftab = extract_defs thy; |
18454 | 991 |
val insttab = mk_insttab thy; |
18702 | 992 |
val overltabs = mk_overltabs thy deftab; |
18454 | 993 |
val dtcontab = mk_dtcontab thy; |
994 |
val clsmemtab = mk_clsmemtab thy; |
|
995 |
in ((deftab, clsmemtab), (insttab, overltabs, dtcontab)) end; |
|
18217 | 996 |
|
18756 | 997 |
fun get_serializer target = |
998 |
case Symtab.lookup (!serializers) target |
|
999 |
of SOME seri => seri |
|
1000 |
| NONE => error ("unknown code target language: " ^ quote target); |
|
18335 | 1001 |
|
18516 | 1002 |
fun map_module f = |
18702 | 1003 |
map_codegen_data (fn (modl, gens, target_data, logic_data) => |
1004 |
(f modl, gens, target_data, logic_data)); |
|
18516 | 1005 |
|
18702 | 1006 |
fun expand_module gen thy = |
18516 | 1007 |
(#modl o CodegenData.get) thy |
18702 | 1008 |
|> start_transact (gen thy (mk_tabs thy)) |
18516 | 1009 |
|-> (fn x:'a => fn modl => (x, map_module (K modl) thy)); |
1010 |
||
1011 |
fun rename_inconsistent thy = |
|
18217 | 1012 |
let |
18516 | 1013 |
fun get_inconsistent thyname = |
1014 |
let |
|
1015 |
val thy = theory thyname; |
|
1016 |
fun own_tables get = |
|
1017 |
(get thy) |
|
1018 |
|> fold (Symtab.fold (Symtab.remove (K true)) o get) (Theory.parents_of thy) |
|
1019 |
|> Symtab.keys; |
|
1020 |
val names = own_tables (#2 o #types o Type.rep_tsig o Sign.tsig_of) |
|
1021 |
@ own_tables (#2 o #declarations o Consts.dest o #consts o Sign.rep_sg); |
|
1022 |
fun diff names = |
|
1023 |
fold (fn name => |
|
1024 |
if is_prefix (op =) (NameSpace.unpack thyname) (NameSpace.unpack name) |
|
1025 |
then I |
|
1026 |
else cons (name, NameSpace.append thyname (NameSpace.base name))) names []; |
|
1027 |
in diff names end; |
|
1028 |
val inconsistent = map get_inconsistent (ThyInfo.names ()) |> Library.flat; |
|
1029 |
fun add (src, dst) thy = |
|
1030 |
if (is_some oo Symtab.lookup o fst o #alias o #logic_data o CodegenData.get) thy src |
|
1031 |
then (warning ("code generator alias already defined for " ^ quote src ^ ", will not overwrite"); thy) |
|
1032 |
else add_alias (src, dst) thy |
|
1033 |
in fold add inconsistent thy end; |
|
1034 |
||
18517 | 1035 |
fun ensure_datatype_case_consts get_datatype_case_consts get_case_const_data thy = |
1036 |
let |
|
1037 |
fun ensure case_c thy = |
|
1038 |
if |
|
1039 |
Symtab.defined ((#appconst o #gens o CodegenData.get) thy) case_c |
|
1040 |
then |
|
1041 |
(warning ("case constant " ^ quote case_c ^ " already present in application table, will not overwrite"); thy) |
|
1042 |
else |
|
18702 | 1043 |
add_case_const_i get_case_const_data case_c thy; |
18517 | 1044 |
in |
1045 |
fold ensure (get_datatype_case_consts thy) thy |
|
1046 |
end; |
|
1047 |
||
18516 | 1048 |
|
1049 |
||
1050 |
(** target languages **) |
|
1051 |
||
1052 |
(* primitive definitions *) |
|
1053 |
||
18702 | 1054 |
fun read_typ thy = |
1055 |
Sign.read_typ (thy, K NONE); |
|
1056 |
||
18517 | 1057 |
fun read_const thy (raw_c, raw_ty) = |
1058 |
let |
|
1059 |
val c = Sign.intern_const thy raw_c; |
|
18702 | 1060 |
val _ = if Sign.declared_const thy c |
1061 |
then () |
|
1062 |
else error ("no such constant: " ^ quote c); |
|
18517 | 1063 |
val ty = case raw_ty |
1064 |
of NONE => Sign.the_const_constraint thy c |
|
18702 | 1065 |
| SOME raw_ty => read_typ thy raw_ty; |
18517 | 1066 |
in (c, ty) end; |
1067 |
||
18702 | 1068 |
fun read_quote reader gen raw thy = |
1069 |
expand_module |
|
1070 |
(fn thy => fn tabs => gen thy tabs (reader thy raw)) |
|
1071 |
thy; |
|
1072 |
||
18517 | 1073 |
fun gen_add_prim prep_name prep_primdef raw_name deps (target, raw_primdef) thy = |
18516 | 1074 |
let |
18702 | 1075 |
val _ = if Symtab.defined ((#target_data o CodegenData.get) thy) target |
18516 | 1076 |
then () else error ("unknown target language: " ^ quote target); |
1077 |
val tabs = mk_tabs thy; |
|
1078 |
val name = prep_name thy tabs raw_name; |
|
1079 |
val primdef = prep_primdef raw_primdef; |
|
18217 | 1080 |
in |
18516 | 1081 |
thy |
18517 | 1082 |
|> map_module (CodegenThingol.add_prim name deps (target, primdef)) |
18217 | 1083 |
end; |
1084 |
||
18516 | 1085 |
val add_prim_i = gen_add_prim ((K o K) I) I; |
1086 |
val add_prim_class = gen_add_prim |
|
1087 |
(fn thy => K (idf_of_name thy nsp_class o Sign.intern_class thy)) |
|
18702 | 1088 |
(Pretty.str o CodegenSerializer.parse_targetdef I); |
18516 | 1089 |
val add_prim_tyco = gen_add_prim |
1090 |
(fn thy => K (idf_of_name thy nsp_tyco o Sign.intern_type thy)) |
|
18702 | 1091 |
(Pretty.str o CodegenSerializer.parse_targetdef I); |
18516 | 1092 |
val add_prim_const = gen_add_prim |
18517 | 1093 |
(fn thy => fn tabs => idf_of_const thy tabs o read_const thy) |
18702 | 1094 |
(Pretty.str o CodegenSerializer.parse_targetdef I); |
18516 | 1095 |
|
18702 | 1096 |
val ensure_prim = (map_module oo CodegenThingol.ensure_prim); |
18217 | 1097 |
|
18517 | 1098 |
|
18217 | 1099 |
(* syntax *) |
1100 |
||
18865 | 1101 |
fun gen_add_syntax_class prep_class class target pretty thy = |
1102 |
thy |
|
1103 |
|> map_codegen_data |
|
1104 |
(fn (modl, gens, target_data, logic_data) => |
|
1105 |
(modl, gens, |
|
1106 |
target_data |> Symtab.map_entry target |
|
1107 |
(map_target_data |
|
1108 |
(fn (syntax_class, syntax_tyco, syntax_const) => |
|
1109 |
(syntax_class |
|
1110 |
|> Symtab.update (prep_class thy class, pretty), syntax_tyco, syntax_const))), |
|
1111 |
logic_data)); |
|
1112 |
||
1113 |
val add_syntax_class = gen_add_syntax_class Sign.intern_class; |
|
1114 |
||
18702 | 1115 |
val parse_syntax_tyco = |
18217 | 1116 |
let |
18702 | 1117 |
fun mk reader raw_tyco target thy = |
1118 |
let |
|
18756 | 1119 |
val _ = get_serializer target; |
18702 | 1120 |
fun check_tyco tyco = |
1121 |
if Sign.declared_tyname thy tyco |
|
1122 |
then tyco |
|
1123 |
else error ("no such type constructor: " ^ quote tyco); |
|
1124 |
fun prep_tyco thy tyco = |
|
1125 |
tyco |
|
1126 |
|> Sign.intern_type thy |
|
1127 |
|> check_tyco |
|
1128 |
|> idf_of_name thy nsp_tyco; |
|
1129 |
val tyco = prep_tyco thy raw_tyco; |
|
1130 |
in |
|
1131 |
thy |
|
1132 |
|> ensure_prim tyco target |
|
1133 |
|> reader |
|
1134 |
|-> (fn pretty => map_codegen_data |
|
1135 |
(fn (modl, gens, target_data, logic_data) => |
|
1136 |
(modl, gens, |
|
1137 |
target_data |> Symtab.map_entry target |
|
1138 |
(map_target_data |
|
18865 | 1139 |
(fn (syntax_class, syntax_tyco, syntax_const) => |
1140 |
(syntax_class, syntax_tyco |> Symtab.update |
|
18702 | 1141 |
(tyco, (pretty, stamp ())), |
1142 |
syntax_const))), |
|
1143 |
logic_data))) |
|
1144 |
end; |
|
18217 | 1145 |
in |
18865 | 1146 |
CodegenSerializer.parse_syntax |
1147 |
(read_quote read_typ (fn thy => fn tabs => exprgen_type thy tabs o devarify_type)) |
|
18702 | 1148 |
#-> (fn reader => pair (mk reader)) |
18217 | 1149 |
end; |
1150 |
||
18704
2c86ced392a8
substantial improvement in serialization handling
haftmann
parents:
18702
diff
changeset
|
1151 |
fun add_pretty_syntax_const c target pretty = |
2c86ced392a8
substantial improvement in serialization handling
haftmann
parents:
18702
diff
changeset
|
1152 |
map_codegen_data |
2c86ced392a8
substantial improvement in serialization handling
haftmann
parents:
18702
diff
changeset
|
1153 |
(fn (modl, gens, target_data, logic_data) => |
2c86ced392a8
substantial improvement in serialization handling
haftmann
parents:
18702
diff
changeset
|
1154 |
(modl, gens, |
2c86ced392a8
substantial improvement in serialization handling
haftmann
parents:
18702
diff
changeset
|
1155 |
target_data |> Symtab.map_entry target |
2c86ced392a8
substantial improvement in serialization handling
haftmann
parents:
18702
diff
changeset
|
1156 |
(map_target_data |
18865 | 1157 |
(fn (syntax_class, syntax_tyco, syntax_const) => |
1158 |
(syntax_class, syntax_tyco, |
|
18704
2c86ced392a8
substantial improvement in serialization handling
haftmann
parents:
18702
diff
changeset
|
1159 |
syntax_const |
2c86ced392a8
substantial improvement in serialization handling
haftmann
parents:
18702
diff
changeset
|
1160 |
|> Symtab.update |
2c86ced392a8
substantial improvement in serialization handling
haftmann
parents:
18702
diff
changeset
|
1161 |
(c, (pretty, stamp ()))))), |
2c86ced392a8
substantial improvement in serialization handling
haftmann
parents:
18702
diff
changeset
|
1162 |
logic_data)); |
2c86ced392a8
substantial improvement in serialization handling
haftmann
parents:
18702
diff
changeset
|
1163 |
|
18702 | 1164 |
val parse_syntax_const = |
18217 | 1165 |
let |
18702 | 1166 |
fun mk reader raw_const target thy = |
1167 |
let |
|
18756 | 1168 |
val _ = get_serializer target; |
18702 | 1169 |
val tabs = mk_tabs thy; |
1170 |
val c = idf_of_const thy tabs (read_const thy raw_const); |
|
1171 |
in |
|
1172 |
thy |
|
1173 |
|> ensure_prim c target |
|
1174 |
|> reader |
|
18704
2c86ced392a8
substantial improvement in serialization handling
haftmann
parents:
18702
diff
changeset
|
1175 |
|-> (fn pretty => add_pretty_syntax_const c target pretty) |
18702 | 1176 |
end; |
18217 | 1177 |
in |
18702 | 1178 |
CodegenSerializer.parse_syntax (read_quote Sign.read_term exprgen_term) |
1179 |
#-> (fn reader => pair (mk reader)) |
|
18217 | 1180 |
end; |
1181 |
||
18704
2c86ced392a8
substantial improvement in serialization handling
haftmann
parents:
18702
diff
changeset
|
1182 |
fun add_pretty_list raw_nil raw_cons (target, seri) thy = |
2c86ced392a8
substantial improvement in serialization handling
haftmann
parents:
18702
diff
changeset
|
1183 |
let |
18756 | 1184 |
val _ = get_serializer target; |
18704
2c86ced392a8
substantial improvement in serialization handling
haftmann
parents:
18702
diff
changeset
|
1185 |
val tabs = mk_tabs thy; |
2c86ced392a8
substantial improvement in serialization handling
haftmann
parents:
18702
diff
changeset
|
1186 |
fun mk_const raw_name = |
2c86ced392a8
substantial improvement in serialization handling
haftmann
parents:
18702
diff
changeset
|
1187 |
let |
2c86ced392a8
substantial improvement in serialization handling
haftmann
parents:
18702
diff
changeset
|
1188 |
val name = Sign.intern_const thy raw_name; |
2c86ced392a8
substantial improvement in serialization handling
haftmann
parents:
18702
diff
changeset
|
1189 |
in idf_of_const thy tabs (name, Sign.the_const_type thy name) end; |
2c86ced392a8
substantial improvement in serialization handling
haftmann
parents:
18702
diff
changeset
|
1190 |
val nil' = mk_const raw_nil; |
2c86ced392a8
substantial improvement in serialization handling
haftmann
parents:
18702
diff
changeset
|
1191 |
val cons' = mk_const raw_cons; |
2c86ced392a8
substantial improvement in serialization handling
haftmann
parents:
18702
diff
changeset
|
1192 |
val pr' = CodegenSerializer.pretty_list nil' cons' seri; |
2c86ced392a8
substantial improvement in serialization handling
haftmann
parents:
18702
diff
changeset
|
1193 |
in |
2c86ced392a8
substantial improvement in serialization handling
haftmann
parents:
18702
diff
changeset
|
1194 |
thy |
2c86ced392a8
substantial improvement in serialization handling
haftmann
parents:
18702
diff
changeset
|
1195 |
|> ensure_prim cons' target |
2c86ced392a8
substantial improvement in serialization handling
haftmann
parents:
18702
diff
changeset
|
1196 |
|> add_pretty_syntax_const cons' target pr' |
2c86ced392a8
substantial improvement in serialization handling
haftmann
parents:
18702
diff
changeset
|
1197 |
end; |
2c86ced392a8
substantial improvement in serialization handling
haftmann
parents:
18702
diff
changeset
|
1198 |
|
18217 | 1199 |
|
18516 | 1200 |
|
18756 | 1201 |
(** toplevel interface **) |
1202 |
||
1203 |
local |
|
18217 | 1204 |
|
18756 | 1205 |
fun generate_code (SOME raw_consts) thy = |
1206 |
let |
|
1207 |
val consts = map (read_const thy) raw_consts; |
|
1208 |
fun generate thy tabs = fold_map (ensure_def_const thy tabs) consts |
|
1209 |
in |
|
1210 |
thy |
|
1211 |
|> expand_module generate |
|
1212 |
|-> (fn cs => pair (SOME cs)) |
|
1213 |
end |
|
1214 |
| generate_code NONE thy = |
|
1215 |
(NONE, thy); |
|
1216 |
||
1217 |
fun serialize_code target seri raw_consts thy = |
|
18217 | 1218 |
let |
18756 | 1219 |
fun serialize cs thy = |
18702 | 1220 |
let |
18756 | 1221 |
val module = (#modl o CodegenData.get) thy; |
18702 | 1222 |
val target_data = |
1223 |
thy |
|
1224 |
|> CodegenData.get |
|
1225 |
|> #target_data |
|
1226 |
|> (fn data => (the oo Symtab.lookup) data target); |
|
18756 | 1227 |
in (seri ( |
18865 | 1228 |
(Symtab.lookup o #syntax_class) target_data, |
18702 | 1229 |
(Option.map fst oo Symtab.lookup o #syntax_tyco) target_data, |
1230 |
(Option.map fst oo Symtab.lookup o #syntax_const) target_data |
|
18850 | 1231 |
) cs module : unit; thy) end; |
18217 | 1232 |
in |
1233 |
thy |
|
18756 | 1234 |
|> generate_code raw_consts |
1235 |
|-> (fn cs => serialize cs) |
|
18217 | 1236 |
end; |
1237 |
||
1238 |
structure P = OuterParse |
|
1239 |
and K = OuterKeyword |
|
1240 |
||
1241 |
in |
|
1242 |
||
18850 | 1243 |
val (generateK, serializeK, |
18517 | 1244 |
primclassK, primtycoK, primconstK, |
18865 | 1245 |
syntax_classK, syntax_tycoK, syntax_constK, aliasK) = |
18850 | 1246 |
("code_generate", "code_serialize", |
18517 | 1247 |
"code_primclass", "code_primtyco", "code_primconst", |
18865 | 1248 |
"code_syntax_class", "code_syntax_tyco", "code_syntax_const", "code_alias"); |
18756 | 1249 |
val dependingK = |
1250 |
("depending_on"); |
|
18335 | 1251 |
|
18217 | 1252 |
val generateP = |
18282 | 1253 |
OuterSyntax.command generateK "generate executable code for constants" K.thy_decl ( |
18850 | 1254 |
Scan.repeat1 (P.name -- Scan.option (P.$$$ "::" |-- P.typ)) |
18756 | 1255 |
>> (fn raw_consts => |
1256 |
Toplevel.theory (generate_code (SOME raw_consts) #> snd)) |
|
18217 | 1257 |
); |
1258 |
||
1259 |
val serializeP = |
|
18282 | 1260 |
OuterSyntax.command serializeK "serialize executable code for constants" K.thy_decl ( |
18217 | 1261 |
P.name |
18850 | 1262 |
-- Scan.option (Scan.repeat1 (P.name -- Scan.option (P.$$$ "::" |-- P.typ))) |
18756 | 1263 |
#-> (fn (target, raw_consts) => |
18850 | 1264 |
P.$$$ "(" |
1265 |
|-- get_serializer target |
|
1266 |
--| P.$$$ ")" |
|
18756 | 1267 |
>> (fn seri => |
1268 |
Toplevel.theory (serialize_code target seri raw_consts) |
|
1269 |
)) |
|
18217 | 1270 |
); |
1271 |
||
1272 |
val aliasP = |
|
18282 | 1273 |
OuterSyntax.command aliasK "declare an alias for a theory identifier" K.thy_decl ( |
18702 | 1274 |
Scan.repeat1 (P.name -- P.name) |
1275 |
>> (Toplevel.theory oo fold) add_alias |
|
18217 | 1276 |
); |
1277 |
||
18517 | 1278 |
val primclassP = |
1279 |
OuterSyntax.command primclassK "define target-lanugage specific class" K.thy_decl ( |
|
1280 |
P.xname |
|
18702 | 1281 |
-- Scan.optional (P.$$$ dependingK |-- |
1282 |
P.$$$ "(" |-- P.list1 P.name --| P.$$$ ")") [] |
|
18517 | 1283 |
-- Scan.repeat1 (P.name -- P.text) |
18702 | 1284 |
>> (fn ((raw_class, depends), primdefs) => |
18517 | 1285 |
(Toplevel.theory oo fold) (add_prim_class raw_class depends) primdefs) |
1286 |
); |
|
1287 |
||
1288 |
val primtycoP = |
|
1289 |
OuterSyntax.command primtycoK "define target-lanugage specific type constructor" K.thy_decl ( |
|
1290 |
P.xname |
|
18702 | 1291 |
-- Scan.optional (P.$$$ dependingK |-- |
1292 |
P.$$$ "(" |-- P.list1 P.name --| P.$$$ ")") [] |
|
18517 | 1293 |
-- Scan.repeat1 (P.name -- P.text) |
18702 | 1294 |
>> (fn ((raw_tyco, depends), primdefs) => |
18517 | 1295 |
(Toplevel.theory oo fold) (add_prim_tyco raw_tyco depends) primdefs) |
1296 |
); |
|
1297 |
||
1298 |
val primconstP = |
|
1299 |
OuterSyntax.command primconstK "define target-lanugage specific constant" K.thy_decl ( |
|
18702 | 1300 |
(P.xname -- Scan.option (P.$$$ "::" |-- P.typ)) |
1301 |
-- Scan.optional (P.$$$ dependingK |-- |
|
1302 |
P.$$$ "(" |-- P.list1 P.name --| P.$$$ ")") [] |
|
18517 | 1303 |
-- Scan.repeat1 (P.name -- P.text) |
18702 | 1304 |
>> (fn ((raw_const, depends), primdefs) => |
18517 | 1305 |
(Toplevel.theory oo fold) (add_prim_const raw_const depends) primdefs) |
1306 |
); |
|
1307 |
||
18865 | 1308 |
val syntax_classP = |
1309 |
OuterSyntax.command syntax_tycoK "define code syntax for class" K.thy_decl ( |
|
1310 |
Scan.repeat1 ( |
|
1311 |
P.xname |
|
1312 |
-- Scan.repeat1 ( |
|
1313 |
P.name -- P.string |
|
1314 |
) |
|
1315 |
) |
|
1316 |
>> (Toplevel.theory oo fold) (fn (raw_class, syns) => |
|
1317 |
fold (fn (target, p) => add_syntax_class raw_class target p) syns) |
|
1318 |
); |
|
1319 |
||
18217 | 1320 |
val syntax_tycoP = |
1321 |
OuterSyntax.command syntax_tycoK "define code syntax for type constructor" K.thy_decl ( |
|
18702 | 1322 |
Scan.repeat1 ( |
1323 |
P.xname |
|
1324 |
-- Scan.repeat1 ( |
|
1325 |
P.name -- parse_syntax_tyco |
|
1326 |
) |
|
1327 |
) |
|
1328 |
>> (Toplevel.theory oo fold) (fn (raw_tyco, syns) => |
|
1329 |
fold (fn (target, modifier) => modifier raw_tyco target) syns) |
|
18217 | 1330 |
); |
1331 |
||
1332 |
val syntax_constP = |
|
1333 |
OuterSyntax.command syntax_constK "define code syntax for constant" K.thy_decl ( |
|
18702 | 1334 |
Scan.repeat1 ( |
1335 |
(P.xname -- Scan.option (P.$$$ "::" |-- P.typ)) |
|
1336 |
-- Scan.repeat1 ( |
|
1337 |
P.name -- parse_syntax_const |
|
1338 |
) |
|
1339 |
) |
|
1340 |
>> (Toplevel.theory oo fold) (fn (raw_c, syns) => |
|
1341 |
fold (fn (target, modifier) => modifier raw_c target) syns) |
|
18217 | 1342 |
); |
1343 |
||
18850 | 1344 |
val _ = OuterSyntax.add_parsers [generateP, serializeP, aliasP, |
18517 | 1345 |
primclassP, primtycoP, primconstP, syntax_tycoP, syntax_constP]; |
18850 | 1346 |
val _ = OuterSyntax.add_keywords [dependingK]; |
18217 | 1347 |
|
1348 |
||
18516 | 1349 |
|
18708 | 1350 |
(** theory setup **) |
18516 | 1351 |
|
18850 | 1352 |
val _ = Context.add_setup ( |
1353 |
add_eqextr ("defs", eqextr_defs) |
|
18708 | 1354 |
(* add_appconst_i ("op =", ((2, 2), appgen_eq)) *) |
18850 | 1355 |
); |
18217 | 1356 |
|
1357 |
end; (* local *) |
|
1358 |
||
1359 |
end; (* struct *) |