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

Futhark.IR.Prop.Types

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.

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.

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

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.

elemType :: TypeBase shape u -> PrimType Source #

Returns the bottommost type of an array. For [][]i32, this would be i32. If the given type is not an array, it 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].

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.

mapOnExtType :: Monad m => (SubExp -> m SubExp) -> TypeBase ExtShape u -> m (TypeBase ExtShape u) Source #

Transform any SubExps in the type.

mapOnType :: Monad m => (SubExp -> m SubExp) -> TypeBase Shape u -> m (TypeBase Shape u) Source #

Transform any SubExps in the type.

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

toDecl :: TypeBase shape NoUniqueness -> Uniqueness -> TypeBase shape Uniqueness Source #

Add the given uniqueness information to the types.

fromDecl :: TypeBase shape Uniqueness -> TypeBase shape NoUniqueness Source #

Remove uniqueness information from the type.

isExt :: Ext a -> Maybe Int Source #

If an existential, then return its existential index.

isFree :: Ext a -> Maybe a Source #

If a known size, then return that size.

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.

hasStaticShape :: TypeBase ExtShape u -> Maybe (TypeBase Shape u) Source #

If all dimensions of the given ExtShape are statically known, change to the corresponding Shape.

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

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

Produce a mapping for the dimensions context.

Abbreviations

int8 :: PrimType Source #

IntType Int8

int16 :: PrimType Source #

IntType Int16

int32 :: PrimType Source #

IntType Int32

int64 :: PrimType Source #

IntType Int64

float32 :: PrimType Source #

FloatType Float32

float64 :: PrimType Source #

FloatType Float64

The Typed typeclass

class Typed t where Source #

Typeclass for things that contain Types.

Methods

typeOf :: t -> Type Source #

Instances

Instances details
Typed Ident Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

typeOf :: Ident -> Type Source #

Typed DeclType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

typeOf :: DeclType -> Type Source #

Typed Type Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

typeOf :: Type -> Type Source #

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

Defined in Futhark.IR.Prop.Types

Methods

typeOf :: PatElemT dec -> Type Source #

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

Defined in Futhark.IR.Prop.Types

Methods

typeOf :: Param dec -> Type Source #

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

Defined in Futhark.IR.Prop.Scope

Methods

typeOf :: NameInfo lore -> Type Source #

ASTLore lore => Typed (Entry lore) Source # 
Instance details

Defined in Futhark.Analysis.SymbolTable

Methods

typeOf :: Entry lore -> Type Source #

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

Defined in Futhark.IR.Prop.Types

Methods

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

Typed (MemInfo SubExp Uniqueness ret) Source # 
Instance details

Defined in Futhark.IR.Mem

Typed (MemInfo SubExp NoUniqueness ret) Source # 
Instance details

Defined in Futhark.IR.Mem

class DeclTyped t where Source #

Typeclass for things that contain DeclTypes.

Methods

declTypeOf :: t -> DeclType Source #

Instances

Instances details
DeclTyped DeclType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

DeclTyped dec => DeclTyped (Param dec) Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

declTypeOf :: Param dec -> DeclType Source #

DeclTyped (MemInfo SubExp Uniqueness ret) Source # 
Instance details

Defined in Futhark.IR.Mem

class FixExt t => ExtTyped t where Source #

Typeclass for things that contain ExtTypes.

Methods

extTypeOf :: t -> ExtType Source #

Instances

Instances details
ExtTyped ExtType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

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

Defined in Futhark.IR.Mem

class FixExt t => DeclExtTyped t where Source #

Typeclass for things that contain DeclExtTypes.

Instances

Instances details
DeclExtTyped DeclExtType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

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

Defined in Futhark.IR.Mem

class Typed a => SetType a where Source #

Typeclass for things whose type can be changed.

Methods

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

Instances

Instances details
SetType Type Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

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

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

Defined in Futhark.IR.Prop.Types

Methods

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

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

Defined in Futhark.IR.Prop.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

Instances details
FixExt () Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

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

FixExt ExtSize Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

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

FixExt MemReturn Source # 
Instance details

Defined in Futhark.IR.Mem

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

Defined in Futhark.IR.Prop.Types

Methods

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

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

Defined in Futhark.IR.Prop.Types

Methods

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

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

Defined in Futhark.IR.Prop.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.IR.Mem

Methods

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