Vectorisation of method types
[ghc-hetmet.git] / compiler / vectorise / VectMonad.hs
index 2649716..51e7601 100644 (file)
@@ -1,3 +1,4 @@
+{-# LANGUAGE NamedFieldPuns #-}
 
 -- | The Vectorisation monad.
 module VectMonad (
@@ -439,6 +440,8 @@ newTyVar fs k
       u <- liftDs newUnique
       return $ mkTyVar (mkSysTvName u fs) k
 
+
+-- | Add a mapping between a global var and its vectorised version to the state.
 defGlobalVar :: Var -> Var -> VM ()
 defGlobalVar v v' = updGEnv $ \env ->
   env { global_vars = extendVarEnv (global_vars env) v v'
@@ -448,20 +451,36 @@ defGlobalVar v v' = updGEnv $ \env ->
     upd env | isExportedId v = extendVarEnv env v (v, v')
             | otherwise      = env
 
+-- Var ------------------------------------------------------------------------
 -- | Lookup the vectorised and\/or lifted versions of this variable.
 --     If it's in the global environment we get the vectorised version.
 --      If it's in the local environment we get both the vectorised and lifted version.
 --     
 lookupVar :: Var -> VM (Scope Var (Var, Var))
 lookupVar v
-  = do
-      r <- readLEnv $ \env -> lookupVarEnv (local_vars env) v
+ = do r <- readLEnv $ \env -> lookupVarEnv (local_vars env) v
       case r of
         Just e  -> return (Local e)
         Nothing -> liftM Global
-                . maybeCantVectoriseM "Variable not vectorised:" (ppr v)
+                . maybeCantVectoriseVarM v
                 . readGEnv $ \env -> lookupVarEnv (global_vars env) v
 
+maybeCantVectoriseVarM :: Monad m => Var -> m (Maybe Var) -> m Var
+maybeCantVectoriseVarM v p
+ = do r <- p
+      case r of
+        Just x  -> return x
+        Nothing -> dumpVar v
+
+dumpVar :: Var -> a
+dumpVar var
+       | Just cls              <- isClassOpId_maybe var
+       = cantVectorise "ClassOpId not vectorised:" (ppr var)
+
+       | otherwise
+       = cantVectorise "Variable not vectorised:" (ppr var)
+
+-------------------------------------------------------------------------------
 globalScalars :: VM VarSet
 globalScalars = readGEnv global_scalars
 
@@ -581,6 +600,8 @@ lookupFamInst tycon tys
                       (ppr $ mkTyConApp tycon tys)
        }
 
+
+-- | Run a vectorisation computation.
 initV :: PackageId -> HscEnv -> ModGuts -> VectInfo -> VM a -> IO (Maybe (VectInfo, a))
 initV pkg hsc_env guts info p
   = do