Fix bug in vectorisation
[ghc-hetmet.git] / compiler / vectorise / Vectorise.hs
index ccb33ee..166eae6 100644 (file)
@@ -13,6 +13,8 @@ import CoreLint             ( showPass, endPass )
 import CoreSyn
 import CoreUtils
 import CoreFVs
+import SimplMonad           ( SimplCount, zeroSimplCount )
+import Rules                ( RuleBase )
 import DataCon
 import TyCon
 import Type
@@ -38,23 +40,26 @@ import FastString
 import Control.Monad        ( liftM, liftM2, mapAndUnzipM, zipWithM_ )
 import Data.Maybe           ( maybeToList )
 
-vectorise :: HscEnv -> ModGuts -> IO ModGuts
-vectorise hsc_env guts
-  | not (Opt_Vectorise `dopt` dflags) = return guts
-  | otherwise
+vectorise :: HscEnv -> UniqSupply -> RuleBase -> ModGuts
+          -> IO (SimplCount, ModGuts)
+vectorise hsc_env _ _ guts
   = do
       showPass dflags "Vectorisation"
       eps <- hscEPS hsc_env
       let info = hptVectInfo hsc_env `plusVectInfo` eps_vect_info eps
       Just (info', guts') <- initV hsc_env guts info (vectModule guts)
       endPass dflags "Vectorisation" Opt_D_dump_vect (mg_binds guts')
-      return $ guts' { mg_vect_info = info' }
+      return (zeroSimplCount dflags, guts' { mg_vect_info = info' })
   where
     dflags = hsc_dflags hsc_env
 
 vectModule :: ModGuts -> VM ModGuts
-vectModule guts = return guts
+vectModule guts
+  = do
+      binds' <- mapM vectTopBind (mg_binds guts)
+      return $ guts { mg_binds = binds' }
 
+vectTopBind :: CoreBind -> VM CoreBind
 vectTopBind b@(NonRec var expr)
   = do
       var'  <- vectTopBinder var
@@ -78,14 +83,12 @@ vectTopBind b@(Rec bs)
 vectTopBinder :: Var -> VM Var
 vectTopBinder var
   = do
-      vty <- liftM (mkForAllTys tyvars) $ vectType mono_ty
+      vty <- vectType (idType var)
       name <- cloneName mkVectOcc (getName var)
       let var' | isExportedId var = Id.mkExportedLocalId name vty
                | otherwise        = Id.mkLocalId         name vty
       defGlobalVar var var'
       return var'
-  where
-    (tyvars, mono_ty) = splitForAllTys (idType var)
     
 vectTopRhs :: CoreExpr -> VM CoreExpr
 vectTopRhs = liftM fst . closedV . vectPolyExpr (panic "Empty lifting context") . freeVars
@@ -433,7 +436,7 @@ vectTyCon tc
                     Nothing  -> pprTrace "ccTyCon:" (ppr tc) $ return tc
 
 vectType :: Type -> VM Type
-vectType ty | Just ty' <- coreView ty = vectType ty
+vectType ty | Just ty' <- coreView ty = vectType ty'
 vectType (TyVarTy tv) = return $ TyVarTy tv
 vectType (AppTy ty1 ty2) = liftM2 AppTy (vectType ty1) (vectType ty2)
 vectType (TyConApp tc tys) = liftM2 TyConApp (vectTyCon tc) (mapM vectType tys)