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

Safe HaskellNone
LanguageHaskell2010

Futhark.Representation.AST.Attributes.Reshape

Contents

Synopsis

Basic tools

newDim :: DimChange d -> d Source #

The new dimension.

newDims :: ShapeChange d -> [d] Source #

The new dimensions resulting from a reshape operation.

newShape :: ShapeChange SubExp -> Shape Source #

Construct a Reshape where all dimension changes are DimCoercions.

The new shape resulting from a reshape operation.

Construction

repeatShapes :: [Shape] -> Type -> ([Shape], Shape) Source #

Construct a pair suitable for a Repeat.

Execution

reshapeOuter :: ShapeChange SubExp -> Int -> Shape -> ShapeChange SubExp Source #

reshapeOuter newshape n oldshape returns a Reshape expression that replaces the outer n dimensions of oldshape with newshape.

reshapeInner :: ShapeChange SubExp -> Int -> Shape -> ShapeChange SubExp Source #

reshapeInner newshape n oldshape returns a Reshape expression that replaces the inner m-n dimensions (where m is the rank of oldshape) of src with newshape.

repeatDims :: [Shape] -> Shape -> Type -> Type Source #

Modify the shape of an array type as Repeat would do

Inspection

shapeCoercion :: ShapeChange d -> Maybe [d] Source #

If the shape change is nothing but shape coercions, return the new dimensions. Otherwise, return Nothing.

Simplification

fuseReshape :: Eq d => ShapeChange d -> ShapeChange d -> ShapeChange d Source #

fuseReshape s1 s2 creates a new ShapeChange that is semantically the same as first applying s1 and then s2. This may take advantage of properties of DimCoercion versus DimNew to preserve information.

fuseReshapes :: (Eq d, Foldable t) => ShapeChange d -> t (ShapeChange d) -> ShapeChange d Source #

fuseReshapes s ss creates a fused ShapeChange that is logically the same as first applying s and then the changes in ss from left to right.

informReshape :: Eq d => [d] -> ShapeChange d -> ShapeChange d Source #

Given concrete information about the shape of the source array, convert some DimNews into DimCoercions.

Shape calculations

reshapeIndex :: IntegralExp num => [num] -> [num] -> [num] -> [num] Source #

reshapeIndex to_dims from_dims is transforms the index list is (which is into an array of shape from_dims) into an index list is', which is into an array of shape to_dims. is must have the same length as from_dims, and is' will have the same length as to_dims.

flattenIndex :: IntegralExp num => [num] -> [num] -> num Source #

flattenIndex dims is computes the flat index of is into an array with dimensions dims. The length of dims and is must be the same.

unflattenIndex :: IntegralExp num => [num] -> num -> [num] Source #

unflattenIndex dims i computes a list of indices into an array with dimension dims given the flat index i. The resulting list will have the same size as dims.

sliceSizes :: IntegralExp num => [num] -> [num] Source #

Given a length n list of dimensions dims, sizeSizes dims will compute a length n+1 list of the size of each possible array slice. The first element of this list will be the product of dims, and the last element will be 1.