Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
The most primitive ("core") aspects of the AST. Split out of Futhark.IR.Syntax in order for Futhark.IR.Decorations to use these definitions. This module is re-exported from Futhark.IR.Syntax and there should be no reason to include it explicitly.
Synopsis
- module Language.Futhark.Core
- module Futhark.IR.Primitive
- data Uniqueness
- data NoUniqueness = NoUniqueness
- newtype ShapeBase d = Shape {
- shapeDims :: [d]
- type Shape = ShapeBase SubExp
- data Ext a
- type ExtSize = Ext SubExp
- type ExtShape = ShapeBase ExtSize
- newtype Rank = Rank Int
- class (Monoid a, Eq a, Ord a) => ArrayShape a where
- data Space
- type SpaceId = String
- data TypeBase shape u
- type Type = TypeBase Shape NoUniqueness
- type ExtType = TypeBase ExtShape NoUniqueness
- type DeclType = TypeBase Shape Uniqueness
- type DeclExtType = TypeBase ExtShape Uniqueness
- data Diet
- newtype ErrorMsg a = ErrorMsg [ErrorMsgPart a]
- data ErrorMsgPart a
- = ErrorString String
- | ErrorInt32 a
- | ErrorInt64 a
- errorMsgArgTypes :: ErrorMsg a -> [PrimType]
- data PrimValue
- data Ident = Ident {}
- newtype Certificates = Certificates {
- unCertificates :: [VName]
- data SubExp
- data Param dec = Param {}
- data DimIndex d
- type Slice d = [DimIndex d]
- dimFix :: DimIndex d -> Maybe d
- sliceIndices :: Slice d -> Maybe [d]
- sliceDims :: Slice d -> [d]
- unitSlice :: Num d => d -> d -> DimIndex d
- fixSlice :: Num d => Slice d -> [d] -> [d]
- sliceSlice :: Num d => Slice d -> Slice d -> Slice d
- data PatElemT dec = PatElem {
- patElemName :: VName
- patElemDec :: dec
Documentation
module Language.Futhark.Core
module Futhark.IR.Primitive
Types
data Uniqueness Source #
The uniqueness attribute of a type. This essentially indicates
whether or not in-place modifications are acceptable. With respect
to ordering, Unique
is greater than Nonunique
.
Instances
data NoUniqueness Source #
A fancier name for ()
- encodes no uniqueness information.
Instances
The size of an array type as a list of its dimension sizes, with the type of sizes being parametric.
Instances
type Shape = ShapeBase SubExp Source #
The size of an array as a list of subexpressions. If a variable, that variable must be in scope where this array is used.
Something that may be existential.
Instances
type ExtShape = ShapeBase ExtSize Source #
Like Shape
but some of its elements may be bound in a local
environment instead. These are denoted with integral indices.
The size of an array type as merely the number of dimensions, with no further information.
class (Monoid a, Eq a, Ord a) => ArrayShape a where Source #
A class encompassing types containing array shape information.
shapeRank :: a -> Int Source #
Return the rank of an array with the given size.
stripDims :: Int -> a -> a Source #
stripDims n shape
strips the outer n
dimensions from
shape
.
subShapeOf :: a -> a -> Bool Source #
Check whether one shape if a subset of another shape.
Instances
The memory space of a block. If DefaultSpace
, this is the "default"
space, whatever that is. The exact meaning of the SpaceId
depends on the backend used. In GPU kernels, for example, this is
used to distinguish between constant, global and shared memory
spaces. In GPU-enabled host code, it is used to distinguish
between host memory (DefaultSpace
) and GPU space.
DefaultSpace | |
Space SpaceId | |
ScalarSpace [SubExp] PrimType | A special kind of memory that is a statically sized array of some primitive type. Used for private memory on GPUs. |
data TypeBase shape u Source #
The type of a value. When comparing types for equality with
==
, shapes must match.
Prim PrimType | |
Acc VName Shape [Type] u | Token, index space, element type, and uniqueness. |
Array PrimType shape u | |
Mem Space |
Instances
type Type = TypeBase Shape NoUniqueness Source #
A type with shape information, used for describing the type of variables.
type ExtType = TypeBase ExtShape NoUniqueness Source #
A type with existentially quantified shapes - used as part of function (and function-like) return types. Generally only makes sense when used in a list.
type DeclType = TypeBase Shape Uniqueness Source #
A type with shape and uniqueness information, used declaring return- and parameters types.
type DeclExtType = TypeBase ExtShape Uniqueness Source #
An ExtType
with uniqueness information, used for function
return types.
Information about which parts of a value/type are consumed. For
example, we might say that a function taking three arguments of
types ([int], *[int], [int])
has diet [Observe, Consume,
Observe]
.
Consume | Consumes this value. |
Observe | Only observes value in this position, does not consume. A result may alias this. |
ObservePrim | As |
An error message is a list of error parts, which are concatenated to form the final message.
ErrorMsg [ErrorMsgPart a] |
Instances
Functor ErrorMsg Source # | |
Foldable ErrorMsg Source # | |
Defined in Futhark.IR.Syntax.Core fold :: Monoid m => ErrorMsg m -> m # foldMap :: Monoid m => (a -> m) -> ErrorMsg a -> m # foldMap' :: Monoid m => (a -> m) -> ErrorMsg a -> m # foldr :: (a -> b -> b) -> b -> ErrorMsg a -> b # foldr' :: (a -> b -> b) -> b -> ErrorMsg a -> b # foldl :: (b -> a -> b) -> b -> ErrorMsg a -> b # foldl' :: (b -> a -> b) -> b -> ErrorMsg a -> b # foldr1 :: (a -> a -> a) -> ErrorMsg a -> a # foldl1 :: (a -> a -> a) -> ErrorMsg a -> a # elem :: Eq a => a -> ErrorMsg a -> Bool # maximum :: Ord a => ErrorMsg a -> a # minimum :: Ord a => ErrorMsg a -> a # | |
Traversable ErrorMsg Source # | |
Eq a => Eq (ErrorMsg a) Source # | |
Ord a => Ord (ErrorMsg a) Source # | |
Show a => Show (ErrorMsg a) Source # | |
IsString (ErrorMsg a) Source # | |
Defined in Futhark.IR.Syntax.Core fromString :: String -> ErrorMsg a # | |
Pretty a => Pretty (ErrorMsg a) Source # | |
data ErrorMsgPart a Source #
A part of an error message.
ErrorString String | A literal string. |
ErrorInt32 a | A run-time integer value. |
ErrorInt64 a | A bigger run-time integer value. |
Instances
errorMsgArgTypes :: ErrorMsg a -> [PrimType] Source #
How many non-constant parts does the error message have, and what is their type?
Values
Non-array values.
IntValue !IntValue | |
FloatValue !FloatValue | |
BoolValue !Bool | |
UnitValue | The only value of type |
Abstract syntax tree
An identifier consists of its name and the type of the value bound to the identifier.
newtype Certificates Source #
A list of names used for certificates in some expressions.
Instances
A subexpression is either a scalar constant or a variable. One important property is that evaluation of a subexpression is guaranteed to complete in constant time.
Instances
A function or lambda parameter.
Instances
How to index a single dimension of an array.
Instances
An element of a pattern - consisting of a name and an addditional parametric decoration. This decoration is what is expected to contain the type of the resulting variable.
PatElem | |
|