futhark-0.22.2: An optimising compiler for a functional, array-oriented language.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Futhark.CodeGen.ImpCode

Description

ImpCode is an imperative intermediate language used as a stepping stone in code generation. The functional core IR (Futhark.IR.Syntax) gets translated into ImpCode by Futhark.CodeGen.ImpGen. Later we then translate ImpCode to, for example, C.

Basic design

ImpCode distinguishes between statements (Code), which may have side effects, and expressions (Exp) which do not. Expressions involve only scalars and have a type. The actual expression definition is in Futhark.Analysis.PrimExp, specifically PrimExp and its phantom-typed variant TPrimExp.

Code is a generic representation parametrised on an extensible arbitrary operation, represented by the Op constructor. Specific instantiations of ImpCode, such as Futhark.CodeGen.ImpCode.Multicore, will pass in a specific kind of operation to express backend-specific functionality (in the case of multicore, this is Multicore).

Arrays and memory

ImpCode does not have arrays. DeclareArray is for declaring constant array literals, not arrays in general. Instead, ImpCode deals only with memory. Array operations present in core IR programs are turned into Write, Read, and Copy operations that use flat indexes and offsets based on the index function of the original array.

Scoping

ImpCode is much simpler than the functional core IR; partly because we hope to do less work on it. We don't have real optimisation passes on ImpCode. One result of this simplicity is that ImpCode has a fairly naive view of scoping. The only things that can bring new names into scope are DeclareMem, DeclareScalar, DeclareArray, For, and function parameters. In particular, Ops cannot bind parameters. The standard workaround is to define Ops that retrieve the value of an implicit parameter and assign it to a variable declared with the normal mechanisms. GetLoopBounds is an example of this pattern.

Inspiration

ImpCode was originally inspired by the paper "Defunctionalizing Push Arrays" (FHPC '14).

Synopsis

Documentation

data Definitions a Source #

A collection of imperative functions and constants.

Instances

Instances details
Functor Definitions Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

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

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

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

Defined in Futhark.CodeGen.ImpCode

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

Defined in Futhark.CodeGen.ImpCode

Methods

pretty :: Definitions op -> Doc ann #

prettyList :: [Definitions op] -> Doc ann #

newtype Functions a Source #

A collection of imperative functions.

Constructors

Functions [(Name, Function a)] 

Instances

Instances details
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) #

Functor Functions Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

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

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

Monoid (Functions a) Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

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 #

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

Defined in Futhark.CodeGen.ImpCode

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

Defined in Futhark.CodeGen.ImpCode

Methods

freeIn' :: Functions a -> FV Source #

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

Defined in Futhark.CodeGen.ImpCode

Methods

pretty :: Functions op -> Doc ann #

prettyList :: [Functions op] -> Doc ann #

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 present if the function is an entry point.

Instances

Instances details
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) #

Functor FunctionT Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

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

(<$) :: a -> FunctionT b -> 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

pretty :: FunctionT op -> Doc ann #

prettyList :: [FunctionT op] -> Doc ann #

data EntryPoint Source #

Information about how this function can be called from the outside world.

Instances

Instances details
Show EntryPoint Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

FreeIn EntryPoint Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Pretty EntryPoint Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

pretty :: EntryPoint -> Doc ann #

prettyList :: [EntryPoint] -> Doc ann #

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
Functor Constants Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

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

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

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

Defined in Futhark.CodeGen.ImpCode

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

Defined in Futhark.CodeGen.ImpCode

Methods

pretty :: Constants op -> Doc ann #

prettyList :: [Constants op] -> Doc ann #

data ValueDesc Source #

A description of an externally meaningful value.

Constructors

ArrayValue VName Space PrimType Signedness [DimSize]

An array with memory block 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
Show ValueDesc Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

FreeIn ValueDesc Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

freeIn' :: ValueDesc -> FV Source #

Eq ValueDesc Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Pretty ValueDesc Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

pretty :: ValueDesc -> Doc ann #

prettyList :: [ValueDesc] -> Doc ann #

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. We record the uniqueness because it is important to the external interface as well.

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

FreeIn ExternalValue Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Pretty ExternalValue Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

pretty :: ExternalValue -> Doc ann #

prettyList :: [ExternalValue] -> Doc ann #

data Param Source #

An ImpCode function parameter.

Instances

Instances details
Show Param Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

showsPrec :: Int -> Param -> ShowS #

show :: Param -> String #

showList :: [Param] -> ShowS #

Eq Param Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

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

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

Pretty Param Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

pretty :: Param -> Doc ann #

prettyList :: [Param] -> Doc ann #

paramName :: Param -> VName Source #

The name of a parameter.

type MemSize = SubExp Source #

The size of a memory block.

type DimSize = SubExp Source #

