futhark-0.9.1: An optimising compiler for a functional, array-oriented language.

Safe HaskellNone
LanguageHaskell2010

Futhark.CodeGen.Backends.GenericC

Contents

Description

C code generator framework.

Synopsis

Documentation

compileProg :: MonadFreshNames m => Operations op () -> CompilerM op () () -> String -> [Space] -> [Option] -> Functions op -> m CParts Source #

Compile imperative program to a C program. Always uses the function named "main" as entry point, so make sure it is defined.

data CParts Source #

The result of compilation to C is four parts, which can be put together in various ways. The obvious way is to concatenate all of them, which yields a CLI program. Another is to compile the library part by itself, and use the header file to call into it.

Constructors

CParts 

Fields

asLibrary :: CParts -> (String, String) Source #

Produce header and implementation files.

asExecutable :: CParts -> String Source #

As executable with command-line interface.

Pluggable compiler

data Operations op s Source #

Constructors

Operations 

Fields

defaultOperations :: Operations op s Source #

A set of operations that fail for every operation involving non-default memory spaces. Uses plain pointers and malloc for memory management.

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

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

type PointerQuals op s = String -> CompilerM op s [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 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 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 -> SpaceId -> CompilerM op s () Source #

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

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

Copy from one memory block to another.

type StaticArray op s = VName -> SpaceId -> PrimType -> [PrimValue] -> CompilerM op s () Source #

Create a static array of values - initialised at load time.

Monadic compiler interface

data CompilerM op s a Source #

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

Defined in Futhark.CodeGen.Backends.GenericC

Methods

get :: CompilerM op s (CompilerState s) #

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

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

Monad (CompilerM op s) Source # 
Instance details

Defined in Futhark.CodeGen.Backends.GenericC

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 #

fail :: String -> CompilerM op s a #

Functor (CompilerM op s) Source # 
Instance details

Defined in Futhark.CodeGen.Backends.GenericC

Methods

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

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

Applicative (CompilerM op s) Source # 
Instance details

Defined in Futhark.CodeGen.Backends.GenericC

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 #

MonadFreshNames (CompilerM op s) Source # 
Instance details

Defined in Futhark.CodeGen.Backends.GenericC

data CompilerState s Source #

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

Defined in Futhark.CodeGen.Backends.GenericC

Methods

get :: CompilerM op s (CompilerState s) #

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

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

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

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

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

compileCode :: Code op -> CompilerM op s () Source #

compilePrimExp :: Monad m => (v -> m Exp) -> PrimExp v -> m Exp Source #

Tell me how to compile a v, and I'll Compile any PrimExp v for you.

rawMem :: ToExp a => a -> CompilerM op s Exp Source #

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

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

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

publicDef :: String -> HeaderSection -> (String -> (Definition, Definition)) -> CompilerM op s String 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_ :: String -> HeaderSection -> (String -> (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 :: String -> CompilerM op s String Source #

Public names must have a consitent prefix.

contextType :: CompilerM op s Type Source #

The generated code must define a struct with this name.

Building Blocks

primTypeToCType :: PrimType -> Type Source #

The C type corresponding to a primitive type. Integers are assumed to be unsigned.

Orphan instances

ToIdent VName Source # 
Instance details

Methods

toIdent :: VName -> SrcLoc -> Id #

ToIdent Name Source # 
Instance details

Methods

toIdent :: Name -> SrcLoc -> Id #

ToExp PrimValue Source # 
Instance details

Methods

toExp :: PrimValue -> SrcLoc -> Exp #

ToExp FloatValue Source # 
Instance details

Methods

toExp :: FloatValue -> SrcLoc -> Exp #

ToExp IntValue Source # 
Instance details

Methods

toExp :: IntValue -> SrcLoc -> Exp #

ToExp VName Source # 
Instance details

Methods

toExp :: VName -> SrcLoc -> Exp #