Safe Haskell | None |
---|---|
Language | Haskell2010 |
This Haskell module is for/of functions for handling LLVM modules.
Synopsis
- newtype Module = Module (IORef (Ptr Module))
- newModule :: Ptr Module -> IO Module
- readModule :: MonadIO m => Module -> m (Ptr Module)
- deleteModule :: Module -> IO ()
- newtype File = File FilePath
- linkModules :: Module -> Module -> IO ()
- class LLVMAssemblyInput s where
- withModuleFromLLVMAssembly :: LLVMAssemblyInput s => Context -> s -> (Module -> IO a) -> IO a
- moduleLLVMAssembly :: Module -> IO ByteString
- writeLLVMAssemblyToFile :: File -> Module -> IO ()
- class BitcodeInput b where
- withModuleFromBitcode :: BitcodeInput b => Context -> b -> (Module -> IO a) -> IO a
- moduleBitcode :: Module -> IO ByteString
- writeBitcodeToFile :: File -> Module -> IO ()
- targetMachineEmit :: CodeGenFileType -> TargetMachine -> Module -> Ptr RawPWriteStream -> IO ()
- emitToFile :: CodeGenFileType -> TargetMachine -> File -> Module -> IO ()
- emitToByteString :: CodeGenFileType -> TargetMachine -> Module -> IO ByteString
- writeTargetAssemblyToFile :: TargetMachine -> File -> Module -> IO ()
- moduleTargetAssembly :: TargetMachine -> Module -> IO ByteString
- moduleObject :: TargetMachine -> Module -> IO ByteString
- writeObjectToFile :: TargetMachine -> File -> Module -> IO ()
- setTargetTriple :: Ptr Module -> ShortByteString -> EncodeAST ()
- getTargetTriple :: Ptr Module -> IO (Maybe ShortByteString)
- setDataLayout :: Ptr Module -> DataLayout -> EncodeAST ()
- getDataLayout :: Ptr Module -> IO (Maybe DataLayout)
- withModuleFromAST :: Context -> Module -> (Module -> IO a) -> IO a
- decodeGlobalVariables :: Ptr Module -> DecodeAST (DecodeAST [Global])
- decodeGlobalAliases :: Ptr Module -> DecodeAST (DecodeAST [Global])
- getMetadata :: Ptr GlobalObject -> DecodeAST [(ShortByteString, MDRef MDNode)]
- setMetadata :: Ptr GlobalObject -> [(ShortByteString, MDRef MDNode)] -> EncodeAST ()
- decodeFunctions :: Ptr Module -> DecodeAST (DecodeAST [Global])
- decodeNamedMetadataDefinitions :: Ptr Module -> DecodeAST [Definition]
- moduleAST :: Module -> IO Module
Documentation
deleteModule :: Module -> IO () Source #
Signal that a module does no longer exist and thus must not be disposed. It is the responsibility of the caller to ensure that the module has been disposed. If you use only the functions provided by llvm-hs you should never call this yourself.
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 # |
:: 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
.
class LLVMAssemblyInput s where Source #
llvmAssemblyMemoryBuffer :: (MonadThrow m, MonadIO m, MonadAnyCont IO m) => s -> m (OwnerTransfered (Ptr MemoryBuffer)) Source #
Instances
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
class BitcodeInput b where Source #
bitcodeMemoryBuffer :: (MonadThrow m, MonadIO m, MonadAnyCont IO m) => b -> m (Ptr MemoryBuffer) Source #
Instances
BitcodeInput File Source # | |
Defined in LLVM.Internal.Module bitcodeMemoryBuffer :: (MonadThrow m, MonadIO m, MonadAnyCont IO m) => File -> m (Ptr MemoryBuffer) Source # | |
BitcodeInput (String, ByteString) Source # | |
Defined in LLVM.Internal.Module bitcodeMemoryBuffer :: (MonadThrow m, MonadIO m, MonadAnyCont IO m) => (String, ByteString) -> m (Ptr MemoryBuffer) Source # |
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
targetMachineEmit :: CodeGenFileType -> TargetMachine -> Module -> Ptr RawPWriteStream -> IO () Source #
May throw TargetMachineEmitException
.
emitToFile :: CodeGenFileType -> TargetMachine -> File -> Module -> IO () Source #
May throw FdStreamException
and TargetMachineEmitException
.
emitToByteString :: CodeGenFileType -> TargetMachine -> Module -> IO ByteString Source #
May throw TargetMachineEmitException
.
writeTargetAssemblyToFile :: TargetMachine -> File -> Module -> IO () Source #
write target-specific assembly directly into a file
moduleTargetAssembly :: TargetMachine -> Module -> IO ByteString Source #
produce target-specific assembly as a ByteString
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
setTargetTriple :: Ptr Module -> ShortByteString -> EncodeAST () Source #
getTargetTriple :: Ptr Module -> IO (Maybe ShortByteString) Source #
setDataLayout :: Ptr Module -> DataLayout -> EncodeAST () Source #
getDataLayout :: Ptr Module -> IO (Maybe DataLayout) 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
.
getMetadata :: Ptr GlobalObject -> DecodeAST [(ShortByteString, MDRef MDNode)] Source #
setMetadata :: Ptr GlobalObject -> [(ShortByteString, MDRef MDNode)] -> EncodeAST () Source #