futhark-0.15.5: An optimising compiler for a functional, array-oriented language.
Safe HaskellNone
LanguageHaskell2010

Futhark.CodeGen.ImpCode

Description

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

Documentation

data Definitions a Source #

A collection of imperative functions and constants.

Constructors

Definitions (Constants a) (Functions a) 

Instances

Instances details
Pretty op => Pretty (Definitions op) Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

ppr :: Definitions op -> Doc

pprPrec :: Int -> Definitions op -> Doc

pprList :: [Definitions op] -> Doc

newtype Functions a Source #

A collection of imperative functions.

Constructors

Functions [(Name, Function a)] 

Instances

Instances details
Functor Functions Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

fmap :: (a -> b) -> Functions a -> Functions b #

(<$) :: a -> Functions b -> Functions a #

Foldable Functions Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

fold :: Monoid m => Functions m -> m #

foldMap :: Monoid m => (a -> m) -> Functions a -> 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] #

null :: Functions a -> Bool #

length :: Functions a -> Int #

elem :: Eq a => a -> Functions a -> Bool #

maximum :: Ord a => Functions a -> a #

minimum :: Ord a => Functions a -> a #

sum :: Num a => Functions a -> a #

product :: Num a => Functions a -> a #

Traversable Functions Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

traverse :: Applicative f => (a -> f b) -> Functions a -> f (Functions b) #

sequenceA :: Applicative f => Functions (f a) -> f (Functions a) #

mapM :: Monad m => (a -> m b) -> Functions a -> m (Functions b) #

sequence :: Monad m => Functions (m a) -> m (Functions a) #

Semigroup (Functions a) Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

(<>) :: Functions a -> Functions a -> Functions a #

sconcat :: NonEmpty (Functions a) -> Functions a #

stimes :: Integral b => b -> Functions a -> Functions a #

Monoid (Functions a) Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Pretty op => Pretty (Functions op) Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

ppr :: Functions op -> Doc

pprPrec :: Int -> Functions op -> Doc

pprList :: [Functions op] -> Doc

FreeIn a => FreeIn (Functions a) Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

freeIn' :: Functions a -> FV Source #

type Function = FunctionT Source #

Type alias for namespace control.

data FunctionT a 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.

Instances

Instances details
Functor FunctionT Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

fmap :: (a -> b) -> FunctionT a -> FunctionT b #

(<$) :: a -> FunctionT b -> FunctionT a #

Foldable FunctionT Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

fold :: Monoid m => FunctionT m -> m #

foldMap :: Monoid m => (a -> m) -> FunctionT a -> 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] #

null :: FunctionT a -> Bool #

length :: FunctionT a -> Int #

elem :: Eq a => a -> FunctionT a -> Bool #

maximum :: Ord a => FunctionT a -> a #

minimum :: Ord a => FunctionT a -> a #

sum :: Num a => FunctionT a -> a #

product :: Num a => FunctionT a -> a #

Traversable FunctionT Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

traverse :: Applicative f => (a -> f b) -> FunctionT a -> f (FunctionT b) #

sequenceA :: Applicative f => FunctionT (f a) -> f (FunctionT a) #

mapM :: Monad m => (a -> m b) -> FunctionT a -> m (FunctionT b) #

sequence :: Monad m => FunctionT (m a) -> m (FunctionT a) #

Show a => Show (FunctionT a) Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Pretty op => Pretty (FunctionT op) Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

ppr :: FunctionT op -> Doc

pprPrec :: Int -> FunctionT op -> Doc

pprList :: [FunctionT op] -> Doc

data Constants a Source #

A collection of imperative constants.

Constructors

Constants 

Fields

  • constsDecl :: [Param]

    The constants that are made available to the functions.

  • constsInit :: Code a

    Setting the value of the constants. Note that this must not contain declarations of the names defined in constsDecl.

Instances

Instances details
Pretty op => Pretty (Constants op) Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

ppr :: Constants op -> Doc

pprPrec :: Int -> Constants op -> Doc

pprList :: [Constants op] -> Doc

data ValueDesc Source #

