Safe Haskell | None |
---|---|
Language | Haskell98 |
Vectorisation of expressions.
Vectorise right-hand sides of toplevel bindings
vectTopExpr :: Var -> CoreExpr -> VM (Maybe (Bool, Inline, CoreExpr)) Source
Vectorise a polymorphic expression that forms a *non-recursive* binding.
Return Nothing
if the expression is scalar; otherwise, the first component of the result
(which is of type Bool
) indicates whether the expression is parallel (i.e., whether it is
tagged as VIParr
).
We have got the non-recursive case as a special case as it doesn't require to compute vectorisation information twice.
vectScalarFun :: CoreExpr -> VM VExpr Source
Vectorise an expression of functional type, where all arguments and the result are of primitive
types (i.e., Int
, Float
, Double
etc., which have instances of the Scalar
type class) and
which does not contain any subcomputations that involve parallel arrays. Such functionals do not
require the full blown vectorisation transformation; instead, they can be lifted by application
of a member of the zipWith family (i.e., map
, zipWith
, zipWith3', etc.)
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.