Safe Haskell | None |
---|---|
Language | Haskell2010 |
Imperative intermediate language used as a stepping stone in code generation.
This is a generic representation parametrised on an extensible arbitrary operation.
Originally inspired by the paper "Defunctionalizing Push Arrays" (FHPC '14).
Synopsis
- newtype Functions a = Functions [(Name, Function a)]
- type Function = FunctionT
- data FunctionT a = Function {
- functionEntry :: Bool
- functionOutput :: [Param]
- functionInput :: [Param]
- functionbBody :: Code a
- functionResult :: [ExternalValue]
- functionArgs :: [ExternalValue]
- data ValueDesc
- data Signedness
- data ExternalValue
- data Param
- paramName :: Param -> VName
- data Size
- type MemSize = Size
- type DimSize = Size
- data Type
- data Space
- type SpaceId = String
- data Code a
- = Skip
- | (Code a) :>>: (Code a)
- | For VName IntType Exp (Code a)
- | While Exp (Code a)
- | DeclareMem VName Space
- | DeclareScalar VName PrimType
- | DeclareArray VName Space PrimType [PrimValue]
- | Allocate VName (Count Bytes) Space
- | Free VName Space
- | Copy VName (Count Bytes) Space VName (Count Bytes) Space (Count Bytes)
- | Write VName (Count Bytes) PrimType Space Volatility Exp
- | SetScalar VName Exp
- | SetMem VName VName Space
- | Call [VName] Name [Arg]
- | If Exp (Code a) (Code a)
- | Assert Exp (ErrorMsg Exp) (SrcLoc, [SrcLoc])
- | Comment String (Code a)
- | DebugPrint String PrimType Exp
- | Op a
- data PrimValue
- = IntValue !IntValue
- | FloatValue !FloatValue
- | BoolValue !Bool
- | Checked
- data ExpLeaf
- type Exp = PrimExp ExpLeaf
- data Volatility
- data Arg
- var :: VName -> PrimType -> Exp
- index :: VName -> Count Bytes -> PrimType -> Space -> Volatility -> Exp
- newtype ErrorMsg a = ErrorMsg [ErrorMsgPart a]
- data ErrorMsgPart a
- = ErrorString String
- | ErrorInt32 a
- newtype Count u = Count {}
- data Bytes
- data Elements
- elements :: Exp -> Count Elements
- bytes :: Exp -> Count Bytes
- withElemType :: Count Elements -> PrimType -> Count Bytes
- sizeToExp :: Size -> Exp
- dimSizeToExp :: DimSize -> Count Elements
- memSizeToExp :: MemSize -> Count Bytes
- module Language.Futhark.Core
- module Futhark.Representation.Primitive
- module Futhark.Analysis.PrimExp
Documentation
A collection of imperative functions.
Instances
Functor Functions Source # | |
Foldable Functions Source # | |
Defined in Futhark.CodeGen.ImpCode fold :: Monoid m => Functions m -> m # foldMap :: Monoid m => (a -> m) -> Functions a -> m # foldr :: (a -> b -> b) -> b -> Functions a -> b # foldr' :: (a -> b -> b) -> b -> Functions a -> b # foldl :: (b -> a -> b) -> b -> Functions a -> b # foldl' :: (b -> a -> b) -> b -> Functions a -> b # foldr1 :: (a -> a -> a) -> Functions a -> a # foldl1 :: (a -> a -> a) -> Functions a -> a # toList :: Functions a -> [a] # length :: Functions a -> Int # elem :: Eq a => a -> Functions a -> Bool # maximum :: Ord a => Functions a -> a # minimum :: Ord a => Functions a -> a # | |
Traversable Functions Source # | |
Defined in Futhark.CodeGen.ImpCode | |
Semigroup (Functions a) Source # | |
Monoid (Functions a) Source # | |
Pretty op => Pretty (Functions op) Source # | |
A imperative function, containing the body as well as its low-level inputs and outputs, as well as its high-level arguments and results. The latter are only used if the function is an entry point.
Function | |
|
Instances
Functor FunctionT Source # | |
Foldable FunctionT Source # | |
Defined in Futhark.CodeGen.ImpCode fold :: Monoid m => FunctionT m -> m # foldMap :: Monoid m => (a -> m) -> FunctionT a -> m # foldr :: (a -> b -> b) -> b -> FunctionT a -> b # foldr' :: (a -> b -> b) -> b -> FunctionT a -> b # foldl :: (b -> a -> b) -> b -> FunctionT a -> b # foldl' :: (b -> a -> b) -> b -> FunctionT a -> b # foldr1 :: (a -> a -> a) -> FunctionT a -> a # foldl1 :: (a -> a -> a) -> FunctionT a -> a # toList :: FunctionT a -> [a] # length :: FunctionT a -> Int # elem :: Eq a => a -> FunctionT a -> Bool # maximum :: Ord a => FunctionT a -> a # minimum :: Ord a => FunctionT a -> a # | |
Traversable FunctionT Source # | |
Defined in Futhark.CodeGen.ImpCode | |
Show a => Show (FunctionT a) Source # | |
Pretty op => Pretty (FunctionT op) Source # | |
A description of an externally meaningful value.
ArrayValue VName MemSize Space PrimType Signedness [DimSize] | An array with memory block, memory block size, memory space, element type, signedness of element type (if applicable), and shape. |
ScalarValue PrimType Signedness VName | A scalar value with signedness if applicable. |
data Signedness Source #
Instances
Eq Signedness Source # | |
Defined in Futhark.CodeGen.ImpCode (==) :: Signedness -> Signedness -> Bool # (/=) :: Signedness -> Signedness -> Bool # | |
Show Signedness Source # | |
Defined in Futhark.CodeGen.ImpCode showsPrec :: Int -> Signedness -> ShowS # show :: Signedness -> String # showList :: [Signedness] -> ShowS # |
data ExternalValue Source #
^ An externally visible value. This can be an opaque value (covering several physical internal values), or a single value that can be used externally.
OpaqueValue String [ValueDesc] | The string is a human-readable description with no other semantics. |
TransparentValue ValueDesc |
Instances
Show ExternalValue Source # | |
Defined in Futhark.CodeGen.ImpCode showsPrec :: Int -> ExternalValue -> ShowS # show :: ExternalValue -> String # showList :: [ExternalValue] -> ShowS # | |
Pretty ExternalValue Source # | |
Defined in Futhark.CodeGen.ImpCode ppr :: ExternalValue -> Doc # pprPrec :: Int -> ExternalValue -> Doc # pprList :: [ExternalValue] -> Doc # |
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.
Skip | |
(Code a) :>>: (Code a) | |
For VName IntType Exp (Code a) | |
While Exp (Code a) | |
DeclareMem VName Space | |
DeclareScalar VName PrimType | |
DeclareArray VName Space PrimType [PrimValue] | Create an array containing the given values. The lifetime of the array will be the entire application. This is mostly used for constant arrays, but also for some bookkeeping data, like the synchronisation counts used to implement reduction. |
Allocate VName (Count Bytes) Space | Memory space must match the corresponding
|
Free VName Space | Indicate that some memory block will never again be referenced via the indicated variable. However, it may still be accessed through aliases. It is only safe to actually deallocate the memory block if this is the last reference. There is no guarantee that all memory blocks will be freed with this statement. Backends are free to ignore it entirely. |
Copy VName (Count Bytes) Space VName (Count Bytes) Space (Count Bytes) | Destination, offset in destination, destination space, source, offset in source, offset space, number of bytes. |
Write VName (Count Bytes) PrimType Space Volatility Exp | |
SetScalar VName Exp | |
SetMem VName VName Space | Must be in same space. |
Call [VName] Name [Arg] | |
If Exp (Code a) (Code a) | |
Assert Exp (ErrorMsg Exp) (SrcLoc, [SrcLoc]) | |
Comment String (Code a) | Has the same semantics as the contained code, but the comment should show up in generated code for ease of inspection. |
DebugPrint String PrimType Exp | Print the given value (of the given type) to the screen, somehow annotated with the given string as a description. This has no semantic meaning, but is used entirely for debugging. Code generators are free to ignore this statement. |
Op a |
Instances
Functor Code Source # | |
Foldable Code Source # | |
Defined in Futhark.CodeGen.ImpCode fold :: Monoid m => Code m -> m # foldMap :: Monoid m => (a -> m) -> Code a -> m # foldr :: (a -> b -> b) -> b -> Code a -> b # foldr' :: (a -> b -> b) -> b -> Code a -> b # foldl :: (b -> a -> b) -> b -> Code a -> b # foldl' :: (b -> a -> b) -> b -> Code a -> b # foldr1 :: (a -> a -> a) -> Code a -> a # foldl1 :: (a -> a -> a) -> Code a -> a # elem :: Eq a => a -> Code a -> Bool # maximum :: Ord a => Code a -> a # | |
Traversable Code Source # | |
Show a => Show (Code a) Source # | |
Semigroup (Code a) Source # | |
Monoid (Code a) Source # | |
Pretty op => Pretty (Code op) Source # | |
FreeIn a => FreeIn (Code a) Source # | |
MonadWriter (Code op) (ImpM lore op) Source # | |
Non-array values.
IntValue !IntValue | |
FloatValue !FloatValue | |
BoolValue !Bool | |
Checked | The only value of type |
data Volatility Source #
The volatility of a memory access.
Instances
Eq Volatility Source # | |
Defined in Futhark.CodeGen.ImpCode (==) :: Volatility -> Volatility -> Bool # (/=) :: Volatility -> Volatility -> Bool # | |
Ord Volatility Source # | |
Defined in Futhark.CodeGen.ImpCode compare :: Volatility -> Volatility -> Ordering # (<) :: Volatility -> Volatility -> Bool # (<=) :: Volatility -> Volatility -> Bool # (>) :: Volatility -> Volatility -> Bool # (>=) :: Volatility -> Volatility -> Bool # max :: Volatility -> Volatility -> Volatility # min :: Volatility -> Volatility -> Volatility # | |
Show Volatility Source # | |
Defined in Futhark.CodeGen.ImpCode showsPrec :: Int -> Volatility -> ShowS # show :: Volatility -> String # showList :: [Volatility] -> ShowS # |
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.Representation.AST.Syntax.Core fold :: Monoid m => ErrorMsg m -> 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 # | |
Defined in Futhark.Representation.AST.Syntax.Core | |
Eq a => Eq (ErrorMsg a) Source # | |
Ord a => Ord (ErrorMsg a) Source # | |
Defined in Futhark.Representation.AST.Syntax.Core | |
Show a => Show (ErrorMsg a) Source # | |
IsString (ErrorMsg a) Source # | |
Defined in Futhark.Representation.AST.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. |
Instances
Typed enumerations
A wrapper around Exp
that maintains a unit as a phantom
type.
Instances
Eq (Count u) Source # | |
Num (Count u) Source # | |
Show (Count u) Source # | |
Pretty (Count u) Source # | |
IntegralExp (Count u) Source # | |
Defined in Futhark.CodeGen.ImpCode quot :: Count u -> Count u -> Count u Source # rem :: Count u -> Count u -> Count u Source # div :: Count u -> Count u -> Count u Source # mod :: Count u -> Count u -> Count u Source # sgn :: Count u -> Maybe Int Source # fromInt8 :: Int8 -> Count u Source # fromInt16 :: Int16 -> Count u Source # | |
FreeIn (Count u) Source # | |
withElemType :: Count Elements -> PrimType -> Count Bytes Source #
Convert a count of elements into a count of bytes, given the per-element size.
Converting from sizes
Analysis
Re-exports from other modules.
module Language.Futhark.Core
module Futhark.Analysis.PrimExp