Safe Haskell | None |
---|
Vectorisation of expressions.
- vectPolyExpr :: Bool -> [Var] -> CoreExprWithFVs -> Maybe VITree -> VM (Inline, Bool, VExpr)
- vectDictExpr :: CoreExpr -> VM CoreExpr
- vectScalarFun :: CoreExpr -> VM VExpr
- vectScalarDFun :: Var -> VM CoreExpr
Vectorise polymorphic expressions with special cases for right-hand sides of particular
vectPolyExpr :: Bool -> [Var] -> CoreExprWithFVs -> Maybe VITree -> VM (Inline, Bool, VExpr)Source
Vectorise a polymorphic expression.
If not yet available, precompute vectorisation avoidance information before vectorising. If the vectorisation avoidance optimisation is enabled, also use the vectorisation avoidance information to encapsulated subexpression that do not need to be vectorised.
vectDictExpr :: CoreExpr -> VM CoreExprSource
Vectorise the body of a dfun.
Dictionary computations are special for the following reasons. The application of dictionary functions are always saturated, so there is no need to create closures. Dictionary computations don't depend on array values, so they are always scalar computations whose result we can replicate (instead of executing them in parallel).
NB: To keep things simple, we are not rewriting any of the bindings introduced in a dictionary computation. Consequently, the variable case needs to deal with cases where binders are in the vectoriser environments and where that is not the case.
vectScalarFun :: CoreExpr -> VM VExprSource
Vectorise an expression of functional type by lifting it by an application of a member of the
zipWith family (i.e., map
, zipWith
, zipWith3', etc.) This is only a valid strategy if the
function does not contain parallel subcomputations and has only Scalar
types in its result and
arguments — this is a predcondition for calling this function.
Dictionary functions are also scalar functions (as dictionaries themselves are not vectorised,
instead they become dictionaries of vectorised methods). We treat them differently, though see
Note [Scalar dfuns] in Vectorise
.
Vectorise a dictionary function that has a 'VECTORISE SCALAR instance' pragma.
In other words, all methods in that dictionary are scalar functions — to be vectorised with
vectScalarFun
. The dictionary function itself may be a constant, though.
NB: You may think that we could implement this function guided by the struture of the Core
expression of the right-hand side of the dictionary function. We cannot proceed like this as
vectScalarDFun
must also work for *imported* dfuns, where we don't necessarily have access
to the Core code of the unvectorised dfun.
Here an example — assume,
class Eq a where { (==) :: a -> a -> Bool } instance (Eq a, Eq b) => Eq (a, b) where { (==) = ... } {-# VECTORISE SCALAR instance Eq (a, b) }
The unvectorised dfun for the above instance has the following signature:
$dEqPair :: forall a b. Eq a -> Eq b -> Eq (a, b)
We generate the following (scalar) vectorised dfun (liberally using TH notation):
$v$dEqPair :: forall a b. V:Eq a -> V:Eq b -> V:Eq (a, b) $v$dEqPair = /\a b -> \dEqa :: V:Eq a -> \dEqb :: V:Eq b -> D:V:Eq $(vectScalarFun True recFns [| (==) @(a, b) ($dEqPair @a @b $(unVect dEqa) $(unVect dEqb)) |])
NB: * '(,)' vectorises to '(,)' — hence, the type constructor in the result type remains the same. * We share the '$(unVect di)' sub-expressions between the different selectors, but duplicate the application of the unvectorised dfun, to enable the dictionary selection rules to fire.