1 (* Title: HOL/Tools/recfun_codegen.ML |
|
2 Author: Stefan Berghofer, TU Muenchen |
|
3 |
|
4 Code generator for recursive functions. |
|
5 *) |
|
6 |
|
7 signature RECFUN_CODEGEN = |
|
8 sig |
|
9 val setup: theory -> theory |
|
10 end; |
|
11 |
|
12 structure RecfunCodegen : RECFUN_CODEGEN = |
|
13 struct |
|
14 |
|
15 val const_of = dest_Const o head_of o fst o Logic.dest_equals; |
|
16 |
|
17 structure ModuleData = Theory_Data |
|
18 ( |
|
19 type T = string Symtab.table; |
|
20 val empty = Symtab.empty; |
|
21 val extend = I; |
|
22 fun merge data = Symtab.merge (K true) data; |
|
23 ); |
|
24 |
|
25 fun add_thm_target module_name thm thy = |
|
26 let |
|
27 val (thm', _) = Code.mk_eqn thy (thm, true) |
|
28 in |
|
29 thy |
|
30 |> ModuleData.map (Symtab.update (fst (Code.const_typ_eqn thy thm'), module_name)) |
|
31 end; |
|
32 |
|
33 fun avoid_value thy [thm] = |
|
34 let val (_, T) = Code.const_typ_eqn thy thm |
|
35 in |
|
36 if null (Term.add_tvarsT T []) orelse null (binder_types T) |
|
37 then [thm] |
|
38 else [Code.expand_eta thy 1 thm] |
|
39 end |
|
40 | avoid_value thy thms = thms; |
|
41 |
|
42 fun get_equations thy defs (raw_c, T) = if raw_c = @{const_name HOL.eq} then ([], "") else |
|
43 let |
|
44 val c = AxClass.unoverload_const thy (raw_c, T); |
|
45 val raw_thms = Code.get_cert thy (Code_Preproc.preprocess_functrans thy) c |
|
46 |> Code.bare_thms_of_cert thy |
|
47 |> map (AxClass.overload thy) |
|
48 |> filter (Codegen.is_instance T o snd o const_of o prop_of); |
|
49 val module_name = case Symtab.lookup (ModuleData.get thy) c |
|
50 of SOME module_name => module_name |
|
51 | NONE => |
|
52 case Codegen.get_defn thy defs c T |
|
53 of SOME ((_, (thyname, _)), _) => thyname |
|
54 | NONE => Codegen.thyname_of_const thy c; |
|
55 in if null raw_thms then ([], "") else |
|
56 raw_thms |
|
57 |> Codegen.preprocess thy |
|
58 |> avoid_value thy |
|
59 |> rpair module_name |
|
60 end; |
|
61 |
|
62 fun mk_suffix thy defs (s, T) = |
|
63 (case Codegen.get_defn thy defs s T of |
|
64 SOME (_, SOME i) => " def" ^ string_of_int i |
|
65 | _ => ""); |
|
66 |
|
67 exception EQN of string * typ * string; |
|
68 |
|
69 fun cycle g x xs = |
|
70 if member (op =) xs x then xs |
|
71 else fold (cycle g) (flat (Graph.all_paths (fst g) (x, x))) (x :: xs); |
|
72 |
|
73 fun add_rec_funs thy mode defs dep module eqs gr = |
|
74 let |
|
75 fun dest_eq t = (fst (const_of t) ^ mk_suffix thy defs (const_of t), |
|
76 Logic.dest_equals (Codegen.rename_term t)); |
|
77 val eqs' = map dest_eq eqs; |
|
78 val (dname, _) :: _ = eqs'; |
|
79 val (s, T) = const_of (hd eqs); |
|
80 |
|
81 fun mk_fundef module fname first [] gr = ([], gr) |
|
82 | mk_fundef module fname first ((fname' : string, (lhs, rhs)) :: xs) gr = |
|
83 let |
|
84 val (pl, gr1) = Codegen.invoke_codegen thy mode defs dname module false lhs gr; |
|
85 val (pr, gr2) = Codegen.invoke_codegen thy mode defs dname module false rhs gr1; |
|
86 val (rest, gr3) = mk_fundef module fname' false xs gr2 ; |
|
87 val (ty, gr4) = Codegen.invoke_tycodegen thy mode defs dname module false T gr3; |
|
88 val num_args = (length o snd o strip_comb) lhs; |
|
89 val prfx = if fname = fname' then " |" |
|
90 else if not first then "and" |
|
91 else if num_args = 0 then "val" |
|
92 else "fun"; |
|
93 val pl' = Pretty.breaks (Codegen.str prfx |
|
94 :: (if num_args = 0 then [pl, Codegen.str ":", ty] else [pl])); |
|
95 in |
|
96 (Pretty.blk (4, pl' |
|
97 @ [Codegen.str " =", Pretty.brk 1, pr]) :: rest, gr4) |
|
98 end; |
|
99 |
|
100 fun put_code module fundef = Codegen.map_node dname |
|
101 (K (SOME (EQN ("", dummyT, dname)), module, Codegen.string_of (Pretty.blk (0, |
|
102 separate Pretty.fbrk fundef @ [Codegen.str ";"])) ^ "\n\n")); |
|
103 |
|
104 in |
|
105 (case try (Codegen.get_node gr) dname of |
|
106 NONE => |
|
107 let |
|
108 val gr1 = Codegen.add_edge (dname, dep) |
|
109 (Codegen.new_node (dname, (SOME (EQN (s, T, "")), module, "")) gr); |
|
110 val (fundef, gr2) = mk_fundef module "" true eqs' gr1 ; |
|
111 val xs = cycle gr2 dname []; |
|
112 val cs = map (fn x => |
|
113 case Codegen.get_node gr2 x of |
|
114 (SOME (EQN (s, T, _)), _, _) => (s, T) |
|
115 | _ => error ("RecfunCodegen: illegal cyclic dependencies:\n" ^ |
|
116 implode (separate ", " xs))) xs |
|
117 in |
|
118 (case xs of |
|
119 [_] => (module, put_code module fundef gr2) |
|
120 | _ => |
|
121 if not (member (op =) xs dep) then |
|
122 let |
|
123 val thmss as (_, thyname) :: _ = map (get_equations thy defs) cs; |
|
124 val module' = Codegen.if_library mode thyname module; |
|
125 val eqs'' = map (dest_eq o prop_of) (maps fst thmss); |
|
126 val (fundef', gr3) = mk_fundef module' "" true eqs'' |
|
127 (Codegen.add_edge (dname, dep) |
|
128 (List.foldr (uncurry Codegen.new_node) (Codegen.del_nodes xs gr2) |
|
129 (map (fn k => |
|
130 (k, (SOME (EQN ("", dummyT, dname)), module', ""))) xs))) |
|
131 in (module', put_code module' fundef' gr3) end |
|
132 else (module, gr2)) |
|
133 end |
|
134 | SOME (SOME (EQN (_, _, s)), module', _) => |
|
135 (module', if s = "" then |
|
136 if dname = dep then gr else Codegen.add_edge (dname, dep) gr |
|
137 else if s = dep then gr else Codegen.add_edge (s, dep) gr)) |
|
138 end; |
|
139 |
|
140 fun recfun_codegen thy mode defs dep module brack t gr = |
|
141 (case strip_comb t of |
|
142 (Const (p as (s, T)), ts) => |
|
143 (case (get_equations thy defs p, Codegen.get_assoc_code thy (s, T)) of |
|
144 (([], _), _) => NONE |
|
145 | (_, SOME _) => NONE |
|
146 | ((eqns, thyname), NONE) => |
|
147 let |
|
148 val module' = Codegen.if_library mode thyname module; |
|
149 val (ps, gr') = fold_map |
|
150 (Codegen.invoke_codegen thy mode defs dep module true) ts gr; |
|
151 val suffix = mk_suffix thy defs p; |
|
152 val (module'', gr'') = |
|
153 add_rec_funs thy mode defs dep module' (map prop_of eqns) gr'; |
|
154 val (fname, gr''') = Codegen.mk_const_id module'' (s ^ suffix) gr'' |
|
155 in |
|
156 SOME (Codegen.mk_app brack (Codegen.str (Codegen.mk_qual_id module fname)) ps, gr''') |
|
157 end) |
|
158 | _ => NONE); |
|
159 |
|
160 val setup = |
|
161 Codegen.add_codegen "recfun" recfun_codegen |
|
162 #> Code.set_code_target_attr add_thm_target; |
|
163 |
|
164 end; |
|