The Big INLINE Patch: totally reorganise way that INLINE pragmas work
[ghc-hetmet.git] / compiler / vectorise / VectCore.hs
index 63178bd..d651526 100644 (file)
@@ -1,20 +1,29 @@
 module VectCore (
-  Vect, VVar, VExpr,
+  Vect, VVar, VExpr, VBind,
 
   vectorised, lifted,
   mapVect,
 
-  vVar, mkVLams, mkVVarApps
+  vVarType,
+
+  vNonRec, vRec,
+
+  vVar, vType, vNote, vLet,
+  vLams, vLamsWithoutLC, vVarApps,
+  vCaseDEFAULT, vInlineMe
 ) where
 
 #include "HsVersions.h"
 
 import CoreSyn
+import Type           ( Type )
 import Var
+import Outputable
 
 type Vect a = (a,a)
 type VVar   = Vect Var
 type VExpr  = Vect CoreExpr
+type VBind  = Vect CoreBind
 
 vectorised :: Vect a -> a
 vectorised = fst
@@ -25,17 +34,57 @@ lifted = snd
 mapVect :: (a -> b) -> Vect a -> Vect b
 mapVect f (x,y) = (f x, f y)
 
+zipWithVect :: (a -> b -> c) -> Vect a -> Vect b -> Vect c
+zipWithVect f (x1,y1) (x2,y2) = (f x1 x2, f y1 y2)
+
+vVarType :: VVar -> Type
+vVarType = varType . vectorised
+
 vVar :: VVar -> VExpr
 vVar = mapVect Var
 
-mkVLams :: [VVar] -> VExpr -> VExpr
-mkVLams vvs (ve,le) = (mkLams vs ve, mkLams ls le)
+vType :: Type -> VExpr
+vType ty = (Type ty, Type ty)
+
+vNote :: Note -> VExpr -> VExpr
+vNote = mapVect . Note
+
+vNonRec :: VVar -> VExpr -> VBind
+vNonRec = zipWithVect NonRec
+
+vRec :: [VVar] -> [VExpr] -> VBind
+vRec vs es = (Rec (zip vvs ves), Rec (zip lvs les))
+  where
+    (vvs, lvs) = unzip vs
+    (ves, les) = unzip es
+
+vLet :: VBind -> VExpr -> VExpr
+vLet = zipWithVect Let
+
+vLams :: Var -> [VVar] -> VExpr -> VExpr
+vLams lc vs (ve, le) = (mkLams vvs ve, mkLams (lc:lvs) le)
+  where
+    (vvs,lvs) = unzip vs
+
+vLamsWithoutLC :: [VVar] -> VExpr -> VExpr
+vLamsWithoutLC vvs (ve,le) = (mkLams vs ve, mkLams ls le)
   where
     (vs,ls) = unzip vvs
 
-mkVVarApps :: Var -> VExpr -> [VVar] -> VExpr
-mkVVarApps lc (ve, le) vvs = (ve `mkVarApps` vs, le `mkVarApps` (lc : ls))
+vVarApps :: Var -> VExpr -> [VVar] -> VExpr
+vVarApps lc (ve, le) vvs = (ve `mkVarApps` vs, le `mkVarApps` (lc : ls))
   where
     (vs,ls) = unzip vvs 
 
+vCaseDEFAULT :: VExpr -> VVar -> Type -> Type -> VExpr -> VExpr
+vCaseDEFAULT (vscrut, lscrut) (vbndr, lbndr) vty lty (vbody, lbody)
+  = (Case vscrut vbndr vty (mkDEFAULT vbody),
+     Case lscrut lbndr lty (mkDEFAULT lbody))
+  where
+    mkDEFAULT e = [(DEFAULT, [], e)]
+
+vInlineMe :: VExpr -> VExpr
+vInlineMe (vexpr, lexpr) = (mkInlineMe vexpr, mkInlineMe lexpr)
 
+mkInlineMe :: CoreExpr -> CoreExpr
+mkInlineMe = pprTrace "VectCore.mkInlineMe" (text "Roman: need to replace mkInlineMe with an InlineRule somehow")