futhark-0.25.7: An optimising compiler for a functional, array-oriented language.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Futhark.IR.Mem.LMAD

Description

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

Documentation

type Shape num = [num] Source #

The shape of an index function.

type Indices num = [num] Source #

Indices passed to an LMAD. Must always match the rank of the LMAD.

data LMAD num Source #

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 ~ \} \]

Constructors

LMAD 

Fields

Instances

Instances details
Foldable LMAD Source # 
Instance details

Defined in Futhark.IR.Mem.LMAD

Methods

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 #

toList :: LMAD a -> [a] #

null :: LMAD a -> Bool #

length :: LMAD a -> Int #

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

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

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

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

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

Traversable LMAD Source # 
Instance details

Defined in Futhark.IR.Mem.LMAD

Methods

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

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

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

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

Functor LMAD Source # 
Instance details

Defined in Futhark.IR.Mem.LMAD

Methods

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

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

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

Defined in Futhark.IR.Mem.LMAD

Methods

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

show :: LMAD num -> String #

showList :: [LMAD num] -> ShowS #

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

Defined in Futhark.IR.Mem.LMAD

Methods

freeIn' :: LMAD num -> FV Source #

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

Defined in Futhark.IR.Mem.LMAD

Methods

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

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

Defined in Futhark.IR.Mem.LMAD

Methods

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

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

Defined in Futhark.IR.Mem.LMAD

Methods

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

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

Ord num => Ord (LMAD num) Source # 
Instance details

Defined in Futhark.IR.Mem.LMAD

Methods

compare :: LMAD num -> LMAD num -> Ordering #

(<) :: LMAD num -> LMAD num -> Bool #

(<=) :: LMAD num -> LMAD num -> Bool #

(>) :: LMAD num -> LMAD num -> Bool #

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

max :: LMAD num -> LMAD num -> LMAD num #

min :: LMAD num -> LMAD num -> LMAD num #

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

Defined in Futhark.IR.Mem.LMAD

Methods

pretty :: LMAD num -> Doc ann #

prettyList :: [LMAD num] -> Doc ann #

data LMADDim num Source #

A single dimension in an LMAD.

Constructors

LMADDim 

Fields

Instances

Instances details
Show num => Show (LMADDim num) Source # 
Instance details

Defined in Futhark.IR.Mem.LMAD

Methods

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

show :: LMADDim num -> String #

showList :: [LMADDim num] -> ShowS #

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

Defined in Futhark.IR.Mem.LMAD

Methods

freeIn' :: LMADDim num -> FV Source #

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

Defined in Futhark.IR.Mem.LMAD

Methods

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

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

Ord num => Ord (LMADDim num) Source # 
Instance details

Defined in Futhark.IR.Mem.LMAD

Methods

compare :: LMADDim num -> LMADDim num -> Ordering #

(<) :: LMADDim num -> LMADDim num -> Bool #

(<=) :: LMADDim num -> LMADDim num -> Bool #

(>) :: LMADDim num -> LMADDim num -> Bool #

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

max :: LMADDim num -> LMADDim num -> LMADDim num #

min :: LMADDim num -> LMADDim num -> LMADDim num #

type Permutation = [Int] Source #

A complete permutation.

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

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

Handle the case where a slice can stay within a single LMAD.

flatSlice :: IntegralExp num => LMAD num -> FlatSlice num -> LMAD num Source #

Flat-slice an 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.

permute :: LMAD num -> Permutation -> LMAD num Source #

Permute dimensions.

shape :: LMAD num -> Shape num Source #

Shape of an LMAD.

rank :: LMAD num -> Int Source #

Rank of an LMAD.

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

dynamicEqualsLMAD :: Eq num => LMAD (TPrimExp t num) -> LMAD (TPrimExp t num) -> TPrimExp Bool num Source #

Dynamically determine if two LMAD are equal.

True if offset and constituent LMADDim are equal.

iota Source #

Arguments

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

equivalent :: Eq num => LMAD num -> LMAD num -> Bool Source #

Returns true if two LMADs are equivalent.

Equivalence in this case is matching in offsets and strides.

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

Is this is a row-major array with zero offset?