Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Functions for inspecting and constructing various types.
Synopsis
- rankShaped :: ArrayShape shape => TypeBase shape u -> TypeBase Rank u
- arrayRank :: ArrayShape shape => TypeBase shape u -> Int
- arrayShape :: ArrayShape shape => TypeBase shape u -> shape
- setArrayShape :: ArrayShape newshape => TypeBase oldshape u -> newshape -> TypeBase newshape u
- existential :: ExtType -> Bool
- uniqueness :: TypeBase shape Uniqueness -> Uniqueness
- unique :: TypeBase shape Uniqueness -> Bool
- staticShapes :: [TypeBase Shape u] -> [TypeBase ExtShape u]
- staticShapes1 :: TypeBase Shape u -> TypeBase ExtShape u
- primType :: TypeBase shape u -> Bool
- arrayOf :: ArrayShape shape => TypeBase shape u_unused -> shape -> u -> TypeBase shape u
- arrayOfRow :: ArrayShape (ShapeBase d) => TypeBase (ShapeBase d) NoUniqueness -> d -> TypeBase (ShapeBase d) NoUniqueness
- arrayOfShape :: Type -> Shape -> Type
- setOuterSize :: ArrayShape (ShapeBase d) => TypeBase (ShapeBase d) u -> d -> TypeBase (ShapeBase d) u
- setDimSize :: ArrayShape (ShapeBase d) => Int -> TypeBase (ShapeBase d) u -> d -> TypeBase (ShapeBase d) u
- setOuterDim :: ShapeBase d -> d -> ShapeBase d
- setDim :: Int -> ShapeBase d -> d -> ShapeBase d
- setArrayDims :: TypeBase oldshape u -> [SubExp] -> TypeBase Shape u
- peelArray :: ArrayShape shape => Int -> TypeBase shape u -> Maybe (TypeBase shape u)
- stripArray :: ArrayShape shape => Int -> TypeBase shape u -> TypeBase shape u
- arrayDims :: TypeBase Shape u -> [SubExp]
- arrayExtDims :: TypeBase ExtShape u -> [ExtSize]
- shapeSize :: Int -> Shape -> SubExp
- arraySize :: Int -> TypeBase Shape u -> SubExp
- arraysSize :: Int -> [TypeBase Shape u] -> SubExp
- rowType :: ArrayShape shape => TypeBase shape u -> TypeBase shape u
- elemType :: TypeBase shape u -> PrimType
- transposeType :: Type -> Type
- rearrangeType :: [Int] -> Type -> Type
- mapOnExtType :: Monad m => (SubExp -> m SubExp) -> TypeBase ExtShape u -> m (TypeBase ExtShape u)
- mapOnType :: Monad m => (SubExp -> m SubExp) -> TypeBase Shape u -> m (TypeBase Shape u)
- diet :: TypeBase shape Uniqueness -> Diet
- subtypeOf :: (Ord u, ArrayShape shape) => TypeBase shape u -> TypeBase shape u -> Bool
- subtypesOf :: (Ord u, ArrayShape shape) => [TypeBase shape u] -> [TypeBase shape u] -> Bool
- toDecl :: TypeBase shape NoUniqueness -> Uniqueness -> TypeBase shape Uniqueness
- fromDecl :: TypeBase shape Uniqueness -> TypeBase shape NoUniqueness
- isExt :: Ext a -> Maybe Int
- isFree :: Ext a -> Maybe a
- extractShapeContext :: [TypeBase ExtShape u] -> [[a]] -> [a]
- shapeContext :: [TypeBase ExtShape u] -> Set Int
- hasStaticShape :: TypeBase ExtShape u -> Maybe (TypeBase Shape u)
- generaliseExtTypes :: [TypeBase ExtShape u] -> [TypeBase ExtShape u] -> [TypeBase ExtShape u]
- existentialiseExtTypes :: [VName] -> [ExtType] -> [ExtType]
- shapeExtMapping :: [TypeBase ExtShape u] -> [TypeBase Shape u1] -> Map Int SubExp
- int8 :: PrimType
- int16 :: PrimType
- int32 :: PrimType
- int64 :: PrimType
- float32 :: PrimType
- float64 :: PrimType
- class Typed t where
- class DeclTyped t where
- declTypeOf :: t -> DeclType
- class FixExt t => ExtTyped t where
- class FixExt t => DeclExtTyped t where
- declExtTypeOf :: t -> DeclExtType
- class Typed a => SetType a where
- class FixExt t where
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
.
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.
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.
mapOnExtType :: Monad m => (SubExp -> m SubExp) -> TypeBase ExtShape u -> m (TypeBase ExtShape u) Source #
Transform any SubExp
s in the type.
mapOnType :: Monad m => (SubExp -> m SubExp) -> TypeBase Shape u -> m (TypeBase Shape u) Source #
Transform any SubExp
s 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.
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
ExtType
s.
generaliseExtTypes :: [TypeBase ExtShape u] -> [TypeBase ExtShape u] -> [TypeBase ExtShape u] Source #
shapeExtMapping :: [TypeBase ExtShape u] -> [TypeBase Shape u1] -> Map Int SubExp Source #
Produce a mapping for the dimensions context.
Abbreviations
The Typed typeclass
Typeclass for things that contain Type
s.
Instances
Typed Ident Source # | |
Typed DeclType Source # | |
Typed Type Source # | |
Typed dec => Typed (PatElemT dec) Source # | |
Typed dec => Typed (Param dec) Source # | |
Decorations lore => Typed (NameInfo lore) Source # | |
ASTLore lore => Typed (Entry lore) Source # | |
Typed b => Typed (a, b) Source # | |
Defined in Futhark.IR.Prop.Types | |
Typed (MemInfo SubExp Uniqueness ret) Source # | |
Defined in Futhark.IR.Mem | |
Typed (MemInfo SubExp NoUniqueness ret) Source # | |
Defined in Futhark.IR.Mem |
class DeclTyped t where Source #
Typeclass for things that contain DeclType
s.
declTypeOf :: t -> DeclType Source #
Instances
DeclTyped DeclType Source # | |
Defined in Futhark.IR.Prop.Types declTypeOf :: DeclType -> DeclType Source # | |
DeclTyped dec => DeclTyped (Param dec) Source # | |
Defined in Futhark.IR.Prop.Types declTypeOf :: Param dec -> DeclType Source # | |
DeclTyped (MemInfo SubExp Uniqueness ret) Source # | |
Defined in Futhark.IR.Mem declTypeOf :: MemInfo SubExp Uniqueness ret -> DeclType Source # |
class FixExt t => DeclExtTyped t where Source #
Typeclass for things that contain DeclExtType
s.
declExtTypeOf :: t -> DeclExtType Source #
Instances
DeclExtTyped DeclExtType Source # | |
Defined in Futhark.IR.Prop.Types | |
FixExt ret => DeclExtTyped (MemInfo ExtSize Uniqueness ret) Source # | |
Defined in Futhark.IR.Mem declExtTypeOf :: MemInfo ExtSize Uniqueness ret -> DeclExtType Source # |
class Typed a => SetType a where Source #
Typeclass for things whose type can be changed.
Something with an existential context that can be (partially) fixed.
fixExt :: Int -> SubExp -> t -> t Source #
Fix the given existentional variable to the indicated free value.