Safe Haskell | None |
---|---|
Language | Haskell2010 |
A generic C# code generator which is polymorphic in the type of the operations. Concretely, we use this to handle both sequential and OpenCL C# code.
Synopsis
- compileProg :: MonadFreshNames m => Maybe String -> Constructor -> [CSStmt] -> [CSStmt] -> Operations op s -> s -> CompilerM op s () -> [CSStmt] -> [Space] -> [Option] -> Functions op -> m String
- data Constructor = Constructor [CSFunDefArg] [CSStmt]
- emptyConstructor :: Constructor
- assignScalarPointer :: CSExp -> CSExp -> CSStmt
- toIntPtr :: CSExp -> CSExp
- compileName :: VName -> String
- compileDim :: DimSize -> CSExp
- compileExp :: Exp -> CompilerM op s CSExp
- compileCode :: Code op -> CompilerM op s ()
- compilePrimValue :: PrimValue -> CSExp
- compilePrimType :: PrimType -> String
- compilePrimTypeExt :: PrimType -> Signedness -> String
- compilePrimTypeToAST :: PrimType -> CSType
- compilePrimTypeToASText :: PrimType -> Signedness -> CSType
- contextFinalInits :: CompilerM op s [CSStmt]
- debugReport :: CSStmt -> CompilerM op s ()
- data Operations op s = Operations {
- opsWriteScalar :: WriteScalar op s
- opsReadScalar :: ReadScalar op s
- opsAllocate :: Allocate op s
- opsCopy :: Copy op s
- opsStaticArray :: StaticArray op s
- opsCompiler :: OpCompiler op s
- opsEntryOutput :: EntryOutput op s
- opsEntryInput :: EntryInput op s
- opsSyncRun :: CSStmt
- defaultOperations :: Operations op s
- unpackDim :: CSExp -> DimSize -> Int32 -> CompilerM op s ()
- newtype CompilerM op s a = CompilerM (RWS (CompilerEnv op s) (CompilerAcc op s) (CompilerState s) a)
- type OpCompiler op s = op -> CompilerM op s ()
- type WriteScalar op s = VName -> CSExp -> PrimType -> SpaceId -> CSExp -> CompilerM op s ()
- type ReadScalar op s = VName -> CSExp -> PrimType -> SpaceId -> CompilerM op s CSExp
- type Allocate op s = VName -> CSExp -> SpaceId -> CompilerM op s ()
- type Copy op s = VName -> CSExp -> Space -> VName -> CSExp -> Space -> CSExp -> PrimType -> CompilerM op s ()
- type StaticArray op s = VName -> SpaceId -> PrimType -> [PrimValue] -> CompilerM op s ()
- type EntryOutput op s = VName -> SpaceId -> PrimType -> Signedness -> [DimSize] -> CompilerM op s CSExp
- type EntryInput op s = VName -> MemSize -> SpaceId -> PrimType -> Signedness -> [DimSize] -> CSExp -> CompilerM op s ()
- data CompilerEnv op s = CompilerEnv {
- envOperations :: Operations op s
- envFtable :: Map Name [Type]
- data CompilerState s = CompilerState {
- compNameSrc :: VNameSource
- compBeforeParse :: [CSStmt]
- compInit :: [CSStmt]
- compStaticMemDecls :: [CSStmt]
- compStaticMemAllocs :: [CSStmt]
- compDebugItems :: [CSStmt]
- compUserState :: s
- compMemberDecls :: [CSStmt]
- compAssignedVars :: [VName]
- compDeclaredMem :: [(VName, Space)]
- stm :: CSStmt -> CompilerM op s ()
- stms :: [CSStmt] -> CompilerM op s ()
- atInit :: CSStmt -> CompilerM op s ()
- staticMemDecl :: CSStmt -> CompilerM op s ()
- staticMemAlloc :: CSStmt -> CompilerM op s ()
- addMemberDecl :: CSStmt -> CompilerM op s ()
- beforeParse :: CSStmt -> CompilerM op s ()
- collect' :: CompilerM op s a -> CompilerM op s (a, [CSStmt])
- collect :: CompilerM op s () -> CompilerM op s [CSStmt]
- simpleCall :: String -> [CSExp] -> CSExp
- callMethod :: CSExp -> String -> [CSExp] -> CSExp
- simpleInitClass :: String -> [CSExp] -> CSExp
- parametrizedCall :: String -> String -> [CSExp] -> CSExp
- copyMemoryDefaultSpace :: VName -> CSExp -> VName -> CSExp -> CSExp -> CompilerM op s ()
- consoleErrorWrite :: String -> [CSExp] -> CSExp
- consoleErrorWriteLine :: String -> [CSExp] -> CSExp
- consoleWrite :: String -> [CSExp] -> CSExp
- consoleWriteLine :: String -> [CSExp] -> CSExp
- publicName :: String -> String
- sizeOf :: CSType -> CSExp
- privateFunDef :: String -> CSType -> [(CSType, String)] -> [CSStmt] -> CSStmt
- publicFunDef :: String -> CSType -> [(CSType, String)] -> [CSStmt] -> CSStmt
- getDefaultDecl :: Param -> CSStmt
Documentation
compileProg :: MonadFreshNames m => Maybe String -> Constructor -> [CSStmt] -> [CSStmt] -> Operations op s -> s -> CompilerM op s () -> [CSStmt] -> [Space] -> [Option] -> Functions op -> m String Source #
data Constructor Source #
The class generated by the code generator must have a constructor, although it can be vacuous.
emptyConstructor :: Constructor Source #
A constructor that takes no arguments and does nothing.
compileName :: VName -> String Source #
compileDim :: DimSize -> CSExp Source #
compileCode :: Code op -> CompilerM op s () Source #
compilePrimTypeExt :: PrimType -> Signedness -> String Source #
The ctypes type corresponding to a PrimType
, taking sign into account.
compilePrimTypeToASText :: PrimType -> Signedness -> CSType Source #
contextFinalInits :: CompilerM op s [CSStmt] Source #
debugReport :: CSStmt -> CompilerM op s () Source #
data Operations op s Source #
Operations | |
|
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.
newtype CompilerM op s a Source #
CompilerM (RWS (CompilerEnv op s) (CompilerAcc op s) (CompilerState s) a) |
Instances
type OpCompiler op s = op -> CompilerM op s () Source #
A substitute expression compiler, tried before the main compilation function.
type WriteScalar op s = VName -> CSExp -> PrimType -> SpaceId -> CSExp -> 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 = VName -> CSExp -> PrimType -> SpaceId -> CompilerM op s CSExp Source #
Read a scalar from the given memory block with the given index and in the given memory space.
type Allocate op s = VName -> CSExp -> SpaceId -> CompilerM op s () Source #
Allocate a memory block of the given size in the given memory space, saving a reference in the given variable name.
type Copy op s = VName -> CSExp -> Space -> VName -> CSExp -> Space -> CSExp -> PrimType -> 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.
type EntryOutput op s = VName -> SpaceId -> PrimType -> Signedness -> [DimSize] -> CompilerM op s CSExp Source #
Construct the C# array being returned from an entry point.
type EntryInput op s = VName -> MemSize -> SpaceId -> PrimType -> Signedness -> [DimSize] -> CSExp -> CompilerM op s () Source #
Unpack the array being passed to an entry point.
data CompilerEnv op s Source #
CompilerEnv | |
|
Instances
MonadReader (CompilerEnv op s) (CompilerM op s) Source # | |
Defined in Futhark.CodeGen.Backends.GenericCSharp 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 CompilerState s Source #
CompilerState | |
|
Instances
MonadState (CompilerState s) (CompilerM op s) Source # | |
Defined in Futhark.CodeGen.Backends.GenericCSharp get :: CompilerM op s (CompilerState s) # put :: CompilerState s -> CompilerM op s () # state :: (CompilerState s -> (a, CompilerState s)) -> CompilerM op s a # |
staticMemDecl :: CSStmt -> CompilerM op s () Source #
staticMemAlloc :: CSStmt -> CompilerM op s () Source #
addMemberDecl :: CSStmt -> CompilerM op s () Source #
beforeParse :: CSStmt -> CompilerM op s () Source #
publicName :: String -> String Source #
Public names must have a consistent prefix.
getDefaultDecl :: Param -> CSStmt Source #