Refactoring
[ghc-hetmet.git] / compiler / vectorise / VectType.hs
index 405d6ab..6e10dee 100644 (file)
@@ -224,8 +224,30 @@ data Repr = ProdRepr {
             , sum_arr_data_con  :: DataCon
             }
 
-mkProduct :: [Type] -> VM Repr
-mkProduct tys
+          | IdRepr Type
+
+          | VoidRepr {
+              void_tycon        :: TyCon
+            , void_bottom       :: CoreExpr
+            }
+
+voidRepr :: VM Repr
+voidRepr
+  = do
+      tycon <- builtin voidTyCon
+      var   <- builtin voidVar
+      return $ VoidRepr {
+                 void_tycon  = tycon
+               , void_bottom = Var var
+               }
+
+unboxedProductRepr :: [Type] -> VM Repr
+unboxedProductRepr []   = voidRepr
+unboxedProductRepr [ty] = return $ IdRepr ty
+unboxedProductRepr tys  = boxedProductRepr tys
+
+boxedProductRepr :: [Type] -> VM Repr
+boxedProductRepr tys
   = do
       tycon <- builtin (prodTyCon arity)
       let [data_con] = tyConDataCons tycon
@@ -243,9 +265,10 @@ mkProduct tys
   where
     arity = length tys
 
-mkSum :: [Repr] -> VM Repr
-mkSum [repr] = return repr
-mkSum reprs
+sumRepr :: [Repr] -> VM Repr
+sumRepr []     = voidRepr
+sumRepr [repr] = boxRepr repr
+sumRepr reprs
   = do
       tycon <- builtin (sumTyCon arity)
       (arr_tycon, _) <- parrayReprTyCon
@@ -263,11 +286,18 @@ mkSum reprs
   where
     arity = length reprs
 
+boxRepr :: Repr -> VM Repr
+boxRepr (VoidRepr {}) = boxedProductRepr []
+boxRepr (IdRepr ty)   = boxedProductRepr [ty]
+boxRepr repr          = return repr
+
 reprType :: Repr -> Type
 reprType (ProdRepr { prod_tycon = tycon, prod_components = tys })
   = mkTyConApp tycon tys
 reprType (SumRepr { sum_tycon = tycon, sum_components = reprs })
   = mkTyConApp tycon (map reprType reprs)
+reprType (IdRepr ty) = ty
+reprType (VoidRepr { void_tycon = tycon }) = mkTyConApp tycon []
 
 arrReprType :: Repr -> VM Type
 arrReprType = mkPArrayType . reprType
@@ -277,7 +307,9 @@ arrShapeTys (SumRepr  {})
   = do
       int_arr <- builtin parrayIntPrimTyCon
       return [intPrimTy, mkTyConApp int_arr [], mkTyConApp int_arr []]
-arrShapeTys repr = return [intPrimTy]
+arrShapeTys (ProdRepr {}) = return [intPrimTy]
+arrShapeTys (IdRepr _)    = return []
+arrShapeTys (VoidRepr {}) = return [intPrimTy]
 
 arrShapeVars :: Repr -> VM [Var]
 arrShapeVars repr = mapM (newLocalVar FSLIT("sh")) =<< arrShapeTys repr
@@ -289,20 +321,32 @@ replicateShape (SumRepr {})  len tag
       rep <- builtin replicatePAIntPrimVar
       up  <- builtin upToPAIntPrimVar
       return [len, Var rep `mkApps` [len, tag], Var up `App` len]
+replicateShape (IdRepr _) _ _ = return []
+replicateShape (VoidRepr {}) len _ = return [len]
 
-arrReprElemTys :: Repr -> [[Type]]
+arrReprElemTys :: Repr -> VM [[Type]]
 arrReprElemTys (SumRepr { sum_components = prods })
-  = map arrProdElemTys prods
+  = mapM arrProdElemTys prods
 arrReprElemTys prod@(ProdRepr {})
-  = [arrProdElemTys prod]
+  = do
+      tys <- arrProdElemTys prod
+      return [tys]
+arrReprElemTys (IdRepr ty) = return [[ty]]
+arrReprElemTys (VoidRepr { void_tycon = tycon })
+  = return [[mkTyConApp tycon []]]
 
 arrProdElemTys (ProdRepr { prod_components = [] })
-  = [unitTy]
+  = do
+      void <- builtin voidTyCon
+      return [mkTyConApp void []]
 arrProdElemTys (ProdRepr { prod_components = tys })
-  = tys
+  = return tys
+arrProdElemTys (IdRepr ty) = return [ty]
+arrProdElemTys (VoidRepr { void_tycon = tycon })
+  = return [mkTyConApp tycon []]
 
 arrReprTys :: Repr -> VM [[Type]]
-arrReprTys = mapM (mapM mkPArrayType) . arrReprElemTys
+arrReprTys repr = mapM (mapM mkPArrayType) =<< arrReprElemTys repr
 
 arrReprVars :: Repr -> VM [[Var]]
 arrReprVars repr
@@ -310,8 +354,9 @@ arrReprVars repr
 
 mkRepr :: TyCon -> VM Repr
 mkRepr vect_tc
