futhark-0.25.31: An optimising compiler for a functional, array-oriented language.
Safe HaskellNone
LanguageGHC2021

Futhark.IR.Prop.Reshape

Description

Facilities for creating, inspecting, and simplifying reshape and coercion operations.

Synopsis

Construction

shapeCoerce :: [SubExp] -> VName -> Exp rep Source #

Construct a Reshape that is a ReshapeCoerce.

reshapeAll :: ArrayShape old => old -> ShapeBase new -> NewShape new Source #

Construct a NewShape that completely reshapes the initial shape.

reshapeCoerce :: ShapeBase new -> NewShape new Source #

Construct a NewShape that coerces the shape.

Execution

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

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

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

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

newshapeInner :: Shape -> NewShape SubExp -> NewShape SubExp Source #

newshapeInner outershape newshape bumps all the dimensions in newshape by the rank of outershape, essentially making them operate on the inner dimensions of a larger array, and also updates the shape of newshape to have outershape outermost.

applySplice :: ShapeBase d -> DimSplice d -> ShapeBase d Source #

Apply the splice to a shape.

Simplification

flipReshapeRearrange :: Eq d => [d] -> [d] -> [Int] -> Maybe [Int] Source #

Interchange a reshape and rearrange. Essentially, rewrite composition

let v1 = reshape(v0, v1_shape)
let v2 = rearrange(v1, perm)

into

let v1' = rearrange(v0, perm')
let v2' = reshape(v1', v1_shape')

The function is given the shape of v0, v1, and the perm, and returns perm'. This is a meaningful operation when v2 is itself reshaped, as the reshape-reshape can be fused. This can significantly simplify long chains of reshapes and rearranges.

flipRearrangeReshape :: [Int] -> NewShape d -> Maybe (NewShape d, [Int]) Source #

Interchange a reshape and rearrange. Essentially, rewrite composition

let v1 = rearrange(v0, perm)
let v2 = reshape(v1, v1_shape)

into

let v1' = reshape(v0, v1_shape')
let v2' = rearrange(v1', perm')

The function is given perm and v1_shape, and returns perm' and v1_shape'. This is a meaningful operation when v2 is itself rearranged (or v0 the result of a reshape), as this enables fusion.

simplifyNewShape :: Eq d => ShapeBase d -> NewShape d -> Maybe (NewShape d) Source #

Try to simplify the given NewShape. Returns Nothing if no improvement is possible.

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.

Analysis

data ReshapeKind Source #

Which kind of reshape is this?

Constructors

ReshapeCoerce

New shape is dynamically same as original.

ReshapeArbitrary

Any kind of reshaping.

reshapeKind :: NewShape SubExp -> ReshapeKind Source #

Determine whether this might be a coercion.

newShape :: NewShape d -> ShapeBase d Source #

The resulting shape.