Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module contains a representation of linear-memory accessor descriptors (LMAD); see work by Zhu, Hoeflinger and David.
This module is designed to be used as a qualified import, as the exported names are quite generic.
Synopsis
- type Shape num = [num]
- type Indices num = [num]
- data LMAD num = LMAD {}
- data LMADDim num = LMADDim {}
- type Permutation = [Int]
- index :: (IntegralExp num, Eq num) => LMAD num -> Indices num -> num
- slice :: (Eq num, IntegralExp num) => LMAD num -> Slice num -> LMAD num
- flatSlice :: IntegralExp num => LMAD num -> FlatSlice num -> LMAD num
- reshape :: (Eq num, IntegralExp num) => LMAD num -> Shape num -> Maybe (LMAD num)
- permute :: LMAD num -> Permutation -> LMAD num
- shape :: LMAD num -> Shape num
- rank :: LMAD num -> Int
- substituteInLMAD :: Ord a => Map a (TPrimExp t a) -> LMAD (TPrimExp t a) -> LMAD (TPrimExp t a)
- disjoint :: [(VName, PrimExp VName)] -> Names -> LMAD (TPrimExp Int64 VName) -> LMAD (TPrimExp Int64 VName) -> Bool
- disjoint2 :: scope -> asserts -> [(VName, PrimExp VName)] -> Names -> LMAD (TPrimExp Int64 VName) -> LMAD (TPrimExp Int64 VName) -> Bool
- disjoint3 :: Map VName Type -> [PrimExp VName] -> [(VName, PrimExp VName)] -> [PrimExp VName] -> LMAD (TPrimExp Int64 VName) -> LMAD (TPrimExp Int64 VName) -> Bool
- dynamicEqualsLMAD :: Eq num => LMAD (TPrimExp t num) -> LMAD (TPrimExp t num) -> TPrimExp Bool num
- iota :: IntegralExp num => num -> [num] -> LMAD num
- mkExistential :: Int -> Int -> LMAD (Ext a)
- equivalent :: Eq num => LMAD num -> LMAD num -> Bool
- isDirect :: (Eq num, IntegralExp num) => LMAD num -> Bool
Documentation
LMAD's representation consists of a general offset and for each dimension a stride, number of elements (or shape), and permutation. Note that the permutation is not strictly necessary in that the permutation can be performed directly on LMAD dimensions, but then it is difficult to extract the permutation back from an LMAD.
LMAD algebra is closed under composition w.r.t. operators such as permute, index and slice. However, other operations, such as reshape, cannot always be represented inside the LMAD algebra.
It follows that the general representation of an index function is a list of LMADS, in which each following LMAD in the list implicitly corresponds to an irregular reshaping operation.
However, we expect that the common case is when the index function is one LMAD -- we call this the "nice" representation.
Finally, the list of LMADs is kept in an IxFun
together with the shape of
the original array, and a bit to indicate whether the index function is
contiguous, i.e., if we instantiate all the points of the current index
function, do we get a contiguous memory interval?
By definition, the LMAD \( \sigma + \{ (n_1, s_1), \ldots, (n_k, s_k) \} \), where \(n\) and \(s\) denote the shape and stride of each dimension, denotes the set of points:
\[ \{ ~ \sigma + i_1 * s_1 + \ldots + i_m * s_m ~ | ~ 0 \leq i_1 < n_1, \ldots, 0 \leq i_m < n_m ~ \} \]
Instances
Foldable LMAD Source # | |
Defined in Futhark.IR.Mem.LMAD fold :: Monoid m => LMAD m -> m # foldMap :: Monoid m => (a -> m) -> LMAD a -> m # foldMap' :: Monoid m => (a -> m) -> LMAD a -> m # foldr :: (a -> b -> b) -> b -> LMAD a -> b # foldr' :: (a -> b -> b) -> b -> LMAD a -> b # foldl :: (b -> a -> b) -> b -> LMAD a -> b # foldl' :: (b -> a -> b) -> b -> LMAD a -> b # foldr1 :: (a -> a -> a) -> LMAD a -> a # foldl1 :: (a -> a -> a) -> LMAD a -> a # elem :: Eq a => a -> LMAD a -> Bool # maximum :: Ord a => LMAD a -> a # | |
Traversable LMAD Source # | |
Functor LMAD Source # | |
Show num => Show (LMAD num) Source # | |
FreeIn num => FreeIn (LMAD num) Source # | |
Substitute num => Rename (LMAD num) Source # | |
Substitute num => Substitute (LMAD num) Source # | |
Defined in Futhark.IR.Mem.LMAD | |
Eq num => Eq (LMAD num) Source # | |
Ord num => Ord (LMAD num) Source # | |
Defined in Futhark.IR.Mem.LMAD | |
Pretty num => Pretty (LMAD num) Source # | |
Defined in Futhark.IR.Mem.LMAD |
A single dimension in an LMAD
.
Instances
Show num => Show (LMADDim num) Source # | |
FreeIn num => FreeIn (LMADDim num) Source # | |
Eq num => Eq (LMADDim num) Source # | |
Ord num => Ord (LMADDim num) Source # | |
Defined in Futhark.IR.Mem.LMAD |
type Permutation = [Int] Source #
A complete permutation.
slice :: (Eq num, IntegralExp num) => LMAD num -> Slice num -> LMAD num Source #
Handle the case where a slice can stay within a single LMAD.
reshape :: (Eq num, IntegralExp num) => LMAD num -> Shape num -> Maybe (LMAD num) Source #
Handle the case where a reshape operation can stay inside a single LMAD. See "Futhark.IR.Mem.IxFun.reshape" for conditions.
substituteInLMAD :: Ord a => Map a (TPrimExp t a) -> LMAD (TPrimExp t a) -> LMAD (TPrimExp t a) Source #
Substitute a name with a PrimExp in an LMAD.
disjoint :: [(VName, PrimExp VName)] -> Names -> LMAD (TPrimExp Int64 VName) -> LMAD (TPrimExp Int64 VName) -> Bool Source #
Returns True
if the two LMAD
s could be proven disjoint.
Uses some best-approximation heuristics to determine disjointness. For two
1-dimensional arrays, we can guarantee whether or not they are disjoint, but
as soon as more than one dimension is involved, things get more
tricky. Currently, we try to conservativelyFlatten
any LMAD with more than
one dimension.
disjoint2 :: scope -> asserts -> [(VName, PrimExp VName)] -> Names -> LMAD (TPrimExp Int64 VName) -> LMAD (TPrimExp Int64 VName) -> Bool Source #
disjoint3 :: Map VName Type -> [PrimExp VName] -> [(VName, PrimExp VName)] -> [PrimExp VName] -> LMAD (TPrimExp Int64 VName) -> LMAD (TPrimExp Int64 VName) -> Bool Source #
dynamicEqualsLMAD :: Eq num => LMAD (TPrimExp t num) -> LMAD (TPrimExp t num) -> TPrimExp Bool num Source #
:: IntegralExp num | |
=> num | Offset |
-> [num] | Shape |
-> LMAD num |
Generalised iota with user-specified offset.
mkExistential :: Int -> Int -> LMAD (Ext a) Source #
Create an LMAD that is existential in everything.