-  = mkSum
-  =<< mapM mkProduct (map dataConRepArgTys $ tyConDataCons vect_tc)
+  = sumRepr =<< mapM unboxedProductRepr rep_tys
+  where
+    rep_tys = map dataConRepArgTys $ tyConDataCons vect_tc
 
 buildPReprType :: TyCon -> VM Type
 buildPReprType = liftM reprType . mkRepr
@@ -358,6 +403,15 @@ buildToPRepr repr vect_tc prepr_tc _
           vars <- mapM (newLocalVar FSLIT("r")) tys
           return (vars, mkConApp data_con (map Type tys ++ map Var vars))
 
+    prod_alt (IdRepr ty)
+      = do
+          var <- newLocalVar FSLIT("y") ty
+          return ([var], Var var)
+
+    prod_alt (VoidRepr { void_bottom = bottom })
+      = return ([], bottom)
+
+
 buildFromPRepr :: Repr -> TyCon -> TyCon -> TyCon -> VM CoreExpr
 buildFromPRepr repr vect_tc prepr_tc _
   = do
@@ -397,6 +451,12 @@ buildFromPRepr repr vect_tc prepr_tc _
           return $ Case expr (mkWildId (reprType prod)) res_ty
                    [(DataAlt data_con, vars, con `mkVarApps` vars)]
 
+    from_prod (IdRepr _) con expr
+       = return $ con `App` expr
+
+    from_prod (VoidRepr {}) con expr
+       = return con
+
 buildToArrPRepr :: Repr -> TyCon -> TyCon -> TyCon -> VM CoreExpr
 buildToArrPRepr repr vect_tc prepr_tc arr_tc
   = do
@@ -435,7 +495,7 @@ buildToArrPRepr repr vect_tc prepr_tc arr_tc
                      , sum_arr_tycon    = tycon
                      , sum_arr_data_con = data_con })
       = do
-          exprs <- zipWithM (to_prod len_var) repr_vars prods
+          exprs <- zipWithM to_prod repr_vars prods
 
           return . wrapFamInstBody tycon tys
                  . mkConApp data_con
@@ -443,16 +503,28 @@ buildToArrPRepr repr vect_tc prepr_tc arr_tc
       where
         tys = map reprType prods
 
-    to_repr [len_var] [repr_vars] prod = to_prod len_var repr_vars prod
+    to_repr [len_var]
+            [repr_vars]
+            (ProdRepr { prod_components   = tys
+                      , prod_arr_tycon    = tycon
+                      , prod_arr_data_con = data_con })
+       = return . wrapFamInstBody tycon tys
+                . mkConApp data_con
+                $ map Type tys ++ map Var (len_var : repr_vars)
 
-    to_prod len_var
-            repr_vars
+    to_prod repr_vars@(r : _)
             (ProdRepr { prod_components   = tys
                       , prod_arr_tycon    = tycon
                       , prod_arr_data_con = data_con })
-      = return . wrapFamInstBody tycon tys
-               . mkConApp data_con
-               $ map Type tys ++ map Var (len_var : repr_vars)
+      = do
+          len <- lengthPA (Var r)
+          return . wrapFamInstBody tycon tys
+                 . mkConApp data_con
+                 $ map Type tys ++ len : map Var repr_vars
+
+    to_prod [var] (IdRepr ty)   = return (Var var)
+    to_prod [var] (VoidRepr {}) = return (Var var)
+
 
 buildFromArrPRepr :: Repr -> TyCon -> TyCon -> TyCon -> VM CoreExpr
 buildFromArrPRepr repr vect_tc prepr_tc arr_tc
@@ -531,7 +603,26 @@ buildFromArrPRepr repr vect_tc prepr_tc arr_tc
           return $ Case scrut (mkWildId scrut_ty) res_ty
                    [(DataAlt data_con, shape_vars ++ repr_vars, body)]
 
+    from_prod (IdRepr ty)
+              expr
+              shape_vars
+              [repr_var]
+              res_ty
+              body
+      = return $ Let (NonRec repr_var expr) body
+
+    from_prod (VoidRepr {})
+              expr
+              shape_vars
+              [repr_var]
+              res_ty
+              body
+      = return $ Let (NonRec repr_var expr) body
+
 buildPRDictRepr :: Repr -> VM CoreExpr
+buildPRDictRepr (VoidRepr { void_tycon = tycon })
+  = prDFunOfTyCon tycon
+buildPRDictRepr (IdRepr ty) = mkPR ty
 buildPRDictRepr (ProdRepr {
                    prod_components = tys
                  , prod_tycon      = tycon
@@ -638,6 +729,7 @@ vectDataConWorkers :: Repr -> TyCon -> TyCon -> TyCon
                    -> VM ()
 vectDataConWorkers repr orig_tc vect_tc arr_tc
   = do
+      arr_tys <- arrReprElemTys repr
       bs <- sequence
           . zipWith3 def_worker  (tyConDataCons orig_tc) rep_tys
           $ zipWith4 mk_data_con (tyConDataCons vect_tc)
@@ -653,7 +745,6 @@ vectDataConWorkers repr orig_tc vect_tc arr_tc
     res_ty   = mkTyConApp vect_tc var_tys
 
     rep_tys  = map dataConRepArgTys $ tyConDataCons vect_tc
-    arr_tys  = arrReprElemTys repr
 
     [arr_dc] = tyConDataCons arr_tc