Safe Haskell | None |
---|---|
Language | Haskell2010 |
An index function represents a mapping from an array index space
to a flat byte offset. This implements a representation for the
index function based on linear-memory accessor descriptors, see
Zhu, Hoeflinger and David work. Our specific representation is:
LMAD = overline{s,r,n}^k + o, where o
is the offset, and s_j
,
r_j
, and n_j
are the stride, the rotate factor and the number
of elements on dimension j. Dimensions are ordered in row major fashion.
By definition, the LMAD above denotes the set of points:
{ o + Sigma_{j=0}^{k} ((i_j+r_j) mod
n_j)*s_j,
forall i_j such that 0<=i_j<n_j, j=1..k }
Synopsis
- data IxFun num = IxFun [Lmad num] (Shape num) Bool
- index :: (IntegralExp num, Eq num) => IxFun num -> Indices num -> num -> num
- iota :: IntegralExp num => Shape num -> IxFun num
- offsetIndex :: (Eq num, IntegralExp num) => IxFun num -> num -> IxFun num
- strideIndex :: (Eq num, IntegralExp num) => IxFun num -> num -> IxFun num
- permute :: IntegralExp num => IxFun num -> Permutation -> IxFun num
- rotate :: (Eq num, IntegralExp num) => IxFun num -> Indices num -> IxFun num
- reshape :: (Eq num, IntegralExp num) => IxFun num -> ShapeChange num -> IxFun num
- slice :: (Eq num, IntegralExp num) => IxFun num -> Slice num -> IxFun num
- base :: IxFun num -> Shape num
- rebase :: (Eq num, IntegralExp num) => IxFun num -> IxFun num -> IxFun num
- repeat :: (Eq num, IntegralExp num) => IxFun num -> [Shape num] -> Shape num -> IxFun num
- isContiguous :: (Eq num, IntegralExp num) => IxFun num -> Bool
- shape :: (Eq num, IntegralExp num) => IxFun num -> Shape num
- rank :: IntegralExp num => IxFun num -> Int
- getMonotonicity :: (Eq num, IntegralExp num) => IxFun num -> DimInfo
- linearWithOffset :: (Eq num, IntegralExp num) => IxFun num -> num -> Maybe num
- rearrangeWithOffset :: (Eq num, IntegralExp num) => IxFun num -> num -> Maybe (num, [(Int, num)])
- isDirect :: (Eq num, IntegralExp num) => IxFun num -> Bool
- isLinear :: (Eq num, IntegralExp num) => IxFun num -> Bool
- substituteInIxFun :: Map VName (PrimExp VName) -> IxFun (PrimExp VName) -> IxFun (PrimExp VName)
Documentation
LMAD algebra is closed under composition w.r.t.
operators such as permute, repeat, index and slice.
However, other operations, such as reshape, cannot be
always 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 tupled with the shape of the
original array, and with contiguous info, i.e., if we instantiate
all the points of the current index function, do we get a
contiguous memory interval?
Instances
Functor IxFun Source # | |
Foldable IxFun Source # | |
Defined in Futhark.Representation.ExplicitMemory.Lmad fold :: Monoid m => IxFun m -> m # foldMap :: Monoid m => (a -> m) -> IxFun a -> m # foldr :: (a -> b -> b) -> b -> IxFun a -> b # foldr' :: (a -> b -> b) -> b -> IxFun a -> b # foldl :: (b -> a -> b) -> b -> IxFun a -> b # foldl' :: (b -> a -> b) -> b -> IxFun a -> b # foldr1 :: (a -> a -> a) -> IxFun a -> a # foldl1 :: (a -> a -> a) -> IxFun a -> a # elem :: Eq a => a -> IxFun a -> Bool # maximum :: Ord a => IxFun a -> a # minimum :: Ord a => IxFun a -> a # | |
Traversable IxFun Source # | |
Eq num => Eq (IxFun num) Source # | |
Show num => Show (IxFun num) Source # | |
Pretty num => Pretty (IxFun num) Source # | |
FreeIn num => FreeIn (IxFun num) Source # | |
Substitute num => Substitute (IxFun num) Source # | |
Defined in Futhark.Representation.ExplicitMemory.Lmad | |
Substitute num => Rename (IxFun num) Source # | |
index :: (IntegralExp num, Eq num) => IxFun num -> Indices num -> num -> num Source #
Computing the flat memory index for a complete set inds
of array indices and a certain element size elem_size
.
iota :: IntegralExp num => Shape num -> IxFun num Source #
iota
offsetIndex :: (Eq num, IntegralExp num) => IxFun num -> num -> IxFun num Source #
results in the index function corresponding to indexing
with i
on the outermost dimension.
strideIndex :: (Eq num, IntegralExp num) => IxFun num -> num -> IxFun num Source #
results in the index function corresponding to making
the outermost dimension strided by s
.
rotate :: (Eq num, IntegralExp num) => IxFun num -> Indices num -> IxFun num Source #
Rotating an index function:
reshape :: (Eq num, IntegralExp num) => IxFun num -> ShapeChange num -> IxFun num Source #
Reshaping an index function. There are four conditions that all must hold for the result of a reshape operation to remain into the one-Lmad domain: (1) the permutation of the underlying Lmad must leave unchanged the Lmad dimensions that were *not* reshape coercions. (2) the repetition of dimensions of the underlying Lmad must refer only to the coerced-dimensions of the reshape operation. (3) similarly, the rotated dimensions must refer only to dimensions that are coerced by the reshape operation. (4) finally, the underlying memory is contiguous (and monotonous)
If any of this conditions does not hold then the reshape operation will conservatively add a new Lmad to the list, leading to a representation that provides less opportunities for further analysis.
Actually there are some special cases that need to be treated, for example if everything is a coercion, then it should succeed no matter what.
slice :: (Eq num, IntegralExp num) => IxFun num -> Slice num -> IxFun num Source #
Slicing an index function.
rebase :: (Eq num, IntegralExp num) => IxFun num -> IxFun num -> IxFun num Source #
Correctness assumption: the shape of the new base is equal to the base of the index function (to be rebased).
repeat :: (Eq num, IntegralExp num) => IxFun num -> [Shape num] -> Shape num -> IxFun num Source #
repeating dimensions
isContiguous :: (Eq num, IntegralExp num) => IxFun num -> Bool Source #
whether an index function has contiguous memory support
getMonotonicity :: (Eq num, IntegralExp num) => IxFun num -> DimInfo Source #
linearWithOffset :: (Eq num, IntegralExp num) => IxFun num -> num -> Maybe num Source #
If the memory support of the index function is contiguous and row-major (i.e., no transpositions, repetitions, rotates, etc.), then this should return the offset from which the memory-support of this index function starts.
rearrangeWithOffset :: (Eq num, IntegralExp num) => IxFun num -> num -> Maybe (num, [(Int, num)]) Source #
Similar restrictions to linearWithOffset
except
for transpositions, which are returned together
with the offset.