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

Safe HaskellNone
LanguageHaskell2010

Futhark.Representation.AST.Attributes.Types

Contents

Description

Functions for inspecting and constructing various types.

Synopsis

Documentation

rankShaped :: ArrayShape shape => TypeBase shape u -> TypeBase Rank u Source #

Remove shape information from a type.

arrayRank :: ArrayShape shape => TypeBase shape u -> Int Source #

Return the dimensionality of a type. For non-arrays, this is zero. For a one-dimensional array it is one, for a two-dimensional it is two, and so forth.

arrayShape :: ArrayShape shape => TypeBase shape u -> shape Source #

Return the shape of a type - for non-arrays, this is the mempty.

modifyArrayShape :: ArrayShape newshape => (oldshape -> newshape) -> TypeBase oldshape u -> TypeBase newshape u Source #

Modify the shape of an array - for non-arrays, this does nothing.

setArrayShape :: ArrayShape newshape => TypeBase oldshape u -> newshape -> TypeBase newshape u Source #

Set the shape of an array. If the given type is not an array, return the type unchanged.

existential :: ExtType -> Bool Source #

True if the given type has a dimension that is existentially sized.

uniqueness :: TypeBase shape Uniqueness -> Uniqueness Source #

Return the uniqueness of a type.

setUniqueness :: TypeBase shape Uniqueness -> Uniqueness -> TypeBase shape Uniqueness Source #

Set the uniqueness attribute of a type.

unique :: TypeBase shape Uniqueness -> Bool Source #

unique t is True if the type of the argument is unique.

staticShapes :: [TypeBase Shape u] -> [TypeBase ExtShape u] Source #

Convert types with non-existential shapes to types with non-existential shapes. Only the representation is changed, so all the shapes will be Free.

staticShapes1 :: TypeBase Shape u -> TypeBase ExtShape u Source #

As staticShapes, but on a single type.

primType :: TypeBase shape u -> Bool Source #

A type is a primitive type if it is not an array or memory block.

arrayOf :: ArrayShape shape => TypeBase shape u_unused -> shape -> u -> TypeBase shape u Source #

arrayOf t s u constructs an array type. The convenience compared to using the Array constructor directly is that t can itself be an array. If t is an n-dimensional array, and s is a list of length n, the resulting type is of an n+m dimensions. The uniqueness of the new array will be u, no matter the uniqueness of t. If the shape s has rank 0, then the t will be returned, although if it is an array, with the uniqueness changed to u.

arrayOfRow :: ArrayShape (ShapeBase d) => TypeBase (ShapeBase d) NoUniqueness -> d -> TypeBase (ShapeBase d) NoUniqueness Source #

Construct an array whose rows are the given type, and the outer size is the given dimension. This is just a convenient wrapper around arrayOf.

arrayOfShape :: Type -> Shape -> Type Source #

Construct an array whose rows are the given type, and the outer size is the given ShapeBase. This is just a convenient wrapper around arrayOf.

setOuterSize :: ArrayShape (ShapeBase d) => TypeBase (ShapeBase d) u -> d -> TypeBase (ShapeBase d) u Source #

Replace the size of the outermost dimension of an array. If the given type is not an array, it is returned unchanged.

setDimSize :: ArrayShape (ShapeBase d) => Int -> TypeBase (ShapeBase d) u -> d -> TypeBase (ShapeBase d) u Source #

Replace the size of the given dimension of an array. If the given type is not an array, it is returned unchanged.

setOuterDim :: ShapeBase d -> d -> ShapeBase d Source #

Replace the outermost dimension of an array shape.

setDim :: Int -> ShapeBase d -> d -> ShapeBase d Source #

Replace the specified dimension of an array shape.

setArrayDims :: TypeBase oldshape u -> [SubExp] -> TypeBase Shape u Source #

Set the dimensions of an array. If the given type is not an array, return the type unchanged.

setArrayExtDims :: TypeBase oldshape u -> [ExtSize] -> TypeBase ExtShape u Source #

Set the existential dimensions of an array. If the given type is not an array, return the type unchanged.

peelArray :: ArrayShape shape => Int -> TypeBase shape u -> Maybe (TypeBase shape u) Source #

peelArray n t returns the type resulting from peeling the first n array dimensions from t. Returns Nothing if t has less than n dimensions.

stripArray :: ArrayShape shape => Int -> TypeBase shape u -> TypeBase shape u Source #

stripArray n t removes the n outermost layers of the array. Essentially, it is the type of indexing an array of type t with n indexes.

arrayDims :: TypeBase Shape u -> [SubExp] Source #

Return the dimensions of a type - for non-arrays, this is the empty list.

arrayExtDims :: TypeBase ExtShape u -> [ExtSize] Source #

Return the existential dimensions of a type - for non-arrays, this is the empty list.

shapeSize :: Int -> Shape -> SubExp Source #

Return the size of the given dimension. If the dimension does not exist, the zero constant is returned.

arraySize :: Int -> TypeBase Shape u -> SubExp Source #

Return the size of the given dimension. If the dimension does not exist, the zero constant is returned.

arraysSize :: Int -> [TypeBase Shape u] -> SubExp Source #

Return the size of the given dimension in the first element of the given type list. If the dimension does not exist, or no types are given, the zero constant is returned.

rowType :: ArrayShape shape => TypeBase shape u -> TypeBase shape u Source #

Return the immediate row-type of an array. For [[int]], this would be [int].

elemType :: TypeBase shape u -> PrimType Source #

