Safe Haskell | None |
---|---|
Language | Haskell2010 |
A Module
holds a C++ LLVM IR module. Module
s may be converted to or from strings or Haskell ASTs, or
added to an ExecutionEngine
and so JIT compiled to get function pointers.
Synopsis
- data Module
- newtype File = File FilePath
- withModuleFromAST :: Context -> Module -> (Module -> IO a) -> IO a
- moduleAST :: Module -> IO Module
- withModuleFromLLVMAssembly :: LLVMAssemblyInput s => Context -> s -> (Module -> IO a) -> IO a
- moduleLLVMAssembly :: Module -> IO ByteString
- writeLLVMAssemblyToFile :: File -> Module -> IO ()
- withModuleFromBitcode :: BitcodeInput b => Context -> b -> (Module -> IO a) -> IO a
- moduleBitcode :: Module -> IO ByteString
- writeBitcodeToFile :: File -> Module -> IO ()
- moduleTargetAssembly :: TargetMachine -> Module -> IO ByteString
- writeTargetAssemblyToFile :: TargetMachine -> File -> Module -> IO ()
- moduleObject :: TargetMachine -> Module -> IO ByteString
- writeObjectToFile :: TargetMachine -> File -> Module -> IO ()
- linkModules :: Module -> Module -> IO ()
Documentation
A newtype to distinguish strings used for paths from other strings
Instances
Eq File Source # | |
Ord File Source # | |
Read File Source # | |
Show File Source # | |
BitcodeInput File Source # | |
Defined in LLVM.Internal.Module bitcodeMemoryBuffer :: (MonadThrow m, MonadIO m, MonadAnyCont IO m) => File -> m (Ptr MemoryBuffer) Source # | |
LLVMAssemblyInput File Source # | |
Defined in LLVM.Internal.Module llvmAssemblyMemoryBuffer :: (MonadThrow m, MonadIO m, MonadAnyCont IO m) => File -> m (OwnerTransfered (Ptr MemoryBuffer)) Source # |
withModuleFromAST :: Context -> Module -> (Module -> IO a) -> IO a Source #
Execute a function after encoding the module in LLVM’s internal representation.
May throw EncodeException
.
withModuleFromLLVMAssembly :: LLVMAssemblyInput s => Context -> s -> (Module -> IO a) -> IO a Source #
parse Module
from LLVM assembly. May throw ParseFailureException
.
moduleLLVMAssembly :: Module -> IO ByteString Source #
generate LLVM assembly from a Module
writeLLVMAssemblyToFile :: File -> Module -> IO () Source #
write LLVM assembly for a Module
to a file
withModuleFromBitcode :: BitcodeInput b => Context -> b -> (Module -> IO a) -> IO a Source #
parse Module
from LLVM bitcode. May throw ParseFailureException
.
moduleBitcode :: Module -> IO ByteString Source #
generate LLVM bitcode from a Module
moduleTargetAssembly :: TargetMachine -> Module -> IO ByteString Source #
produce target-specific assembly as a ByteString
writeTargetAssemblyToFile :: TargetMachine -> File -> Module -> IO () Source #
write target-specific assembly directly into a file
moduleObject :: TargetMachine -> Module -> IO ByteString Source #
produce target-specific object code as a ByteString
writeObjectToFile :: TargetMachine -> File -> Module -> IO () Source #
write target-specific object code directly into a file
:: Module | The module into which to link |
-> Module | The module to link into the other (this module is destroyed) |
-> IO () |
link LLVM modules - move or copy parts of a source module into a
destination module. Note that this operation is not commutative -
not only concretely (e.g. the destination module is modified,
becoming the result) but abstractly (e.g. unused private globals in
the source module do not appear in the result, but similar globals
in the destination remain). The source module is destroyed. May
throw a LinkException
.