module Vectorise.Convert
( fromVect
)
where
import Vectorise.Monad
import Vectorise.Builtins
import Vectorise.Type.Type
import CoreSyn
import TyCon
import Type
import TypeRep
import NameSet
import FastString
import Outputable
import Control.Applicative
fromVect :: Type
-> CoreExpr
-> VM CoreExpr
fromVect ty expr
| Just ty' <- coreView ty
= fromVect ty' expr
fromVect (FunTy arg_ty res_ty) expr
= do
arg <- newLocalVar (fsLit "x") arg_ty
varg <- toVect arg_ty (Var arg)
varg_ty <- vectType arg_ty
vres_ty <- vectType res_ty
apply <- builtin applyVar
body <- fromVect res_ty
$ Var apply `mkTyApps` [varg_ty, vres_ty] `mkApps` [expr, varg]
return $ Lam arg body
fromVect ty expr
= identityConv ty >> return expr
toVect :: Type -> CoreExpr -> VM CoreExpr
toVect ty expr = identityConv ty >> return expr
identityConv :: Type -> VM ()
identityConv ty
| Just ty' <- coreView ty
= identityConv ty'
identityConv (TyConApp tycon tys)
= do { mapM_ identityConv tys
; identityConvTyCon tycon
}
identityConv (LitTy {}) = noV $ text "identityConv: not sure about literal types under vectorisation"
identityConv (TyVarTy {}) = noV $ text "identityConv: type variable changes under vectorisation"
identityConv (AppTy {}) = noV $ text "identityConv: type appl. changes under vectorisation"
identityConv (FunTy {}) = noV $ text "identityConv: function type changes under vectorisation"
identityConv (ForAllTy {}) = noV $ text "identityConv: quantified type changes under vectorisation"
identityConvTyCon :: TyCon -> VM ()
identityConvTyCon tc
= do
{ isParallel <- (tyConName tc `elemNameSet`) <$> globalParallelTyCons
; parray <- builtin parrayTyCon
; if isParallel && not (tc == parray)
then noV idErr
else return ()
}
where
idErr = text "identityConvTyCon: type constructor contains parallel arrays" <+> ppr tc