futhark-0.9.1: An optimising compiler for a functional, array-oriented language.

Safe HaskellNone
LanguageHaskell2010

Futhark.Representation.ExplicitMemory.Lmad

Description

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

Documentation

data IxFun num Source #

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?

Constructors

IxFun [Lmad num] (Shape num) Bool 
Instances
Functor IxFun Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory.Lmad

Methods

fmap :: (a -> b) -> IxFun a -> IxFun b #

(<$) :: a -> IxFun b -> IxFun a #

Foldable IxFun Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory.Lmad

Methods

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 #

toList :: IxFun a -> [a] #

null :: IxFun a -> Bool #

length :: IxFun a -> Int #

elem :: Eq a => a -> IxFun a -> Bool #

maximum :: Ord a => IxFun a -> a #

minimum :: Ord a => IxFun a -> a #

sum :: Num a => IxFun a -> a #

product :: Num a => IxFun a -> a #

Traversable IxFun Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory.Lmad

Methods

traverse :: Applicative f => (a -> f b) -> IxFun a -> f (IxFun b) #

sequenceA :: Applicative f => IxFun (f a) -> f (IxFun a) #

mapM :: Monad m => (a -> m b) -> IxFun a -> m (IxFun b) #

sequence :: Monad m => IxFun (m a) -> m (IxFun a) #

Eq num => Eq (IxFun num) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory.Lmad

Methods

(==) :: IxFun num -> IxFun num -> Bool #

(/=) :: IxFun num -> IxFun num -> Bool #

Show num => Show (IxFun num) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory.Lmad

Methods

showsPrec :: Int -> IxFun num -> ShowS #

show :: IxFun num -> String #

showList :: [IxFun num] -> ShowS #

Pretty num => Pretty (IxFun num) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory.Lmad

Methods

ppr :: IxFun num -> Doc #

pprPrec :: Int -> IxFun num -> Doc #

pprList :: [IxFun num] -> Doc #

FreeIn num => FreeIn (IxFun num) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory.Lmad

Methods

freeIn :: IxFun num -> Names Source #

Substitute num => Substitute (IxFun num) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory.Lmad

Methods

substituteNames :: Map VName VName -> IxFun num -> IxFun num Source #

Substitute num => Rename (IxFun num) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory.Lmad

Methods

rename :: IxFun num -> RenameM (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.

permute :: IntegralExp num => IxFun num -> Permutation -> IxFun num Source #

permute dimensions

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.

base :: IxFun num -> Shape num Source #

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

shape :: (Eq num, IntegralExp num) => IxFun num -> Shape num Source #

Shape of an index function

rank :: IntegralExp num => IxFun num -> Int Source #

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.

isDirect :: (Eq num, IntegralExp num) => IxFun num -> Bool Source #

whether this is a row-major array

isLinear :: (Eq num, IntegralExp num) => IxFun num -> Bool Source #

substituteInIxFun :: Map VName (PrimExp VName) -> IxFun (PrimExp VName) -> IxFun (PrimExp VName) Source #

Substituting a name with a PrimExp in an index function.