Safe Haskell | None |
---|---|
Language | Haskell2010 |
C code generator. This module can convert a correct ImpCode program to an equivalent C program.
Synopsis
- compileProg :: MonadFreshNames m => Text -> Prog MCMem -> m (Warnings, CParts)
- generateContext :: CompilerM op s ()
- data CParts = CParts {}
- asLibrary :: CParts -> (Text, Text, Text)
- asExecutable :: CParts -> Text
- asServer :: CParts -> Text
- operations :: Operations Multicore s
- cliOptions :: [Option]
- compileOp :: OpCompiler Multicore s
- data ValueType
- paramToCType :: Param -> CompilerM op s (Type, ValueType)
- prepareTaskStruct :: DefSpecifier s -> String -> [VName] -> [(Type, ValueType)] -> [VName] -> [(Type, ValueType)] -> CompilerM Multicore s Name
- closureFreeStructField :: VName -> Name
- generateParLoopFn :: ToIdent a => Map VName Space -> String -> MCCode -> a -> [(VName, (Type, ValueType))] -> [(VName, (Type, ValueType))] -> CompilerM Multicore s Name
- addTimingFields :: Name -> CompilerM op s ()
- functionTiming :: Name -> Id
- functionIterations :: Name -> Id
- multiCoreReport :: [(Name, Bool)] -> [BlockItem]
- multicoreDef :: DefSpecifier s
- multicoreName :: String -> CompilerM op s Name
- type DefSpecifier s = String -> (Name -> CompilerM Multicore s Definition) -> CompilerM Multicore s Name
- atomicOps :: AtomicOp -> (Type -> VName -> CompilerM op s Type) -> CompilerM op s ()
Documentation
compileProg :: MonadFreshNames m => Text -> Prog MCMem -> m (Warnings, CParts) Source #
Compile the program to ImpCode with multicore operations.
generateContext :: CompilerM op s () Source #
Generate the multicore context definitions. This is exported because the WASM backend needs it.
The result of compilation to C is multiple 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.
asLibrary :: CParts -> (Text, Text, Text) Source #
Produce header, implementation, and manifest files.
asExecutable :: CParts -> Text Source #
As executable with command-line interface.
operations :: Operations Multicore s Source #
Operations for generating multicore code.
cliOptions :: [Option] Source #
Multicore-related command line options.
compileOp :: OpCompiler Multicore s Source #
prepareTaskStruct :: DefSpecifier s -> String -> [VName] -> [(Type, ValueType)] -> [VName] -> [(Type, ValueType)] -> CompilerM Multicore s Name Source #
closureFreeStructField :: VName -> Name Source #
generateParLoopFn :: ToIdent a => Map VName Space -> String -> MCCode -> a -> [(VName, (Type, ValueType))] -> [(VName, (Type, ValueType))] -> CompilerM Multicore s Name Source #
addTimingFields :: Name -> CompilerM op s () Source #
functionTiming :: Name -> Id Source #
functionIterations :: Name -> Id Source #
multicoreDef :: DefSpecifier s Source #