The size of an array.

data Code a Source #

A block of imperative code. Parameterised by an Op, which allows extensibility. Concrete uses of this type will instantiate the type parameter with e.g. a construct for launching GPU kernels.

Constructors

Skip

No-op. Crucial for the Monoid instance.

(:>>:) 

Fields

For VName Exp (Code a)

A for-loop iterating the given number of times. The loop parameter starts counting from zero and will have the same (integer) type as the bound. The bound is evaluated just once, before the loop is entered.

While (TExp Bool) (Code a)

While loop. The conditional is (of course) re-evaluated before every iteration of the loop.

DeclareMem VName Space

Declare a memory block variable that will point to memory in the given memory space. Note that this is distinct from allocation. The memory block must be the target of either an Allocate or a SetMem before it can be used for reading or writing.

DeclareScalar VName Volatility PrimType

Declare a scalar variable with an initially undefined value.

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 (TExp Int64)) 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 PrimType VName (Count Bytes (TExp Int64)) Space VName (Count Bytes (TExp Int64)) Space (Count Bytes (TExp Int64))

Element type being copied, destination, offset in destination, destination space, source, offset in source, offset space, number of bytes.

Write VName (Count Elements (TExp Int64)) PrimType Space Volatility Exp

Write mem i t space vol v writes the value v to mem offset by i elements of type t. The Space argument is the memory space of mem (technically redundant, but convenient).

SetScalar VName Exp

Set a scalar variable.

Read VName VName (Count Elements (TExp Int64)) PrimType Space Volatility

Read a scalar from memory from memory. The first VName is the target scalar variable, and the remaining arguments have the same meaning as with Write.

SetMem VName VName Space

Must be in same space.

Call [VName] Name [Arg]

Function call. The results are written to the provided VName variables.

If (TExp Bool) (Code a) (Code a)

Conditional execution.

Assert Exp (ErrorMsg Exp) (SrcLoc, [SrcLoc])

Assert that something must be true. Should it turn out not to be true, then report a failure along with the given error message.

Comment Text (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.

TracePrint (ErrorMsg Exp)

Log the given message, *without* a trailing linebreak (unless part of the mssage).

Op a

Perform an extensible operation.

Instances

Instances details
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) #

Functor Code Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

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

(<$) :: a -> Code b -> 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 #

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 #

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 #

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

Defined in Futhark.CodeGen.ImpCode

Methods

freeIn' :: Code a -> FV Source #

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

Defined in Futhark.CodeGen.ImpCode

Methods

pretty :: Code op -> Doc ann #

prettyList :: [Code op] -> Doc ann #

data PrimValue Source #

Non-array values.

Constructors

IntValue !IntValue 
FloatValue !FloatValue 
BoolValue !Bool 
UnitValue

The only value of type Unit.

Instances

Instances details
Show PrimValue Source # 
Instance details

Defined in Language.Futhark.Primitive

IsValue PrimValue Source # 
Instance details

Defined in Futhark.IR.Prop.Constants

Eq PrimValue Source # 
Instance details

Defined in Language.Futhark.Primitive

Ord PrimValue Source # 
Instance details

Defined in Language.Futhark.Primitive

ToExp PrimValue Source # 
Instance details

Defined in Futhark.CodeGen.Backends.SimpleRep

Methods

toExp :: PrimValue -> SrcLoc -> Exp #

Pretty PrimValue Source # 
Instance details

Defined in Language.Futhark.Primitive

Methods

pretty :: PrimValue -> Doc ann #

prettyList :: [PrimValue] -> Doc ann #

type Exp = PrimExp VName Source #

A side-effect free expression whose execution will produce a single primitive value.

type TExp t = TPrimExp t VName Source #

Like Exp, but with a required/known type.

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 #

FreeIn Arg Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

freeIn' :: Arg -> FV Source #

Pretty Arg Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

pretty :: Arg -> Doc ann #

prettyList :: [Arg] -> Doc ann #

var :: VName -> PrimType -> Exp Source #

Turn a VName into a Exp.

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

Methods

pretty :: ArrayContents -> Doc ann #

prettyList :: [ArrayContents] -> Doc ann #

declaredIn :: Code a -> Names Source #

The names declared with DeclareMem, DeclareScalar, and DeclareArray in the given code.

lexicalMemoryUsage :: Function a -> Map VName Space Source #

Find those memory blocks that are used only lexically. That is, are not used as the source or target of a SetMem, or are the result of the function, nor passed as arguments to other functions. This is interesting because such memory blocks do not need reference counting, but can be managed in a purely stack-like fashion.

We do not look inside any Ops. We assume that no Op is going to SetMem a memory block declared outside it.

calledFuncs :: Code a -> Set Name Source #

