author | isatest |
Wed, 19 Sep 2007 13:52:54 +0200 | |
changeset 24647 | 212c9b342a67 |
parent 24584 | 01e83ffa6c54 |
child 25217 | 3224db6415ae |
permissions | -rw-r--r-- |
24584 | 1 |
(* Title: Tools/Compute_Oracle/am_ghc.ML |
23663 | 2 |
ID: $Id$ |
3 |
Author: Steven Obua |
|
4 |
*) |
|
5 |
||
6 |
structure AM_GHC : ABSTRACT_MACHINE = struct |
|
7 |
||
8 |
open AbstractMachine; |
|
9 |
||
10 |
type program = string * string * (int Inttab.table) |
|
11 |
||
12 |
||
13 |
(*Returns true iff at most 0 .. (free-1) occur unbound. therefore |
|
14 |
check_freevars 0 t iff t is closed*) |
|
15 |
fun check_freevars free (Var x) = x < free |
|
16 |
| check_freevars free (Const c) = true |
|
17 |
| check_freevars free (App (u, v)) = check_freevars free u andalso check_freevars free v |
|
18 |
| check_freevars free (Abs m) = check_freevars (free+1) m |
|
19 |
||
20 |
fun count_patternvars PVar = 1 |
|
21 |
| count_patternvars (PConst (_, ps)) = |
|
22 |
List.foldl (fn (p, count) => (count_patternvars p)+count) 0 ps |
|
23 |
||
24 |
fun update_arity arity code a = |
|
25 |
(case Inttab.lookup arity code of |
|
26 |
NONE => Inttab.update_new (code, a) arity |
|
24134
6e69e0031f34
added int type constraints to accomodate hacked SML/NJ;
wenzelm
parents:
23663
diff
changeset
|
27 |
| SOME (a': int) => if a > a' then Inttab.update (code, a) arity else arity) |
23663 | 28 |
|
29 |
(* We have to find out the maximal arity of each constant *) |
|
30 |
fun collect_pattern_arity PVar arity = arity |
|
31 |
| collect_pattern_arity (PConst (c, args)) arity = fold collect_pattern_arity args (update_arity arity c (length args)) |
|
32 |
||
33 |
local |
|
34 |
fun collect applevel (Var _) arity = arity |
|
35 |
| collect applevel (Const c) arity = update_arity arity c applevel |
|
36 |
| collect applevel (Abs m) arity = collect 0 m arity |
|
37 |
| collect applevel (App (a,b)) arity = collect 0 b (collect (applevel + 1) a arity) |
|
38 |
in |
|
39 |
fun collect_term_arity t arity = collect 0 t arity |
|
40 |
end |
|
41 |
||
42 |
fun nlift level n (Var m) = if m < level then Var m else Var (m+n) |
|
43 |
| nlift level n (Const c) = Const c |
|
44 |
| nlift level n (App (a,b)) = App (nlift level n a, nlift level n b) |
|
45 |
| nlift level n (Abs b) = Abs (nlift (level+1) n b) |
|
46 |
||
47 |
fun rep n x = if n = 0 then [] else x::(rep (n-1) x) |
|
48 |
||
49 |
fun adjust_rules rules = |
|
50 |
let |
|
51 |
val arity = fold (fn (p, t) => fn arity => collect_term_arity t (collect_pattern_arity p arity)) rules Inttab.empty |
|
52 |
fun arity_of c = the (Inttab.lookup arity c) |
|
53 |
fun adjust_pattern PVar = PVar |
|
54 |
| adjust_pattern (C as PConst (c, args)) = if (length args <> arity_of c) then raise Compile ("Constant inside pattern must have maximal arity") else C |
|
55 |
fun adjust_rule (PVar, t) = raise Compile ("pattern may not be a variable") |
|
56 |
| adjust_rule (rule as (p as PConst (c, args),t)) = |
|
57 |
let |
|
58 |
val _ = if not (check_freevars (count_patternvars p) t) then raise Compile ("unbound variables on right hand side") else () |
|
59 |
val args = map adjust_pattern args |
|
60 |
val len = length args |
|
61 |
val arity = arity_of c |
|
62 |
fun lift level n (Var m) = if m < level then Var m else Var (m+n) |
|
63 |
| lift level n (Const c) = Const c |
|
64 |
| lift level n (App (a,b)) = App (lift level n a, lift level n b) |
|
65 |
| lift level n (Abs b) = Abs (lift (level+1) n b) |
|
66 |
val lift = lift 0 |
|
67 |
fun adjust_term n t = if n=0 then t else adjust_term (n-1) (App (t, Var (n-1))) |
|
68 |
in |
|
69 |
if len = arity then |
|
70 |
rule |
|
71 |
else if arity >= len then |
|
72 |
(PConst (c, args @ (rep (arity-len) PVar)), adjust_term (arity-len) (lift (arity-len) t)) |
|
73 |
else (raise Compile "internal error in adjust_rule") |
|
74 |
end |
|
75 |
in |
|
76 |
(arity, map adjust_rule rules) |
|
77 |
end |
|
78 |
||
79 |
fun print_term arity_of n = |
|
80 |
let |
|
81 |
fun str x = string_of_int x |
|
82 |
fun protect_blank s = if exists_string Symbol.is_ascii_blank s then "(" ^ s ^")" else s |
|
83 |
||
84 |
fun print_apps d f [] = f |
|
85 |
| print_apps d f (a::args) = print_apps d ("app "^(protect_blank f)^" "^(protect_blank (print_term d a))) args |
|
86 |
and print_call d (App (a, b)) args = print_call d a (b::args) |
|
87 |
| print_call d (Const c) args = |
|
88 |
(case arity_of c of |
|
89 |
NONE => print_apps d ("Const "^(str c)) args |
|
90 |
| SOME a => |
|
91 |
let |
|
92 |
val len = length args |
|
93 |
in |
|
94 |
if a <= len then |
|
95 |
let |
|
96 |
val s = "c"^(str c)^(concat (map (fn t => " "^(protect_blank (print_term d t))) (List.take (args, a)))) |
|
97 |
in |
|
98 |
print_apps d s (List.drop (args, a)) |
|
99 |
end |
|
100 |
else |
|
101 |
let |
|
102 |
fun mk_apps n t = if n = 0 then t else mk_apps (n-1) (App (t, Var (n-1))) |
|
103 |
fun mk_lambdas n t = if n = 0 then t else mk_lambdas (n-1) (Abs t) |
|
104 |
fun append_args [] t = t |
|
105 |
| append_args (c::cs) t = append_args cs (App (t, c)) |
|
106 |
in |
|
107 |
print_term d (mk_lambdas (a-len) (mk_apps (a-len) (nlift 0 (a-len) (append_args args (Const c))))) |
|
108 |
end |
|
109 |
end) |
|
110 |
| print_call d t args = print_apps d (print_term d t) args |
|
111 |
and print_term d (Var x) = if x < d then "b"^(str (d-x-1)) else "x"^(str (n-(x-d)-1)) |
|
112 |
| print_term d (Abs c) = "Abs (\\b"^(str d)^" -> "^(print_term (d + 1) c)^")" |
|
113 |
| print_term d t = print_call d t [] |
|
114 |
in |
|
115 |
print_term 0 |
|
116 |
end |
|
117 |
||
118 |
fun print_rule arity_of (p, t) = |
|
119 |
let |
|
120 |
fun str x = Int.toString x |
|
121 |
fun print_pattern top n PVar = (n+1, "x"^(str n)) |
|
122 |
| print_pattern top n (PConst (c, [])) = (n, (if top then "c" else "C")^(str c)) |
|
123 |
| print_pattern top n (PConst (c, args)) = |
|
124 |
let |
|
125 |
val (n,s) = print_pattern_list (n, (if top then "c" else "C")^(str c)) args |
|
126 |
in |
|
127 |
(n, if top then s else "("^s^")") |
|
128 |
end |
|
129 |
and print_pattern_list r [] = r |
|
130 |
| print_pattern_list (n, p) (t::ts) = |
|
131 |
let |
|
132 |
val (n, t) = print_pattern false n t |
|
133 |
in |
|
134 |
print_pattern_list (n, p^" "^t) ts |
|
135 |
end |
|
136 |
val (n, pattern) = print_pattern true 0 p |
|
137 |
in |
|
138 |
pattern^" = "^(print_term arity_of n t) |
|
139 |
end |
|
140 |
||
141 |
fun group_rules rules = |
|
142 |
let |
|
143 |
fun add_rule (r as (PConst (c,_), _)) groups = |
|
144 |
let |
|
145 |
val rs = (case Inttab.lookup groups c of NONE => [] | SOME rs => rs) |
|
146 |
in |
|
147 |
Inttab.update (c, r::rs) groups |
|
148 |
end |
|
149 |
| add_rule _ _ = raise Compile "internal error group_rules" |
|
150 |
in |
|
151 |
fold_rev add_rule rules Inttab.empty |
|
152 |
end |
|
153 |
||
154 |
fun haskell_prog name rules = |
|
155 |
let |
|
156 |
val buffer = ref "" |
|
157 |
fun write s = (buffer := (!buffer)^s) |
|
158 |
fun writeln s = (write s; write "\n") |
|
159 |
fun writelist [] = () |
|
160 |
| writelist (s::ss) = (writeln s; writelist ss) |
|
161 |
fun str i = Int.toString i |
|
162 |
val (arity, rules) = adjust_rules rules |
|
163 |
val rules = group_rules rules |
|
164 |
val constants = Inttab.keys arity |
|
165 |
fun arity_of c = Inttab.lookup arity c |
|
166 |
fun rep_str s n = concat (rep n s) |
|
167 |
fun indexed s n = s^(str n) |
|
168 |
fun section n = if n = 0 then [] else (section (n-1))@[n-1] |
|
169 |
fun make_show c = |
|
170 |
let |
|
171 |
val args = section (the (arity_of c)) |
|
172 |
in |
|
173 |
" show ("^(indexed "C" c)^(concat (map (indexed " a") args))^") = " |
|
174 |
^"\""^(indexed "C" c)^"\""^(concat (map (fn a => "++(show "^(indexed "a" a)^")") args)) |
|
175 |
end |
|
176 |
fun default_case c = |
|
177 |
let |
|
178 |
val args = concat (map (indexed " x") (section (the (arity_of c)))) |
|
179 |
in |
|
180 |
(indexed "c" c)^args^" = "^(indexed "C" c)^args |
|
181 |
end |
|
182 |
val _ = writelist [ |
|
183 |
"module "^name^" where", |
|
184 |
"", |
|
185 |
"data Term = Const Integer | App Term Term | Abs (Term -> Term)", |
|
186 |
" "^(concat (map (fn c => " | C"^(str c)^(rep_str " Term" (the (arity_of c)))) constants)), |
|
187 |
"", |
|
188 |
"instance Show Term where"] |
|
189 |
val _ = writelist (map make_show constants) |
|
190 |
val _ = writelist [ |
|
191 |
" show (Const c) = \"c\"++(show c)", |
|
192 |
" show (App a b) = \"A\"++(show a)++(show b)", |
|
193 |
" show (Abs _) = \"L\"", |
|
194 |
""] |
|
195 |
val _ = writelist [ |
|
196 |
"app (Abs a) b = a b", |
|
197 |
"app a b = App a b", |
|
198 |
"", |
|
199 |
"calc s c = writeFile s (show c)", |
|
200 |
""] |
|
201 |
fun list_group c = (writelist (case Inttab.lookup rules c of |
|
202 |
NONE => [default_case c, ""] |
|
203 |
| SOME (rs as ((PConst (_, []), _)::rs')) => |
|
204 |
if not (null rs') then raise Compile "multiple declaration of constant" |
|
205 |
else (map (print_rule arity_of) rs) @ [""] |
|
206 |
| SOME rs => (map (print_rule arity_of) rs) @ [default_case c, ""])) |
|
207 |
val _ = map list_group constants |
|
208 |
in |
|
209 |
(arity, !buffer) |
|
210 |
end |
|
211 |
||
212 |
val guid_counter = ref 0 |
|
213 |
fun get_guid () = |
|
214 |
let |
|
215 |
val c = !guid_counter |
|
216 |
val _ = guid_counter := !guid_counter + 1 |
|
217 |
in |
|
218 |
(LargeInt.toString (Time.toMicroseconds (Time.now ()))) ^ (string_of_int c) |
|
219 |
end |
|
220 |
||
221 |
fun tmp_file s = Path.implode (Path.expand (File.tmp_path (Path.make [s]))); |
|
222 |
fun wrap s = "\""^s^"\"" |
|
223 |
||
224 |
fun writeTextFile name s = File.write (Path.explode name) s |
|
225 |
||
226 |
val ghc = ref (case getenv "GHC_PATH" of "" => "ghc" | s => s) |
|
227 |
||
228 |
fun fileExists name = ((OS.FileSys.fileSize name; true) handle OS.SysErr _ => false) |
|
229 |
||
230 |
fun compile eqs = |
|
231 |
let |
|
232 |
val _ = if exists (fn (a,b,c) => not (null a)) eqs then raise Compile ("cannot deal with guards") else () |
|
233 |
val eqs = map (fn (a,b,c) => (b,c)) eqs |
|
234 |
val guid = get_guid () |
|
235 |
val module = "AMGHC_Prog_"^guid |
|
236 |
val (arity, source) = haskell_prog module eqs |
|
237 |
val module_file = tmp_file (module^".hs") |
|
238 |
val object_file = tmp_file (module^".o") |
|
239 |
val _ = writeTextFile module_file source |
|
240 |
val _ = system ((!ghc)^" -c "^module_file) |
|
241 |
val _ = if not (fileExists object_file) then raise Compile ("Failure compiling haskell code (GHC_PATH = '"^(!ghc)^"')") else () |
|
242 |
in |
|
243 |
(guid, module_file, arity) |
|
244 |
end |
|
245 |
||
246 |
fun readResultFile name = File.read (Path.explode name) |
|
247 |
||
248 |
fun parse_result arity_of result = |
|
249 |
let |
|
250 |
val result = String.explode result |
|
251 |
fun shift NONE x = SOME x |
|
252 |
| shift (SOME y) x = SOME (y*10 + x) |
|
253 |
fun parse_int' x (#"0"::rest) = parse_int' (shift x 0) rest |
|
254 |
| parse_int' x (#"1"::rest) = parse_int' (shift x 1) rest |
|
255 |
| parse_int' x (#"2"::rest) = parse_int' (shift x 2) rest |
|
256 |
| parse_int' x (#"3"::rest) = parse_int' (shift x 3) rest |
|
257 |
| parse_int' x (#"4"::rest) = parse_int' (shift x 4) rest |
|
258 |
| parse_int' x (#"5"::rest) = parse_int' (shift x 5) rest |
|
259 |
| parse_int' x (#"6"::rest) = parse_int' (shift x 6) rest |
|
260 |
| parse_int' x (#"7"::rest) = parse_int' (shift x 7) rest |
|
261 |
| parse_int' x (#"8"::rest) = parse_int' (shift x 8) rest |
|
262 |
| parse_int' x (#"9"::rest) = parse_int' (shift x 9) rest |
|
263 |
| parse_int' x rest = (x, rest) |
|
264 |
fun parse_int rest = parse_int' NONE rest |
|
265 |
||
266 |
fun parse (#"C"::rest) = |
|
267 |
(case parse_int rest of |
|
268 |
(SOME c, rest) => |
|
269 |
let |
|
270 |
val (args, rest) = parse_list (the (arity_of c)) rest |
|
271 |
fun app_args [] t = t |
|
272 |
| app_args (x::xs) t = app_args xs (App (t, x)) |
|
273 |
in |
|
274 |
(app_args args (Const c), rest) |
|
275 |
end |
|
276 |
| (NONE, rest) => raise Run "parse C") |
|
277 |
| parse (#"c"::rest) = |
|
278 |
(case parse_int rest of |
|
279 |
(SOME c, rest) => (Const c, rest) |
|
280 |
| _ => raise Run "parse c") |
|
281 |
| parse (#"A"::rest) = |
|
282 |
let |
|
283 |
val (a, rest) = parse rest |
|
284 |
val (b, rest) = parse rest |
|
285 |
in |
|
286 |
(App (a,b), rest) |
|
287 |
end |
|
288 |
| parse (#"L"::rest) = raise Run "there may be no abstraction in the result" |
|
289 |
| parse _ = raise Run "invalid result" |
|
290 |
and parse_list n rest = |
|
291 |
if n = 0 then |
|
292 |
([], rest) |
|
293 |
else |
|
294 |
let |
|
295 |
val (x, rest) = parse rest |
|
296 |
val (xs, rest) = parse_list (n-1) rest |
|
297 |
in |
|
298 |
(x::xs, rest) |
|
299 |
end |
|
300 |
val (parsed, rest) = parse result |
|
301 |
fun is_blank (#" "::rest) = is_blank rest |
|
302 |
| is_blank (#"\n"::rest) = is_blank rest |
|
303 |
| is_blank [] = true |
|
304 |
| is_blank _ = false |
|
305 |
in |
|
306 |
if is_blank rest then parsed else raise Run "non-blank suffix in result file" |
|
307 |
end |
|
308 |
||
309 |
fun run (guid, module_file, arity) t = |
|
310 |
let |
|
311 |
val _ = if check_freevars 0 t then () else raise Run ("can only compute closed terms") |
|
312 |
fun arity_of c = Inttab.lookup arity c |
|
313 |
val callguid = get_guid() |
|
314 |
val module = "AMGHC_Prog_"^guid |
|
315 |
val call = module^"_Call_"^callguid |
|
316 |
val result_file = tmp_file (module^"_Result_"^callguid^".txt") |
|
317 |
val call_file = tmp_file (call^".hs") |
|
318 |
val term = print_term arity_of 0 t |
|
319 |
val call_source = "module "^call^" where\n\nimport "^module^"\n\ncall = "^module^".calc \""^result_file^"\" ("^term^")" |
|
320 |
val _ = writeTextFile call_file call_source |
|
321 |
val _ = system ((!ghc)^" -e \""^call^".call\" "^module_file^" "^call_file) |
|
322 |
val result = readResultFile result_file handle IO.Io _ => raise Run ("Failure running haskell compiler (GHC_PATH = '"^(!ghc)^"')") |
|
323 |
val t' = parse_result arity_of result |
|
324 |
val _ = OS.FileSys.remove call_file |
|
325 |
val _ = OS.FileSys.remove result_file |
|
326 |
in |
|
327 |
t' |
|
328 |
end |
|
329 |
||
330 |
||
331 |
fun discard _ = () |
|
332 |
||
333 |
end |
|
334 |