llvm-0.6.7.0: Bindings to the LLVM compiler toolkit.Source codeContentsIndex
LLVM.Core
Contents
Modules
Instructions
Terminator instructions
Arithmetic binary operations
Logical binary operations
Vector operations
Memory access
Conversions
Comparison
Other
Classes and types
Types classification
Type classifier
Special type classifiers
Others
Structs
Type tests
Extra types
Values and constants
Code generation
Functions
Global variable creation
Globals
Basic blocks
Misc
Debugging
Transformations
Description

The LLVM (Low Level Virtual Machine) is virtual machine at a machine code level. It supports both stand alone code generation and JITing. The Haskell llvm package is a (relatively) high level interface to the LLVM. The high level interface makes it easy to construct LLVM code. There is also an interface to the raw low level LLVM API as exposed by the LLVM C interface.

LLVM code is organized into modules (type Module). Each module contains a number of global variables and functions (type Function). Each functions has a number of basic blocks (type BasicBlock). Each basic block has a number instructions, where each instruction produces a value (type Value).

Unlike assembly code for a real processor the assembly code for LLVM is in SSA (Static Single Assignment) form. This means that each instruction generates a new bound variable which may not be assigned again. A consequence of this is that where control flow joins from several execution paths there has to be a phi pseudo instruction if you want different variables to be joined into one.

The definition of several of the LLVM entities (Module, Function, and BasicBlock) follow the same pattern. First the entity has to be created using newX (where X is one of Module, Function, or BasicBlock), then at some later point it has to given its definition using defineX. The reason for splitting the creation and definition is that you often need to be able to refer to an entity before giving it's body, e.g., in two mutually recursive functions. The the newX and defineX function can also be done at the same time by using createX. Furthermore, an explicit name can be given to an entity by the newNamedX function; the newX function just generates a fresh name.

