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

Futhark.IR.Mem.IxFun

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 #

An index function is a mapping from a multidimensional array index space (the domain) to a one-dimensional memory index space. Essentially, it explains where the element at position [i,j,p] of some array is stored inside the flat one-dimensional array that constitutes its memory. For example, we can use this to distinguish row-major and column-major representations.

An index function is represented as an LMAD.

Constructors

IxFun 

Fields

  • ixfunLMAD :: LMAD num
     
  • base :: Shape num

    the shape of the support array, i.e., the original array that birthed (is the start point) of this index function.

Instances

Instances details
Foldable IxFun Source # 
Instance details

Defined in Futhark.IR.Mem.IxFun

Methods

fold :: Monoid m => IxFun m -> m #

foldMap :: Monoid m => (a -> m) -> IxFun a -> 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.IR.Mem.IxFun

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

Functor IxFun Source # 
Instance details

Defined in Futhark.IR.Mem.IxFun

Methods

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

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

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

Defined in Futhark.IR.Mem.IxFun

Methods

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

show :: IxFun num -> String #

showList :: [IxFun num] -> ShowS #

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

Defined in Futhark.IR.Mem.IxFun

Methods

freeIn' :: IxFun num -> FV Source #

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

Defined in Futhark.IR.Mem.IxFun

Methods

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

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

Defined in Futhark.IR.Mem.IxFun

Methods

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

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

Defined in Futhark.IR.Mem.IxFun

Methods

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

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

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

Defined in Futhark.IR.Mem.IxFun

Methods

pretty :: IxFun num -> Doc ann #

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

type Shape num = [num] Source #

The shape of an index function.

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 #

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.

mkExistential :: Int -> [Int] -> Int -> IxFun (Ext a) Source #

Create a single-LMAD index function that is existential in everything, with the provided permutation.

iota :: IntegralExp num => Shape num -> IxFun num Source #

iota.

iotaOffset :: IntegralExp num => num -> Shape num -> IxFun num Source #

iota with offset.

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

Permute dimensions.

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

Reshape an index function.

There are four conditions that all must hold for the result of a reshape operation to remain in 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.

If any of these conditions do 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

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

Coerce an index function to look like it has a new shape. Dynamically the shape must be the same.

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

Slice an index function.

flatSlice :: (Eq num, IntegralExp num) => IxFun num -> FlatSlice num -> Maybe (IxFun num) Source #

Flat-slice an index function.

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

Essentially rebase new_base ixfun = ixfun o new_base Core soundness condition: base ixfun == shape new_base Handles the case where a rebase operation can stay within m + n - 1 LMADs, where m is the number of LMADs in the index function, and n is the number of LMADs in the new base. If both index function have only on LMAD, this means that we stay within the single-LMAD domain.

We can often stay in that domain if the original ixfun is essentially a slice, e.g. `x[i, (k1,m,s1), (k2,n,s2)] = orig`.

However, I strongly suspect that for in-place update what we need is actually the INVERSE of the rebase function, i.e., given an index function new-base and another one orig, compute the index function ixfun0 such that:

new-base == rebase ixfun0 ixfun, or equivalently: new-base == ixfun o ixfun0

because then I can go bottom up and compose with ixfun0 all the index functions corresponding to the memory block associated with ixfun.

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

The index space of the index function. This is the same as the shape of arrays that the index function supports.

permutation :: IxFun num -> Permutation Source #

The permutation of the first LMAD of the index function.

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

The number of dimensions in the domain of the input function.

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

Is this is a row-major array?

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

Substitute a name with a PrimExp in an index function.

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.

existentialize :: IxFun (TPrimExp Int64 a) -> IxFun (TPrimExp Int64 (Ext b)) Source #

Turn all the leaves of the index function into Exts. We require that there's only one LMAD, that the index function is contiguous, and the base shape has only one dimension.

closeEnough :: IxFun num -> IxFun num -> Bool Source #

When comparing index functions as part of the type check in KernelsMem, we may run into problems caused by the simplifier. As index functions can be generalized over if-then-else expressions, the simplifier might hoist some of the code from inside the if-then-else (computing the offset of an array, for instance), but now the type checker cannot verify that the generalized index function is valid, because some of the existentials are computed somewhere else. To Work around this, we've had to relax the KernelsMem type-checker a bit, specifically, we've introduced this function to verify whether two index functions are "close enough" that we can assume that they match. We use this instead of `ixfun1 == ixfun2` and hope that it's good enough.

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

Returns true if two IxFuns are equivalent.

Equivalence in this case is defined as having the same number of LMADs, with each pair of LMADs matching in permutation, offsets, and strides.

permuteInv :: Permutation -> [a] -> [a] Source #

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.