The set of functions that are called by this code. Assumes there are no function calls in Ops.

Typed enumerations

data Bytes Source #

Phantom type for a count of bytes.

data Elements Source #

Phantom type for a count of elements.

elements :: a -> Count Elements a Source #

This expression counts elements.

bytes :: a -> Count Bytes a Source #

This expression counts bytes.

withElemType :: Count Elements (TExp Int64) -> PrimType -> Count Bytes (TExp Int64) Source #

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

Re-exports from other modules.

prettyText :: Pretty a => a -> Text Source #

Prettyprint a value to a Text, appropriately wrapped.

prettyString :: Pretty a => a -> String Source #

Prettyprint a value to a String, appropriately wrapped.

newtype OpaqueTypes Source #

Names of opaque types and their representation.

Constructors

OpaqueTypes [(String, OpaqueType)] 

data OpaqueType Source #

The representation of an opaque type.

Constructors

OpaqueType [ValueType] 
OpaqueRecord [(Name, EntryPointType)]

Note that the field ordering here denote the actual representation - make sure it is preserved.

data EntryPointType Source #

Every entry point argument and return value has an annotation indicating how it maps to the original source program type.

Constructors

TypeOpaque String

An opaque type of this name.

TypeTransparent ValueType

A transparent type, which is scalar if the rank is zero.

data ValueType Source #

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.

Instances

Instances details
Show ValueType Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Eq ValueType Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Ord ValueType Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Pretty ValueType Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: ValueType -> Doc ann #

prettyList :: [ValueType] -> Doc ann #

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.

Constructors

Unsigned 
Signed 

data ErrorMsgPart a Source #

A part of an error message.

Constructors

ErrorString Text

A literal string.

ErrorVal PrimType a

A run-time value.

Instances

Instances details
Foldable ErrorMsgPart Source # 
Instance details

Defined in Futhark.IR.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.IR.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) #

Functor ErrorMsgPart Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

IsString (ErrorMsgPart a) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

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

Defined in Futhark.IR.Syntax.Core

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

Defined in Futhark.IR.Syntax.Core

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

Defined in Futhark.IR.Syntax.Core

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
Foldable ErrorMsg Source # 
Instance details

Defined in Futhark.IR.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.IR.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) #

Functor ErrorMsg Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

IsString (ErrorMsg a) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

fromString :: String -> ErrorMsg a #

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

Defined in Futhark.IR.Syntax.Core

Methods

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

show :: ErrorMsg a -> String #

showList :: [ErrorMsg a] -> ShowS #

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

Defined in Futhark.IR.Syntax.Core

Methods

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

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

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

Defined in Futhark.IR.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 #

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

Defined in Futhark.IR.Pretty

Methods

pretty :: ErrorMsg a -> Doc ann #

prettyList :: [ErrorMsg a] -> Doc ann #

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
Show SubExp Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

ToExp SubExp Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

Methods

toExp :: forall {k} (rep :: k) r op. SubExp -> ImpM rep r op Exp Source #

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

ToExp SubExp Source # 
Instance details

Defined in Futhark.Construct

Methods

toExp :: MonadBuilder m => SubExp -> m (Exp (Rep m)) Source #

HasLetDecMem LetDecMem Source # 
Instance details

Defined in Futhark.IR.Mem

FreeIn SubExp Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: SubExp -> FV Source #

DeclExtTyped DeclExtType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

DeclTyped DeclType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

ExtTyped ExtType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

FixExt ExtSize Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

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

SetType Type Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

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

Typed DeclType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

typeOf :: DeclType -> Type Source #

Typed Type Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

typeOf :: Type -> Type Source #

IsBodyType BodyReturns Source # 
Instance details

Defined in Futhark.IR.Mem

IsBodyType ExtType Source # 
Instance details

Defined in Futhark.IR.RetType

IsRetType FunReturns Source # 
Instance details

Defined in Futhark.IR.Mem

IsRetType DeclExtType Source # 
Instance details

Defined in Futhark.IR.RetType

Simplifiable ExtSize Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Engine

Methods

simplify :: forall {k} (rep :: k). SimplifiableRep rep => ExtSize -> SimpleM rep ExtSize Source #

Simplifiable SubExp Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Engine

Methods

simplify :: forall {k} (rep :: k). SimplifiableRep rep => SubExp -> SimpleM rep SubExp Source #

Rename ExtSize Source # 
Instance details

Defined in Futhark.Transform.Rename

Rename SubExp Source # 
Instance details

Defined in Futhark.Transform.Rename

Substitute SubExp Source # 
Instance details

Defined in Futhark.Transform.Substitute

Eq SubExp Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

Ord SubExp Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

ToExp SubExp Source # 
Instance details

