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

Futhark.CodeGen.Backends.GenericC.Monad

Description

C code generator framework.

Synopsis

Pluggable compiler

data Operations op s Source #

Constructors

Operations 

Fields

type OpCompiler op s = op -> CompilerM op s () Source #

A substitute expression compiler, tried before the main compilation function.

type ErrorCompiler op s = ErrorMsg Exp -> String -> CompilerM op s () Source #

type CallCompiler op s = [VName] -> Name -> [Exp] -> CompilerM op s () Source #

Call a function.

type PointerQuals = String -> [TypeQual] Source #

The address space qualifiers for a pointer of the given type with the given annotation.

type MemoryType op s = SpaceId -> CompilerM op s Type Source #

The type of a memory block in the given memory space.

type WriteScalar op s = Exp -> Exp -> Type -> SpaceId -> Volatility -> Exp -> CompilerM op s () Source #

Write a scalar to the given memory block with the given element index and in the given memory space.

type ReadScalar op s = Exp -> Exp -> Type -> SpaceId -> Volatility -> CompilerM op s Exp Source #

Read a scalar from the given memory block with the given element index and in the given memory space.

type Allocate op s = Exp -> Exp -> Exp -> SpaceId -> CompilerM op s () Source #

Allocate a memory block of the given size and with the given tag in the given memory space, saving a reference in the given variable name.

type Deallocate op s = Exp -> Exp -> Exp -> SpaceId -> CompilerM op s () Source #

De-allocate the given memory block, with the given tag, with the given size,, which is in the given memory space.

data CopyBarrier Source #

Whether a copying operation should implicitly function as a barrier regarding further operations on the source. This is a rather subtle detail and is mostly useful for letting some device/GPU copies be asynchronous (#1664).

Constructors

CopyBarrier 
CopyNoBarrier

Explicit context synchronisation should be done before the source or target is used.

type Copy op s = CopyBarrier -> Exp -> Exp -> Space -> Exp -> Exp -> Space -> Exp -> CompilerM op s () Source #

Copy from one memory block to another.

Monadic compiler interface

data CompilerM op s a Source #

Instances

Instances details
MonadState (CompilerState s) (CompilerM op s) Source # 
Instance details

Defined in Futhark.CodeGen.Backends.GenericC.Monad

Methods

get :: CompilerM op s (CompilerState s) #

put :: CompilerState s -> CompilerM op s () #

state :: (CompilerState s -> (a, CompilerState s)) -> CompilerM op s a #

Applicative (CompilerM op s) Source # 
Instance details

Defined in Futhark.CodeGen.Backends.GenericC.Monad

Methods

pure :: a -> CompilerM op s a #

(<*>) :: CompilerM op s (a -> b) -> CompilerM op s a -> CompilerM op s b #

liftA2 :: (a -> b -> c) -> CompilerM op s a -> CompilerM op s b -> CompilerM op s c #

(*>) :: CompilerM op s a -> CompilerM op s b -> CompilerM op s b #

(<*) :: CompilerM op s a -> CompilerM op s b -> CompilerM op s a #

Functor (CompilerM op s) Source # 
Instance details

Defined in Futhark.CodeGen.Backends.GenericC.Monad

Methods

fmap :: (a -> b) -> CompilerM op s a -> CompilerM op s b #

(<$) :: a -> CompilerM op s b -> CompilerM op s a #

Monad (CompilerM op s) Source # 
Instance details

Defined in Futhark.CodeGen.Backends.GenericC.Monad

Methods

(>>=) :: CompilerM op s a -> (a -> CompilerM op s b) -> CompilerM op s b #

(>>) :: CompilerM op s a -> CompilerM op s b -> CompilerM op s b #

return :: a -> CompilerM op s a #

MonadFreshNames (CompilerM op s) Source # 
Instance details

Defined in Futhark.CodeGen.Backends.GenericC.Monad

MonadReader (CompilerEnv op s) (CompilerM op s) Source # 
Instance details

Defined in Futhark.CodeGen.Backends.GenericC.Monad

Methods

ask :: CompilerM op s (CompilerEnv op s) #

local :: (CompilerEnv op s -> CompilerEnv op s) -> CompilerM op s a -> CompilerM op s a #

reader :: (CompilerEnv op s -> a) -> CompilerM op s a #

data CompilerEnv op s Source #

Constructors

CompilerEnv 

Fields

  • envOperations :: Operations op s
     
  • envCachedMem :: Map Exp VName

    Mapping memory blocks to sizes. These memory blocks are CPU memory that we know are used in particularly simple ways (no reference counting necessary). To cut down on allocator pressure, we keep these allocations around for a long time, and record their sizes so we can reuse them if possible (and realloc() when needed).

Instances

Instances details
MonadReader (CompilerEnv op s) (CompilerM op s) Source # 
Instance details

Defined in Futhark.CodeGen.Backends.GenericC.Monad

Methods

ask :: CompilerM op s (CompilerEnv op s) #

local :: (CompilerEnv op s -> CompilerEnv op s) -> CompilerM op s a -> CompilerM op s a #

reader :: (CompilerEnv op s -> a) -> CompilerM op s a #

modifyUserState :: (s -> s) -> CompilerM op s () Source #

runCompilerM :: Operations op s -> VNameSource -> s -> CompilerM op s a -> (a, CompilerState s) Source #

inNewFunction :: CompilerM op s a -> CompilerM op s a Source #

Used when we, inside an existing CompilerM action, want to generate code for a new function. Use this so that the compiler understands that previously declared memory doesn't need to be freed inside this action.

cachingMemory :: Map VName Space -> ([BlockItem] -> [Stm] -> CompilerM op s a) -> CompilerM op s a Source #

items :: [BlockItem] -> CompilerM op s () Source #

stm :: Stm -> CompilerM op s () Source #

stms :: [Stm] -> CompilerM op s () Source #

publicDef :: Text -> HeaderSection -> (Text -> (Definition, Definition)) -> CompilerM op s Text Source #

Construct a publicly visible definition using the specified name as the template. The first returned definition is put in the header file, and the second is the implementation. Returns the public name.

publicDef_ :: Text -> HeaderSection -> (Text -> (Definition, Definition)) -> CompilerM op s () Source #

As publicDef, but ignores the public name.

data HeaderSection Source #

In which part of the header file we put the declaration. This is to ensure that the header file remains structured and readable.

publicName :: Text -> CompilerM op s Text Source #

Public names must have a consitent prefix.

contextFieldDyn :: Id -> Type -> Stm -> Stm -> CompilerM op s () Source #

cacheMem :: ToExp a => a -> CompilerM op s (Maybe VName) Source #

freeRawMem :: (ToExp a, ToExp b, ToExp c) => a -> b -> Space -> c -> CompilerM op s () Source #

allocRawMem :: (ToExp a, ToExp b, ToExp c) => a -> b -> Space -> c -> CompilerM op s () Source #

collect' :: CompilerM op s a -> CompilerM op s (a, [BlockItem]) Source #

contextType :: CompilerM op s Type Source #

The generated code must define a context struct with this name.

configType :: CompilerM op s Type Source #

The generated code must define a configuration struct with this name.

Building Blocks

setMem :: (ToExp a, ToExp b) => a -> b -> Space -> CompilerM op s () Source #

allocMem :: (ToExp a, ToExp b) => a -> b -> Space -> Stm -> CompilerM op s () Source #

unRefMem :: ToExp a => a -> Space -> CompilerM op s () Source #

declMem :: VName -> Space -> CompilerM op s () Source #

resetMem :: ToExp a => a -> Space -> CompilerM op s () Source #