llvm-hs-6.3.0: General purpose LLVM bindings

Safe HaskellNone
LanguageHaskell2010

LLVM.Module

Description

A Module holds a C++ LLVM IR module. Modules may be converted to or from strings or Haskell ASTs, or added to an ExecutionEngine and so JIT compiled to get function pointers.

Synopsis

Documentation

newtype File Source #

A newtype to distinguish strings used for paths from other strings

Constructors

File FilePath 
Instances
Eq File Source # 
Instance details

Defined in LLVM.Internal.Module

Methods

(==) :: File -> File -> Bool #

(/=) :: File -> File -> Bool #

Ord File Source # 
Instance details

Defined in LLVM.Internal.Module

Methods

compare :: File -> File -> Ordering #

(<) :: File -> File -> Bool #

(<=) :: File -> File -> Bool #

(>) :: File -> File -> Bool #

(>=) :: File -> File -> Bool #

max :: File -> File -> File #

min :: File -> File -> File #

Read File Source # 
Instance details

Defined in LLVM.Internal.Module

Show File Source # 
Instance details

Defined in LLVM.Internal.Module

Methods

showsPrec :: Int -> File -> ShowS #

show :: File -> String #

showList :: [File] -> ShowS #

BitcodeInput File Source # 
Instance details

Defined in LLVM.Internal.Module

Methods

bitcodeMemoryBuffer :: (MonadThrow m, MonadIO m, MonadAnyCont IO m) => File -> m (Ptr MemoryBuffer) Source #

LLVMAssemblyInput File Source # 
Instance details

Defined in LLVM.Internal.Module

withModuleFromAST :: Context -> Module -> (Module -> IO a) -> IO a Source #

Execute a function after encoding the module in LLVM’s internal representation. May throw EncodeException.

moduleAST :: Module -> IO Module Source #

Get an LLVM.AST.Module from a LLVM.Module - i.e. raise C++ objects into an Haskell AST.

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

writeBitcodeToFile :: File -> Module -> IO () Source #

write LLVM bitcode from a Module into a file

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

linkModules Source #

Arguments

:: 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.