A description of an externally meaningful value.

Constructors

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

Instances

Instances details
Eq ValueDesc Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Show ValueDesc Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Pretty ValueDesc Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

data Signedness Source #

Constructors

TypeUnsigned 
TypeDirect 

Instances

Instances details
Eq Signedness Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Show Signedness Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

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.

Constructors

OpaqueValue String [ValueDesc]

The string is a human-readable description with no other semantics.

TransparentValue ValueDesc 

Instances

Instances details
Show ExternalValue Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Pretty ExternalValue Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

data Param Source #

Instances

Instances details
Show Param Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

showsPrec :: Int -> Param -> ShowS #

show :: Param -> String #

showList :: [Param] -> ShowS #

Pretty Param Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

ppr :: Param -> Doc

pprPrec :: Int -> Param -> Doc

pprList :: [Param] -> Doc

data SubExp Source #

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.

Constructors

Constant PrimValue 
Var VName 

Instances

Instances details
Eq SubExp Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

(==) :: SubExp -> SubExp -> Bool #

(/=) :: SubExp -> SubExp -> Bool #

Ord SubExp Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Show SubExp Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

ToExp SubExp 
Instance details

Defined in Futhark.CodeGen.Backends.GenericC

Methods

toExp :: SubExp -> SrcLoc -> Exp

Pretty SubExp 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: SubExp -> Doc

pprPrec :: Int -> SubExp -> Doc

pprList :: [SubExp] -> Doc

Pretty ExtShape 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: ExtShape -> Doc

pprPrec :: Int -> ExtShape -> Doc

pprList :: [ExtShape] -> Doc

Pretty Shape 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: Shape -> Doc

pprPrec :: Int -> Shape -> Doc

pprList :: [Shape] -> Doc

FixExt ExtSize Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

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

SetType Type Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

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

DeclExtTyped DeclExtType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

ExtTyped ExtType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

DeclTyped DeclType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Typed DeclType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

typeOf :: DeclType -> Type Source #

Typed Type Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

typeOf :: Type -> Type Source #

IsRetType DeclExtType Source # 
Instance details

Defined in Futhark.Representation.AST.RetType

IsRetType FunReturns Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

IsBodyType ExtType Source # 
Instance details

Defined in Futhark.Representation.AST.RetType

IsBodyType BodyReturns Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

FreeIn SubExp Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn' :: SubExp -> FV Source #

Substitute SubExp Source # 
Instance details

Defined in Futhark.Transform.Substitute

Rename SubExp Source # 
Instance details

Defined in Futhark.Transform.Rename

Rename ExtSize Source # 
Instance details

Defined in Futhark.Transform.Rename

RangeOf SubExp Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Ranges

Methods

rangeOf :: SubExp -> Range Source #

ToExp SubExp Source # 
Instance details

Defined in Futhark.Construct

Methods

toExp :: MonadBinder m => SubExp -> m (Exp (Lore m)) Source #

Simplifiable SubExp Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Engine

Simplifiable ExtSize Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Engine

ToExp SubExp Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

Methods

toExp :: SubExp -> ImpM lore r op Exp Source #

toExp' :: PrimType -> SubExp -> Exp Source #

Pretty (PatElemT Type) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Pretty (PatElemT (MemInfo SubExp NoUniqueness ret)) 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Pretty (Param DeclType) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Pretty (Param Type) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: Param Type -> Doc

pprPrec :: Int -> Param Type -> Doc

pprList :: [Param Type] -> Doc

Pretty (Param (MemInfo SubExp Uniqueness ret)) 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Pretty (Param (MemInfo SubExp NoUniqueness ret)) 
Instance details

Defined in Futhark.Representation.ExplicitMemory

ArrayShape (ShapeBase SubExp) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

ArrayShape (ShapeBase ExtSize) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

(Pretty u, Pretty r) => PrettyAnnot (PatElemT (MemInfo SubExp u r)) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

(Pretty u, Pretty r) => PrettyAnnot (Param (MemInfo SubExp u r)) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Simplifiable [FunReturns] Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Pretty u => Pretty (TypeBase ExtShape u) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Pretty u => Pretty (TypeBase Shape u) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: TypeBase Shape u -> Doc

