adamc@1272: (* Copyright (c) 2008-2010, Adam Chlipala adamc@443: * All rights reserved. adamc@443: * adamc@443: * Redistribution and use in source and binary forms, with or without adamc@443: * modification, are permitted provided that the following conditions are met: adamc@443: * adamc@443: * - Redistributions of source code must retain the above copyright notice, adamc@443: * this list of conditions and the following disclaimer. adamc@443: * - Redistributions in binary form must reproduce the above copyright notice, adamc@443: * this list of conditions and the following disclaimer in the documentation adamc@443: * and/or other materials provided with the distribution. adamc@443: * - The names of contributors may not be used to endorse or promote products adamc@443: * derived from this software without specific prior written permission. adamc@443: * adamc@443: * THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" adamc@443: * AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE adamc@443: * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE adamc@443: * ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER OR CONTRIBUTORS BE adamc@443: * LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR adamc@443: * CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF adamc@443: * SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS adamc@443: * INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN adamc@443: * CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) adamc@443: * ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE adamc@443: * POSSIBILITY OF SUCH DAMAGE. adamc@443: *) adamc@443: adamc@443: structure ESpecialize :> ESPECIALIZE = struct adamc@443: adamc@443: open Core adamc@443: adamc@443: structure E = CoreEnv adamc@443: structure U = CoreUtil adamc@443: adamc@479: type skey = exp adamc@453: adamc@453: structure K = struct adamc@479: type ord_key = exp list adamc@479: val compare = Order.joinL U.Exp.compare adamc@443: end adamc@443: adamc@453: structure KM = BinaryMapFn(K) adamc@443: structure IM = IntBinaryMap adamc@482: structure IS = IntBinarySet adamc@443: adamc@626: val freeVars = U.Exp.foldB {kind = fn (_, _, xs) => xs, adamc@488: con = fn (_, _, xs) => xs, adamc@488: exp = fn (bound, e, xs) => adamc@488: case e of adamc@488: ERel x => adamc@488: if x >= bound then adamc@488: IS.add (xs, x - bound) adamc@488: else adamc@488: xs adamc@488: | _ => xs, adamc@488: bind = fn (bound, b) => adamc@488: case b of adamc@488: U.Exp.RelE _ => bound + 1 adamc@488: | _ => bound} adamc@488: 0 IS.empty adamc@479: adamc@1120: fun isPolyT (t, _) = adamc@1120: case t of adamc@1120: TFun (_, ran) => isPolyT ran adamc@1120: | TCFun _ => true adamc@1120: | TKFun _ => true adamc@1120: | _ => false adamc@1120: adamc@1120: fun isPoly (d, _) = adamc@1120: case d of adamc@1120: DVal (_, _, t, _, _) => isPolyT t adamc@1120: | DValRec vis => List.exists (isPolyT o #3) vis adamc@1120: | _ => false adamc@522: adamc@488: fun positionOf (v : int, ls) = adamc@488: let adamc@488: fun pof (pos, ls) = adamc@488: case ls of adamc@488: [] => raise Fail "Defunc.positionOf" adamc@488: | v' :: ls' => adamc@488: if v = v' then adamc@488: pos adamc@488: else adamc@488: pof (pos + 1, ls') adamc@488: in adamc@488: pof (0, ls) adamc@488: end adamc@488: adamc@1079: fun squish fvs = adamc@626: U.Exp.mapB {kind = fn _ => fn k => k, adamc@488: con = fn _ => fn c => c, adamc@488: exp = fn bound => fn e => adamc@479: case e of adamc@488: ERel x => adamc@488: if x >= bound then adamc@1079: ERel (positionOf (x - bound, fvs) + bound) adamc@488: else adamc@488: e adamc@488: | _ => e, adamc@488: bind = fn (bound, b) => adamc@488: case b of adamc@488: U.Exp.RelE _ => bound + 1 adamc@488: | _ => bound} adamc@488: 0 adamc@453: adamc@443: type func = { adamc@443: name : string, adamc@453: args : int KM.map, adamc@443: body : exp, adamc@443: typ : con, adamc@443: tag : string adamc@443: } adamc@443: adamc@443: type state = { adamc@443: maxName : int, adamc@443: funcs : func IM.map, adamc@1079: decls : (string * int * con * exp * string) list, adamc@1080: specialized : IS.set adamc@443: } adamc@443: adamc@488: fun default (_, x, st) = (x, st) adamc@443: adamc@800: structure SS = BinarySetFn(struct adamc@800: type ord_key = string adamc@800: val compare = String.compare adamc@800: end) adamc@800: adamc@800: val mayNotSpec = ref SS.empty adamc@800: adamc@1080: fun specialize' (funcs, specialized) file = adamc@443: let adamc@488: fun bind (env, b) = adamc@488: case b of adamc@521: U.Decl.RelE xt => xt :: env adamc@521: | _ => env adamc@488: adamc@1080: fun exp (env, e as (_, loc), st : state) = adamc@482: let adamc@721: (*val () = Print.prefaces "exp" [("e", CorePrint.p_exp CoreEnv.empty adamc@721: (e, ErrorMsg.dummySpan))]*) adamc@721: adamc@1080: fun getApp (e, _) = adamc@482: case e of adamc@488: ENamed f => SOME (f, []) adamc@482: | EApp (e1, e2) => adamc@1080: (case getApp e1 of adamc@482: NONE => NONE adamc@488: | SOME (f, xs) => SOME (f, xs @ [e2])) adamc@482: | _ => NONE adamc@1080: adamc@1080: val getApp = fn e => case getApp e of adamc@1080: v as SOME (_, _ :: _) => v adamc@1080: | _ => NONE adamc@1080: adamc@1080: fun default () = adamc@1080: case #1 e of adamc@1080: EPrim _ => (e, st) adamc@1080: | ERel _ => (e, st) adamc@1080: | ENamed _ => (e, st) adamc@1080: | ECon (_, _, _, NONE) => (e, st) adamc@1080: | ECon (dk, pc, cs, SOME e) => adamc@1080: let adamc@1080: val (e, st) = exp (env, e, st) adamc@1080: in adamc@1080: ((ECon (dk, pc, cs, SOME e), loc), st) adamc@1080: end adamc@1080: | EFfi _ => (e, st) adamc@1080: | EFfiApp (m, x, es) => adamc@1080: let adamc@1080: val (es, st) = ListUtil.foldlMap (fn (e, st) => exp (env, e, st)) st es adamc@1080: in adamc@1080: ((EFfiApp (m, x, es), loc), st) adamc@1080: end adamc@1080: | EApp (e1, e2) => adamc@1080: let adamc@1080: val (e1, st) = exp (env, e1, st) adamc@1080: val (e2, st) = exp (env, e2, st) adamc@1080: in adamc@1080: ((EApp (e1, e2), loc), st) adamc@1080: end adamc@1080: | EAbs (x, d, r, e) => adamc@1080: let adamc@1080: val (e, st) = exp ((x, d) :: env, e, st) adamc@1080: in adamc@1080: ((EAbs (x, d, r, e), loc), st) adamc@1080: end adamc@1080: | ECApp (e, c) => adamc@1080: let adamc@1080: val (e, st) = exp (env, e, st) adamc@1080: in adamc@1080: ((ECApp (e, c), loc), st) adamc@1080: end adamc@1185: | ECAbs _ => (e, st) adamc@1120: | EKAbs _ => (e, st) adamc@1080: | EKApp (e, k) => adamc@1080: let adamc@1080: val (e, st) = exp (env, e, st) adamc@1080: in adamc@1080: ((EKApp (e, k), loc), st) adamc@1080: end adamc@1080: | ERecord fs => adamc@1080: let adamc@1080: val (fs, st) = ListUtil.foldlMap (fn ((c1, e, c2), st) => adamc@1080: let adamc@1080: val (e, st) = exp (env, e, st) adamc@1080: in adamc@1080: ((c1, e, c2), st) adamc@1080: end) st fs adamc@1080: in adamc@1080: ((ERecord fs, loc), st) adamc@1080: end adamc@1080: | EField (e, c, cs) => adamc@1080: let adamc@1080: val (e, st) = exp (env, e, st) adamc@1080: in adamc@1080: ((EField (e, c, cs), loc), st) adamc@1080: end adamc@1080: | EConcat (e1, c1, e2, c2) => adamc@1080: let adamc@1080: val (e1, st) = exp (env, e1, st) adamc@1080: val (e2, st) = exp (env, e2, st) adamc@1080: in adamc@1080: ((EConcat (e1, c1, e2, c2), loc), st) adamc@1080: end adamc@1080: | ECut (e, c, cs) => adamc@1080: let adamc@1080: val (e, st) = exp (env, e, st) adamc@1080: in adamc@1080: ((ECut (e, c, cs), loc), st) adamc@1080: end adamc@1080: | ECutMulti (e, c, cs) => adamc@1080: let adamc@1080: val (e, st) = exp (env, e, st) adamc@1080: in adamc@1080: ((ECutMulti (e, c, cs), loc), st) adamc@1080: end adamc@1080: adamc@1080: | ECase (e, pes, cs) => adamc@1080: let adamc@1080: val (e, st) = exp (env, e, st) adamc@1080: val (pes, st) = ListUtil.foldlMap (fn ((p, e), st) => adamc@1080: let adamc@1080: val (e, st) = exp (E.patBindsL p @ env, e, st) adamc@1080: in adamc@1080: ((p, e), st) adamc@1080: end) st pes adamc@1080: in adamc@1080: ((ECase (e, pes, cs), loc), st) adamc@1080: end adamc@1080: adamc@1080: | EWrite e => adamc@1080: let adamc@1080: val (e, st) = exp (env, e, st) adamc@1080: in adamc@1080: ((EWrite e, loc), st) adamc@1080: end adamc@1080: | EClosure (n, es) => adamc@1080: let adamc@1080: val (es, st) = ListUtil.foldlMap (fn (e, st) => exp (env, e, st)) st es adamc@1080: in adamc@1080: ((EClosure (n, es), loc), st) adamc@1080: end adamc@1080: | ELet (x, t, e1, e2) => adamc@1080: let adamc@1080: val (e1, st) = exp (env, e1, st) adamc@1080: val (e2, st) = exp ((x, t) :: env, e2, st) adamc@1080: in adamc@1080: ((ELet (x, t, e1, e2), loc), st) adamc@1080: end adamc@1080: | EServerCall (n, es, t) => adamc@1080: let adamc@1080: val (es, st) = ListUtil.foldlMap (fn (e, st) => exp (env, e, st)) st es adamc@1080: in adamc@1080: ((EServerCall (n, es, t), loc), st) adamc@1080: end adamc@482: in adamc@482: case getApp e of adamc@1080: NONE => default () adamc@488: | SOME (f, xs) => adamc@485: case IM.find (#funcs st, f) of adamc@1272: NONE => ((*print ("No find: " ^ Int.toString f ^ "\n");*) default ()) adamc@485: | SOME {name, args, body, typ, tag} => adamc@488: let adamc@1080: val (xs, st) = ListUtil.foldlMap (fn (e, st) => exp (env, e, st)) st xs adamc@1080: adamc@721: (*val () = Print.prefaces "Consider" [("e", CorePrint.p_exp CoreEnv.empty adamc@721: (e, ErrorMsg.dummySpan))]*) adamc@721: adamc@1185: val functionInside = U.Con.exists {kind = fn _ => false, adamc@1185: con = fn TFun _ => true adamc@1185: | CFfi ("Basis", "transaction") => true adamc@1185: | CFfi ("Basis", "eq") => true adamc@1185: | CFfi ("Basis", "num") => true adamc@1185: | CFfi ("Basis", "ord") => true adamc@1185: | CFfi ("Basis", "show") => true adamc@1185: | CFfi ("Basis", "read") => true adamc@1185: | CFfi ("Basis", "sql_injectable_prim") => true adamc@1185: | CFfi ("Basis", "sql_injectable") => true adamc@1185: | _ => false} adamc@488: val loc = ErrorMsg.dummySpan adamc@488: adamc@1080: fun findSplit av (xs, typ, fxs, fvs, fin) = adamc@488: case (#1 typ, xs) of adamc@488: (TFun (dom, ran), e :: xs') => adamc@1078: let adamc@1079: val av = case #1 e of adamc@1079: ERel _ => av adamc@1079: | _ => false adamc@1078: in adamc@1079: if functionInside dom orelse (av andalso case #1 e of adamc@1079: ERel _ => true adamc@1079: | _ => false) then adamc@1079: findSplit av (xs', adamc@1079: ran, adamc@1079: e :: fxs, adamc@1080: IS.union (fvs, freeVars e), adamc@1080: fin orelse functionInside dom) adamc@1078: else adamc@1080: (rev fxs, xs, fvs, fin) adamc@1078: end adamc@1080: | _ => (rev fxs, xs, fvs, fin) adamc@488: adamc@1080: val (fxs, xs, fvs, fin) = findSplit true (xs, typ, [], IS.empty, false) adamc@1079: adamc@1079: val fxs' = map (squish (IS.listItems fvs)) fxs adamc@488: in adamc@800: (*Print.preface ("fxs'", Print.p_list (CorePrint.p_exp CoreEnv.empty) fxs');*) adamc@1080: if not fin adamc@1080: orelse List.all (fn (ERel _, _) => true adamc@1080: | _ => false) fxs' adamc@1079: orelse (IS.numItems fvs >= length fxs adamc@1079: andalso IS.exists (fn n => functionInside (#2 (List.nth (env, n)))) fvs) then adamc@1083: ((*Print.prefaces "No" [("name", Print.PD.string name), adamc@1120: ("f", Print.PD.string (Int.toString f)), adamc@1083: ("fxs'", adamc@1083: Print.p_list (CorePrint.p_exp CoreEnv.empty) fxs')];*) adamc@1083: default ()) adamc@488: else adamc@1079: case (KM.find (args, fxs'), adamc@1083: SS.member (!mayNotSpec, name) (*orelse IS.member (#specialized st, f)*)) of adamc@800: (SOME f', _) => adamc@485: let adamc@488: val e = (ENamed f', loc) adamc@488: val e = IS.foldr (fn (arg, e) => (EApp (e, (ERel arg, loc)), loc)) adamc@488: e fvs adamc@1079: val e = foldl (fn (arg, e) => (EApp (e, arg), loc)) adamc@488: e xs adamc@488: in adamc@488: (*Print.prefaces "Brand new (reuse)" adamc@721: [("e'", CorePrint.p_exp CoreEnv.empty e)];*) adamc@1080: (e, st) adamc@488: end adamc@1083: | (_, true) => ((*Print.prefaces ("No!(" ^ name ^ ")") adamc@818: [("fxs'", adamc@818: Print.p_list (CorePrint.p_exp CoreEnv.empty) fxs')];*) adamc@1080: default ()) adamc@800: | (NONE, false) => adamc@488: let adamc@800: (*val () = Print.prefaces "New one" adamc@800: [("f", Print.PD.string (Int.toString f)), adamc@800: ("mns", Print.p_list Print.PD.string adamc@800: (SS.listItems (!mayNotSpec)))]*) adamc@800: adamc@818: (*val () = Print.prefaces ("Yes(" ^ name ^ ")") adamc@818: [("fxs'", adamc@818: Print.p_list (CorePrint.p_exp CoreEnv.empty) fxs')]*) adamc@818: adamc@1079: fun subBody (body, typ, fxs') = adamc@1079: case (#1 body, #1 typ, fxs') of adamc@488: (_, _, []) => SOME (body, typ) adamc@1079: | (EAbs (_, _, _, body'), TFun (_, typ'), x :: fxs'') => adamc@488: let adamc@1079: val body'' = E.subExpInExp (0, x) body' adamc@488: in adamc@488: subBody (body'', adamc@488: typ', adamc@1079: fxs'') adamc@488: end adamc@488: | _ => NONE adamc@488: in adamc@1079: case subBody (body, typ, fxs') of adamc@1080: NONE => default () adamc@488: | SOME (body', typ') => adamc@488: let adamc@488: val f' = #maxName st adamc@488: val args = KM.insert (args, fxs', f') adamc@488: val funcs = IM.insert (#funcs st, f, {name = name, adamc@488: args = args, adamc@488: body = body, adamc@488: typ = typ, adamc@488: tag = tag}) adamc@1079: adamc@488: val st = { adamc@488: maxName = f' + 1, adamc@488: funcs = funcs, adamc@1079: decls = #decls st, adamc@1080: specialized = IS.add (#specialized st, f') adamc@488: } adamc@487: adamc@488: (*val () = Print.prefaces "specExp" adamc@488: [("f", CorePrint.p_exp env (ENamed f, loc)), adamc@488: ("f'", CorePrint.p_exp env (ENamed f', loc)), adamc@488: ("xs", Print.p_list (CorePrint.p_exp env) xs), adamc@488: ("fxs'", Print.p_list adamc@488: (CorePrint.p_exp E.empty) fxs'), adamc@488: ("e", CorePrint.p_exp env (e, loc))]*) adamc@488: val (body', typ') = IS.foldl (fn (n, (body', typ')) => adamc@488: let adamc@521: val (x, xt) = List.nth (env, n) adamc@488: in adamc@488: ((EAbs (x, xt, typ', body'), adamc@488: loc), adamc@488: (TFun (xt, typ'), loc)) adamc@488: end) adamc@488: (body', typ') fvs adamc@800: val mns = !mayNotSpec adamc@1080: (*val () = mayNotSpec := SS.add (mns, name)*) adamc@1272: (*val () = print ("NEW: " ^ name ^ "__" ^ Int.toString f' ^ "\n");*) adamc@1272: val body' = ReduceLocal.reduceExp body' adamc@1080: (*val () = Print.preface ("PRE", CorePrint.p_exp CoreEnv.empty body')*) adamc@1080: val (body', st) = exp (env, body', st) adamc@800: val () = mayNotSpec := mns adamc@482: adamc@488: val e' = (ENamed f', loc) adamc@488: val e' = IS.foldr (fn (arg, e) => (EApp (e, (ERel arg, loc)), loc)) adamc@488: e' fvs adamc@1079: val e' = foldl (fn (arg, e) => (EApp (e, arg), loc)) adamc@488: e' xs adamc@488: (*val () = Print.prefaces "Brand new" adamc@721: [("e'", CorePrint.p_exp CoreEnv.empty e'), adamc@1080: ("e", CorePrint.p_exp CoreEnv.empty e), adamc@721: ("body'", CorePrint.p_exp CoreEnv.empty body')]*) adamc@488: in adamc@1080: (e', adamc@488: {maxName = #maxName st, adamc@488: funcs = #funcs st, adamc@1079: decls = (name, f', typ', body', tag) :: #decls st, adamc@1079: specialized = #specialized st}) adamc@488: end adamc@485: end adamc@488: end adamc@485: end adamc@482: adamc@521: fun doDecl (d, (st : state, changed)) = adamc@488: let adamc@521: (*val befor = Time.now ()*) adamc@482: adamc@453: val funcs = #funcs st adamc@453: val funcs = adamc@453: case #1 d of adamc@453: DValRec vis => adamc@453: foldl (fn ((x, n, c, e, tag), funcs) => adamc@453: IM.insert (funcs, n, {name = x, adamc@453: args = KM.empty, adamc@453: body = e, adamc@453: typ = c, adamc@453: tag = tag})) adamc@453: funcs vis adamc@453: | _ => funcs adamc@453: adamc@453: val st = {maxName = #maxName st, adamc@453: funcs = funcs, adamc@1079: decls = [], adamc@1079: specialized = #specialized st} adamc@453: adamc@482: (*val () = Print.prefaces "decl" [("d", CorePrint.p_decl CoreEnv.empty d)]*) adamc@521: adamc@1080: val () = mayNotSpec := SS.empty adamc@1080: adamc@522: val (d', st) = adamc@522: if isPoly d then adamc@522: (d, st) adamc@522: else adamc@1080: case #1 d of adamc@1080: DVal (x, n, t, e, s) => adamc@1080: let adamc@1080: val (e, st) = exp ([], e, st) adamc@1080: in adamc@1080: ((DVal (x, n, t, e, s), #2 d), st) adamc@1080: end adamc@1080: | DValRec vis => adamc@1080: let adamc@1120: (*val () = Print.preface ("Visiting", Print.p_list (fn vi => adamc@1120: Print.PD.string (#1 vi ^ "__" adamc@1120: ^ Int.toString adamc@1120: (#2 vi))) adamc@1120: vis)*) adamc@1120: adamc@1080: val (vis, st) = ListUtil.foldlMap (fn ((x, n, t, e, s), st) => adamc@1080: let adamc@1120: val () = mayNotSpec := SS.empty adamc@1080: val (e, st) = exp ([], e, st) adamc@1080: in adamc@1080: ((x, n, t, e, s), st) adamc@1080: end) st vis adamc@1080: in adamc@1080: ((DValRec vis, #2 d), st) adamc@1080: end adamc@1080: | DTable (s, n, t, s1, e1, t1, e2, t2) => adamc@1080: let adamc@1080: val (e1, st) = exp ([], e1, st) adamc@1080: val (e2, st) = exp ([], e2, st) adamc@1080: in adamc@1080: ((DTable (s, n, t, s1, e1, t2, e2, t2), #2 d), st) adamc@1080: end adamc@1080: | DView (x, n, s, e, t) => adamc@1080: let adamc@1080: val (e, st) = exp ([], e, st) adamc@1080: in adamc@1080: ((DView (x, n, s, e, t), #2 d), st) adamc@1080: end adamc@1080: | DTask (e1, e2) => adamc@1080: let adamc@1080: val (e1, st) = exp ([], e1, st) adamc@1080: val (e2, st) = exp ([], e2, st) adamc@1080: in adamc@1080: ((DTask (e1, e2), #2 d), st) adamc@1080: end adamc@1080: | _ => (d, st) adamc@1080: adamc@1080: val () = mayNotSpec := SS.empty adamc@521: adamc@482: (*val () = print "/decl\n"*) adamc@443: adamc@443: val funcs = #funcs st adamc@443: val funcs = adamc@443: case #1 d of adamc@443: DVal (x, n, c, e as (EAbs _, _), tag) => adamc@443: IM.insert (funcs, n, {name = x, adamc@453: args = KM.empty, adamc@443: body = e, adamc@443: typ = c, adamc@443: tag = tag}) adamc@469: | DVal (_, n, _, (ENamed n', _), _) => adamc@469: (case IM.find (funcs, n') of adamc@469: NONE => funcs adamc@469: | SOME v => IM.insert (funcs, n, v)) adamc@443: | _ => funcs adamc@443: adamc@453: val (changed, ds) = adamc@443: case #decls st of adamc@453: [] => (changed, [d']) adamc@453: | vis => adamc@453: (true, case d' of adamc@453: (DValRec vis', _) => [(DValRec (vis @ vis'), ErrorMsg.dummySpan)] adamc@453: | _ => [(DValRec vis, ErrorMsg.dummySpan), d']) adamc@443: in adamc@802: (*Print.prefaces "doDecl" [("d", CorePrint.p_decl E.empty d), adamc@802: ("d'", CorePrint.p_decl E.empty d')];*) adamc@521: (ds, ({maxName = #maxName st, adamc@453: funcs = funcs, adamc@1079: decls = [], adamc@1079: specialized = #specialized st}, changed)) adamc@443: end adamc@443: adamc@1120: (*val () = Print.preface ("RESET", CorePrint.p_file CoreEnv.empty file)*) adamc@1079: val (ds, (st, changed)) = ListUtil.foldlMapConcat doDecl adamc@521: ({maxName = U.File.maxName file + 1, adamc@1080: funcs = funcs, adamc@1079: decls = [], adamc@1079: specialized = specialized}, adamc@488: false) adamc@488: file adamc@443: in adamc@1120: (*print ("Changed = " ^ Bool.toString changed ^ "\n");*) adamc@1080: (changed, ds, #funcs st, #specialized st) adamc@443: end adamc@443: adamc@1080: fun specializeL (funcs, specialized) file = adamc@453: let adamc@721: val file = ReduceLocal.reduce file adamc@520: (*val file = ReduceLocal.reduce file*) adamc@1080: val (changed, file, funcs, specialized) = specialize' (funcs, specialized) file adamc@520: (*val file = ReduceLocal.reduce file adamc@520: val file = CoreUntangle.untangle file adamc@488: val file = Shake.shake file*) adamc@453: in adamc@488: (*print "Round over\n";*) adamc@453: if changed then adamc@520: let adamc@721: (*val file = ReduceLocal.reduce file*) adamc@802: (*val () = Print.prefaces "Pre-untangle" [("file", CorePrint.p_file CoreEnv.empty file)]*) adamc@520: val file = CoreUntangle.untangle file adamc@802: (*val () = Print.prefaces "Post-untangle" [("file", CorePrint.p_file CoreEnv.empty file)]*) adamc@520: val file = Shake.shake file adamc@520: in adamc@520: (*print "Again!\n";*) adamc@1080: (*Print.prefaces "Again" [("file", CorePrint.p_file CoreEnv.empty file)];*) adamc@1080: specializeL (funcs, specialized) file adamc@520: end adamc@453: else adamc@453: file adamc@453: end adamc@453: adamc@1080: val specialize = specializeL (IM.empty, IS.empty) adamc@1079: adamc@443: end