Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
The most primitive ("core") aspects of the AST. Split out of Futhark.IR.Syntax in order for Futhark.IR.Rep 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 Language.Futhark.Primitive
- data Commutativity
- data Uniqueness
- newtype ShapeBase d = Shape {
- shapeDims :: [d]
- type Shape = ShapeBase SubExp
- stripDims :: Int -> ShapeBase d -> ShapeBase d
- 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
- shapeRank :: a -> Int
- subShapeOf :: a -> a -> Bool
- 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 Text
- | ErrorVal PrimType a
- errorMsgArgTypes :: ErrorMsg a -> [PrimType]
- data ValueType = ValueType Signedness Rank PrimType
- data OpaqueType
- = OpaqueType [ValueType]
- | OpaqueRecord [(Name, EntryPointType)]
- | OpaqueSum [ValueType] [(Name, [(EntryPointType, [Int])])]
- | OpaqueArray Int Name [ValueType]
- | OpaqueRecordArray Int Name [(Name, EntryPointType)]
- newtype OpaqueTypes = OpaqueTypes [(Name, OpaqueType)]
- data Signedness
- data EntryPointType
- data Attr
- newtype Attrs = Attrs {}
- oneAttr :: Attr -> Attrs
- inAttrs :: Attr -> Attrs -> Bool
- withoutAttrs :: Attrs -> Attrs -> Attrs
- mapAttrs :: (Attr -> a) -> Attrs -> [a]
- data PrimValue
- data Ident = Ident {}
- newtype Certs = Certs {}
- data SubExp
- data Param dec = Param {
- paramAttrs :: Attrs
- paramName :: VName
- paramDec :: dec
- data DimIndex d
- newtype Slice d = Slice {}
- dimFix :: DimIndex d -> Maybe d
- sliceIndices :: Slice d -> Maybe [d]
- sliceDims :: Slice d -> [d]
- sliceShape :: Slice d -> ShapeBase 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 PatElem dec = PatElem {
- patElemName :: VName
- patElemDec :: dec
- data FlatSlice d = FlatSlice d [FlatDimIndex d]
- data FlatDimIndex d = FlatDimIndex d d
- flatSliceDims :: FlatSlice d -> [d]
- flatSliceStrides :: FlatSlice d -> [d]
Documentation
module Language.Futhark.Core
module Language.Futhark.Primitive
Types
data Commutativity Source #
Whether some operator is commutative or not. The Monoid
instance returns the least commutative of its arguments.
Instances
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
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.
stripDims :: Int -> ShapeBase d -> ShapeBase d Source #
stripDims n shape
strips the outer n
dimensions from
shape
.
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.
Instances
Monoid Rank Source # | |
Semigroup Rank Source # | |
Show Rank Source # | |
ArrayShape Rank Source # | |
Rename Rank Source # | |
Substitute Rank Source # | |
Defined in Futhark.Transform.Substitute | |
Eq Rank Source # | |
Ord Rank Source # | |
Pretty Rank Source # | |
Defined in Futhark.IR.Pretty | |
Pretty u => Pretty (TypeBase Rank u) Source # | |
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.
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
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 # | |
Functor ErrorMsg Source # | |
IsString (ErrorMsg a) Source # | |
Defined in Futhark.IR.Syntax.Core fromString :: String -> ErrorMsg a # | |
Monoid (ErrorMsg a) Source # | |
Semigroup (ErrorMsg a) Source # | |
Show a => Show (ErrorMsg a) Source # | |
Eq a => Eq (ErrorMsg a) Source # | |
Ord a => Ord (ErrorMsg a) Source # | |
Pretty a => Pretty (ErrorMsg a) Source # | |
Defined in Futhark.IR.Pretty |
data ErrorMsgPart a Source #
A part of an error message.
ErrorString Text | A literal string. |
ErrorVal PrimType a | A run-time value. |
Instances
errorMsgArgTypes :: ErrorMsg a -> [PrimType] Source #
How many non-constant parts does the error message have, and what is their type?
Entry point information
An actual non-opaque type that can be passed to and from Futhark programs, or serve as the contents of opaque types. Scalars are represented with zero rank.
data OpaqueType Source #
The representation of an opaque type.
OpaqueType [ValueType] | |
OpaqueRecord [(Name, EntryPointType)] | Note that the field ordering here denote the actual representation - make sure it is preserved. |
OpaqueSum [ValueType] [(Name, [(EntryPointType, [Int])])] | Constructor ordering also denotes representation, in that the index of the constructor is the identifying number. The total values used to represent a sum values is the
|
OpaqueArray Int Name [ValueType] | An array with this rank and named opaque element type. |
OpaqueRecordArray Int Name [(Name, EntryPointType)] | An array with known rank and where the elements are this record type. |
Instances
Show OpaqueType Source # | |
Defined in Futhark.IR.Syntax.Core showsPrec :: Int -> OpaqueType -> ShowS # show :: OpaqueType -> String # showList :: [OpaqueType] -> ShowS # | |
Eq OpaqueType Source # | |
Defined in Futhark.IR.Syntax.Core (==) :: OpaqueType -> OpaqueType -> Bool # (/=) :: OpaqueType -> OpaqueType -> Bool # | |
Ord OpaqueType Source # | |
Defined in Futhark.IR.Syntax.Core compare :: OpaqueType -> OpaqueType -> Ordering # (<) :: OpaqueType -> OpaqueType -> Bool # (<=) :: OpaqueType -> OpaqueType -> Bool # (>) :: OpaqueType -> OpaqueType -> Bool # (>=) :: OpaqueType -> OpaqueType -> Bool # max :: OpaqueType -> OpaqueType -> OpaqueType # min :: OpaqueType -> OpaqueType -> OpaqueType # | |
Pretty OpaqueType Source # | |
Defined in Futhark.IR.Pretty pretty :: OpaqueType -> Doc ann # prettyList :: [OpaqueType] -> Doc ann # |
newtype OpaqueTypes Source #
Names of opaque types and their representation.
OpaqueTypes [(Name, OpaqueType)] |
Instances
data Signedness Source #
Since the core language does not care for signedness, but the source language does, entry point input/output information has metadata for integer types (and arrays containing these) that indicate whether they are really unsigned integers. This doesn't matter for non-integer types.
Instances
Show Signedness Source # | |
Defined in Futhark.IR.Syntax.Core showsPrec :: Int -> Signedness -> ShowS # show :: Signedness -> String # showList :: [Signedness] -> ShowS # | |
Eq Signedness Source # | |
Defined in Futhark.IR.Syntax.Core (==) :: Signedness -> Signedness -> Bool # (/=) :: Signedness -> Signedness -> Bool # | |
Ord Signedness Source # | |
Defined in Futhark.IR.Syntax.Core compare :: Signedness -> Signedness -> Ordering # (<) :: Signedness -> Signedness -> Bool # (<=) :: Signedness -> Signedness -> Bool # (>) :: Signedness -> Signedness -> Bool # (>=) :: Signedness -> Signedness -> Bool # max :: Signedness -> Signedness -> Signedness # min :: Signedness -> Signedness -> Signedness # | |
Pretty Signedness Source # | |
Defined in Futhark.IR.Pretty pretty :: Signedness -> Doc ann # prettyList :: [Signedness] -> Doc ann # |
data EntryPointType Source #
Every entry point argument and return value has an annotation indicating how it maps to the original source program type.
TypeOpaque Name | An opaque type of this name. |
TypeTransparent ValueType | A transparent type, which is scalar if the rank is zero. |
Instances
Show EntryPointType Source # | |
Defined in Futhark.IR.Syntax.Core showsPrec :: Int -> EntryPointType -> ShowS # show :: EntryPointType -> String # showList :: [EntryPointType] -> ShowS # | |
Eq EntryPointType Source # | |
Defined in Futhark.IR.Syntax.Core (==) :: EntryPointType -> EntryPointType -> Bool # (/=) :: EntryPointType -> EntryPointType -> Bool # | |
Ord EntryPointType Source # | |
Defined in Futhark.IR.Syntax.Core compare :: EntryPointType -> EntryPointType -> Ordering # (<) :: EntryPointType -> EntryPointType -> Bool # (<=) :: EntryPointType -> EntryPointType -> Bool # (>) :: EntryPointType -> EntryPointType -> Bool # (>=) :: EntryPointType -> EntryPointType -> Bool # max :: EntryPointType -> EntryPointType -> EntryPointType # min :: EntryPointType -> EntryPointType -> EntryPointType # | |
Pretty EntryPointType Source # | |
Defined in Futhark.IR.Pretty pretty :: EntryPointType -> Doc ann # prettyList :: [EntryPointType] -> Doc ann # |
Attributes
A single attribute.
Every statement is associated with a set of attributes, which can have various effects throughout the compiler.
withoutAttrs :: Attrs -> Attrs -> Attrs Source #
x
gives withoutAttrs
yx
except for any attributes also in y
.
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.
A list of names used for certificates in some expressions.
Instances
Monoid Certs Source # | |
Semigroup Certs Source # | |
Show Certs Source # | |
FreeIn Certs Source # | |
Simplifiable Certs Source # | |
Defined in Futhark.Optimise.Simplify.Engine | |
Rename Certs Source # | |
Substitute Certs Source # | |
Defined in Futhark.Transform.Substitute | |
Eq Certs Source # | |
Ord Certs Source # | |
Pretty Certs Source # | |
Defined in Futhark.IR.Pretty | |
MonadState (VNameSource, Bool, Certs) (SimpleM rep) Source # | |
Defined in Futhark.Optimise.Simplify.Engine |
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
A list of DimIndex
s, indicating how an array should be sliced.
Whenever a function accepts a Slice
, that slice should be total,
i.e, cover all dimensions of the array. Deviators should be
indicated by taking a list of DimIndex
es instead.
Instances
Foldable Slice Source # | |
Defined in Futhark.IR.Syntax.Core fold :: Monoid m => Slice m -> m # foldMap :: Monoid m => (a -> m) -> Slice a -> m # foldMap' :: Monoid m => (a -> m) -> Slice a -> m # foldr :: (a -> b -> b) -> b -> Slice a -> b # foldr' :: (a -> b -> b) -> b -> Slice a -> b # foldl :: (b -> a -> b) -> b -> Slice a -> b # foldl' :: (b -> a -> b) -> b -> Slice a -> b # foldr1 :: (a -> a -> a) -> Slice a -> a # foldl1 :: (a -> a -> a) -> Slice a -> a # elem :: Eq a => a -> Slice a -> Bool # maximum :: Ord a => Slice a -> a # minimum :: Ord a => Slice a -> a # | |
Traversable Slice Source # | |
Functor Slice Source # | |
Show d => Show (Slice d) Source # | |
FreeIn d => FreeIn (Slice d) Source # | |
Simplifiable d => Simplifiable (Slice d) Source # | |
Defined in Futhark.Optimise.Simplify.Engine | |
Substitute d => Substitute (Slice d) Source # | |
Defined in Futhark.Transform.Substitute | |
Eq d => Eq (Slice d) Source # | |
Ord d => Ord (Slice d) Source # | |
Pretty a => Pretty (Slice a) Source # | |
Defined in Futhark.IR.Pretty |
sliceShape :: Slice d -> ShapeBase d Source #
The shape of the array produced by this slice.
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 | |
|
Instances
Flat (LMAD) slices
A flat slice is a way of viewing a one-dimensional array as a
multi-dimensional array, using a more compressed mechanism than
reshaping and using Slice
. The initial d
is an offset, and the
list then specifies the shape of the resulting array.
FlatSlice d [FlatDimIndex d] |
Instances
data FlatDimIndex d Source #
A dimension in a FlatSlice
.
FlatDimIndex | |
|
Instances
flatSliceDims :: FlatSlice d -> [d] Source #
The dimensions (shape) of the view produced by a flat slice.
flatSliceStrides :: FlatSlice d -> [d] Source #
The strides of each dimension produced by a flat slice.