X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Fvectorise%2FVectMonad.hs;h=836a0209a089911ef30a00789695fbee256669d1;hb=bdcefe88baa952422da335cbd743a32db5b06fb6;hp=5ef06eed6f6af90736fbe1433c89e25988e340f3;hpb=a9192907a271905c4ec1a37b1737ce119ac48905;p=ghc-hetmet.git diff --git a/compiler/vectorise/VectMonad.hs b/compiler/vectorise/VectMonad.hs index 5ef06ee..836a020 100644 --- a/compiler/vectorise/VectMonad.hs +++ b/compiler/vectorise/VectMonad.hs @@ -1,10 +1,3 @@ -{-# OPTIONS -w #-} --- The above warning supression flag is a temporary kludge. --- While working on this module you are encouraged to remove it and fix --- any warnings in the module. See --- http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#Warnings --- for details - module VectMonad ( Scope(..), VM, @@ -14,7 +7,8 @@ module VectMonad ( cloneName, cloneId, cloneVar, newExportedVar, newLocalVar, newDummyVar, newTyVar, - Builtins(..), sumTyCon, prodTyCon, combinePAVar, + Builtins(..), sumTyCon, prodTyCon, uarrTy, intPrimArrayTy, + combinePAVar, builtin, builtins, GlobalEnv(..), @@ -47,30 +41,23 @@ import CoreSyn import TyCon import DataCon import Type -import Class import Var import VarEnv import Id -import OccName import Name import NameEnv -import TysPrim ( intPrimTy ) -import Module -import IfaceEnv -import IOEnv ( ioToIOEnv ) +import IOEnv ( liftIO ) import DsMonad -import PrelNames import InstEnv import FamInstEnv -import Panic import Outputable import FastString import SrcLoc ( noSrcSpan ) -import Control.Monad ( liftM, zipWithM ) +import Control.Monad data Scope a b = Global a | Local b @@ -182,6 +169,7 @@ setBoxedTyConsEnv :: [(Name, TyCon)] -> GlobalEnv -> GlobalEnv setBoxedTyConsEnv ps genv = genv { global_boxed_tycons = mkNameEnv ps } +emptyLocalEnv :: LocalEnv emptyLocalEnv = LocalEnv { local_vars = emptyVarEnv , local_tyvars = [] @@ -209,7 +197,7 @@ data VResult a = Yes GlobalEnv LocalEnv a | No newtype VM a = VM { runVM :: Builtins -> GlobalEnv -> LocalEnv -> DsM (VResult a) } instance Monad VM where - return x = VM $ \bi genv lenv -> return (Yes genv lenv x) + return x = VM $ \_ genv lenv -> return (Yes genv lenv x) VM p >>= f = VM $ \bi genv lenv -> do r <- p bi genv lenv case r of @@ -240,9 +228,10 @@ orElseV :: VM a -> VM a -> VM a orElseV p q = maybe q return =<< tryV p fixV :: (a -> VM a) -> VM a -fixV f = VM (\bi genv lenv -> fixDs $ \r -> runVM (f (unYes r)) bi genv lenv ) - where - unYes (Yes _ _ x) = x +fixV f = VM $ \bi genv lenv -> fixDs $ + \r -> case r of + Yes _ _ x -> runVM (f x) bi genv lenv + No -> return No localV :: VM a -> VM a localV p = do @@ -260,7 +249,7 @@ closedV p = do return x liftDs :: DsM a -> VM a -liftDs p = VM $ \bi genv lenv -> do { x <- p; return (Yes genv lenv x) } +liftDs p = VM $ \_ genv lenv -> do { x <- p; return (Yes genv lenv x) } builtin :: (Builtins -> a) -> VM a builtin f = VM $ \bi genv lenv -> return (Yes genv lenv (f bi)) @@ -269,7 +258,7 @@ builtins :: (a -> Builtins -> b) -> VM (a -> b) builtins f = VM $ \bi genv lenv -> return (Yes genv lenv (`f` bi)) readGEnv :: (GlobalEnv -> a) -> VM a -readGEnv f = VM $ \bi genv lenv -> return (Yes genv lenv (f genv)) +readGEnv f = VM $ \_ genv lenv -> return (Yes genv lenv (f genv)) setGEnv :: GlobalEnv -> VM () setGEnv genv = VM $ \_ _ lenv -> return (Yes genv lenv ()) @@ -278,7 +267,7 @@ updGEnv :: (GlobalEnv -> GlobalEnv) -> VM () updGEnv f = VM $ \_ genv lenv -> return (Yes (f genv) lenv ()) readLEnv :: (LocalEnv -> a) -> VM a -readLEnv f = VM $ \bi genv lenv -> return (Yes genv lenv (f lenv)) +readLEnv f = VM $ \_ genv lenv -> return (Yes genv lenv (f lenv)) setLEnv :: LocalEnv -> VM () setLEnv lenv = VM $ \_ genv _ -> return (Yes genv lenv ()) @@ -286,8 +275,10 @@ setLEnv lenv = VM $ \_ genv _ -> return (Yes genv lenv ()) updLEnv :: (LocalEnv -> LocalEnv) -> VM () updLEnv f = VM $ \_ genv lenv -> return (Yes genv (f lenv) ()) +{- getInstEnv :: VM (InstEnv, InstEnv) getInstEnv = readGEnv global_inst_env +-} getFamInstEnv :: VM FamInstEnvs getFamInstEnv = readGEnv global_fam_inst_env @@ -376,7 +367,9 @@ defTyCon tc tc' = updGEnv $ \env -> env { global_tycons = extendNameEnv (global_tycons env) (tyConName tc) tc' } lookupDataCon :: DataCon -> VM (Maybe DataCon) -lookupDataCon dc = readGEnv $ \env -> lookupNameEnv (global_datacons env) (dataConName dc) +lookupDataCon dc + | isTupleTyCon (dataConTyCon dc) = return (Just dc) + | otherwise = readGEnv $ \env -> lookupNameEnv (global_datacons env) (dataConName dc) defDataCon :: DataCon -> DataCon -> VM () defDataCon dc dc' = updGEnv $ \env -> @@ -493,14 +486,14 @@ initV hsc_env guts info p go = do builtins <- initBuiltins - let builtin_vars = initBuiltinVars builtins - builtin_tycons = initBuiltinTyCons builtins - builtin_datacons = initBuiltinDataCons builtins + builtin_vars <- initBuiltinVars builtins + builtin_tycons <- initBuiltinTyCons builtins + let builtin_datacons = initBuiltinDataCons builtins builtin_pas <- initBuiltinPAs builtins builtin_prs <- initBuiltinPRs builtins builtin_boxed <- initBuiltinBoxedTyCons builtins - eps <- ioToIOEnv $ hscEPS hsc_env + eps <- liftIO $ hscEPS hsc_env let famInstEnvs = (eps_fam_inst_env eps, mg_fam_inst_env guts) instEnvs = (eps_inst_env eps, mg_inst_env guts)