pprPrec :: Int -> TypeBase Shape u -> Doc

pprList :: [TypeBase Shape u] -> Doc

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

Defined in Futhark.Representation.ExplicitMemory

Methods

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

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

Defined in Futhark.Representation.ExplicitMemory

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

Defined in Futhark.Representation.ExplicitMemory

DeclTyped (MemInfo SubExp Uniqueness ret) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Typed (MemInfo SubExp Uniqueness ret) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Typed (MemInfo SubExp NoUniqueness ret) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

data Type Source #

Constructors

Scalar PrimType 
Mem Space 

data Space Source #

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.

Constructors

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.

Instances

Instances details
Eq Space Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

(==) :: Space -> Space -> Bool #

(/=) :: Space -> Space -> Bool #

Ord Space Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

compare :: Space -> Space -> Ordering #

(<) :: Space -> Space -> Bool #

(<=) :: Space -> Space -> Bool #

(>) :: Space -> Space -> Bool #

(>=) :: Space -> Space -> Bool #

max :: Space -> Space -> Space #

min :: Space -> Space -> Space #

Show Space Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

showsPrec :: Int -> Space -> ShowS #

show :: Space -> String #

showList :: [Space] -> ShowS #

Pretty Space 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: Space -> Doc

pprPrec :: Int -> Space -> Doc

pprList :: [Space] -> Doc

FreeIn Space Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn' :: Space -> FV Source #

Simplifiable Space Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Engine

Methods

simplify :: SimplifiableLore lore => Space -> SimpleM lore Space Source #

type SpaceId = String Source #

A string representing a specific non-default memory space.

data Code a Source #

Constructors

Skip 
(Code a) :>>: (Code a) 
For VName IntType Exp (Code a) 
While Exp (Code a) 
DeclareMem VName Space 
DeclareScalar VName Volatility PrimType 
DeclareArray VName Space PrimType ArrayContents

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 Exp) Space

Memory space must match the corresponding DeclareMem.

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 Exp) Space VName (Count Bytes Exp) Space (Count Bytes Exp)

Destination, offset in destination, destination space, source, offset in source, offset space, number of bytes.

Write VName (Count Elements Exp) 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 (Maybe Exp)

Print the given value to the screen, somehow annotated with the given string as a description. If no type/value pair, just print the string. This has no semantic meaning, but is used entirely for debugging. Code generators are free to ignore this statement.

Op a 

Instances

Instances details
Functor Code Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

fmap :: (a -> b) -> Code a -> Code b #

(<$) :: a -> Code b -> Code a #

Foldable Code Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

fold :: Monoid m => Code m -> m #

foldMap :: Monoid m => (a -> m) -> Code a -> 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 #

toList :: Code a -> [a] #

null :: Code a -> Bool #

length :: Code a -> Int #

elem :: Eq a => a -> Code a -> Bool #

maximum :: Ord a => Code a -> a #

minimum :: Ord a => Code a -> a #

sum :: Num a => Code a -> a #

product :: Num a => Code a -> a #

Traversable Code Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

traverse :: Applicative f => (a -> f b) -> Code a -> f (Code b) #

sequenceA :: Applicative f => Code (f a) -> f (Code a) #

mapM :: Monad m => (a -> m b) -> Code a -> m (Code b) #

sequence :: Monad m => Code (m a) -> m (Code a) #

Show a => Show (Code a) Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

showsPrec :: Int -> Code a -> ShowS #

show :: Code a -> String #

showList :: [Code a] -> ShowS #

Semigroup (Code a) Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

(<>) :: Code a -> Code a -> Code a #

sconcat :: NonEmpty (Code a) -> Code a #

stimes :: Integral b => b -> Code a -> Code a #

Monoid (Code a) Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

mempty :: Code a #

mappend :: Code a -> Code a -> Code a #

mconcat :: [Code a] -> Code a #

Pretty op => Pretty (Code op) Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

ppr :: Code op -> Doc

pprPrec :: Int -> Code op -> Doc