Defined in Futhark.CodeGen.Backends.SimpleRep

Methods

toExp :: SubExp -> SrcLoc -> Exp #

Pretty ExtShape Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: ExtShape -> Doc ann #

prettyList :: [ExtShape] -> Doc ann #

Pretty Shape Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Shape -> Doc ann #

prettyList :: [Shape] -> Doc ann #

Pretty SubExp Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: SubExp -> Doc ann #

prettyList :: [SubExp] -> Doc ann #

ArrayShape (ShapeBase ExtSize) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

ArrayShape (ShapeBase SubExp) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Simplifiable [FunReturns] Source # 
Instance details

Defined in Futhark.IR.Mem

Methods

simplify :: forall {k} (rep :: k). SimplifiableRep rep => [FunReturns] -> SimpleM rep [FunReturns] Source #

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

Defined in Futhark.IR.Pretty

Methods

pretty :: TypeBase ExtShape u -> Doc ann #

prettyList :: [TypeBase ExtShape u] -> Doc ann #

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

Defined in Futhark.IR.Pretty

Methods

pretty :: TypeBase Shape u -> Doc ann #

prettyList :: [TypeBase Shape u] -> Doc ann #

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

Defined in Futhark.IR.Mem

DeclTyped (MemInfo SubExp Uniqueness ret) Source # 
Instance details

Defined in Futhark.IR.Mem

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

Defined in Futhark.IR.Mem

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

Defined in Futhark.IR.Mem

Methods

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

Typed (MemInfo SubExp NoUniqueness ret) Source # 
Instance details

Defined in Futhark.IR.Mem

Typed (MemInfo SubExp Uniqueness ret) Source # 
Instance details

Defined in Futhark.IR.Mem

type SpaceId = String Source #

A string representing a specific non-default memory 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
Show Space Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

showsPrec :: Int -> Space -> ShowS #

show :: Space -> String #

showList :: [Space] -> ShowS #

FreeIn Space Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Space -> FV Source #

Simplifiable Space Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Engine

Methods

simplify :: forall {k} (rep :: k). SimplifiableRep rep => Space -> SimpleM rep Space Source #

Eq Space Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

Ord Space Source # 
Instance details

Defined in Futhark.IR.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 #

Pretty Space Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Space -> Doc ann #

prettyList :: [Space] -> Doc ann #

newtype Rank Source #

The size of an array type as merely the number of dimensions, with no further information.

Constructors

Rank Int 

Instances

Instances details
Monoid Rank Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

mempty :: Rank #

mappend :: Rank -> Rank -> Rank #

mconcat :: [Rank] -> Rank #

Semigroup Rank Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

(<>) :: Rank -> Rank -> Rank #

sconcat :: NonEmpty Rank -> Rank #

stimes :: Integral b => b -> Rank -> Rank #

Show Rank Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

showsPrec :: Int -> Rank -> ShowS #

show :: Rank -> String #

showList :: [Rank] -> ShowS #

ArrayShape Rank Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Rename Rank Source # 
Instance details

Defined in Futhark.Transform.Rename

Substitute Rank Source # 
Instance details

Defined in Futhark.Transform.Substitute

Eq Rank Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

Ord Rank Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

compare :: Rank -> Rank -> Ordering #

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

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

(>) :: Rank -> Rank -> Bool #

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

max :: Rank -> Rank -> Rank #

min :: Rank -> Rank -> Rank #

Pretty Rank Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Rank -> Doc ann #

prettyList :: [Rank] -> Doc ann #

Pretty u => Pretty (TypeBase Rank u) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: TypeBase Rank u -> Doc ann #

prettyList :: [TypeBase Rank u] -> Doc ann #

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

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

newtype Count u e Source #

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

Constructors

Count 

Fields

Instances

Instances details
Foldable (Count u) Source # 
Instance details

Defined in Futhark.IR.GPU.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.IR.GPU.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) #

Functor (Count u) Source # 
Instance details

Defined in Futhark.IR.GPU.Sizes

Methods

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

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

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

Defined in Futhark.IR.GPU.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 #

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

Defined in Futhark.IR.GPU.Sizes

Methods

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

show :: Count u e -> String #

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

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

Defined in Futhark.IR.GPU.Sizes

Methods

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

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

Defined in Futhark.IR.GPU.Sizes

Methods

substituteNames :: Map VName VName -> Count u e -> Count u e Source #

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

Defined in Futhark.IR.GPU.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 #

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

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

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

Defined in Futhark.IR.GPU.Sizes

Methods

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

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

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

Defined in Futhark.IR.GPU.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 #

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

Defined in Futhark.IR.GPU.Sizes

Methods

pretty :: Count u e -> Doc ann #

prettyList :: [Count u e] -> Doc ann #