adamc@443: (* Copyright (c) 2008, 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@522: val isPoly = U.Decl.exists {kind = fn _ => false, adamc@522: con = fn _ => false, adamc@522: exp = fn ECAbs _ => true adamc@522: | _ => false, adamc@522: decl = fn _ => 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@488: 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@488: 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@443: decls : (string * int * con * exp * string) list adamc@443: } adamc@443: adamc@488: fun default (_, x, st) = (x, st) adamc@443: adamc@453: fun specialize' file = adamc@443: let adamc@488: fun default' (_, fs) = fs adamc@482: adamc@482: fun actionableExp (e, fs) = adamc@482: case e of adamc@482: ERecord xes => adamc@482: foldl (fn (((CName s, _), e, _), fs) => adamc@482: if s = "Action" orelse s = "Link" then adamc@482: let adamc@482: fun findHead (e, _) = adamc@482: case e of adamc@482: ENamed n => IS.add (fs, n) adamc@482: | EApp (e, _) => findHead e adamc@482: | _ => fs adamc@482: in adamc@482: findHead e adamc@482: end adamc@482: else adamc@482: fs adamc@482: | (_, fs) => fs) adamc@482: fs xes adamc@482: | _ => fs adamc@482: adamc@482: val actionable = adamc@488: U.File.fold {kind = default', adamc@488: con = default', adamc@482: exp = actionableExp, adamc@488: decl = default'} adamc@482: IS.empty file adamc@482: 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@488: fun exp (env, e, st : state) = adamc@482: let adamc@488: fun getApp e = adamc@482: case e of adamc@488: ENamed f => SOME (f, []) adamc@482: | EApp (e1, e2) => adamc@488: (case getApp (#1 e1) of adamc@482: NONE => NONE adamc@488: | SOME (f, xs) => SOME (f, xs @ [e2])) adamc@482: | _ => NONE adamc@482: in adamc@482: case getApp e of adamc@482: NONE => (e, st) adamc@488: | SOME (f, xs) => adamc@485: case IM.find (#funcs st, f) of adamc@485: NONE => (e, st) adamc@485: | SOME {name, args, body, typ, tag} => adamc@488: let adamc@488: val functionInside = U.Con.exists {kind = fn _ => false, adamc@488: con = fn TFun _ => true adamc@488: | CFfi ("Basis", "transaction") => true adamc@488: | _ => false} adamc@488: val loc = ErrorMsg.dummySpan adamc@488: adamc@488: fun findSplit (xs, typ, fxs, fvs) = adamc@488: case (#1 typ, xs) of adamc@488: (TFun (dom, ran), e :: xs') => adamc@488: if functionInside dom then adamc@488: findSplit (xs', adamc@488: ran, adamc@488: e :: fxs, adamc@488: IS.union (fvs, freeVars e)) adamc@488: else adamc@488: (rev fxs, xs, fvs) adamc@488: | _ => (rev fxs, xs, fvs) adamc@488: adamc@488: val (fxs, xs, fvs) = findSplit (xs, typ, [], IS.empty) adamc@488: adamc@488: val fxs' = map (squish (IS.listItems fvs)) fxs adamc@488: adamc@488: fun firstRel () = adamc@488: case fxs' of adamc@488: (ERel _, _) :: _ => true adamc@488: | _ => false adamc@488: in adamc@488: if firstRel () adamc@488: orelse List.all (fn (ERel _, _) => true adamc@488: | _ => false) fxs' then adamc@488: (e, st) adamc@488: else adamc@488: case KM.find (args, fxs') of adamc@488: 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@488: 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@488: [("e'", CorePrint.p_exp env e)];*) adamc@488: (#1 e, st) adamc@488: end adamc@488: | NONE => adamc@488: let adamc@488: fun subBody (body, typ, fxs') = adamc@488: case (#1 body, #1 typ, fxs') of adamc@488: (_, _, []) => SOME (body, typ) adamc@488: | (EAbs (_, _, _, body'), TFun (_, typ'), x :: fxs'') => adamc@488: let adamc@488: val body'' = E.subExpInExp (0, x) body' adamc@488: in adamc@488: subBody (body'', adamc@488: typ', adamc@488: fxs'') adamc@488: end adamc@488: | _ => NONE adamc@488: in adamc@488: case subBody (body, typ, fxs') of adamc@488: NONE => (e, st) 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@488: val st = { adamc@488: maxName = f' + 1, adamc@488: funcs = funcs, adamc@488: decls = #decls st 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@488: val (body', st) = specExp env st body' 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@488: val e' = foldl (fn (arg, e) => (EApp (e, arg), loc)) adamc@488: e' xs adamc@488: (*val () = Print.prefaces "Brand new" adamc@488: [("e'", CorePrint.p_exp env e'), adamc@488: ("e", CorePrint.p_exp env (e, loc)), adamc@488: ("body'", CorePrint.p_exp env body')]*) adamc@488: in adamc@488: (#1 e', adamc@488: {maxName = #maxName st, adamc@488: funcs = #funcs st, adamc@488: decls = (name, f', typ', body', tag) :: #decls st}) adamc@488: end adamc@485: end adamc@488: end adamc@485: end adamc@482: adamc@626: and specExp env = U.Exp.foldMapB {kind = default, con = default, exp = exp, bind = bind} env adamc@482: adamc@626: val specDecl = U.Decl.foldMapB {kind = default, con = default, exp = exp, decl = default, bind = bind} 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@453: decls = []} adamc@453: adamc@482: (*val () = Print.prefaces "decl" [("d", CorePrint.p_decl CoreEnv.empty d)]*) adamc@521: adamc@522: val (d', st) = adamc@522: if isPoly d then adamc@522: (d, st) adamc@522: else adamc@522: specDecl [] st d 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@521: (*Print.prefaces "doDecl" [("d", CorePrint.p_decl E.empty d), adamc@521: ("t", Print.PD.string (Real.toString (Time.toReal adamc@521: (Time.- (Time.now (), befor)))))];*) adamc@521: (ds, ({maxName = #maxName st, adamc@453: funcs = funcs, adamc@453: decls = []}, changed)) adamc@443: end adamc@443: adamc@521: val (ds, (_, changed)) = ListUtil.foldlMapConcat doDecl adamc@521: ({maxName = U.File.maxName file + 1, adamc@488: funcs = IM.empty, adamc@488: decls = []}, adamc@488: false) adamc@488: file adamc@443: in adamc@453: (changed, ds) adamc@443: end adamc@443: adamc@453: fun specialize file = adamc@453: let adamc@487: (*val () = Print.prefaces "Intermediate" [("file", CorePrint.p_file CoreEnv.empty file)];*) adamc@520: (*val file = ReduceLocal.reduce file*) adamc@453: val (changed, file) = specialize' 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@520: val file = ReduceLocal.reduce file adamc@520: val file = CoreUntangle.untangle file adamc@520: val file = Shake.shake file adamc@520: in adamc@520: (*print "Again!\n";*) adamc@520: specialize file adamc@520: end adamc@453: else adamc@453: file adamc@453: end adamc@453: adamc@443: end