pprList :: [Code op] -> Doc

FreeIn a => FreeIn (Code a) Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

freeIn' :: Code a -> FV Source #

MonadWriter (Code op) (ImpM lore r op) Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

Methods

writer :: (a, Code op) -> ImpM lore r op a #

tell :: Code op -> ImpM lore r op () #

listen :: ImpM lore r op a -> ImpM lore r op (a, Code op) #

pass :: ImpM lore r op (a, Code op -> Code op) -> ImpM lore r op a #

data PrimValue Source #

Non-array values.

Constructors

IntValue !IntValue 
FloatValue !FloatValue 
BoolValue !Bool 
Checked

The only value of type cert.

data ExpLeaf Source #

Instances

Instances details
Eq ExpLeaf Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

(==) :: ExpLeaf -> ExpLeaf -> Bool #

(/=) :: ExpLeaf -> ExpLeaf -> Bool #

Show ExpLeaf Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Pretty ExpLeaf Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

ppr :: ExpLeaf -> Doc

pprPrec :: Int -> ExpLeaf -> Doc

pprList :: [ExpLeaf] -> Doc

FreeIn ExpLeaf Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

freeIn' :: ExpLeaf -> FV Source #

data Volatility Source #

The volatility of a memory access or variable. Feel free to ignore this for backends where it makes no sense (anything but C and similar low-level things)

Constructors

Volatile 
Nonvolatile 

data Arg Source #

A function call argument.

Constructors

ExpArg Exp 
MemArg VName 

Instances

Instances details
Show Arg Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

showsPrec :: Int -> Arg -> ShowS #

show :: Arg -> String #

showList :: [Arg] -> ShowS #

Pretty Arg Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

ppr :: Arg -> Doc

pprPrec :: Int -> Arg -> Doc

pprList :: [Arg] -> Doc

FreeIn Arg Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

freeIn' :: Arg -> FV Source #

vi32 :: VName -> Exp Source #

Turn a VName into a int32 ScalarVar.

newtype ErrorMsg a Source #

An error message is a list of error parts, which are concatenated to form the final message.

Constructors

ErrorMsg [ErrorMsgPart a] 

Instances

Instances details
Functor ErrorMsg Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

fmap :: (a -> b) -> ErrorMsg a -> ErrorMsg b #

(<$) :: a -> ErrorMsg b -> ErrorMsg a #

Foldable ErrorMsg Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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 #

toList :: ErrorMsg a -> [a] #

null :: ErrorMsg a -> Bool #

length :: ErrorMsg a -> Int #

elem :: Eq a => a -> ErrorMsg a -> Bool #

maximum :: Ord a => ErrorMsg a -> a #

minimum :: Ord a => ErrorMsg a -> a #

sum :: Num a => ErrorMsg a -> a #

product :: Num a => ErrorMsg a -> a #

Traversable ErrorMsg Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

traverse :: Applicative f => (a -> f b) -> ErrorMsg a -> f (ErrorMsg b) #

sequenceA :: Applicative f => ErrorMsg (f a) -> f (ErrorMsg a) #

mapM :: Monad m => (a -> m b) -> ErrorMsg a -> m (ErrorMsg b) #

sequence :: Monad m => ErrorMsg (m a) -> m (ErrorMsg a) #

Eq a => Eq (ErrorMsg a) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

(==) :: ErrorMsg a -> ErrorMsg a -> Bool #

(/=) :: ErrorMsg a -> ErrorMsg a -> Bool #

Ord a => Ord (ErrorMsg a) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

compare :: ErrorMsg a -> ErrorMsg a -> Ordering #

(<) :: ErrorMsg a -> ErrorMsg a -> Bool #

(<=) :: ErrorMsg a -> ErrorMsg a -> Bool #

(>) :: ErrorMsg a -> ErrorMsg a -> Bool #

(>=) :: ErrorMsg a -> ErrorMsg a -> Bool #

max :: ErrorMsg a -> ErrorMsg a -> ErrorMsg a #

min :: ErrorMsg a -> ErrorMsg a -> ErrorMsg a #

