SCM Repository
Annotation of /trunk/src/compiler/simplify/simplify.sml
Parent Directory
|
Revision Log
Revision 3349 - (view) (download)
1 : | jhr | 171 | (* simplify.sml |
2 : | * | ||
3 : | jhr | 3349 | * This code is part of the Diderot Project (http://diderot-language.cs.uchicago.edu) |
4 : | * | ||
5 : | * COPYRIGHT (c) 2015 The University of Chicago | ||
6 : | jhr | 171 | * All rights reserved. |
7 : | * | ||
8 : | * Simplify the AST representation. | ||
9 : | *) | ||
10 : | |||
11 : | structure Simplify : sig | ||
12 : | |||
13 : | jhr | 1140 | val transform : Error.err_stream * AST.program -> Simple.program |
14 : | jhr | 171 | |
15 : | end = struct | ||
16 : | |||
17 : | jhr | 2491 | structure TU = TypeUtil |
18 : | jhr | 171 | structure S = Simple |
19 : | jhr | 2491 | structure VMap = Var.Map |
20 : | jhr | 2636 | structure InP = Inputs |
21 : | jhr | 171 | |
22 : | jhr | 2491 | val cvtTy = SimpleTypes.simplify |
23 : | jhr | 2356 | |
24 : | jhr | 2491 | fun newTemp ty = SimpleVar.new ("_t", SimpleVar.LocalVar, ty) |
25 : | jhr | 171 | |
26 : | jhr | 2491 | (* convert an AST variable to a Simple variable *) |
27 : | fun cvtVar (env, x as Var.V{name, kind, ty=([], ty), ...}) = let | ||
28 : | val x' = SimpleVar.new (name, kind, cvtTy ty) | ||
29 : | in | ||
30 : | (x', VMap.insert(env, x, x')) | ||
31 : | end | ||
32 : | |||
33 : | fun cvtVars (env, xs) = List.foldr | ||
34 : | (fn (x, (xs, env)) => let | ||
35 : | val (x', env) = cvtVar(env, x) | ||
36 : | in | ||
37 : | (x'::xs, env) | ||
38 : | end) ([], env) xs | ||
39 : | |||
40 : | fun lookupVar (env, x) = (case VMap.find (env, x) | ||
41 : | of SOME x' => x' | ||
42 : | | NONE => raise Fail(concat["lookupVar(", Var.uniqueNameOf x, ")"]) | ||
43 : | (* end case *)) | ||
44 : | |||
45 : | jhr | 171 | (* make a block out of a list of statements that are in reverse order *) |
46 : | jhr | 197 | fun mkBlock stms = S.Block(List.rev stms) |
47 : | jhr | 171 | |
48 : | jhr | 2636 | (* convert an AST expression to an input initialization. Note that the Diderot grammar |
49 : | * limits the forms of expression that we might encounter in this context. | ||
50 : | *) | ||
51 : | fun expToInit (ty, exp) = (case exp | ||
52 : | of AST.E_Lit(Literal.Int n) => InP.Int n | ||
53 : | | AST.E_Lit(Literal.Float f) => InP.Real f | ||
54 : | | AST.E_Lit(Literal.String s) => InP.String s | ||
55 : | | AST.E_Lit(Literal.Bool b) => InP.Bool b | ||
56 : | | AST.E_Tuple es => raise Fail "E_Tuple not yet implemented" | ||
57 : | | AST.E_Cons es => let | ||
58 : | val shp = (case ty | ||
59 : | of SimpleTypes.T_Tensor shp => shp | ||
60 : | | _ => raise Fail "not tensor type" | ||
61 : | (* end case *)) | ||
62 : | fun flatten (AST.E_Lit(Literal.Int n), l) = FloatLit.fromInt n :: l | ||
63 : | | flatten (AST.E_Lit(Literal.Float f), l) = f :: l | ||
64 : | | flatten (AST.E_Coerce{e, ...}, l) = flatten(e, l) | ||
65 : | | flatten (AST.E_Cons es, l) = flattenList (es, l) | ||
66 : | | flatten _ = raise Fail "impossible" | ||
67 : | and flattenList ([], l) = l | ||
68 : | | flattenList (x::xs, l) = flatten(x, flattenList(xs, l)) | ||
69 : | in | ||
70 : | InP.Tensor(shp, Vector.fromList(flattenList (es, []))) | ||
71 : | end | ||
72 : | (* | ||
73 : | | AST.E_Seq es => ?? | ||
74 : | | AST.E_Coerce{srcTy, dstTy, e} => ?? | ||
75 : | *) | ||
76 : | | _ => raise Fail "impossible initialization expression" | ||
77 : | (* end case *)) | ||
78 : | |||
79 : | fun inputImage (nrrd, dim, shape) = ( | ||
80 : | case ImageInfo.fromNrrd(NrrdInfo.getInfo nrrd, dim, shape) | ||
81 : | of NONE => raise Fail(concat["nrrd file \"", nrrd, "\" does not have expected type"]) | ||
82 : | | SOME info => InP.Proxy(nrrd, info) | ||
83 : | (* end case *)) | ||
84 : | |||
85 : | jhr | 2356 | (* is the given statement's continuation the syntactically following statement? *) |
86 : | fun contIsNext (AST.S_Block stms) = List.all contIsNext stms | ||
87 : | | contIsNext (AST.S_IfThenElse(_, s1, s2)) = contIsNext s1 orelse contIsNext s2 | ||
88 : | | contIsNext AST.S_Die = false | ||
89 : | | contIsNext AST.S_Stabilize = false | ||
90 : | | contIsNext (AST.S_Return _) = false | ||
91 : | | contIsNext _ = true | ||
92 : | |||
93 : | jhr | 2636 | fun simplifyProgram (AST.Program{props, decls}) = let |
94 : | val inputs = ref [] | ||
95 : | jhr | 2356 | val globals = ref [] |
96 : | val globalInit = ref [] | ||
97 : | val funcs = ref [] | ||
98 : | val initially = ref NONE | ||
99 : | val strands = ref [] | ||
100 : | fun setInitially init = (case !initially | ||
101 : | of NONE => initially := SOME init | ||
102 : | jhr | 1116 | (* FIXME: the check for multiple initially decls should happen in type checking *) |
103 : | jhr | 2356 | | SOME _ => raise Fail "multiple initially declarations" |
104 : | (* end case *)) | ||
105 : | jhr | 2491 | fun simplifyDecl (dcl, env) = (case dcl |
106 : | jhr | 2356 | of AST.D_Input(x, desc, NONE) => let |
107 : | jhr | 2491 | val (x', env) = cvtVar(env, x) |
108 : | jhr | 2636 | val (ty, init) = (case SimpleVar.typeOf x' |
109 : | of ty as SimpleTypes.T_Image{dim, shape} => let | ||
110 : | val info = ImageInfo.mkInfo(dim, shape) | ||
111 : | in | ||
112 : | (ty, SOME(InP.Image info)) | ||
113 : | end | ||
114 : | | ty => (ty, NONE) | ||
115 : | (* end case *)) | ||
116 : | val inp = InP.INP{ | ||
117 : | ty = ty, | ||
118 : | name = SimpleVar.nameOf x', | ||
119 : | desc = desc, | ||
120 : | init = init | ||
121 : | } | ||
122 : | jhr | 2356 | in |
123 : | jhr | 2636 | inputs := (x', inp) :: !inputs; |
124 : | jhr | 2491 | env |
125 : | jhr | 2356 | end |
126 : | jhr | 2636 | | AST.D_Input(x, desc, SOME(AST.E_LoadNrrd(tvs, nrrd, ty))) => let |
127 : | val (x', env) = cvtVar(env, x) | ||
128 : | (* load the nrrd proxy here *) | ||
129 : | val info = NrrdInfo.getInfo nrrd | ||
130 : | val (ty, init) = (case SimpleVar.typeOf x' | ||
131 : | of ty as SimpleTypes.T_Image{dim, shape} => | ||
132 : | (ty, inputImage(nrrd, dim, shape)) | ||
133 : | | _ => raise Fail "impossible" | ||
134 : | (* end case *)) | ||
135 : | val inp = InP.INP{ | ||
136 : | ty = ty, | ||
137 : | name = SimpleVar.nameOf x', | ||
138 : | desc = desc, | ||
139 : | init = SOME init | ||
140 : | } | ||
141 : | in | ||
142 : | inputs := (x', inp) :: !inputs; | ||
143 : | env | ||
144 : | end | ||
145 : | jhr | 2356 | | AST.D_Input(x, desc, SOME e) => let |
146 : | jhr | 2491 | val (x', env) = cvtVar(env, x) |
147 : | jhr | 2636 | val inp = InP.INP{ |
148 : | ty = SimpleVar.typeOf x', | ||
149 : | name = SimpleVar.nameOf x', | ||
150 : | desc = desc, | ||
151 : | init = SOME(expToInit(SimpleVar.typeOf x', e)) | ||
152 : | } | ||
153 : | jhr | 2356 | in |
154 : | jhr | 2636 | inputs := (x', inp) :: !inputs; |
155 : | jhr | 2491 | env |
156 : | jhr | 2356 | end |
157 : | | AST.D_Var(AST.VD_Decl(x, e)) => let | ||
158 : | jhr | 2491 | val (x', env) = cvtVar(env, x) |
159 : | val (stms, e') = simplifyExp (env, e, []) | ||
160 : | jhr | 2356 | in |
161 : | jhr | 2491 | globals := x' :: !globals; |
162 : | globalInit := S.S_Assign(x', e') :: (stms @ !globalInit); | ||
163 : | env | ||
164 : | jhr | 2356 | end |
165 : | jhr | 2491 | | AST.D_Func(f, params, body) => let |
166 : | val (f', env) = cvtVar(env, f) | ||
167 : | val (params', env) = cvtVars (env, params) | ||
168 : | val body' = simplifyBlock(env, body) | ||
169 : | in | ||
170 : | funcs := S.Func{f=f', params=params', body=body'} :: !funcs; | ||
171 : | env | ||
172 : | end | ||
173 : | | AST.D_Strand info => ( | ||
174 : | strands := simplifyStrand(env, info) :: !strands; | ||
175 : | env) | ||
176 : | | AST.D_InitialArray(creat, iters) => ( | ||
177 : | setInitially (simplifyInit(env, true, creat, iters)); | ||
178 : | env) | ||
179 : | | AST.D_InitialCollection(creat, iters) => ( | ||
180 : | setInitially (simplifyInit(env, false, creat, iters)); | ||
181 : | env) | ||
182 : | jhr | 2356 | (* end case *)) |
183 : | jhr | 2636 | val env = List.foldl simplifyDecl VMap.empty decls |
184 : | jhr | 2356 | in |
185 : | S.Program{ | ||
186 : | jhr | 2636 | props = props, |
187 : | inputs = List.rev(!inputs), | ||
188 : | jhr | 2356 | globals = List.rev(!globals), |
189 : | globalInit = mkBlock (!globalInit), | ||
190 : | funcs = List.rev(!funcs), | ||
191 : | init = (case !initially | ||
192 : | jhr | 1116 | (* FIXME: the check for the initially block should really happen in typechecking *) |
193 : | jhr | 2356 | of NONE => raise Fail "missing initially declaration" |
194 : | | SOME blk => blk | ||
195 : | (* end case *)), | ||
196 : | strands = List.rev(!strands) | ||
197 : | } | ||
198 : | end | ||
199 : | jhr | 171 | |
200 : | jhr | 2491 | and simplifyInit (env, isArray, AST.C_Create(strand, exps), iters) = let |
201 : | fun simplifyIter (AST.I_Range(x, e1, e2), (env, iters, stms)) = let | ||
202 : | val (stms, lo) = simplifyExpToVar (env, e1, stms) | ||
203 : | val (stms, hi) = simplifyExpToVar (env, e2, stms) | ||
204 : | val (x', env) = cvtVar (env, x) | ||
205 : | in | ||
206 : | (env, {param=x', lo=lo, hi=hi}::iters, stms) | ||
207 : | end | ||
208 : | val (env, iters, iterStms) = List.foldl simplifyIter (env, [], []) iters | ||
209 : | val (stms, xs) = simplifyExpsToVars (env, exps, []) | ||
210 : | jhr | 2356 | val creat = S.C_Create{ |
211 : | argInit = mkBlock stms, | ||
212 : | name = strand, | ||
213 : | args = xs | ||
214 : | } | ||
215 : | in | ||
216 : | S.Initially{ | ||
217 : | isArray = isArray, | ||
218 : | jhr | 2491 | rangeInit = mkBlock iterStms, |
219 : | jhr | 2356 | iters = List.rev iters, |
220 : | create = creat | ||
221 : | } | ||
222 : | end | ||
223 : | jhr | 1116 | |
224 : | jhr | 2491 | and simplifyStrand (env, AST.Strand{name, params, state, methods}) = let |
225 : | val (params', env) = cvtVars (env, params) | ||
226 : | fun simplifyState (env, [], xs, stms) = (List.rev xs, mkBlock stms, env) | ||
227 : | | simplifyState (env, AST.VD_Decl(x, e) :: r, xs, stms) = let | ||
228 : | val (stms, e') = simplifyExp (env, e, stms) | ||
229 : | val (x', env) = cvtVar(env, x) | ||
230 : | jhr | 2356 | in |
231 : | jhr | 2491 | simplifyState (env, r, x'::xs, S.S_Assign(x', e') :: stms) |
232 : | jhr | 2356 | end |
233 : | jhr | 2491 | val (xs, stm, env) = simplifyState (env, state, [], []) |
234 : | jhr | 2356 | in |
235 : | S.Strand{ | ||
236 : | name = name, | ||
237 : | jhr | 2491 | params = params', |
238 : | jhr | 2356 | state = xs, stateInit = stm, |
239 : | jhr | 2491 | methods = List.map (simplifyMethod env) methods |
240 : | jhr | 2356 | } |
241 : | end | ||
242 : | jhr | 171 | |
243 : | jhr | 2491 | and simplifyMethod env (AST.M_Method(name, body)) = |
244 : | S.Method(name, simplifyBlock(env, body)) | ||
245 : | jhr | 171 | |
246 : | jhr | 1116 | (* simplify a statement into a single statement (i.e., a block if it expands |
247 : | * into more than one new statement). | ||
248 : | jhr | 171 | *) |
249 : | jhr | 2491 | and simplifyBlock (env, stm) = mkBlock (#1 (simplifyStmt (env, stm, []))) |
250 : | jhr | 171 | |
251 : | jhr | 2356 | (* simplify the statement stm where stms is a reverse-order list of preceeding simplified |
252 : | * statements. This function returns a reverse-order list of simplified statements. | ||
253 : | * Note that error reporting is done in the typechecker, but it does not prune unreachable | ||
254 : | * code. | ||
255 : | *) | ||
256 : | jhr | 2491 | and simplifyStmt (env, stm, stms) = (case stm |
257 : | jhr | 2356 | of AST.S_Block body => let |
258 : | jhr | 2491 | fun simplify (_, [], stms) = stms |
259 : | | simplify (env', stm::r, stms) = let | ||
260 : | val (stms, env') = simplifyStmt (env', stm, stms) | ||
261 : | in | ||
262 : | if contIsNext stm | ||
263 : | then simplify (env', r, stms) | ||
264 : | else stms (* prune the unreachable statements "r" *) | ||
265 : | end | ||
266 : | jhr | 2356 | in |
267 : | jhr | 2491 | (simplify (env, body, stms), env) |
268 : | jhr | 2356 | end |
269 : | | AST.S_Decl(AST.VD_Decl(x, e)) => let | ||
270 : | jhr | 2491 | val (stms, e') = simplifyExp (env, e, stms) |
271 : | val (x', env) = cvtVar(env, x) | ||
272 : | jhr | 2356 | in |
273 : | jhr | 2491 | (S.S_Assign(x', e') :: stms, env) |
274 : | jhr | 2356 | end |
275 : | | AST.S_IfThenElse(e, s1, s2) => let | ||
276 : | jhr | 2491 | val (stms, x) = simplifyExpToVar (env, e, stms) |
277 : | val s1 = simplifyBlock (env, s1) | ||
278 : | val s2 = simplifyBlock (env, s2) | ||
279 : | jhr | 2356 | in |
280 : | jhr | 2491 | (S.S_IfThenElse(x, s1, s2) :: stms, env) |
281 : | jhr | 2356 | end |
282 : | | AST.S_Assign(x, e) => let | ||
283 : | jhr | 2491 | val (stms, e') = simplifyExp (env, e, stms) |
284 : | jhr | 2356 | in |
285 : | jhr | 2491 | (S.S_Assign(lookupVar(env, x), e') :: stms, env) |
286 : | jhr | 2356 | end |
287 : | | AST.S_New(name, args) => let | ||
288 : | jhr | 2491 | val (stms, xs) = simplifyExpsToVars (env, args, stms) |
289 : | jhr | 2356 | in |
290 : | jhr | 2491 | (S.S_New(name, xs) :: stms, env) |
291 : | jhr | 2356 | end |
292 : | jhr | 2491 | | AST.S_Die => (S.S_Die :: stms, env) |
293 : | | AST.S_Stabilize => (S.S_Stabilize :: stms, env) | ||
294 : | jhr | 2356 | | AST.S_Return e => let |
295 : | jhr | 2491 | val (stms, x) = simplifyExpToVar (env, e, stms) |
296 : | jhr | 2356 | in |
297 : | jhr | 2491 | (S.S_Return x :: stms, env) |
298 : | jhr | 2356 | end |
299 : | jhr | 1640 | | AST.S_Print args => let |
300 : | jhr | 2491 | val (stms, xs) = simplifyExpsToVars (env, args, stms) |
301 : | jhr | 1640 | in |
302 : | jhr | 2491 | (S.S_Print xs :: stms, env) |
303 : | jhr | 1640 | end |
304 : | jhr | 2356 | (* end case *)) |
305 : | jhr | 171 | |
306 : | jhr | 2491 | and simplifyExp (env, exp, stms) = ( |
307 : | jhr | 2356 | case exp |
308 : | of AST.E_Var x => (case Var.kindOf x | ||
309 : | of Var.BasisVar => let | ||
310 : | jhr | 2491 | val ty = cvtTy(Var.monoTypeOf x) |
311 : | jhr | 2356 | val x' = newTemp ty |
312 : | jhr | 2491 | val stm = S.S_Assign(x', S.E_Prim(x, [], [], ty)) |
313 : | jhr | 2356 | in |
314 : | (stm::stms, S.E_Var x') | ||
315 : | end | ||
316 : | jhr | 2491 | | _ => (stms, S.E_Var(lookupVar(env, x))) |
317 : | jhr | 2356 | (* end case *)) |
318 : | | AST.E_Lit lit => (stms, S.E_Lit lit) | ||
319 : | | AST.E_Tuple es => raise Fail "E_Tuple not yet implemented" | ||
320 : | | AST.E_Apply(f, tyArgs, args, ty) => let | ||
321 : | jhr | 2491 | val (stms, xs) = simplifyExpsToVars (env, args, stms) |
322 : | jhr | 2356 | in |
323 : | jhr | 2491 | case Var.kindOf f |
324 : | of S.FunVar => (stms, S.E_Apply(lookupVar(env, f), xs, cvtTy ty)) | ||
325 : | | S.BasisVar => let | ||
326 : | fun cvtTyArg (Types.TYPE tv) = S.TY(cvtTy(TU.resolve tv)) | ||
327 : | | cvtTyArg (Types.DIFF dv) = S.DIFF(TU.monoDiff(TU.resolveDiff dv)) | ||
328 : | | cvtTyArg (Types.SHAPE sv) = S.SHAPE(TU.monoShape(TU.resolveShape sv)) | ||
329 : | | cvtTyArg (Types.DIM dv) = S.DIM(TU.monoDim(TU.resolveDim dv)) | ||
330 : | val tyArgs = List.map cvtTyArg tyArgs | ||
331 : | in | ||
332 : | (stms, S.E_Prim(f, tyArgs, xs, cvtTy ty)) | ||
333 : | end | ||
334 : | | _ => raise Fail "bogus application" | ||
335 : | (* end case *) | ||
336 : | jhr | 2356 | end |
337 : | | AST.E_Cons es => let | ||
338 : | jhr | 2491 | val (stms, xs) = simplifyExpsToVars (env, es, stms) |
339 : | jhr | 2356 | in |
340 : | (stms, S.E_Cons xs) | ||
341 : | end | ||
342 : | jhr | 2636 | | AST.E_Seq es => let |
343 : | val (stms, xs) = simplifyExpsToVars (env, es, stms) | ||
344 : | in | ||
345 : | (stms, S.E_Seq xs) | ||
346 : | end | ||
347 : | jhr | 2356 | | AST.E_Slice(e, indices, ty) => let (* tensor slicing *) |
348 : | jhr | 2491 | val (stms, x) = simplifyExpToVar (env, e, stms) |
349 : | jhr | 2356 | fun f ([], ys, stms) = (stms, List.rev ys) |
350 : | | f (NONE::es, ys, stms) = f (es, NONE::ys, stms) | ||
351 : | | f (SOME e::es, ys, stms) = let | ||
352 : | jhr | 2491 | val (stms, y) = simplifyExpToVar (env, e, stms) |
353 : | jhr | 2356 | in |
354 : | f (es, SOME y::ys, stms) | ||
355 : | end | ||
356 : | val (stms, indices) = f (indices, [], stms) | ||
357 : | in | ||
358 : | jhr | 2491 | (stms, S.E_Slice(x, indices, cvtTy ty)) |
359 : | jhr | 2356 | end |
360 : | | AST.E_Cond(e1, e2, e3, ty) => let | ||
361 : | (* a conditional expression gets turned into an if-then-else statememt *) | ||
362 : | jhr | 2491 | val result = newTemp(cvtTy ty) |
363 : | val (stms, x) = simplifyExpToVar (env, e1, S.S_Var result :: stms) | ||
364 : | jhr | 2356 | fun simplifyBranch e = let |
365 : | jhr | 2491 | val (stms, e) = simplifyExp (env, e, []) |
366 : | jhr | 2356 | in |
367 : | mkBlock (S.S_Assign(result, e)::stms) | ||
368 : | end | ||
369 : | val s1 = simplifyBranch e2 | ||
370 : | val s2 = simplifyBranch e3 | ||
371 : | in | ||
372 : | (S.S_IfThenElse(x, s1, s2) :: stms, S.E_Var result) | ||
373 : | end | ||
374 : | jhr | 2636 | | AST.E_LoadNrrd(_, nrrd, ty) => (case cvtTy ty |
375 : | of ty as SimpleTypes.T_Image{dim, shape} => ( | ||
376 : | case ImageInfo.fromNrrd(NrrdInfo.getInfo nrrd, dim, shape) | ||
377 : | of NONE => raise Fail(concat[ | ||
378 : | "nrrd file \"", nrrd, "\" does not have expected type" | ||
379 : | ]) | ||
380 : | | SOME info => (stms, S.E_LoadImage(ty, nrrd, info)) | ||
381 : | (* end case *)) | ||
382 : | | _ => raise Fail "bogus type for E_LoadNrrd" | ||
383 : | (* end case *)) | ||
384 : | jhr | 2356 | | AST.E_Coerce{srcTy, dstTy, e} => let |
385 : | jhr | 2491 | val (stms, x) = simplifyExpToVar (env, e, stms) |
386 : | val dstTy = cvtTy dstTy | ||
387 : | jhr | 2356 | val result = newTemp dstTy |
388 : | jhr | 2491 | val rhs = S.E_Coerce{srcTy = cvtTy srcTy, dstTy = dstTy, x = x} |
389 : | jhr | 2356 | in |
390 : | (S.S_Assign(result, rhs)::stms, S.E_Var result) | ||
391 : | end | ||
392 : | (* end case *)) | ||
393 : | jhr | 171 | |
394 : | jhr | 2491 | and simplifyExpToVar (env, exp, stms) = let |
395 : | val (stms, e) = simplifyExp (env, exp, stms) | ||
396 : | jhr | 2356 | in |
397 : | case e | ||
398 : | of S.E_Var x => (stms, x) | ||
399 : | | _ => let | ||
400 : | val x = newTemp (S.typeOf e) | ||
401 : | in | ||
402 : | (S.S_Assign(x, e)::stms, x) | ||
403 : | end | ||
404 : | (* end case *) | ||
405 : | end | ||
406 : | jhr | 171 | |
407 : | jhr | 2491 | and simplifyExpsToVars (env, exps, stms) = let |
408 : | jhr | 2356 | fun f ([], xs, stms) = (stms, List.rev xs) |
409 : | | f (e::es, xs, stms) = let | ||
410 : | jhr | 2491 | val (stms, x) = simplifyExpToVar (env, e, stms) |
411 : | jhr | 2356 | in |
412 : | f (es, x::xs, stms) | ||
413 : | end | ||
414 : | in | ||
415 : | f (exps, [], stms) | ||
416 : | end | ||
417 : | jhr | 171 | |
418 : | jhr | 1140 | fun transform (errStrm, ast) = let |
419 : | jhr | 2356 | val simple = simplifyProgram ast |
420 : | val _ = SimplePP.output (Log.logFile(), "simplify", simple) (* DEBUG *) | ||
421 : | val simple = Inliner.transform simple | ||
422 : | val _ = SimplePP.output (Log.logFile(), "inlining", simple) (* DEBUG *) | ||
423 : | in | ||
424 : | simple | ||
425 : | end | ||
426 : | jhr | 227 | |
427 : | jhr | 171 | end |
root@smlnj-gforge.cs.uchicago.edu | ViewVC Help |
Powered by ViewVC 1.0.0 |