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

Safe HaskellNone
LanguageHaskell2010

Futhark.Representation.ExplicitMemory.IndexFunction

Description

This module contains a representation for the index function based on linear-memory accessor descriptors; see Zhu, Hoeflinger and David work.

Synopsis

Documentation

data IxFun num Source #

Constructors

IxFun 

Fields

Instances
Functor IxFun Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory.IndexFunction

Methods

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

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

Foldable IxFun Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory.IndexFunction

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.IndexFunction

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.IndexFunction

Methods

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

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

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

Defined in Futhark.Representation.ExplicitMemory.IndexFunction

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.IndexFunction

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.IndexFunction

Methods

freeIn :: IxFun num -> Names Source #

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

Defined in Futhark.Representation.ExplicitMemory.IndexFunction

Methods

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

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

Defined in Futhark.Representation.ExplicitMemory.IndexFunction

Methods

rename :: IxFun num -> RenameM (IxFun num) Source #

index :: (IntegralExp num, Eq num) => IxFun num -> Indices num -> num Source #

Compute 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 #

Offset index. 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 #

Stride index. 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 #

Rotate an index function.

reshape :: (Eq num, IntegralExp num) => IxFun num -> ShapeChange num -> IxFun num Source #

Reshape an index function.

slice :: (Eq num, IntegralExp num) => IxFun num -> Slice num -> IxFun num Source #

Slice an index function.

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

Rebase an index function on top of a new base.

repeat :: (Eq num, IntegralExp num) => IxFun num -> [Shape num] -> Shape num -> IxFun num Source #

Repeat dimensions.

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

Does the index function have 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 #

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 #

Is this is a row-major array?

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

substituteInIxFun :: Ord a => Map a (PrimExp a) -> IxFun (PrimExp a) -> IxFun (PrimExp a) Source #

Substitute a name with a PrimExp in an index function.