Show a => Show (ErrorMsg a) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

showsPrec :: Int -> ErrorMsg a -> ShowS #

show :: ErrorMsg a -> String #

showList :: [ErrorMsg a] -> ShowS #

IsString (ErrorMsg a) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

fromString :: String -> ErrorMsg a #

Pretty a => Pretty (ErrorMsg a) 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: ErrorMsg a -> Doc

pprPrec :: Int -> ErrorMsg a -> Doc

pprList :: [ErrorMsg a] -> Doc

data ErrorMsgPart a Source #

A part of an error message.

Constructors

ErrorString String

A literal string.

ErrorInt32 a

A run-time integer value.

Instances

Instances details
Functor ErrorMsgPart Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

fmap :: (a -> b) -> ErrorMsgPart a -> ErrorMsgPart b #

(<$) :: a -> ErrorMsgPart b -> ErrorMsgPart a #

Foldable ErrorMsgPart Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

fold :: Monoid m => ErrorMsgPart m -> m #

foldMap :: Monoid m => (a -> m) -> ErrorMsgPart a -> m #

foldMap' :: Monoid m => (a -> m) -> ErrorMsgPart a -> m #

foldr :: (a -> b -> b) -> b -> ErrorMsgPart a -> b #

foldr' :: (a -> b -> b) -> b -> ErrorMsgPart a -> b #

foldl :: (b -> a -> b) -> b -> ErrorMsgPart a -> b #

foldl' :: (b -> a -> b) -> b -> ErrorMsgPart a -> b #

foldr1 :: (a -> a -> a) -> ErrorMsgPart a -> a #

foldl1 :: (a -> a -> a) -> ErrorMsgPart a -> a #

toList :: ErrorMsgPart a -> [a] #

null :: ErrorMsgPart a -> Bool #

length :: ErrorMsgPart a -> Int #

elem :: Eq a => a -> ErrorMsgPart a -> Bool #

maximum :: Ord a => ErrorMsgPart a -> a #

minimum :: Ord a => ErrorMsgPart a -> a #

sum :: Num a => ErrorMsgPart a -> a #

product :: Num a => ErrorMsgPart a -> a #

Traversable ErrorMsgPart Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

traverse :: Applicative f => (a -> f b) -> ErrorMsgPart a -> f (ErrorMsgPart b) #

sequenceA :: Applicative f => ErrorMsgPart (f a) -> f (ErrorMsgPart a) #

mapM :: Monad m => (a -> m b) -> ErrorMsgPart a -> m (ErrorMsgPart b) #

sequence :: Monad m => ErrorMsgPart (m a) -> m (ErrorMsgPart a) #

Eq a => Eq (ErrorMsgPart a) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Ord a => Ord (ErrorMsgPart a) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Show a => Show (ErrorMsgPart a) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

IsString (ErrorMsgPart a) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

errorMsgArgTypes :: ErrorMsg a -> [PrimType] Source #

How many non-constant parts does the error message have, and what is their type?

data ArrayContents Source #

The contents of a statically declared constant array. Such arrays are always unidimensional, and reshaped if necessary in the code that uses them.

Constructors

ArrayValues [PrimValue]

Precisely these values.

ArrayZeros Int

This many zeroes.

Instances

Instances details
Show ArrayContents Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Pretty ArrayContents Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Typed enumerations

data Bytes Source #

Phantom type for a count of bytes.

data Elements Source #

Phantom type for a count of elements.

withElemType :: Count Elements Exp -> PrimType -> Count Bytes Exp Source #

Convert a count of elements into a count of bytes, given the per-element size.

Re-exports from other modules.

newtype Count u e Source #

A wrapper supporting a phantom type for indicating what we are counting.

Constructors

Count 

Fields

Instances

Instances details
Functor (Count u) Source # 
Instance details

Defined in Futhark.Representation.Kernels.Sizes

Methods

fmap :: (a -> b) -> Count u a -> Count u b #

(<$) :: a -> Count u b -> Count u a #

Foldable (Count u) Source # 
Instance details