Returns the bottommost type of an array. For [[int]], this would be int. If the given type is not an array, it is returned.

transposeType :: Type -> Type Source #

Swap the two outer dimensions of the type.

rearrangeType :: [Int] -> Type -> Type Source #

Rearrange the dimensions of the type. If the length of the permutation does not match the rank of the type, the permutation will be extended with identity.

diet :: TypeBase shape Uniqueness -> Diet Source #

diet t returns a description of how a function parameter of type t might consume its argument.

subtypeOf :: (Ord u, ArrayShape shape) => TypeBase shape u -> TypeBase shape u -> Bool Source #

x `subtypeOf` y is true if x is a subtype of y (or equal to y), meaning x is valid whenever y is.

subtypesOf :: (Ord u, ArrayShape shape) => [TypeBase shape u] -> [TypeBase shape u] -> Bool Source #

xs `subtypesOf` ys is true if xs is the same size as ys, and each element in xs is a subtype of the corresponding element in ys..

extractShapeContext :: [TypeBase ExtShape u] -> [[a]] -> [a] Source #

Given the existential return type of a function, and the shapes of the values returned by the function, return the existential shape context. That is, those sizes that are existential in the return type.

shapeContext :: [TypeBase ExtShape u] -> Set Int Source #

The set of identifiers used for the shape context in the given ExtTypes.

shapeContextSize :: [ExtType] -> Int Source #

The size of the set that would be returned by shapeContext.

hasStaticShape :: ExtType -> Maybe Type Source #

If all dimensions of the given RetType are statically known, return the corresponding list of Type.

generaliseExtTypes :: [TypeBase ExtShape u] -> [TypeBase ExtShape u] -> [TypeBase ExtShape u] Source #

Given two lists of ExtTypes of the same length, return a list of ExtTypes that is a subtype (as per isSubtypeOf) of the two operands.

existentialiseExtTypes :: [VName] -> [ExtType] -> [ExtType] Source #

Given a list of ExtTypes and a list of "forbidden" names, modify the dimensions of the ExtTypes such that they are Ext where they were previously Free with a variable in the set of forbidden names.

shapeMapping :: [TypeBase Shape u0] -> [TypeBase Shape u1] -> Map VName SubExp Source #

In the call shapeMapping ts1 ts2, the lists ts1 and ts must be of equal length and their corresponding elements have the same types modulo exact dimensions (but matching array rank is important). The result is a mapping from named dimensions of ts1 to the corresponding dimension in ts2.

This function is useful when ts1 are the value parameters of some function and ts2 are the value arguments, and we need to figure out which shape context to pass.

shapeMapping' :: [TypeBase Shape u] -> [[a]] -> Map VName a Source #

Like shapeMapping, but works with explicit dimensions.

shapeExtMapping :: [TypeBase ExtShape u] -> [TypeBase Shape u1] -> Map Int SubExp Source #

Like shapeMapping, but produces a mapping for the dimensions context.

Abbreviations

The Typed typeclass

class Typed t where Source #

Typeclass for things that contain Types.

Methods

typeOf :: t -> Type Source #

Instances
Typed Ident Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

typeOf :: Ident -> Type Source #

Typed DeclType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

typeOf :: DeclType -> Type Source #

Typed Type Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

typeOf :: Type -> Type Source #

Typed attr => Typed (PatElemT attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

typeOf :: PatElemT attr -> Type Source #

Typed attr => Typed (Param attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

typeOf :: Param attr -> Type Source #

Annotations lore => Typed (NameInfo lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Scope

Methods

typeOf :: NameInfo lore -> Type Source #

Typed b => Typed (a, b) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

typeOf :: (a, b) -> Type Source #

Typed (MemInfo SubExp Uniqueness ret) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Typed (MemInfo SubExp NoUniqueness ret) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

class DeclTyped t where Source #

Typeclass for things that contain DeclTypes.

Methods

declTypeOf :: t -> DeclType Source #

class FixExt t => ExtTyped t where Source #

Typeclass for things that contain ExtTypes.

Methods

extTypeOf :: t -> ExtType Source #

class Typed a => SetType a where Source #

Typeclass for things whose type can be changed.

Methods

setType :: a -> Type -> a Source #

Instances
SetType Type Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

setType :: Type -> Type -> Type Source #

SetType attr => SetType (PatElemT attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

setType :: PatElemT attr -> Type -> PatElemT attr Source #

SetType b => SetType (a, b) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

setType :: (a, b) -> Type -> (a, b) Source #

class FixExt t where Source #

Something with an existential context that can be (partially) fixed.

Methods

fixExt :: Int -> SubExp -> t -> t Source #

Fix the given existentional variable to the indicated free value.

Instances
FixExt () Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

fixExt :: Int -> SubExp -> () -> () Source #

FixExt ExtSize Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

fixExt :: Int -> SubExp -> ExtSize -> ExtSize Source #

FixExt MemReturn Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

FixExt a => FixExt [a] Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

fixExt :: Int -> SubExp -> [a] -> [a] Source #

FixExt d => FixExt (ShapeBase d) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

fixExt :: Int -> SubExp -> ShapeBase d -> ShapeBase d Source #

(FixExt shape, ArrayShape shape) => FixExt (TypeBase shape u) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

fixExt :: Int -> SubExp -> TypeBase shape u -> TypeBase shape u Source #

FixExt ret => FixExt (MemInfo ExtSize u ret) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Methods

fixExt :: Int -> SubExp -> MemInfo ExtSize u ret -> MemInfo ExtSize u ret Source #