Synopsis
data Module
newModule :: IO Module
newNamedModule :: String -> IO Module
defineModule :: Module -> CodeGenModule a -> IO a
destroyModule :: Module -> IO ()
createModule :: CodeGenModule a -> IO a
data ModuleProvider
createModuleProviderForExistingModule :: Module -> IO ModuleProvider
data PassManager
createPassManager :: IO PassManager
createFunctionPassManager :: ModuleProvider -> IO PassManager
writeBitcodeToFile :: String -> Module -> IO ()
readBitcodeFromFile :: String -> IO Module
getModuleValues :: Module -> IO [(String, ModuleValue)]
data ModuleValue
castModuleValue :: forall a. IsType a => ModuleValue -> Maybe (Value a)
ret :: Ret a r => a -> CodeGenFunction r Terminate
condBr :: Value Bool -> BasicBlock -> BasicBlock -> CodeGenFunction r Terminate
br :: BasicBlock -> CodeGenFunction r Terminate
switch :: IsInteger a => Value a -> BasicBlock -> [(ConstValue a, BasicBlock)] -> CodeGenFunction r Terminate
invoke :: CallArgs f g => BasicBlock -> BasicBlock -> Function f -> g
unwind :: CodeGenFunction r Terminate
unreachable :: CodeGenFunction r Terminate
add :: (IsArithmetic c, ABinOp a b (v c)) => a -> b -> CodeGenFunction r (v c)
sub :: (IsArithmetic c, ABinOp a b (v c)) => a -> b -> CodeGenFunction r (v c)
mul :: (IsArithmetic c, ABinOp a b (v c)) => a -> b -> CodeGenFunction r (v c)
neg :: IsArithmetic a => Value a -> CodeGenFunction r (Value a)
udiv :: (IsInteger c, ABinOp a b (v c)) => a -> b -> CodeGenFunction r (v c)
sdiv :: (IsInteger c, ABinOp a b (v c)) => a -> b -> CodeGenFunction r (v c)
fdiv :: (IsFloating c, ABinOp a b (v c)) => a -> b -> CodeGenFunction r (v c)
urem :: (IsInteger c, ABinOp a b (v c)) => a -> b -> CodeGenFunction r (v c)
srem :: (IsInteger c, ABinOp a b (v c)) => a -> b -> CodeGenFunction r (v c)
frem :: (IsFloating c, ABinOp a b (v c)) => a -> b -> CodeGenFunction r (v c)
shl :: (IsInteger c, ABinOp a b (v c)) => a -> b -> CodeGenFunction r (v c)
lshr :: (IsInteger c, ABinOp a b (v c)) => a -> b -> CodeGenFunction r (v c)
ashr :: (IsInteger c, ABinOp a b (v c)) => a -> b -> CodeGenFunction r (v c)
and :: (IsInteger c, ABinOp a b (v c)) => a -> b -> CodeGenFunction r (v c)
or :: (IsInteger c, ABinOp a b (v c)) => a -> b -> CodeGenFunction r (v c)
xor :: (IsInteger c, ABinOp a b (v c)) => a -> b -> CodeGenFunction r (v c)
inv :: IsInteger a => Value a -> CodeGenFunction r (Value a)
extractelement :: Value (Vector n a) -> Value Word32 -> CodeGenFunction r (Value a)
insertelement :: Value (Vector n a) -> Value a -> Value Word32 -> CodeGenFunction r (Value (Vector n a))
shufflevector :: Value (Vector n a) -> Value (Vector n a) -> ConstValue (Vector n Word32) -> CodeGenFunction r (Value (Vector n a))
malloc :: forall a r s. IsSized a s => CodeGenFunction r (Value (Ptr a))
arrayMalloc :: forall a n r s. (IsSized a n, AllocArg s) => s -> CodeGenFunction r (Value (Ptr a))
alloca :: forall a r s. IsSized a s => CodeGenFunction r (Value (Ptr a))
arrayAlloca :: forall a n r s. (IsSized a n, AllocArg s) => s -> CodeGenFunction r (Value (Ptr a))
free :: Value (Ptr a) -> CodeGenFunction r (Value ())
load :: Value (Ptr a) -> CodeGenFunction r (Value a)
store :: Value a -> Value (Ptr a) -> CodeGenFunction r (Value ())
getElementPtr :: forall a o i n r. (GetElementPtr o i n, IsIndexArg a) => Value (Ptr o) -> (a, i) -> CodeGenFunction r (Value (Ptr n))
getElementPtr0 :: GetElementPtr o i n => Value (Ptr o) -> i -> CodeGenFunction r (Value (Ptr n))
trunc :: (IsInteger a, IsInteger b, IsPrimitive a, IsPrimitive b, IsSized a sa, IsSized b sb, sa :>: sb) => Value a -> CodeGenFunction r (Value b)
zext :: (IsInteger a, IsInteger b, IsPrimitive a, IsPrimitive b, IsSized a sa, IsSized b sb, sa :<: sb) => Value a -> CodeGenFunction r (Value b)
sext :: (IsInteger a, IsInteger b, IsPrimitive a, IsPrimitive b, IsSized a sa, IsSized b sb, sa :<: sb) => Value a -> CodeGenFunction r (Value b)
fptrunc :: (IsFloating a, IsFloating b, IsPrimitive a, IsPrimitive b, IsSized a sa, IsSized b sb, sa :>: sb) => Value a -> CodeGenFunction r (Value b)
fpext :: (IsFloating a, IsFloating b, IsPrimitive a, IsPrimitive b, IsSized a sa, IsSized b sb, sa :<: sb) => Value a -> CodeGenFunction r (Value b)
fptoui :: (IsFloating a, IsInteger b, IsPrimitive a, IsPrimitive b) => Value a -> CodeGenFunction r (Value b)
fptosi :: (IsFloating a, IsInteger b, IsPrimitive a, IsPrimitive b) => Value a -> CodeGenFunction r (Value b)
uitofp :: (IsInteger a, IsFloating b, IsPrimitive a, IsPrimitive b) => Value a -> CodeGenFunction r (Value b)
sitofp :: (IsInteger a, IsFloating b, IsPrimitive a, IsPrimitive b) => Value a -> CodeGenFunction r (Value b)
ptrtoint :: (IsInteger b, IsPrimitive b) => Value (Ptr a) -> CodeGenFunction r (Value b)
inttoptr :: (IsInteger a, IsType b) => Value a -> CodeGenFunction r (Value (Ptr b))
bitcast :: (IsFirstClass a, IsFirstClass b, IsSized a sa, IsSized b sb, sa :==: sb) => Value a -> CodeGenFunction r (Value b)
data IntPredicate
= IntEQ
| IntNE
| IntUGT
| IntUGE
| IntULT
| IntULE
| IntSGT
| IntSGE
| IntSLT
| IntSLE
data FPPredicate
= FPFalse
| FPOEQ
| FPOGT
| FPOGE
| FPOLT
| FPOLE
| FPONE
| FPORD
| FPUNO
| FPUEQ
| FPUGT
| FPUGE
| FPULT
| FPULE
| FPUNE
| FPT
class CmpRet a b | a -> b
icmp :: (IsIntegerOrPointer c, CmpOp a b c d, CmpRet c d) => IntPredicate -> a -> b -> CodeGenFunction r (Value d)
fcmp :: (IsFloating c, CmpOp a b c d, CmpRet c d) => FPPredicate -> a -> b -> CodeGenFunction r (Value d)
select :: (IsFirstClass a, CmpRet a b) => Value b -> Value a -> Value a -> CodeGenFunction r (Value a)
phi :: forall a r. IsFirstClass a => [(Value a, BasicBlock)] -> CodeGenFunction r (Value a)
addPhiInputs :: forall a r. IsFirstClass a => Value a -> [(Value a, BasicBlock)] -> CodeGenFunction r ()
call :: CallArgs f g => Function f -> g
type Terminate = ()
class Ret a r
class CallArgs f g | f -> g, g -> f
class ABinOp a b c | a b -> c
class CmpOp a b c d | a b -> c
class FunctionArgs f g r | f -> g r, g r -> f
class FunctionArgs (IO a) (CodeGenFunction a ()) (CodeGenFunction a ()) => FunctionRet a
class IsConst a
class AllocArg a
class GetElementPtr optr ixs nptr | optr ixs -> nptr
class IsIndexArg a
class IsType a where
typeDesc :: a -> TypeDesc
class IsFirstClass a => IsArithmetic a
class (IsArithmetic a, IsIntegerOrPointer a) => IsInteger a
class IsIntegerOrPointer a
class IsArithmetic a => IsFloating a
class IsType a => IsPrimitive a
class IsType a => IsFirstClass a
class (IsType a, Pos s) => IsSized a s | a -> s
class IsType a => IsFunction a
class Pos n => IsPowerOf2 n
type :& a as = (a, as)
(&) :: a -> as -> a :& as
data TypeDesc
= TDFloat
| TDDouble
| TDFP128
| TDVoid
| TDInt Bool Integer
| TDArray Integer TypeDesc
| TDVector Integer TypeDesc
| TDPtr TypeDesc
| TDFunction Bool [TypeDesc] TypeDesc
| TDLabel
| TDStruct [TypeDesc] Bool
isFloating :: IsArithmetic a => a -> Bool
isSigned :: IsInteger a => a -> Bool
typeRef :: IsType a => a -> TypeRef
typeName :: IsType a => a -> String
data VarArgs a
class CastVarArgs a b
newtype Pos n => IntN n = IntN Integer
newtype Pos n => WordN n = WordN Integer
newtype FP128 = FP128 Rational
newtype Nat n => Array n a = Array [a]
newtype Vector n a = Vector [a]
Ptr (Ptr)
data Label
newtype Struct a = Struct a
newtype PackedStruct a = PackedStruct a
data Value a
data ConstValue a
valueOf :: IsConst a => a -> Value a
value :: ConstValue a -> Value a
zero :: forall a. IsType a => ConstValue a
allOnes :: forall a. IsInteger a => ConstValue a
undef :: forall a. IsType a => ConstValue a
createString :: String -> TGlobal (Array n Word8)
createStringNul :: String -> TGlobal (Array n Word8)
constVector :: forall a n. Pos n => [ConstValue a] -> ConstValue (Vector n a)
constArray :: forall a n s. (IsSized a s, Nat n) => [ConstValue a] -> ConstValue (Array n a)
toVector :: MkVector va n a => va -> Vector n a
fromVector :: MkVector va n a => Vector n a -> va
data CodeGenFunction r a
data CodeGenModule a
type Function a = Value (Ptr a)
newFunction :: forall a. IsFunction a => Linkage -> CodeGenModule (Function a)
newNamedFunction :: forall a. IsFunction a => Linkage -> String -> CodeGenModule (Function a)
defineFunction :: forall f g r. FunctionArgs f g (CodeGenFunction r ()) => Function f -> g -> CodeGenModule ()
createFunction :: (IsFunction f, FunctionArgs f g (CodeGenFunction r ())) => Linkage -> g -> CodeGenModule (Function f)
createNamedFunction :: (IsFunction f, FunctionArgs f g (CodeGenFunction r ())) => Linkage -> String -> g -> CodeGenModule (Function f)
type TFunction a = CodeGenModule (Function a)
type Global a = Value (Ptr a)
newGlobal :: forall a. IsType a => Bool -> Linkage -> TGlobal a
newNamedGlobal :: forall a. IsType a => Bool -> Linkage -> String -> TGlobal a
defineGlobal :: Global a -> ConstValue a -> CodeGenModule ()
createGlobal :: IsType a => Bool -> Linkage -> ConstValue a -> TGlobal a
createNamedGlobal :: IsType a => Bool -> Linkage -> String -> ConstValue a -> TGlobal a
externFunction :: forall a r. IsFunction a => String -> CodeGenFunction r (Function a)
type TGlobal a = CodeGenModule (Global a)
data Linkage
= ExternalLinkage
| LinkOnceLinkage
| WeakLinkage
| AppendingLinkage
| InternalLinkage
| DLLImportLinkage
| DLLExportLinkage
| ExternalWeakLinkage
| GhostLinkage
data BasicBlock
newBasicBlock :: CodeGenFunction r BasicBlock
newNamedBasicBlock :: String -> CodeGenFunction r BasicBlock
defineBasicBlock :: BasicBlock -> CodeGenFunction r ()
createBasicBlock :: CodeGenFunction r BasicBlock
getCurrentBasicBlock :: CodeGenFunction r BasicBlock
fromLabel :: Value Label -> BasicBlock
toLabel :: BasicBlock -> Value Label
addAttributes :: Value a -> Int -> [Attribute] -> CodeGenFunction r ()
data Attribute
= ZExtAttribute
| SExtAttribute
| NoReturnAttribute
| InRegAttribute
| StructRetAttribute
| NoUnwindAttribute
| NoAliasAttribute
| ByValAttribute
| NestAttribute
| ReadNoneAttribute
| ReadOnlyAttribute
castVarArgs :: CastVarArgs a b => Function a -> Function b
dumpValue :: Value a -> IO ()
dumpType :: Value a -> IO ()
getValueName :: Value a -> IO String
addCFGSimplificationPass :: PassManager -> IO ()
addConstantPropagationPass :: PassManager -> IO ()
addDemoteMemoryToRegisterPass :: PassManager -> IO ()
addGVNPass :: PassManager -> IO ()
addInstructionCombiningPass :: PassManager -> IO ()
addPromoteMemoryToRegisterPass :: PassManager -> IO ()
addReassociatePass :: PassManager -> IO ()
addTargetData :: TargetDataRef -> PassManager -> IO ()
Modules
data Module Source
Type of top level modules.
show/hide Instances
newModule :: IO ModuleSource
Create a new module.
newNamedModuleSource
:: Stringmodule name
-> IO Module
Create a new explicitely named module.
defineModuleSource
::
=> Modulemodule that is defined
-> CodeGenModule amodule body
-> IO a
Give the body for a module.
destroyModule :: Module -> IO ()Source
Free all storage related to a module. *Note*, this is a dangerous call, since referring to the module after this call is an error. The reason for the explicit call to free the module instead of an automatic lifetime management is that modules have a somewhat complicated ownership. Handing a module to a module provider changes the ownership of the module, and the module provider will free the module when necessary.
createModuleSource
::
=> CodeGenModule amodule body
-> IO a
Create a new module with the given body.
data ModuleProvider Source
A module provider is used by the code generator to get access to a module.
show/hide Instances
createModuleProviderForExistingModule :: Module -> IO ModuleProviderSource
Turn a module into a module provider.
data PassManager Source
Manage compile passes.
show/hide Instances
createPassManager :: IO PassManagerSource
Create a pass manager.
createFunctionPassManager :: ModuleProvider -> IO PassManagerSource
Create a pass manager for a module.
writeBitcodeToFile :: String -> Module -> IO ()Source
Write a module to a file.
readBitcodeFromFile :: String -> IO ModuleSource
Read a module from a file.
getModuleValues :: Module -> IO [(String, ModuleValue)]Source
data ModuleValue Source
show/hide Instances
castModuleValue :: forall a. IsType a => ModuleValue -> Maybe (Value a)Source
Instructions
Terminator instructions
ret :: Ret a r => a -> CodeGenFunction r TerminateSource
Return from the current function with the given value. Use () as the return value for what would be a void function is C.
condBrSource
::
=> Value BoolBoolean to branch upon.
-> BasicBlockTarget for true.
-> BasicBlockTarget for false.
-> CodeGenFunction r Terminate
Branch to the first basic block if the boolean is true, otherwise to the second basic block.
brSource
::
=> BasicBlockBranch target.
-> CodeGenFunction r Terminate
Unconditionally branch to the given basic block.
switchSource
:: IsInteger a
=> Value aValue to branch upon.
-> BasicBlockDefault branch target.
-> [(ConstValue a, BasicBlock)]Labels and corresponding branch targets.
-> CodeGenFunction r Terminate
Branch table instruction.
invokeSource
:: CallArgs f g
=> BasicBlockNormal return point.
-> BasicBlockException return point.
-> Function fFunction to call.
-> g
Call a function with exception handling.
unwind :: CodeGenFunction r TerminateSource
Unwind the call stack until a function call performed with invoke is reached. I.e., throw a non-local exception.
unreachable :: CodeGenFunction r TerminateSource
Inform the code generator that this code can never be reached.
Arithmetic binary operations
Arithmetic operations with the normal semantics. The u instractions are unsigned, the s instructions are signed.
add :: (IsArithmetic c, ABinOp a b (v c)) => a -> b -> CodeGenFunction r (v c)Source
sub :: (IsArithmetic c, ABinOp a b (v c)) => a -> b -> CodeGenFunction r (v c)Source
mul :: (IsArithmetic c, ABinOp a b (v c)) => a -> b -> CodeGenFunction r (v c)Source
neg :: IsArithmetic a => Value a -> CodeGenFunction r (Value a)Source
udiv :: (IsInteger c, ABinOp a b (v c)) => a -> b -> CodeGenFunction r (v c)Source
sdiv :: (IsInteger c, ABinOp a b (v c)) => a -> b -> CodeGenFunction r (v c)Source
fdiv :: (IsFloating c, ABinOp a b (v c)) => a -> b -> CodeGenFunction r (v c)Source
Floating point division.
urem :: (IsInteger c, ABinOp a b (v c)) => a -> b -> CodeGenFunction r (v c)Source
srem :: (IsInteger c, ABinOp a b (v c)) => a -> b -> CodeGenFunction r (v c)Source
frem :: (IsFloating c, ABinOp a b (v c)) => a -> b -> CodeGenFunction r (v c)Source
Floating point remainder.
Logical binary operations
Logical instructions with the normal semantics.
shl :: (IsInteger c, ABinOp a b (v c)) => a -> b -> CodeGenFunction r (v c)Source
lshr :: (IsInteger c, ABinOp a b (v c)) => a -> b -> CodeGenFunction r (v c)Source
ashr :: (IsInteger c, ABinOp a b (v c)) => a -> b -> CodeGenFunction r (v c)Source
and :: (IsInteger c, ABinOp a b (v c)) => a -> b -> CodeGenFunction r (v c)Source
or :: (IsInteger c, ABinOp a b (v c)) => a -> b -> CodeGenFunction r (v c)Source
xor :: (IsInteger c, ABinOp a b (v c)) => a -> b -> CodeGenFunction r (v c)Source
inv :: IsInteger a => Value a -> CodeGenFunction r (Value a)Source
Vector operations
extractelementSource
::
=> Value (Vector n a)Vector
-> Value Word32Index into the vector
-> CodeGenFunction r (Value a)
Get a value from a vector.
insertelementSource
::
=> Value (Vector n a)Vector
-> Value aValue to insert
-> Value Word32Index into the vector
-> CodeGenFunction r (Value (Vector n a))
Insert a value into a vector, nondescructive.
shufflevector :: Value (Vector n a) -> Value (Vector n a) -> ConstValue (Vector n Word32) -> CodeGenFunction r (Value (Vector n a))Source
Permute vector.
Memory access
malloc :: forall a r s. IsSized a s => CodeGenFunction r (Value (Ptr a))Source
Allocate heap memory.
arrayMalloc :: forall a n r s. (IsSized a n, AllocArg s) => s -> CodeGenFunction r (Value (Ptr a))Source
Allocate heap (array) memory.
alloca :: forall a r s. IsSized a s => CodeGenFunction r (Value (Ptr a))Source
Allocate stack memory.
arrayAlloca :: forall a n r s. (IsSized a n, AllocArg s) => s -> CodeGenFunction r (Value (Ptr a))Source
Allocate stack (array) memory.
free :: Value (Ptr a) -> CodeGenFunction r (Value ())Source
Free heap memory.
loadSource
::
=> Value (Ptr a)Address to load from.
-> CodeGenFunction r (Value a)
Load a value from memory.
storeSource
::
=> Value aValue to store.
-> Value (Ptr a)Address to store to.
-> CodeGenFunction r (Value ())
Store a value in memory
getElementPtr :: forall a o i n r. (GetElementPtr o i n, IsIndexArg a) => Value (Ptr o) -> (a, i) -> CodeGenFunction r (Value (Ptr n))Source
Address arithmetic. See LLVM description. The index is a nested tuple of the form (i1,(i2,( ... ()))). (This is without a doubt the most confusing LLVM instruction, but the types help.)
getElementPtr0 :: GetElementPtr o i n => Value (Ptr o) -> i -> CodeGenFunction r (Value (Ptr n))Source
Like getElementPtr, but with an initial index that is 0. This is useful since any pointer first need to be indexed off the pointer, and then into its actual value. This first indexing is often with 0.
Conversions
trunc :: (IsInteger a, IsInteger b, IsPrimitive a, IsPrimitive b, IsSized a sa, IsSized b sb, sa :>: sb) => Value a -> CodeGenFunction r (Value b)Source
Truncate a value to a shorter bit width.
zext :: (IsInteger a, IsInteger b, IsPrimitive a, IsPrimitive b, IsSized a sa, IsSized b sb, sa :<: sb) => Value a -> CodeGenFunction r (Value b)Source
Zero extend a value to a wider width.
sext :: (IsInteger a, IsInteger b, IsPrimitive a, IsPrimitive b, IsSized a sa, IsSized b sb, sa :<: sb) => Value a -> CodeGenFunction r (Value b)Source
Sign extend a value to wider width.
fptrunc :: (IsFloating a, IsFloating b, IsPrimitive a, IsPrimitive b, IsSized a sa, IsSized b sb, sa :>: sb) => Value a -> CodeGenFunction r (Value b)Source
Truncate a floating point value.
fpext :: (IsFloating a, IsFloating b, IsPrimitive a, IsPrimitive b, IsSized a sa, IsSized b sb, sa :<: sb) => Value a -> CodeGenFunction r (Value b)Source
Extend a floating point value.
fptoui :: (IsFloating a, IsInteger b, IsPrimitive a, IsPrimitive b) => Value a -> CodeGenFunction r (Value b)Source
Convert a floating point value to an unsigned integer.
fptosi :: (IsFloating a, IsInteger b, IsPrimitive a, IsPrimitive b) => Value a -> CodeGenFunction r (Value b)Source
Convert a floating point value to a signed integer.
uitofp :: (IsInteger a, IsFloating b, IsPrimitive a, IsPrimitive b) => Value a -> CodeGenFunction r (Value b)Source
Convert an unsigned integer to a floating point value.
sitofp :: (IsInteger a, IsFloating b, IsPrimitive a, IsPrimitive b) => Value a -> CodeGenFunction r (Value b)Source
Convert a signed integer to a floating point value.
ptrtoint :: (IsInteger b, IsPrimitive b) => Value (Ptr a) -> CodeGenFunction r (Value b)Source
Convert a pointer to an integer.
inttoptr :: (IsInteger a, IsType b) => Value a -> CodeGenFunction r (Value (Ptr b))Source
Convert an integer to a pointer.
bitcast :: (IsFirstClass a, IsFirstClass b, IsSized a sa, IsSized b sb, sa :==: sb) => Value a -> CodeGenFunction r (Value b)Source
Convert between to values of the same size by just copying the bit pattern.
Comparison
data IntPredicate Source
Constructors
IntEQequal
IntNEnot equal
IntUGTunsigned greater than
IntUGEunsigned greater or equal
IntULTunsigned less than
IntULEunsigned less or equal
IntSGTsigned greater than
IntSGEsigned greater or equal
IntSLTsigned less than
IntSLEsigned less or equal
show/hide Instances
data FPPredicate Source
Constructors
FPFalseAlways false (always folded)
FPOEQTrue if ordered and equal
FPOGTTrue if ordered and greater than
FPOGETrue if ordered and greater than or equal
FPOLTTrue if ordered and less than
FPOLETrue if ordered and less than or equal
FPONETrue if ordered and operands are unequal
FPORDTrue if ordered (no nans)
FPUNOTrue if unordered: isnan(X) | isnan(Y)
FPUEQTrue if unordered or equal
FPUGTTrue if unordered or greater than
FPUGETrue if unordered, greater than, or equal
FPULTTrue if unordered or less than
FPULETrue if unordered, less than, or equal
FPUNETrue if unordered or not equal
FPTAlways true (always folded)
show/hide Instances
class CmpRet a b | a -> bSource
show/hide Instances
icmp :: (IsIntegerOrPointer c, CmpOp a b c d, CmpRet c d) => IntPredicate -> a -> b -> CodeGenFunction r (Value d)Source
Compare integers.
fcmp :: (IsFloating c, CmpOp a b c d, CmpRet c d) => FPPredicate -> a -> b -> CodeGenFunction r (Value d)Source
Compare floating point values.
select :: (IsFirstClass a, CmpRet a b) => Value b -> Value a -> Value a -> CodeGenFunction r (Value a)Source
Select between two values depending on a boolean.
Other
phi :: forall a r. IsFirstClass a => [(Value a, BasicBlock)] -> CodeGenFunction r (Value a)Source
Join several variables (virtual registers) from different basic blocks into one. All of the variables in the list are joined. See also addPhiInputs.
addPhiInputsSource
:: forall a r . IsFirstClass a
=> Value aMust be a variable from a call to phi.
-> [(Value a, BasicBlock)]Variables to add.
-> CodeGenFunction r ()
Add additional inputs to an existing phi node. The reason for this instruction is that sometimes the structure of the code makes it impossible to have all variables in scope at the point where you need the phi node.
call :: CallArgs f g => Function f -> gSource
Call a function with the given arguments. The call instruction is variadic, i.e., the number of arguments it takes depends on the type of f.
Classes and types
type Terminate = ()Source
class Ret a r Source
Acceptable arguments to the ret instruction.
show/hide Instances
class CallArgs f g | f -> g, g -> fSource
Acceptable arguments to call.
show/hide Instances
CallArgs (IO a) (CodeGenFunction r (Value a))
CallArgs (IO a) (CodeGenFunction r (Value a))
CallArgs b b' => CallArgs (a -> b) (Value a -> b')
class ABinOp a b c | a b -> cSource
Acceptable arguments to arithmetic binary instructions.
show/hide Instances
class CmpOp a b c d | a b -> cSource
Acceptable operands to comparison instructions.
show/hide Instances
IsConst a => CmpOp a (Value a) a d
IsConst a => CmpOp (Value a) a a d
CmpOp (Value a) (Value a) a d
class FunctionArgs f g r | f -> g r, g r -> fSource
show/hide Instances
FunctionArgs (IO Bool) (FA Bool) (FA Bool)
FunctionArgs (IO Bool) (FA Bool) (FA Bool)
FunctionArgs (IO Double) (FA Double) (FA Double)
FunctionArgs (IO Double) (FA Double) (FA Double)
FunctionArgs (IO Float) (FA Float) (FA Float)
FunctionArgs (IO Float) (FA Float) (FA Float)
FunctionArgs (IO Int8) (FA Int8) (FA Int8)
FunctionArgs (IO Int8) (FA Int8) (FA Int8)
FunctionArgs (IO Int16) (FA Int16) (FA Int16)
FunctionArgs (IO Int16) (FA Int16) (FA Int16)
FunctionArgs (IO Int32) (FA Int32) (FA Int32)
FunctionArgs (IO Int32) (FA Int32) (FA Int32)
FunctionArgs (IO Int64) (FA Int64) (FA Int64)
FunctionArgs (IO Int64) (FA Int64) (FA Int64)
FunctionArgs (IO Word8) (FA Word8) (FA Word8)
FunctionArgs (IO Word8) (FA Word8) (FA Word8)
FunctionArgs (IO Word16) (FA Word16) (FA Word16)
FunctionArgs (IO Word16) (FA Word16) (FA Word16)
FunctionArgs (IO Word32) (FA Word32) (FA Word32)
FunctionArgs (IO Word32) (FA Word32) (FA Word32)
FunctionArgs (IO Word64) (FA Word64) (FA Word64)
FunctionArgs (IO Word64) (FA Word64) (FA Word64)
IsType a => FunctionArgs (IO (Ptr a)) (FA (Ptr a)) (FA (Ptr a))
IsType a => FunctionArgs (IO (Ptr a)) (FA (Ptr a)) (FA (Ptr a))
FunctionArgs (IO ()) (FA ()) (FA ())
FunctionArgs (IO ()) (FA ()) (FA ())
(Pos n, IsPrimitive a) => FunctionArgs (IO (Vector n a)) (FA (Vector n a)) (FA (Vector n a))
(Pos n, IsPrimitive a) => FunctionArgs (IO (Vector n a)) (FA (Vector n a)) (FA (Vector n a))
FunctionArgs (IO FP128) (FA FP128) (FA FP128)
FunctionArgs (IO FP128) (FA FP128) (FA FP128)
Pos n => FunctionArgs (IO (WordN n)) (FA (WordN n)) (FA (WordN n))
Pos n => FunctionArgs (IO (WordN n)) (FA (WordN n)) (FA (WordN n))
Pos n => FunctionArgs (IO (IntN n)) (FA (IntN n)) (FA (IntN n))
Pos n => FunctionArgs (IO (IntN n)) (FA (IntN n)) (FA (IntN n))
FunctionArgs b b' r => FunctionArgs (a -> b) (Value a -> b') r
class FunctionArgs (IO a) (CodeGenFunction a ()) (CodeGenFunction a ()) => FunctionRet a Source
This class is just to simplify contexts.
class IsConst a Source
show/hide Instances
class AllocArg a Source
Acceptable argument to array memory allocation.
show/hide Instances
class GetElementPtr optr ixs nptr | optr ixs -> nptrSource
Acceptable arguments to getElementPointer.
show/hide Instances
GetElementPtr a () a
(GetElementPtr o i n, GetField fs a o, Nat a) => GetElementPtr (PackedStruct fs) ((,) a i) n
(GetElementPtr o i n, GetField fs a o, Nat a) => GetElementPtr (PackedStruct fs) ((,) a i) n
(GetElementPtr o i n, GetField fs a o, Nat a) => GetElementPtr (Struct fs) ((,) a i) n
(GetElementPtr o i n, GetField fs a o, Nat a) => GetElementPtr (Struct fs) ((,) a i) n
(GetElementPtr o i n, IsIndexArg a) => GetElementPtr (Vector k o) ((,) a i) n
(GetElementPtr o i n, IsIndexArg a) => GetElementPtr (Vector k o) ((,) a i) n
(GetElementPtr o i n, IsIndexArg a) => GetElementPtr (Array k o) ((,) a i) n
(GetElementPtr o i n, IsIndexArg a) => GetElementPtr (Array k o) ((,) a i) n
class IsIndexArg a Source
Acceptable single index to getElementPointer.
show/hide Instances
Types classification
Type classifier
class IsType a whereSource
The IsType class classifies all types that have an LLVM representation.
Methods
typeDesc :: a -> TypeDescSource
show/hide Instances
Special type classifiers
class IsFirstClass a => IsArithmetic a Source
Arithmetic types, i.e., integral and floating types.
show/hide Instances
class (IsArithmetic a, IsIntegerOrPointer a) => IsInteger a Source
Integral types.
show/hide Instances
class IsIntegerOrPointer a Source
Integral or pointer type.
show/hide Instances
class IsArithmetic a => IsFloating a Source
Floating types.
show/hide Instances
class IsType a => IsPrimitive a Source
Primitive types.
show/hide Instances
class IsType a => IsFirstClass a Source
First class types, i.e., the types that can be passed as arguments, etc.
show/hide Instances
class (IsType a, Pos s) => IsSized a s | a -> sSource
Types with a fixed size.
show/hide Instances
class IsType a => IsFunction a Source
Function type.
show/hide Instances
Others
class Pos n => IsPowerOf2 n Source
Structs
type :& a as = (a, as)Source
(&) :: a -> as -> a :& asSource
Type tests
data TypeDesc Source
Type descriptor, used to convey type information through the LLVM API.
Constructors
TDFloat
TDDouble
TDFP128
TDVoid
TDInt Bool Integer
TDArray Integer TypeDesc
TDVector Integer TypeDesc
TDPtr TypeDesc
TDFunction Bool [TypeDesc] TypeDesc
TDLabel
TDStruct [TypeDesc] Bool
show/hide Instances
isFloating :: IsArithmetic a => a -> BoolSource
isSigned :: IsInteger a => a -> BoolSource
typeRefSource
:: IsType a
=> a
-> TypeRefThe argument is never evaluated
typeName :: IsType a => a -> StringSource
data VarArgs a Source
The VarArgs type is a placeholder for the real IO type that can be obtained with castVarArgs.
show/hide Instances
class CastVarArgs a b Source
Define what vararg types are permissible.
show/hide Instances
CastVarArgs (VarArgs a) (IO a)
CastVarArgs (VarArgs a) (IO a)
(IsFirstClass a, CastVarArgs (VarArgs b) c) => CastVarArgs (VarArgs b) (a -> c)
(IsFirstClass a, CastVarArgs (VarArgs b) c) => CastVarArgs (VarArgs b) (a -> c)
CastVarArgs b c => CastVarArgs (a -> b) (a -> c)
Extra types
newtype Pos n => IntN n Source
Variable sized signed integer. The n parameter should belong to PosI.
Constructors
IntN Integer
show/hide Instances
newtype Pos n => WordN n Source
Variable sized unsigned integer. The n parameter should belong to PosI.
Constructors
WordN Integer
show/hide Instances
newtype FP128 Source
128 bit floating point.
Constructors
FP128 Rational
show/hide Instances
newtype Nat n => Array n a Source
Fixed sized arrays, the array size is encoded in the n parameter.
Constructors
Array [a]
show/hide Instances
Typeable2 Array
(Show a, NatI n) => Show (Array n a)
(Nat n, IsSized a s) => IsType (Array n a)
(IsConst a, IsSized a s, Nat n) => IsConst (Array n a)
(Nat n, IsSized a s, Mul n s ns, Pos ns) => IsSized (Array n a) ns
(GetElementPtr o i n, IsIndexArg a) => GetElementPtr (Array k o) ((,) a i) n
newtype Vector n a Source
Fixed sized vector, the array size is encoded in the n parameter.
Constructors
Vector [a]
show/hide Instances
Ptr (Ptr)
data Label Source
Label type, produced by a basic block.
show/hide Instances
newtype Struct a Source
Struct types; a list (nested tuple) of component types.
Constructors
Struct a
show/hide Instances
Typeable1 Struct
Show a => Show (Struct a)
StructFields as => IsFirstClass (Struct as)
StructFields a => IsType (Struct a)
IsConstFields a => IsConst (Struct a)
StructFields as => IsSized (Struct as) UnknownSize
(GetElementPtr o i n, GetField fs a o, Nat a) => GetElementPtr (Struct fs) ((,) a i) n
newtype PackedStruct a Source
Constructors
PackedStruct a
show/hide Instances
Typeable1 PackedStruct
Show a => Show (PackedStruct a)
StructFields a => IsType (PackedStruct a)
IsConstFields a => IsConst (PackedStruct a)
StructFields as => IsSized (PackedStruct as) UnknownSize
(GetElementPtr o i n, GetField fs a o, Nat a) => GetElementPtr (PackedStruct fs) ((,) a i) n
Values and constants
data Value a Source
show/hide Instances
data ConstValue a Source
show/hide Instances
valueOf :: IsConst a => a -> Value aSource
value :: ConstValue a -> Value aSource
zero :: forall a. IsType a => ConstValue aSource
allOnes :: forall a. IsInteger a => ConstValue aSource
undef :: forall a. IsType a => ConstValue aSource
createString :: String -> TGlobal (Array n Word8)Source
createStringNul :: String -> TGlobal (Array n Word8)Source
constVector :: forall a n. Pos n => [ConstValue a] -> ConstValue (Vector n a)Source
Make a constant vector. Replicates or truncates the list to get length n.
constArray :: forall a n s. (IsSized a s, Nat n) => [ConstValue a] -> ConstValue (Array n a)Source
Make a constant array. Replicates or truncates the list to get length n.
toVector :: MkVector va n a => va -> Vector n aSource
fromVector :: MkVector va n a => Vector n a -> vaSource
Code generation
data CodeGenFunction r a Source
show/hide Instances
Typeable2 CodeGenFunction
Monad (CodeGenFunction r)
Functor (CodeGenFunction r)
MonadIO (CodeGenFunction r)
MonadState (CGFState r) (CodeGenFunction r)
FunctionArgs (IO Bool) (FA Bool) (FA Bool)
FunctionArgs (IO Double) (FA Double) (FA Double)
FunctionArgs (IO Float) (FA Float) (FA Float)
FunctionArgs (IO Int8) (FA Int8) (FA Int8)
FunctionArgs (IO Int16) (FA Int16) (FA Int16)
FunctionArgs (IO Int32) (FA Int32) (FA Int32)
FunctionArgs (IO Int64) (FA Int64) (FA Int64)
FunctionArgs (IO Word8) (FA Word8) (FA Word8)
FunctionArgs (IO Word16) (FA Word16) (FA Word16)
FunctionArgs (IO Word32) (FA Word32) (FA Word32)
FunctionArgs (IO Word64) (FA Word64) (FA Word64)
IsType a => FunctionArgs (IO (Ptr a)) (FA (Ptr a)) (FA (Ptr a))
FunctionArgs (IO ()) (FA ()) (FA ())
(Pos n, IsPrimitive a) => FunctionArgs (IO (Vector n a)) (FA (Vector n a)) (FA (Vector n a))
FunctionArgs (IO FP128) (FA FP128) (FA FP128)
Pos n => FunctionArgs (IO (WordN n)) (FA (WordN n)) (FA (WordN n))
Pos n => FunctionArgs (IO (IntN n)) (FA (IntN n)) (FA (IntN n))
CallArgs (IO a) (CodeGenFunction r (Value a))
(IsArithmetic a, Cmp a b, Num a, IsConst a) => Enum (TValue r a)
Eq (TValue r a)
(Cmp a b, CallIntrinsic a, Floating a, IsConst a, IsFloating a) => Floating (TValue r a)
(Cmp a b, Fractional a, IsConst a, IsFloating a) => Fractional (TValue r a)
(Cmp a b, Num a, IsConst a, IsInteger a) => Integral (TValue r a)
(IsArithmetic a, Cmp a b, Num a, IsConst a) => Num (TValue r a)
Ord (TValue r a)
(IsArithmetic a, Cmp a b, Num a, IsConst a) => Real (TValue r a)
(Cmp a b, CallIntrinsic a, RealFloat a, IsConst a, IsFloating a) => RealFloat (TValue r a)
(Cmp a b, Fractional a, IsConst a, IsFloating a) => RealFrac (TValue r a)
Show (TValue r a)
UncurryN (CodeGenFunction r a) (() -> CodeGenFunction r a)
Ret a r => ArithFunction (CodeGenFunction r a) (CodeGenFunction r ())
data CodeGenModule a Source
show/hide Instances
Functions
type Function a = Value (Ptr a)Source
A function is simply a pointer to the function.
newFunction :: forall a. IsFunction a => Linkage -> CodeGenModule (Function a)Source
Create a new function. Use newNamedFunction to create a function with external linkage, since it needs a known name.
newNamedFunctionSource
:: forall a . IsFunction a
=> Linkage
-> StringFunction name
-> CodeGenModule (Function a)
Create a new named function.
defineFunctionSource
:: forall f g r . FunctionArgs f g (CodeGenFunction r ())
=> Function fFunction to define (created by newFunction).
-> gFunction body.
-> CodeGenModule ()
Define a function body. The basic block returned by the function is the function entry point.
createFunctionSource
:: (IsFunction f, FunctionArgs f g (CodeGenFunction r ()))
=> Linkage
-> gFunction body.
-> CodeGenModule (Function f)
Create a new function with the given body.
createNamedFunctionSource
:: (IsFunction f, FunctionArgs f g (CodeGenFunction r ()))
=> Linkage
-> String
-> gFunction body.
-> CodeGenModule (Function f)
Create a new function with the given body.
type TFunction a = CodeGenModule (Function a)Source
Global variable creation
type Global a = Value (Ptr a)Source
newGlobal :: forall a. IsType a => Bool -> Linkage -> TGlobal aSource
Create a new global variable.
newNamedGlobalSource
:: forall a . IsType a
=> BoolConstant?
-> LinkageVisibility
-> StringName
-> TGlobal a
Create a new named global variable.
defineGlobal :: Global a -> ConstValue a -> CodeGenModule ()Source
Give a global variable a (constant) value.
createGlobal :: IsType a => Bool -> Linkage -> ConstValue a -> TGlobal aSource
Create and define a global variable.
createNamedGlobal :: IsType a => Bool -> Linkage -> String -> ConstValue a -> TGlobal aSource
Create and define a named global variable.
externFunction :: forall a r. IsFunction a => String -> CodeGenFunction r (Function a)Source
Create a reference to an external function while code generating for a function.
type TGlobal a = CodeGenModule (Global a)Source
Globals
data Linkage Source
An enumeration for the kinds of linkage for global values.
Constructors
ExternalLinkageExternally visible function
LinkOnceLinkageKeep one copy of function when linking (inline)
WeakLinkageKeep one copy of named function when linking (weak)
AppendingLinkageSpecial purpose, only applies to global arrays
InternalLinkageRename collisions when linking (static functions)
DLLImportLinkageFunction to be imported from DLL
DLLExportLinkageFunction to be accessible from DLL
ExternalWeakLinkageExternalWeak linkage description
GhostLinkageStand-in functions for streaming fns from BC files
show/hide Instances
Basic blocks
data BasicBlock Source
A basic block is a sequence of non-branching instructions, terminated by a control flow instruction.
show/hide Instances
newBasicBlock :: CodeGenFunction r BasicBlockSource
newNamedBasicBlock :: String -> CodeGenFunction r BasicBlockSource
defineBasicBlock :: BasicBlock -> CodeGenFunction r ()Source
createBasicBlock :: CodeGenFunction r BasicBlockSource
getCurrentBasicBlock :: CodeGenFunction r BasicBlockSource
fromLabel :: Value Label -> BasicBlockSource
toLabel :: BasicBlock -> Value LabelSource
Misc
addAttributes :: Value a -> Int -> [Attribute] -> CodeGenFunction r ()Source
Add attributes to a value. Beware, what attributes are allowed depends on what kind of value it is.
data Attribute Source
Constructors
ZExtAttribute
SExtAttribute
NoReturnAttribute
InRegAttribute
StructRetAttribute
NoUnwindAttribute
NoAliasAttribute
ByValAttribute
NestAttribute
ReadNoneAttribute
ReadOnlyAttribute
show/hide Instances
castVarArgs :: CastVarArgs a b => Function a -> Function bSource
Convert a varargs function to a regular function.
Debugging
dumpValue :: Value a -> IO ()Source
Print a value.
dumpType :: Value a -> IO ()Source
Print a type.
getValueName :: Value a -> IO StringSource
Get the name of a Value.
Transformations
addCFGSimplificationPass :: PassManager -> IO ()Source
Add a control flow graph simplification pass to the manager.
addConstantPropagationPass :: PassManager -> IO ()Source
Add a constant propagation pass to the manager.
addDemoteMemoryToRegisterPass :: PassManager -> IO ()Source
addGVNPass :: PassManager -> IO ()Source
Add a global value numbering pass to the manager.
addInstructionCombiningPass :: PassManager -> IO ()Source
addPromoteMemoryToRegisterPass :: PassManager -> IO ()Source
addReassociatePass :: PassManager -> IO ()Source
addTargetData :: TargetDataRef -> PassManager -> IO ()Source
Produced by Haddock version 2.4.2