X-Git-Url: https://git.stderr.nl/gitweb?a=blobdiff_plain;f=Normalize.hs;h=d2f50a708315702bf0cc5478bb8026875c57610d;hb=f20ebcfe03b2f3493be450761c8b3a26c2e0cd30;hp=653cd68cfc1f599fd99cf7e69086154399ff9c19;hpb=ce21f6b5bc31049d9f663bab7c0f7984ccec5875;p=matthijs%2Fmaster-project%2Fc%CE%BBash.git diff --git a/Normalize.hs b/Normalize.hs index 653cd68..d2f50a7 100644 --- a/Normalize.hs +++ b/Normalize.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE PackageImports #-} -- -- Functions to bring a Core expression in normal form. This module provides a -- top level function "normalize", and defines the actual transformation passes that @@ -8,6 +9,7 @@ module Normalize (normalizeModule) where -- Standard modules import Debug.Trace import qualified Maybe +import qualified "transformers" Control.Monad.Trans as Trans import qualified Control.Monad as Monad import qualified Data.Map as Map import Data.Accessor @@ -18,6 +20,7 @@ import qualified UniqSupply import qualified CoreUtils import qualified Type import qualified Id +import qualified Var import qualified VarSet import qualified CoreFVs import Outputable ( showSDoc, ppr, nest ) @@ -274,6 +277,36 @@ appsimpl expr = return expr -- Perform this transform everywhere appsimpltop = everywhere ("appsimpl", appsimpl) + +-------------------------------- +-- Type argument propagation +-------------------------------- +-- Remove all applications to type arguments, by duplicating the function +-- called with the type application in its new definition. We leave +-- dictionaries that might be associated with the type untouched, the funprop +-- transform should propagate these later on. +typeprop, typeproptop :: Transform +-- Transform any function that is applied to a type argument. Since type +-- arguments are always the first ones to apply and we'll remove all type +-- arguments, we can simply do them one by one. +typeprop expr@(App (Var f) (Type ty)) = do + id <- cloneVar f + let newty = Type.applyTy (Id.idType f) ty + let newf = Var.setVarType id newty + body_maybe <- Trans.lift $ getGlobalBind f + case body_maybe of + Just body -> do + let newbody = App body (Type ty) + Trans.lift $ addGlobalBind newf newbody + change (Var newf) + -- If we don't have a body for the function called, leave it unchanged (it + -- should be a primitive function then). + Nothing -> return expr +-- Leave all other expressions unchanged +typeprop expr = return expr +-- Perform this transform everywhere +typeproptop = everywhere ("typeprop", typeprop) + -- TODO: introduce top level let if needed? -------------------------------- @@ -284,7 +317,7 @@ appsimpltop = everywhere ("appsimpl", appsimpl) -- What transforms to run? -transforms = [etatop, betatop, letremovetop, letrectop, letsimpltop, letflattop, casewildtop, scrutsimpltop, casevalsimpltop, caseremovetop, inlinefuntop, appsimpltop] +transforms = [typeproptop, etatop, betatop, letremovetop, letrectop, letsimpltop, letflattop, casewildtop, scrutsimpltop, casevalsimpltop, caseremovetop, inlinefuntop, appsimpltop] -- Turns the given bind into VHDL normalizeModule :: @@ -328,10 +361,10 @@ normalizeBind bndr = do -- Find all vars used with a function type. All of these should be global -- binders (i.e., functions used), since any local binders with a function -- type should have been inlined already. - let used_funcs_set = CoreFVs.exprSomeFreeVars (\v -> trace (showSDoc $ ppr $ Id.idType v) ((Type.isFunTy . snd . Type.splitForAllTys . Id.idType)v)) expr'' + let used_funcs_set = CoreFVs.exprSomeFreeVars (\v -> (Type.isFunTy . snd . Type.splitForAllTys . Id.idType) v) expr'' let used_funcs = VarSet.varSetElems used_funcs_set -- Process each of the used functions recursively - mapM normalizeBind (trace (show used_funcs) used_funcs) + mapM normalizeBind used_funcs return () -- We don't have a value for this binder, let's assume this is a builtin -- function. This might need some extra checking and a nice error