| author | narboux |
| Tue, 06 Mar 2007 16:40:32 +0100 | |
| changeset 22421 | 51a18dd1ea86 |
| parent 22396 | 6c7f9207fa9e |
| child 22423 | c1836b14c63a |
| 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 |
|
| 20855 | 5 |
Code generator extraction kernel. Code generator Isar setup. |
|
18169
45def66f86cb
added modules for code generator generation two, not operational yet
haftmann
parents:
diff
changeset
|
6 |
*) |
|
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 |
signature CODEGEN_PACKAGE = |
|
45def66f86cb
added modules for code generator generation two, not operational yet
haftmann
parents:
diff
changeset
|
9 |
sig |
| 20456 | 10 |
include BASIC_CODEGEN_THINGOL; |
| 21121 | 11 |
val codegen_term: theory -> term -> iterm; |
| 20600 | 12 |
val eval_term: theory -> (string (*reference name!*) * 'a option ref) * term -> 'a; |
| 21881 | 13 |
val codegen_command: theory -> string -> unit; |
| 18217 | 14 |
|
| 19884 | 15 |
type appgen; |
| 20439 | 16 |
val add_appconst: string * appgen -> theory -> theory; |
|
21820
2f2b6a965ccc
introduced mk/dest_numeral/number for mk/dest_binum etc.
haftmann
parents:
21722
diff
changeset
|
17 |
val appgen_numeral: (term -> IntInf.int option) -> appgen; |
|
19607
07eeb832f28d
introduced characters for code generator; some improved code lemmas for some list functions
haftmann
parents:
19597
diff
changeset
|
18 |
val appgen_char: (term -> int option) -> appgen; |
| 20105 | 19 |
val appgen_case: (theory -> term |
20 |
-> ((string * typ) list * ((term * typ) * (term * term) list)) option) |
|
21 |
-> appgen; |
|
22 |
val appgen_let: appgen; |
|
| 21012 | 23 |
|
24 |
val timing: bool ref; |
|
|
18169
45def66f86cb
added modules for code generator generation two, not operational yet
haftmann
parents:
diff
changeset
|
25 |
end; |
|
45def66f86cb
added modules for code generator generation two, not operational yet
haftmann
parents:
diff
changeset
|
26 |
|
| 18217 | 27 |
structure CodegenPackage : CODEGEN_PACKAGE = |
|
18169
45def66f86cb
added modules for code generator generation two, not operational yet
haftmann
parents:
diff
changeset
|
28 |
struct |
|
45def66f86cb
added modules for code generator generation two, not operational yet
haftmann
parents:
diff
changeset
|
29 |
|
| 20896 | 30 |
open BasicCodegenThingol; |
31 |
val tracing = CodegenThingol.tracing; |
|
32 |
val succeed = CodegenThingol.succeed; |
|
33 |
val fail = CodegenThingol.fail; |
|
| 20699 | 34 |
|
35 |
(** code extraction **) |
|
36 |
||
37 |
(* theory data *) |
|
| 18217 | 38 |
|
| 20600 | 39 |
type appgen = theory -> ((sort -> sort) * Sorts.algebra) * Consts.T |
40 |
-> CodegenFuncgr.T |
|
| 20896 | 41 |
-> bool * string list option |
42 |
-> (string * typ) * term list -> CodegenThingol.transact -> iterm * CodegenThingol.transact; |
|
| 20439 | 43 |
|
44 |
type appgens = (int * (appgen * stamp)) Symtab.table; |
|
| 20931 | 45 |
val merge_appgens : appgens * appgens -> appgens = |
| 20105 | 46 |
Symtab.merge (fn ((bounds1, (_, stamp1)), (bounds2, (_, stamp2))) => |
| 20931 | 47 |
bounds1 = bounds2 andalso stamp1 = stamp2); |
| 18217 | 48 |
|
| 20931 | 49 |
structure Consttab = CodegenConsts.Consttab; |
50 |
type abstypes = typ Symtab.table * CodegenConsts.const Consttab.table; |
|
51 |
fun merge_abstypes ((typs1, consts1) : abstypes, (typs2, consts2) : abstypes) = |
|
52 |
(Symtab.merge (Type.eq_type Vartab.empty) (typs1, typs2), |
|
53 |
Consttab.merge CodegenConsts.eq_const (consts1, consts2)); |
|
| 20456 | 54 |
|
| 20600 | 55 |
structure CodegenPackageData = TheoryDataFun |
| 18217 | 56 |
(struct |
| 22213 | 57 |
val name = "Pure/codegen_package_setup"; |
| 20931 | 58 |
type T = appgens * abstypes; |
59 |
val empty = (Symtab.empty, (Symtab.empty, Consttab.empty)); |
|
| 18217 | 60 |
val copy = I; |
61 |
val extend = I; |
|
| 20931 | 62 |
fun merge _ ((appgens1, abstypes1), (appgens2, abstypes2)) = |
63 |
(merge_appgens (appgens1, appgens2), merge_abstypes (abstypes1, abstypes2)); |
|
| 20456 | 64 |
fun print _ _ = (); |
| 18217 | 65 |
end); |
66 |
||
| 22213 | 67 |
structure Funcgr = CodegenFuncgrRetrieval ( |
68 |
val name = "Pure/codegen_package_thms"; |
|
69 |
fun rewrites thy = []; |
|
70 |
); |
|
71 |
||
72 |
fun print_codethms thy = |
|
73 |
Pretty.writeln o CodegenFuncgr.pretty thy o Funcgr.make thy; |
|
74 |
||
75 |
structure Code = CodeDataFun |
|
76 |
(struct |
|
77 |
val name = "Pure/codegen_package_code"; |
|
78 |
type T = CodegenThingol.code; |
|
79 |
val empty = CodegenThingol.empty_code; |
|
80 |
fun merge _ = CodegenThingol.merge_code; |
|
81 |
fun purge _ NONE _ = CodegenThingol.empty_code |
|
82 |
| purge NONE _ _ = CodegenThingol.empty_code |
|
83 |
| purge (SOME thy) (SOME cs) code = |
|
84 |
let |
|
85 |
val cs_exisiting = |
|
86 |
map_filter (CodegenNames.const_rev thy) (Graph.keys code); |
|
87 |
val dels = (Graph.all_preds code |
|
88 |
o map (CodegenNames.const thy) |
|
89 |
o filter (member CodegenConsts.eq_const cs_exisiting) |
|
90 |
) cs; |
|
91 |
in Graph.del_nodes dels code end; |
|
92 |
end); |
|
93 |
||
94 |
val _ = Context.add_setup (CodegenPackageData.init #> Funcgr.init #> Code.init); |
|
| 18708 | 95 |
|
| 18865 | 96 |
|
| 22197 | 97 |
(* preparing defining equations *) |
| 21990 | 98 |
|
99 |
fun prep_eqs thy (thms as thm :: _) = |
|
100 |
let |
|
| 22035 | 101 |
val ty = (Logic.unvarifyT o CodegenFunc.typ_func) thm; |
| 21990 | 102 |
val thms' = if (null o Term.typ_tfrees) ty orelse (null o fst o strip_type) ty |
103 |
then thms |
|
| 22035 | 104 |
else map (CodegenFunc.expand_eta 1) thms; |
| 21990 | 105 |
in (ty, thms') end; |
106 |
||
107 |
||
| 20386 | 108 |
(* extraction kernel *) |
| 18865 | 109 |
|
| 20931 | 110 |
fun check_strict (false, _) has_seri x = |
| 19884 | 111 |
false |
| 20931 | 112 |
| check_strict (_, SOME targets) has_seri x = |
| 20699 | 113 |
not (has_seri targets x) |
| 20931 | 114 |
| check_strict (true, _) has_seri x = |
| 19884 | 115 |
true; |
116 |
||
| 20931 | 117 |
fun get_abstype thy (tyco, tys) = case Symtab.lookup ((fst o snd o CodegenPackageData.get) thy) tyco |
118 |
of SOME ty => SOME ((map_atyps (fn TFree (n, _) => nth tys (the (Int.fromString n)))) ty) |
|
119 |
| NONE => NONE; |
|
120 |
||
| 22035 | 121 |
fun ensure_def thy = CodegenThingol.ensure_def (CodegenNames.labelled_name thy); |
122 |
||
| 22197 | 123 |
fun ensure_def_class thy (algbr as ((_, algebra), _)) funcgr strct class = |
| 20386 | 124 |
let |
| 22185 | 125 |
val superclasses = (Sorts.certify_sort algebra o Sorts.super_classes algebra) class; |
| 21895 | 126 |
val (v, cs) = AxClass.params_of_class thy class; |
|
22076
42ae57200d96
changed dictionary representation to explicit classrel witnesses
haftmann
parents:
22035
diff
changeset
|
127 |
val class' = CodegenNames.class thy class; |
|
42ae57200d96
changed dictionary representation to explicit classrel witnesses
haftmann
parents:
22035
diff
changeset
|
128 |
val classrels' = map (curry (CodegenNames.classrel thy) class) superclasses; |
| 20896 | 129 |
val classops' = map (CodegenNames.const thy o CodegenConsts.norm_of_typ thy) cs; |
| 22197 | 130 |
val defgen_class = |
131 |
fold_map (ensure_def_class thy algbr funcgr strct) superclasses |
|
132 |
##>> (fold_map (exprgen_type thy algbr funcgr strct) o map snd) cs |
|
133 |
#-> (fn (superclasses, classoptyps) => succeed |
|
|
22076
42ae57200d96
changed dictionary representation to explicit classrel witnesses
haftmann
parents:
22035
diff
changeset
|
134 |
(CodegenThingol.Class (superclasses ~~ classrels', (unprefix "'" v, classops' ~~ classoptyps)))) |
| 18454 | 135 |
in |
| 22197 | 136 |
tracing (fn _ => "generating class " ^ quote class) |
137 |
#> ensure_def thy defgen_class true |
|
| 20896 | 138 |
("generating class " ^ quote class) class'
|
| 22197 | 139 |
#> pair class' |
| 18865 | 140 |
end |
| 22197 | 141 |
and ensure_def_classrel thy algbr funcgr strct (subclass, superclass) = |
142 |
ensure_def_class thy algbr funcgr strct subclass |
|
143 |
#>> (fn _ => CodegenNames.classrel thy (subclass, superclass)) |
|
| 22354 | 144 |
and ensure_def_tyco thy algbr funcgr strct "fun" trns = |
145 |
trns |
|
146 |
|> pair "fun" |
|
147 |
| ensure_def_tyco thy algbr funcgr strct tyco trns = |
|
148 |
let |
|
149 |
fun defgen_datatype trns = |
|
| 22396 | 150 |
let |
151 |
val (vs, cos) = case CodegenData.get_datatype thy tyco |
|
152 |
of SOME x => x |
|
153 |
| NONE => (Name.invents Name.context "'a" (Sign.arity_number thy tyco) |
|
154 |
|> map (rpair (Sign.defaultS thy)) , []) |
|
155 |
(*FIXME move to CodegenData*) |
|
156 |
in |
|
157 |
trns |
|
158 |
|> fold_map (exprgen_tyvar_sort thy algbr funcgr strct) vs |
|
159 |
||>> fold_map (fn (c, tys) => |
|
160 |
fold_map (exprgen_type thy algbr funcgr strct) tys |
|
161 |
#-> (fn tys' => |
|
162 |
pair ((CodegenNames.const thy o CodegenConsts.norm_of_typ thy) |
|
163 |
(c, tys ---> Type (tyco, map TFree vs)), tys'))) cos |
|
164 |
|-> (fn (vs, cos) => succeed (CodegenThingol.Datatype (vs, cos))) |
|
165 |
end; |
|
| 22354 | 166 |
val tyco' = CodegenNames.tyco thy tyco; |
167 |
in |
|
168 |
trns |
|
169 |
|> tracing (fn _ => "generating type constructor " ^ quote tyco) |
|
| 22396 | 170 |
|> ensure_def thy defgen_datatype true |
| 22354 | 171 |
("generating type constructor " ^ quote tyco) tyco'
|
172 |
|> pair tyco' |
|
173 |
end |
|
| 20600 | 174 |
and exprgen_tyvar_sort thy (algbr as ((proj_sort, _), _)) funcgr strct (v, sort) trns = |
| 18516 | 175 |
trns |
| 20600 | 176 |
|> fold_map (ensure_def_class thy algbr funcgr strct) (proj_sort sort) |
| 22185 | 177 |
|>> (fn sort => (unprefix "'" v, sort)) |
| 22197 | 178 |
and exprgen_type thy algbr funcgr strct (TFree vs) trns = |
| 18516 | 179 |
trns |
| 20600 | 180 |
|> exprgen_tyvar_sort thy algbr funcgr strct vs |
| 22185 | 181 |
|>> (fn (v, sort) => ITyVar v) |
| 20600 | 182 |
| exprgen_type thy algbr funcgr strct (Type (tyco, tys)) trns = |
| 20931 | 183 |
case get_abstype thy (tyco, tys) |
184 |
of SOME ty => |
|
185 |
trns |
|
186 |
|> exprgen_type thy algbr funcgr strct ty |
|
187 |
| NONE => |
|
188 |
trns |
|
189 |
|> ensure_def_tyco thy algbr funcgr strct tyco |
|
190 |
||>> fold_map (exprgen_type thy algbr funcgr strct) tys |
|
| 22185 | 191 |
|>> (fn (tyco, tys) => tyco `%% tys); |
| 18516 | 192 |
|
| 20835 | 193 |
exception CONSTRAIN of (string * typ) * typ; |
| 21012 | 194 |
val timing = ref false; |
| 20600 | 195 |
|
| 22197 | 196 |
fun exprgen_dicts thy (algbr as ((proj_sort, algebra), consts)) funcgr strct (ty_ctxt, sort_decl) = |
| 20456 | 197 |
let |
198 |
val pp = Sign.pp thy; |
|
|
22076
42ae57200d96
changed dictionary representation to explicit classrel witnesses
haftmann
parents:
22035
diff
changeset
|
199 |
datatype typarg = |
|
42ae57200d96
changed dictionary representation to explicit classrel witnesses
haftmann
parents:
22035
diff
changeset
|
200 |
Global of (class * string) * typarg list list |
|
42ae57200d96
changed dictionary representation to explicit classrel witnesses
haftmann
parents:
22035
diff
changeset
|
201 |
| Local of (class * class) list * (string * (int * sort)); |
|
42ae57200d96
changed dictionary representation to explicit classrel witnesses
haftmann
parents:
22035
diff
changeset
|
202 |
fun classrel (Global ((_, tyco), yss), _) class = |
|
42ae57200d96
changed dictionary representation to explicit classrel witnesses
haftmann
parents:
22035
diff
changeset
|
203 |
Global ((class, tyco), yss) |
|
42ae57200d96
changed dictionary representation to explicit classrel witnesses
haftmann
parents:
22035
diff
changeset
|
204 |
| classrel (Local (classrels, v), subclass) superclass = |
|
42ae57200d96
changed dictionary representation to explicit classrel witnesses
haftmann
parents:
22035
diff
changeset
|
205 |
Local ((subclass, superclass) :: classrels, v); |
|
42ae57200d96
changed dictionary representation to explicit classrel witnesses
haftmann
parents:
22035
diff
changeset
|
206 |
fun constructor tyco yss class = |
|
42ae57200d96
changed dictionary representation to explicit classrel witnesses
haftmann
parents:
22035
diff
changeset
|
207 |
Global ((class, tyco), (map o map) fst yss); |
| 20456 | 208 |
fun variable (TFree (v, sort)) = |
209 |
let |
|
210 |
val sort' = proj_sort sort; |
|
|
22076
42ae57200d96
changed dictionary representation to explicit classrel witnesses
haftmann
parents:
22035
diff
changeset
|
211 |
in map_index (fn (n, class) => (Local ([], (v, (n, sort'))), class)) sort' end; |
|
42ae57200d96
changed dictionary representation to explicit classrel witnesses
haftmann
parents:
22035
diff
changeset
|
212 |
val typargs = Sorts.of_sort_derivation pp algebra |
| 20456 | 213 |
{classrel = classrel, constructor = constructor, variable = variable}
|
214 |
(ty_ctxt, proj_sort sort_decl); |
|
| 22197 | 215 |
fun mk_dict (Global (inst, yss)) = |
216 |
ensure_def_inst thy algbr funcgr strct inst |
|
217 |
##>> (fold_map o fold_map) mk_dict yss |
|
218 |
#>> (fn (inst, dss) => DictConst (inst, dss)) |
|
219 |
| mk_dict (Local (classrels, (v, (k, sort)))) = |
|
220 |
fold_map (ensure_def_classrel thy algbr funcgr strct) classrels |
|
221 |
#>> (fn classrels => DictVar (classrels, (unprefix "'" v, (k, length sort)))) |
|
| 20456 | 222 |
in |
| 22197 | 223 |
fold_map mk_dict typargs |
| 20456 | 224 |
end |
| 22197 | 225 |
and exprgen_dict_parms thy (algbr as (_, consts)) funcgr strct (c, ty_ctxt) = |
| 20600 | 226 |
let |
227 |
val c' = CodegenConsts.norm_of_typ thy (c, ty_ctxt) |
|
| 20699 | 228 |
val idf = CodegenNames.const thy c'; |
| 21722 | 229 |
val ty_decl = Consts.the_declaration consts idf; |
| 22197 | 230 |
val (tys, tys_decl) = pairself (curry (Consts.typargs consts) idf) (ty_ctxt, ty_decl); |
231 |
val sorts = map (snd o dest_TVar) tys_decl; |
|
| 20456 | 232 |
in |
| 22197 | 233 |
fold_map (exprgen_dicts thy algbr funcgr strct) (tys ~~ sorts) |
| 20456 | 234 |
end |
| 22185 | 235 |
and ensure_def_inst thy (algbr as ((_, algebra), _)) funcgr strct (class, tyco) trns = |
| 20456 | 236 |
let |
| 22185 | 237 |
val superclasses = (Sorts.certify_sort algebra o Sorts.super_classes algebra) class; |
238 |
val (var, classops) = try (AxClass.params_of_class thy) class |> the_default ("'a", [])
|
|
239 |
val vs = Name.names (Name.declare var Name.context) "'a" (Sorts.mg_domain algebra tyco [class]); |
|
240 |
val arity_typ = Type (tyco, map TFree vs); |
|
| 20896 | 241 |
fun gen_superarity superclass trns = |
242 |
trns |
|
243 |
|> ensure_def_class thy algbr funcgr strct superclass |
|
|
22076
42ae57200d96
changed dictionary representation to explicit classrel witnesses
haftmann
parents:
22035
diff
changeset
|
244 |
||>> ensure_def_classrel thy algbr funcgr strct (class, superclass) |
|
42ae57200d96
changed dictionary representation to explicit classrel witnesses
haftmann
parents:
22035
diff
changeset
|
245 |
||>> exprgen_dicts thy algbr funcgr strct (arity_typ, [superclass]) |
| 22185 | 246 |
|>> (fn ((superclass, classrel), [DictConst (inst, dss)]) => |
247 |
(superclass, (classrel, (inst, dss)))); |
|
248 |
fun gen_classop_def (classop as (c, ty)) trns = |
|
| 20896 | 249 |
trns |
| 22185 | 250 |
|> ensure_def_const thy algbr funcgr strct (CodegenConsts.norm_of_typ thy classop) |
251 |
||>> exprgen_term thy algbr funcgr strct (Const (c, map_type_tfree (K arity_typ) ty)); |
|
| 20896 | 252 |
fun defgen_inst trns = |
253 |
trns |
|
254 |
|> ensure_def_class thy algbr funcgr strct class |
|
255 |
||>> ensure_def_tyco thy algbr funcgr strct tyco |
|
256 |
||>> fold_map (exprgen_tyvar_sort thy algbr funcgr strct) vs |
|
257 |
||>> fold_map gen_superarity superclasses |
|
| 22185 | 258 |
||>> fold_map gen_classop_def classops |
| 20896 | 259 |
|-> (fn ((((class, tyco), arity), superarities), classops) => |
260 |
succeed (CodegenThingol.Classinst ((class, (tyco, arity)), (superarities, classops)))); |
|
261 |
val inst = CodegenNames.instance thy (class, tyco); |
|
| 18865 | 262 |
in |
263 |
trns |
|
| 20896 | 264 |
|> tracing (fn _ => "generating instance " ^ quote class ^ " / " ^ quote tyco) |
| 22185 | 265 |
|> ensure_def thy defgen_inst true ("generating instance " ^ quote class ^ " / " ^ quote tyco) inst
|
| 18865 | 266 |
|> pair inst |
267 |
end |
|
| 21081 | 268 |
and ensure_def_const thy (algbr as (_, consts)) funcgr strct (c_tys as (c, tys)) trns = |
| 18865 | 269 |
let |
| 21081 | 270 |
val c' = CodegenNames.const thy c_tys; |
| 20896 | 271 |
fun defgen_datatypecons trns = |
272 |
trns |
|
273 |
|> ensure_def_tyco thy algbr funcgr strct |
|
| 21081 | 274 |
((the o CodegenData.get_datatype_of_constr thy) c_tys) |
| 20896 | 275 |
|-> (fn _ => succeed CodegenThingol.Bot); |
276 |
fun defgen_classop trns = |
|
277 |
trns |
|
278 |
|> ensure_def_class thy algbr funcgr strct ((the o AxClass.class_of_param thy) c) |
|
279 |
|-> (fn _ => succeed CodegenThingol.Bot); |
|
280 |
fun defgen_fun trns = |
|
| 21121 | 281 |
case CodegenFuncgr.funcs funcgr |
| 21081 | 282 |
(perhaps (Consttab.lookup ((snd o snd o CodegenPackageData.get) thy)) c_tys) |
| 21990 | 283 |
of thms as _ :: _ => |
| 20456 | 284 |
let |
| 21990 | 285 |
val (ty, eq_thms) = prep_eqs thy thms; |
| 21012 | 286 |
val timeap = if !timing then Output.timeap_msg ("time for " ^ c')
|
287 |
else I; |
|
| 20456 | 288 |
val msg = cat_lines ("generating code for theorems " :: map string_of_thm eq_thms);
|
| 20466 | 289 |
val vs = (map dest_TFree o Consts.typargs consts) (c', ty); |
| 20835 | 290 |
val dest_eqthm = |
291 |
apfst (snd o strip_comb) o Logic.dest_equals o Logic.unvarify o prop_of; |
|
| 20456 | 292 |
fun exprgen_eq (args, rhs) trns = |
293 |
trns |
|
| 20600 | 294 |
|> fold_map (exprgen_term thy algbr funcgr strct) args |
295 |
||>> exprgen_term thy algbr funcgr strct rhs; |
|
| 20456 | 296 |
in |
297 |
trns |
|
| 20896 | 298 |
|> CodegenThingol.message msg (fn trns => trns |
| 21012 | 299 |
|> timeap (fold_map (exprgen_eq o dest_eqthm) eq_thms) |
| 20600 | 300 |
||>> fold_map (exprgen_tyvar_sort thy algbr funcgr strct) vs |
301 |
||>> exprgen_type thy algbr funcgr strct ty |
|
| 20896 | 302 |
|-> (fn ((eqs, vs), ty) => succeed (CodegenThingol.Fun (eqs, (vs, ty))))) |
| 20456 | 303 |
end |
304 |
| [] => |
|
305 |
trns |
|
306 |
|> fail ("No defining equations found for "
|
|
| 21081 | 307 |
^ (quote o CodegenConsts.string_of_const thy) c_tys); |
308 |
val defgen = if (is_some o CodegenData.get_datatype_of_constr thy) c_tys |
|
309 |
then defgen_datatypecons |
|
310 |
else if (is_some o AxClass.class_of_param thy) c andalso |
|
311 |
case tys of [TFree _] => true | [TVar _] => true | _ => false |
|
| 20896 | 312 |
then defgen_classop |
| 21081 | 313 |
else defgen_fun |
| 20931 | 314 |
val strict = check_strict strct (CodegenSerializer.const_has_serialization thy) c'; |
| 18865 | 315 |
in |
316 |
trns |
|
| 20835 | 317 |
|> tracing (fn _ => "generating constant " |
| 21081 | 318 |
^ (quote o CodegenConsts.string_of_const thy) c_tys) |
| 22035 | 319 |
|> ensure_def thy defgen strict ("generating constant "
|
| 21081 | 320 |
^ CodegenConsts.string_of_const thy c_tys) c' |
| 20896 | 321 |
|> pair c' |
| 18865 | 322 |
end |
| 20896 | 323 |
and exprgen_term thy algbr funcgr strct (Const (c, ty)) trns = |
| 18517 | 324 |
trns |
| 20896 | 325 |
|> select_appgen thy algbr funcgr strct ((c, ty), []) |
| 20600 | 326 |
| exprgen_term thy algbr funcgr strct (Free (v, ty)) trns = |
| 18516 | 327 |
trns |
| 20600 | 328 |
|> exprgen_type thy algbr funcgr strct ty |
| 22185 | 329 |
|>> (fn _ => IVar v) |
| 20600 | 330 |
| exprgen_term thy algbr funcgr strct (Abs (raw_v, ty, raw_t)) trns = |
| 19136 | 331 |
let |
| 22035 | 332 |
val (v, t) = Syntax.variant_abs (raw_v, ty, raw_t); |
| 19136 | 333 |
in |
334 |
trns |
|
| 20600 | 335 |
|> exprgen_type thy algbr funcgr strct ty |
336 |
||>> exprgen_term thy algbr funcgr strct t |
|
| 22185 | 337 |
|>> (fn (ty, t) => (v, ty) `|-> t) |
| 19136 | 338 |
end |
| 20896 | 339 |
| exprgen_term thy algbr funcgr strct (t as _ $ _) trns = |
340 |
case strip_comb t |
|
341 |
of (Const (c, ty), ts) => |
|
| 18516 | 342 |
trns |
| 20896 | 343 |
|> select_appgen thy algbr funcgr strct ((c, ty), ts) |
344 |
| (t', ts) => |
|
| 18516 | 345 |
trns |
| 20600 | 346 |
|> exprgen_term thy algbr funcgr strct t' |
347 |
||>> fold_map (exprgen_term thy algbr funcgr strct) ts |
|
| 22185 | 348 |
|>> (fn (t, ts) => t `$$ ts) |
| 20600 | 349 |
and appgen_default thy algbr funcgr strct ((c, ty), ts) trns = |
| 18865 | 350 |
trns |
| 20600 | 351 |
|> ensure_def_const thy algbr funcgr strct (CodegenConsts.norm_of_typ thy (c, ty)) |
| 22305 | 352 |
||>> fold_map (exprgen_type thy algbr funcgr strct) ((fst o Term.strip_type) ty) |
353 |
||>> exprgen_type thy algbr funcgr strct ((snd o Term.strip_type) ty) |
|
|
22076
42ae57200d96
changed dictionary representation to explicit classrel witnesses
haftmann
parents:
22035
diff
changeset
|
354 |
||>> exprgen_dict_parms thy algbr funcgr strct (c, ty) |
| 20600 | 355 |
||>> fold_map (exprgen_term thy algbr funcgr strct) ts |
| 22305 | 356 |
|>> (fn ((((c, tys), ty), iss), ts) => IConst (c, (iss, tys)) `$$ ts) |
| 20896 | 357 |
and select_appgen thy algbr funcgr strct ((c, ty), ts) trns = |
| 20931 | 358 |
case Symtab.lookup (fst (CodegenPackageData.get thy)) c |
| 20896 | 359 |
of SOME (i, (appgen, _)) => |
| 20105 | 360 |
if length ts < i then |
| 18865 | 361 |
let |
| 21161 | 362 |
val k = length ts; |
363 |
val tys = (curry Library.take (i - k) o curry Library.drop k o fst o strip_type) ty; |
|
364 |
val ctxt = (fold o fold_aterms) |
|
365 |
(fn Free (v, _) => Name.declare v | _ => I) ts Name.context; |
|
366 |
val vs = Name.names ctxt "a" tys; |
|
| 18865 | 367 |
in |
368 |
trns |
|
| 20600 | 369 |
|> fold_map (exprgen_type thy algbr funcgr strct) tys |
| 20896 | 370 |
||>> appgen thy algbr funcgr strct ((c, ty), ts @ map Free vs) |
| 22185 | 371 |
|>> (fn (tys, t) => map2 (fn (v, _) => pair v) vs tys `|--> t) |
| 18865 | 372 |
end |
| 20105 | 373 |
else if length ts > i then |
| 18865 | 374 |
trns |
| 20896 | 375 |
|> appgen thy algbr funcgr strct ((c, ty), Library.take (i, ts)) |
| 20600 | 376 |
||>> fold_map (exprgen_term thy algbr funcgr strct) (Library.drop (i, ts)) |
| 22185 | 377 |
|>> (fn (t, ts) => t `$$ ts) |
| 18865 | 378 |
else |
379 |
trns |
|
| 20896 | 380 |
|> appgen thy algbr funcgr strct ((c, ty), ts) |
| 18865 | 381 |
| NONE => |
382 |
trns |
|
| 20896 | 383 |
|> appgen_default thy algbr funcgr strct ((c, ty), ts); |
| 20600 | 384 |
|
385 |
||
| 20835 | 386 |
(* entrance points into extraction kernel *) |
| 20600 | 387 |
|
388 |
fun ensure_def_const' thy algbr funcgr strct c trns = |
|
389 |
ensure_def_const thy algbr funcgr strct c trns |
|
| 20835 | 390 |
handle CONSTRAIN ((c, ty), ty_decl) => error ( |
| 20600 | 391 |
"Constant " ^ c ^ " with most general type\n" |
| 22197 | 392 |
^ CodegenConsts.string_of_typ thy ty |
| 20600 | 393 |
^ "\noccurs with type\n" |
| 22197 | 394 |
^ CodegenConsts.string_of_typ thy ty_decl); |
| 22185 | 395 |
|
396 |
fun perhaps_def_const thy algbr funcgr strct c trns = |
|
397 |
case try (ensure_def_const thy algbr funcgr strct c) trns |
|
398 |
of SOME (c, trns) => (SOME c, trns) |
|
399 |
| NONE => (NONE, trns); |
|
400 |
||
| 20600 | 401 |
fun exprgen_term' thy algbr funcgr strct t trns = |
402 |
exprgen_term thy algbr funcgr strct t trns |
|
| 20835 | 403 |
handle CONSTRAIN ((c, ty), ty_decl) => error ("In term " ^ (quote o Sign.string_of_term thy) t
|
| 20600 | 404 |
^ ",\nconstant " ^ c ^ " with most general type\n" |
| 22197 | 405 |
^ CodegenConsts.string_of_typ thy ty |
| 20600 | 406 |
^ "\noccurs with type\n" |
| 22197 | 407 |
^ CodegenConsts.string_of_typ thy ty_decl); |
| 18516 | 408 |
|
| 18702 | 409 |
|
| 20439 | 410 |
(* parametrized application generators, for instantiation in object logic *) |
411 |
(* (axiomatic extensions of extraction kernel *) |
|
| 18217 | 412 |
|
| 20600 | 413 |
fun appgen_numeral int_of_numeral thy algbr funcgr strct (app as (c, ts)) trns = |
|
21820
2f2b6a965ccc
introduced mk/dest_numeral/number for mk/dest_binum etc.
haftmann
parents:
21722
diff
changeset
|
414 |
case int_of_numeral (list_comb (Const c, ts)) |
| 20835 | 415 |
of SOME i => |
| 20353 | 416 |
trns |
| 21012 | 417 |
|> pair (CodegenThingol.INum i) |
| 19884 | 418 |
| NONE => |
419 |
trns |
|
| 20835 | 420 |
|> appgen_default thy algbr funcgr strct app; |
| 18217 | 421 |
|
| 20600 | 422 |
fun appgen_char char_to_index thy algbr funcgr strct (app as ((_, ty), _)) trns = |
|
19607
07eeb832f28d
introduced characters for code generator; some improved code lemmas for some list functions
haftmann
parents:
19597
diff
changeset
|
423 |
case (char_to_index o list_comb o apfst Const) app |
|
07eeb832f28d
introduced characters for code generator; some improved code lemmas for some list functions
haftmann
parents:
19597
diff
changeset
|
424 |
of SOME i => |
|
07eeb832f28d
introduced characters for code generator; some improved code lemmas for some list functions
haftmann
parents:
19597
diff
changeset
|
425 |
trns |
| 20600 | 426 |
|> exprgen_type thy algbr funcgr strct ty |
| 22185 | 427 |
|>> (fn _ => IChar (chr i)) |
|
19607
07eeb832f28d
introduced characters for code generator; some improved code lemmas for some list functions
haftmann
parents:
19597
diff
changeset
|
428 |
| NONE => |
|
07eeb832f28d
introduced characters for code generator; some improved code lemmas for some list functions
haftmann
parents:
19597
diff
changeset
|
429 |
trns |
| 20600 | 430 |
|> appgen_default thy algbr funcgr strct app; |
|
19607
07eeb832f28d
introduced characters for code generator; some improved code lemmas for some list functions
haftmann
parents:
19597
diff
changeset
|
431 |
|
| 21012 | 432 |
val debug_term = ref (Bound 0); |
433 |
||
| 20600 | 434 |
fun appgen_case dest_case_expr thy algbr funcgr strct (app as (c_ty, ts)) trns = |
| 20105 | 435 |
let |
436 |
val SOME ([], ((st, sty), ds)) = dest_case_expr thy (list_comb (Const c_ty, ts)); |
|
| 22035 | 437 |
fun clausegen (dt, bt) trns = |
438 |
trns |
|
439 |
|> exprgen_term thy algbr funcgr strct dt |
|
440 |
||>> exprgen_term thy algbr funcgr strct bt; |
|
| 20105 | 441 |
in |
442 |
trns |
|
| 20600 | 443 |
|> exprgen_term thy algbr funcgr strct st |
444 |
||>> exprgen_type thy algbr funcgr strct sty |
|
| 20105 | 445 |
||>> fold_map clausegen ds |
| 22185 | 446 |
|>> (fn ((se, sty), ds) => ICase ((se, sty), ds)) |
| 20105 | 447 |
end; |
448 |
||
| 20600 | 449 |
fun appgen_let thy algbr funcgr strct (app as (_, [st, ct])) trns = |
| 20105 | 450 |
trns |
| 20600 | 451 |
|> exprgen_term thy algbr funcgr strct ct |
452 |
||>> exprgen_term thy algbr funcgr strct st |
|
| 21012 | 453 |
|-> (fn ((v, ty) `|-> be, se) => |
454 |
pair (ICase ((se, ty), case be |
|
455 |
of ICase ((IVar w, _), ds) => if v = w then ds else [(IVar v, be)] |
|
| 20105 | 456 |
| _ => [(IVar v, be)] |
| 21012 | 457 |
)) |
458 |
| _ => appgen_default thy algbr funcgr strct app); |
|
| 20105 | 459 |
|
| 20439 | 460 |
fun add_appconst (c, appgen) thy = |
461 |
let |
|
| 20931 | 462 |
val i = (length o fst o strip_type o Sign.the_const_type thy) c; |
463 |
val _ = Code.change thy (K CodegenThingol.empty_code); |
|
464 |
in |
|
465 |
(CodegenPackageData.map o apfst) |
|
466 |
(Symtab.update (c, (i, (appgen, stamp ())))) thy |
|
467 |
end; |
|
468 |
||
469 |
||
470 |
||
471 |
(** abstype and constsubst interface **) |
|
472 |
||
| 21916 | 473 |
local |
474 |
||
475 |
fun add_consts thy f (c1, c2 as (c, tys)) = |
|
476 |
let |
|
477 |
val _ = case tys |
|
478 |
of [TVar _] => if is_some (AxClass.class_of_param thy c) |
|
| 22197 | 479 |
then error ("Not a function: " ^ CodegenConsts.string_of_const thy c2)
|
| 21916 | 480 |
else () |
481 |
| _ => (); |
|
482 |
val _ = if is_some (CodegenData.get_datatype_of_constr thy c2) |
|
| 22197 | 483 |
then error ("Not a function: " ^ CodegenConsts.string_of_const thy c2)
|
| 21916 | 484 |
else (); |
| 22213 | 485 |
val funcgr = Funcgr.make thy [c1, c2]; |
| 21916 | 486 |
val ty1 = (f o CodegenFuncgr.typ funcgr) c1; |
487 |
val ty2 = CodegenFuncgr.typ funcgr c2; |
|
488 |
val _ = if Sign.typ_equiv thy (ty1, ty2) then () else |
|
489 |
error ("Incompatiable type signatures of " ^ CodegenConsts.string_of_const thy c1
|
|
490 |
^ " and " ^ CodegenConsts.string_of_const thy c2 ^ ":\n" |
|
| 22197 | 491 |
^ CodegenConsts.string_of_typ thy ty1 ^ "\n" ^ CodegenConsts.string_of_typ thy ty2); |
| 21916 | 492 |
in Consttab.update (c1, c2) end; |
493 |
||
| 20931 | 494 |
fun gen_abstyp prep_const prep_typ (raw_abstyp, raw_substtyp) raw_absconsts thy = |
495 |
let |
|
496 |
val abstyp = Type.no_tvars (prep_typ thy raw_abstyp); |
|
497 |
val substtyp = Type.no_tvars (prep_typ thy raw_substtyp); |
|
498 |
val absconsts = (map o pairself) (prep_const thy) raw_absconsts; |
|
| 22197 | 499 |
val Type (abstyco, tys) = abstyp handle BIND => error ("Bad type: " ^ Sign.string_of_typ thy abstyp);
|
500 |
val typarms = map (fst o dest_TFree) tys handle MATCH => error ("Bad type: " ^ Sign.string_of_typ thy abstyp);
|
|
| 20931 | 501 |
fun mk_index v = |
502 |
let |
|
503 |
val k = find_index (fn w => v = w) typarms; |
|
504 |
in if k = ~1 |
|
| 22197 | 505 |
then error ("Free type variable: " ^ quote v)
|
| 20931 | 506 |
else TFree (string_of_int k, []) |
507 |
end; |
|
508 |
val typpat = map_atyps (fn TFree (v, _) => mk_index v) substtyp; |
|
509 |
fun apply_typpat (Type (tyco, tys)) = |
|
510 |
let |
|
511 |
val tys' = map apply_typpat tys; |
|
512 |
in if tyco = abstyco then |
|
513 |
(map_atyps (fn TFree (n, _) => nth tys' (the (Int.fromString n)))) typpat |
|
514 |
else |
|
515 |
Type (tyco, tys') |
|
516 |
end |
|
517 |
| apply_typpat ty = ty; |
|
518 |
val _ = Code.change thy (K CodegenThingol.empty_code); |
|
519 |
in |
|
520 |
thy |
|
521 |
|> (CodegenPackageData.map o apsnd) (fn (abstypes, abscs) => |
|
522 |
(abstypes |
|
523 |
|> Symtab.update (abstyco, typpat), |
|
524 |
abscs |
|
| 21916 | 525 |
|> fold (add_consts thy apply_typpat) absconsts) |
| 20931 | 526 |
) |
527 |
end; |
|
528 |
||
529 |
fun gen_constsubst prep_const raw_constsubsts thy = |
|
530 |
let |
|
531 |
val constsubsts = (map o pairself) (prep_const thy) raw_constsubsts; |
|
532 |
val _ = Code.change thy (K CodegenThingol.empty_code); |
|
533 |
in |
|
534 |
thy |
|
| 21916 | 535 |
|> (CodegenPackageData.map o apsnd o apsnd) (fold (add_consts thy I) constsubsts) |
| 20931 | 536 |
end; |
537 |
||
| 21916 | 538 |
in |
539 |
||
| 20931 | 540 |
val abstyp = gen_abstyp CodegenConsts.norm Sign.certify_typ; |
541 |
val abstyp_e = gen_abstyp CodegenConsts.read_const (fn thy => Sign.read_typ (thy, K NONE)); |
|
542 |
||
543 |
val constsubst = gen_constsubst CodegenConsts.norm; |
|
544 |
val constsubst_e = gen_constsubst CodegenConsts.read_const; |
|
| 20439 | 545 |
|
| 21916 | 546 |
end; (*local*) |
| 18217 | 547 |
|
| 18516 | 548 |
|
| 20439 | 549 |
(** code generation interfaces **) |
| 18516 | 550 |
|
| 21881 | 551 |
(* generic generation combinators *) |
552 |
||
| 22185 | 553 |
fun generate thy funcgr targets gen it = |
| 20466 | 554 |
let |
| 21121 | 555 |
val cs = map_filter (Consttab.lookup ((snd o snd o CodegenPackageData.get) thy)) |
556 |
(CodegenFuncgr.all funcgr); |
|
| 22213 | 557 |
val funcgr' = Funcgr.make thy cs; |
| 20931 | 558 |
val qnaming = NameSpace.qualified_names NameSpace.default_naming; |
| 20466 | 559 |
val consttab = Consts.empty |
| 21121 | 560 |
|> fold (fn c => Consts.declare qnaming |
561 |
((CodegenNames.const thy c, CodegenFuncgr.typ funcgr' c), true)) |
|
562 |
(CodegenFuncgr.all funcgr'); |
|
| 22185 | 563 |
val algbr = (CodegenData.operational_algebra thy, consttab); |
| 20466 | 564 |
in |
| 22185 | 565 |
Code.change_yield thy (CodegenThingol.start_transact (gen thy algbr funcgr' |
| 20600 | 566 |
(true, targets) it)) |
| 21121 | 567 |
|> fst |
| 20466 | 568 |
end; |
| 18516 | 569 |
|
| 20600 | 570 |
fun codegen_term thy t = |
| 20353 | 571 |
let |
| 20600 | 572 |
val ct = Thm.cterm_of thy t; |
| 22213 | 573 |
val (ct', funcgr) = Funcgr.make_term thy (K (K K)) ct; |
| 20835 | 574 |
val t' = Thm.term_of ct'; |
| 22185 | 575 |
in generate thy funcgr (SOME []) exprgen_term' t' end; |
| 19136 | 576 |
|
| 20600 | 577 |
fun eval_term thy (ref_spec, t) = |
| 20213 | 578 |
let |
| 21388 | 579 |
val _ = (Term.fold_types o Term.fold_atyps) (fn _ => |
| 20401 | 580 |
error ("Term" ^ Sign.string_of_term thy t ^ "is polymorhpic"))
|
| 21388 | 581 |
t; |
| 21121 | 582 |
val t' = codegen_term thy t; |
| 22305 | 583 |
in CodegenSerializer.eval_term thy CodegenNames.labelled_name (Code.get thy) (ref_spec, t') end; |
| 18217 | 584 |
|
585 |
||
| 21881 | 586 |
(* constant specifications with wildcards *) |
587 |
||
588 |
fun consts_of thy thyname = |
|
589 |
let |
|
590 |
val this_thy = Option.map theory thyname |> the_default thy; |
|
591 |
val defs = (#defs o rep_theory) this_thy; |
|
592 |
val cs_names = (Symtab.keys o snd o #constants o Consts.dest o #consts o Sign.rep_sg) this_thy; |
|
593 |
val consts = maps (fn c => (map (fn tys => CodegenConsts.norm thy (c, tys)) |
|
594 |
o map #lhs o filter #is_def o map snd o Defs.specifications_of defs) c) cs_names; |
|
595 |
fun is_const thyname (c, _) = |
|
596 |
(*this is an approximation*) |
|
597 |
not (exists (fn thy => Sign.declared_const thy c) (Theory.parents_of this_thy)) |
|
598 |
in case thyname |
|
599 |
of NONE => consts |
|
600 |
| SOME thyname => filter (is_const thyname) consts |
|
601 |
end; |
|
602 |
||
| 22185 | 603 |
fun filter_generatable thy targets consts = |
| 21881 | 604 |
let |
| 22213 | 605 |
val (consts', funcgr) = Funcgr.make_consts thy consts; |
| 22185 | 606 |
val consts'' = generate thy funcgr targets (fold_map oooo perhaps_def_const) consts'; |
607 |
val consts''' = map_filter (fn (const, SOME _) => SOME const | (_, NONE) => NONE) |
|
608 |
(consts' ~~ consts''); |
|
609 |
in consts''' end; |
|
| 21881 | 610 |
|
| 22185 | 611 |
fun read_constspec thy targets "*" = filter_generatable thy targets (consts_of thy NONE) |
612 |
| read_constspec thy targets s = if String.isSuffix ".*" s |
|
613 |
then filter_generatable thy targets (consts_of thy (SOME (unsuffix ".*" s))) |
|
| 21881 | 614 |
else [CodegenConsts.read_const thy s]; |
615 |
||
| 18516 | 616 |
|
| 20439 | 617 |
(** toplevel interface and setup **) |
| 18756 | 618 |
|
619 |
local |
|
| 19150 | 620 |
|
| 20699 | 621 |
structure P = OuterParse |
622 |
and K = OuterKeyword |
|
623 |
||
| 20439 | 624 |
fun code raw_cs seris thy = |
| 18217 | 625 |
let |
| 21081 | 626 |
val seris' = map (fn (target, args as _ :: _) => |
| 22305 | 627 |
(target, SOME (CodegenSerializer.get_serializer thy target args CodegenNames.labelled_name)) |
| 21081 | 628 |
| (target, []) => (CodegenSerializer.assert_serializer thy target, NONE)) seris; |
| 22185 | 629 |
val targets = case map fst seris' of [] => NONE | xs => SOME xs; |
630 |
val cs = maps (read_constspec thy targets) raw_cs; |
|
| 20439 | 631 |
fun generate' thy = case cs |
| 20600 | 632 |
of [] => [] |
| 20439 | 633 |
| _ => |
| 22213 | 634 |
generate thy (Funcgr.make thy cs) targets |
| 22185 | 635 |
(fold_map oooo ensure_def_const') cs; |
| 20896 | 636 |
fun serialize' [] code seri = |
637 |
seri NONE code |
|
638 |
| serialize' cs code seri = |
|
639 |
seri (SOME cs) code; |
|
| 20600 | 640 |
val cs = generate' thy; |
| 20699 | 641 |
val code = Code.get thy; |
| 18217 | 642 |
in |
| 21081 | 643 |
(map (serialize' cs code) (map_filter snd seris'); ()) |
| 18217 | 644 |
end; |
645 |
||
| 22213 | 646 |
fun print_codethms_e thy = |
647 |
print_codethms thy o map (CodegenConsts.read_const thy); |
|
| 20699 | 648 |
|
| 18217 | 649 |
|
| 22213 | 650 |
val code_exprP = ( |
| 21916 | 651 |
(Scan.repeat P.term |
| 20439 | 652 |
-- Scan.repeat (P.$$$ "(" |--
|
| 20896 | 653 |
P.name -- P.arguments |
| 21881 | 654 |
--| P.$$$ ")")) |
655 |
>> (fn (raw_cs, seris) => code raw_cs seris) |
|
| 20439 | 656 |
); |
657 |
||
| 22305 | 658 |
val (codeK, code_abstypeK, code_axiomsK, code_thmsK) = |
659 |
("code_gen", "code_abstype", "code_axioms", "code_thms");
|
|
| 22213 | 660 |
|
661 |
in |
|
662 |
||
| 21881 | 663 |
val codeP = |
664 |
OuterSyntax.improper_command codeK "generate and serialize executable code for constants" |
|
| 22213 | 665 |
K.diag (P.!!! code_exprP >> (fn f => Toplevel.keep (f o Toplevel.theory_of))); |
| 21881 | 666 |
|
667 |
fun codegen_command thy cmd = |
|
| 22213 | 668 |
case Scan.read OuterLex.stopper (P.!!! code_exprP) ((filter OuterLex.is_proper o OuterSyntax.scan) cmd) |
| 21916 | 669 |
of SOME f => (writeln "Now generating code..."; f thy) |
| 22197 | 670 |
| NONE => error ("Bad directive " ^ quote cmd);
|
| 21881 | 671 |
|
| 20931 | 672 |
val code_abstypeP = |
673 |
OuterSyntax.command code_abstypeK "axiomatic abstypes for code generation" K.thy_decl ( |
|
674 |
(P.typ -- P.typ -- Scan.optional (P.$$$ "where" |-- Scan.repeat1 |
|
675 |
(P.term --| (P.$$$ "\\<equiv>" || P.$$$ "==") -- P.term)) []) |
|
676 |
>> (Toplevel.theory o uncurry abstyp_e) |
|
| 20428 | 677 |
); |
678 |
||
| 21062 | 679 |
val code_axiomsP = |
680 |
OuterSyntax.command code_axiomsK "axiomatic constant equalities for code generation" K.thy_decl ( |
|
| 20931 | 681 |
Scan.repeat1 (P.term --| (P.$$$ "\\<equiv>" || P.$$$ "==") -- P.term) |
682 |
>> (Toplevel.theory o constsubst_e) |
|
| 18217 | 683 |
); |
684 |
||
| 22305 | 685 |
val code_thmsP = |
686 |
OuterSyntax.improper_command code_thmsK "print cached defining equations" OuterKeyword.diag |
|
687 |
(Scan.repeat P.term |
|
688 |
>> (fn cs => Toplevel.no_timing o Toplevel.unknown_theory |
|
689 |
o Toplevel.keep ((fn thy => print_codethms_e thy cs) o Toplevel.theory_of))); |
|
| 22213 | 690 |
|
| 22305 | 691 |
val _ = OuterSyntax.add_parsers [codeP, code_abstypeP, code_axiomsP, code_thmsP]; |
| 18217 | 692 |
|
693 |
end; (* local *) |
|
694 |
||
695 |
end; (* struct *) |