Defined in Futhark.Representation.Kernels.Sizes

Methods

fold :: Monoid m => Count u m -> m #

foldMap :: Monoid m => (a -> m) -> Count u a -> m #

foldMap' :: Monoid m => (a -> m) -> Count u a -> m #

foldr :: (a -> b -> b) -> b -> Count u a -> b #

foldr' :: (a -> b -> b) -> b -> Count u a -> b #

foldl :: (b -> a -> b) -> b -> Count u a -> b #

foldl' :: (b -> a -> b) -> b -> Count u a -> b #

foldr1 :: (a -> a -> a) -> Count u a -> a #

foldl1 :: (a -> a -> a) -> Count u a -> a #

toList :: Count u a -> [a] #

null :: Count u a -> Bool #

length :: Count u a -> Int #

elem :: Eq a => a -> Count u a -> Bool #

maximum :: Ord a => Count u a -> a #

minimum :: Ord a => Count u a -> a #

sum :: Num a => Count u a -> a #

product :: Num a => Count u a -> a #

Traversable (Count u) Source # 
Instance details

Defined in Futhark.Representation.Kernels.Sizes

Methods

traverse :: Applicative f => (a -> f b) -> Count u a -> f (Count u b) #

sequenceA :: Applicative f => Count u (f a) -> f (Count u a) #

mapM :: Monad m => (a -> m b) -> Count u a -> m (Count u b) #

sequence :: Monad m => Count u (m a) -> m (Count u a) #

Eq e => Eq (Count u e) Source # 
Instance details

Defined in Futhark.Representation.Kernels.Sizes

Methods

(==) :: Count u e -> Count u e -> Bool #

(/=) :: Count u e -> Count u e -> Bool #

Num e => Num (Count u e) Source # 
Instance details

Defined in Futhark.Representation.Kernels.Sizes

Methods

(+) :: Count u e -> Count u e -> Count u e #

(-) :: Count u e -> Count u e -> Count u e #

(*) :: Count u e -> Count u e -> Count u e #

negate :: Count u e -> Count u e #

abs :: Count u e -> Count u e #

signum :: Count u e -> Count u e #

fromInteger :: Integer -> Count u e #

Ord e => Ord (Count u e) Source # 
Instance details

Defined in Futhark.Representation.Kernels.Sizes

Methods

compare :: Count u e -> Count u e -> Ordering #

(<) :: Count u e -> Count u e -> Bool #

(<=) :: Count u e -> Count u e -> Bool #

(>) :: Count u e -> Count u e -> Bool #

(>=) :: Count u e -> Count u e -> Bool #

max :: Count u e -> Count u e -> Count u e #

min :: Count u e -> Count u e -> Count u e #

Show e => Show (Count u e) Source # 
Instance details

Defined in Futhark.Representation.Kernels.Sizes

Methods

showsPrec :: Int -> Count u e -> ShowS #

show :: Count u e -> String #

showList :: [Count u e] -> ShowS #

Pretty e => Pretty (Count u e) Source # 
Instance details

Defined in Futhark.Representation.Kernels.Sizes

Methods

ppr :: Count u e -> Doc

pprPrec :: Int -> Count u e -> Doc

pprList :: [Count u e] -> Doc

IntegralExp e => IntegralExp (Count u e) Source # 
Instance details

Defined in Futhark.Representation.Kernels.Sizes

Methods

quot :: Count u e -> Count u e -> Count u e Source #

rem :: Count u e -> Count u e -> Count u e Source #

div :: Count u e -> Count u e -> Count u e Source #

mod :: Count u e -> Count u e -> Count u e Source #

sgn :: Count u e -> Maybe Int Source #

fromInt8 :: Int8 -> Count u e Source #

fromInt16 :: Int16 -> Count u e Source #

fromInt32 :: Int32 -> Count u e Source #

fromInt64 :: Int64 -> Count u e Source #

FreeIn e => FreeIn (Count u e) Source # 
Instance details

Defined in Futhark.Representation.Kernels.Sizes

Methods

freeIn' :: Count u e -> FV Source #