- Initialize
- Modules
- Instructions
- Terminator instructions
- Arithmetic binary operations
- Logical binary operations
- Vector operations
- Aggregate operations
- Memory access
- Conversions
- Comparison
- Other
- Classes and types
- Types classification
- Type classifier
- Extra types
- Values and constants
- Code generation
- Functions
- Global variable creation
- Globals
- Basic blocks
- Misc
- Debugging
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.
- initializeNativeTarget :: IO ()
- 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)
- fadd :: (IsFloating c, ABinOp a b (v c)) => a -> b -> CodeGenFunction r (v c)
- fsub :: (IsFloating c, ABinOp a b (v c)) => a -> b -> CodeGenFunction r (v c)
- fmul :: (IsFloating c, ABinOp a b (v c)) => a -> b -> CodeGenFunction r (v c)
- 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))
- extractvalue :: forall r agg i a. GetValue agg i a => Value agg -> i -> CodeGenFunction r (Value a)
- insertvalue :: forall r agg i a. GetValue agg i a => Value agg -> Value a -> i -> CodeGenFunction r (Value agg)
- 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, NumberOfElements n a, NumberOfElements n b) => Value a -> CodeGenFunction r (Value b)
- fptosi :: (IsFloating a, IsInteger b, NumberOfElements n a, NumberOfElements n b) => Value a -> CodeGenFunction r (Value b)
- uitofp :: (IsInteger a, IsFloating b, NumberOfElements n a, NumberOfElements n b) => Value a -> CodeGenFunction r (Value b)
- sitofp :: (IsInteger a, IsFloating b, NumberOfElements n a, NumberOfElements n 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)
- bitcastUnify :: (IsFirstClass a, IsFirstClass b, IsSized a s, IsSized b s) => Value a -> CodeGenFunction r (Value b)
- data IntPredicate
- data FPPredicate
- 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 GetValue agg ix el | agg ix -> el
- class IsType a where
- class IsFirstClass a => IsArithmetic a
- class (IsArithmetic a, IsIntegerOrPointer a) => IsInteger a
- class IsIntegerOrPointer a
- class IsArithmetic a => IsFloating a
- class NumberOfElements D1 a => IsPrimitive a
- class IsType a => IsFirstClass a
- class (IsType a, Pos s) => IsSized a s | a -> s
- class IsType a => IsFunction a
- type UnknownSize = D99
- class Pos n => IsPowerOf2 n
- class IsType a => NumberOfElements n a | a -> n
- type :& a as = (a, as)
- (&) :: a -> as -> a :& as
- data a :+-> b
- ($+) :: (a :+-> b) -> a -> b
- class IsTuple a where
- withTuple :: (a -> b) -> a :+-> b
- data TypeDesc
- 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]
- data Ptr a
- 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)
- constStruct :: IsConstStruct c a => c -> ConstValue (Struct a)
- constPackedStruct :: IsConstStruct c a => c -> ConstValue (PackedStruct a)
- toVector :: MkVector va n a => va -> Vector n a
- fromVector :: MkVector va n a => Vector n a -> va
- vector :: forall a n. Pos n => [a] -> Vector n a
- 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)
- class Undefined a => ValueTuple a where
- buildTuple :: FunctionRef -> State Int a
- class Undefined a where
- undefTuple :: a
- class (IsTuple haskellValue, ValueTuple llvmValue) => MakeValueTuple haskellValue llvmValue | haskellValue -> llvmValue where
- valueTupleOf :: haskellValue -> llvmValue
- 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)
- staticFunction :: IsFunction f => FunPtr f -> CodeGenFunction r (Function f)
- data GlobalMappings
- getGlobalMappings :: CodeGenModule GlobalMappings
- type TGlobal a = CodeGenModule (Global a)
- data Linkage
- 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
- castVarArgs :: CastVarArgs a b => Function a -> Function b
- dumpValue :: Value a -> IO ()
- dumpType :: Value a -> IO ()
- getValueName :: Value a -> IO String
Initialize
initializeNativeTarget :: IO ()Source
Initialize jitter to the native target. The operation is idempotent.
Modules
:: Module | module that is defined |
-> CodeGenModule a | module 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.
data ModuleProvider Source
A module provider is used by the code generator to get access to a module.
createModuleProviderForExistingModule :: Module -> IO ModuleProviderSource
Turn a module into a module provider.
createPassManager :: IO PassManagerSource
Create a pass manager.
createFunctionPassManager :: ModuleProvider -> IO PassManagerSource
Create a pass manager for a module.
readBitcodeFromFile :: String -> IO ModuleSource
Read a module from a file.
getModuleValues :: Module -> IO [(String, ModuleValue)]Source
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.
:: Value Bool | Boolean to branch upon. |
-> BasicBlock | Target for true. |
-> BasicBlock | Target for false. |
-> CodeGenFunction r Terminate |
Branch to the first basic block if the boolean is true, otherwise to the second basic block.
:: BasicBlock | Branch target. |
-> CodeGenFunction r Terminate |
Unconditionally branch to the given basic block.
:: IsInteger a | |
=> Value a | Value to branch upon. |
-> BasicBlock | Default branch target. |
-> [(ConstValue a, BasicBlock)] | Labels and corresponding branch targets. |
-> CodeGenFunction r Terminate |
Branch table instruction.
:: CallArgs f g | |
=> BasicBlock | Normal return point. |
-> BasicBlock | Exception return point. |
-> Function f | Function 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
fadd :: (IsFloating c, ABinOp a b (v c)) => a -> b -> CodeGenFunction r (v c)Source
fsub :: (IsFloating c, ABinOp a b (v c)) => a -> b -> CodeGenFunction r (v c)Source
fmul :: (IsFloating c, ABinOp a b (v c)) => a -> b -> CodeGenFunction r (v c)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
Vector operations
Get a value from a vector.
:: Value (Vector n a) | Vector |
-> Value a | Value to insert |
-> Value Word32 | Index into the vector |
-> CodeGenFunction r (Value (Vector n a)) |
Insert a value into a vector, nondestructive.
shufflevector :: Value (Vector n a) -> Value (Vector n a) -> ConstValue (Vector n Word32) -> CodeGenFunction r (Value (Vector n a))Source
Permute vector.
Aggregate operations
:: forall r agg i a . GetValue agg i a | |
=> Value agg | Aggregate |
-> i | Index into the aggregate |
-> CodeGenFunction r (Value a) |
Get a value from an aggregate.
:: forall r agg i a . GetValue agg i a | |
=> Value agg | Aggregate |
-> Value a | Value to insert |
-> i | Index into the aggregate |
-> CodeGenFunction r (Value agg) |
Insert a value into an aggregate, nondestructive.
Memory access
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.
:: Value (Ptr a) | Address to load from. |
-> CodeGenFunction r (Value a) |
Load a value from memory.
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, NumberOfElements n a, NumberOfElements n b) => Value a -> CodeGenFunction r (Value b)Source
Convert a floating point value to an unsigned integer.
fptosi :: (IsFloating a, IsInteger b, NumberOfElements n a, NumberOfElements n b) => Value a -> CodeGenFunction r (Value b)Source
Convert a floating point value to a signed integer.
uitofp :: (IsInteger a, IsFloating b, NumberOfElements n a, NumberOfElements n b) => Value a -> CodeGenFunction r (Value b)Source
Convert an unsigned integer to a floating point value.
sitofp :: (IsInteger a, IsFloating b, NumberOfElements n a, NumberOfElements n 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.
bitcastUnify :: (IsFirstClass a, IsFirstClass b, IsSized a s, IsSized b s) => Value a -> CodeGenFunction r (Value b)Source
Same as bitcast but instead of the '(:==:)' type class it uses type unification. This way, properties like reflexivity, symmetry and transitivity are obvious to the Haskell compiler.
Comparison
data IntPredicate Source
data FPPredicate Source
FPFalse | Always false (always folded) |
FPOEQ | True if ordered and equal |
FPOGT | True if ordered and greater than |
FPOGE | True if ordered and greater than or equal |
FPOLT | True if ordered and less than |
FPOLE | True if ordered and less than or equal |
FPONE | True if ordered and operands are unequal |
FPORD | True if ordered (no nans) |
FPUNO | True if unordered: isnan(X) | isnan(Y) |
FPUEQ | True if unordered or equal |
FPUGT | True if unordered or greater than |
FPUGE | True if unordered, greater than, or equal |
FPULT | True if unordered or less than |
FPULE | True if unordered, less than, or equal |
FPUNE | True if unordered or not equal |
FPT | Always true (always folded) |
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
.
:: forall a r . IsFirstClass a | |
=> Value a | Must be a variable from a call to |
-> [(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
Acceptable arguments to the ret
instruction.
class ABinOp a b c | a b -> cSource
Acceptable arguments to arithmetic binary instructions.
IsConst a => ABinOp a (Value a) (Value a) | |
IsConst a => ABinOp (Value a) a (Value a) | |
ABinOp (ConstValue a) (ConstValue a) (ConstValue a) | |
ABinOp (ConstValue a) (Value a) (Value a) | |
ABinOp (Value a) (ConstValue a) (Value a) | |
ABinOp (Value a) (Value a) (Value a) |
class FunctionArgs f g r | f -> g r, g r -> fSource
class FunctionArgs (IO a) (CodeGenFunction a ()) (CodeGenFunction a ()) => FunctionRet a Source
This class is just to simplify contexts.
FunctionArgs (IO a) (CodeGenFunction a ()) (CodeGenFunction a ()) => FunctionRet a |
IsConst Bool | |
IsConst Double | |
IsConst Float | |
IsConst Int8 | |
IsConst Int16 | |
IsConst Int32 | |
IsConst Int64 | |
IsConst Word8 | |
IsConst Word16 | |
IsConst Word32 | |
IsConst Word64 | |
IsConst (StablePtr a) | |
IsType a => IsConst (Ptr a) | |
IsConstFields a => IsConst (PackedStruct a) | |
IsConstFields a => IsConst (Struct a) | |
(IsPrimitive a, IsConst a, IsPowerOf2 n) => IsConst (Vector n a) | |
(IsConst a, IsSized a s, Nat n) => IsConst (Array n a) |
Acceptable argument to array memory allocation.
class GetElementPtr optr ixs nptr | optr ixs -> nptrSource
Acceptable arguments to getElementPointer
.
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 (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 (Array k o) (a, i) n |
class IsIndexArg a Source
Acceptable single index to getElementPointer
.
class GetValue agg ix el | agg ix -> elSource
Acceptable arguments to extractvalue
and insertvalue
.
Types classification
Type classifier
The IsType
class classifies all types that have an LLVM representation.
IsType Bool | |
IsType Double | |
IsType Float | |
IsType Int8 | |
IsType Int16 | |
IsType Int32 | |
IsType Int64 | |
IsType Word8 | |
IsType Word16 | |
IsType Word32 | |
IsType Word64 | |
IsType () | |
IsType Label | |
IsType FP128 | |
IsType (StablePtr a) | |
IsFirstClass a => IsType (IO a) | |
IsType a => IsType (Ptr a) | |
StructFields a => IsType (PackedStruct a) | |
StructFields a => IsType (Struct a) | |
Pos n => IsType (WordN n) | |
Pos n => IsType (IntN n) | |
IsType (VarArgs a) | |
(IsFirstClass a, IsFunction b) => IsType (a -> b) | |
(IsPowerOf2 n, IsPrimitive a) => IsType (Vector n a) | |
(Nat n, IsSized a s) => IsType (Array n a) | |
(IsTuple a, IsFunction b) => IsType (:+-> a b) |
Special type classifiers
class IsFirstClass a => IsArithmetic a Source
Arithmetic types, i.e., integral and floating types.
class (IsArithmetic a, IsIntegerOrPointer a) => IsInteger a Source
Integral types.
class IsIntegerOrPointer a Source
Integral or pointer type.
class IsArithmetic a => IsFloating a Source
Floating types.
IsFloating Double | |
IsFloating Float | |
IsFloating FP128 | |
(IsPowerOf2 n, IsPrimitive a, IsFloating a) => IsFloating (Vector n a) |
class NumberOfElements D1 a => IsPrimitive a Source
Primitive types.
class IsType a => IsFirstClass a Source
First class types, i.e., the types that can be passed as arguments, etc.
IsFirstClass Bool | |
IsFirstClass Double | |
IsFirstClass Float | |
IsFirstClass Int8 | |
IsFirstClass Int16 | |
IsFirstClass Int32 | |
IsFirstClass Int64 | |
IsFirstClass Word8 | |
IsFirstClass Word16 | |
IsFirstClass Word32 | |
IsFirstClass Word64 | |
IsFirstClass () | |
IsFirstClass Label | |
IsFirstClass FP128 | |
IsFirstClass (StablePtr a) | |
IsType a => IsFirstClass (Ptr a) | |
StructFields as => IsFirstClass (Struct as) | |
Pos n => IsFirstClass (WordN n) | |
Pos n => IsFirstClass (IntN n) | |
(IsPowerOf2 n, IsPrimitive a) => IsFirstClass (Vector n a) | |
(Nat n, IsType a, IsSized a s) => IsFirstClass (Array n a) |
class (IsType a, Pos s) => IsSized a s | a -> sSource
Types with a fixed size.
IsSized Bool D1 | |
IsSized Double D64 | |
IsSized Float D32 | |
IsSized Int8 D8 | |
IsSized Int16 D16 | |
IsSized Int32 D32 | |
IsSized Int64 D64 | |
IsSized Word8 D8 | |
IsSized Word16 D16 | |
IsSized Word32 D32 | |
IsSized Word64 D64 | |
IsSized FP128 D128 | |
IsSized (StablePtr a) PtrSize | |
IsType a => IsSized (Ptr a) PtrSize | |
StructFields as => IsSized (PackedStruct as) UnknownSize | |
StructFields as => IsSized (Struct as) UnknownSize | |
Pos n => IsSized (WordN n) n | |
Pos n => IsSized (IntN n) n | |
(IsPowerOf2 n, IsPrimitive a, IsSized a s, Mul n s ns, Pos ns) => IsSized (Vector n a) ns | |
(Nat n, IsSized a s, Mul n s ns, Pos ns) => IsSized (Array n a) ns |
class IsType a => IsFunction a Source
Function type.
IsFirstClass a => IsFunction (IO a) | |
IsFirstClass a => IsFunction (VarArgs a) | |
(IsFirstClass a, IsFunction b) => IsFunction (a -> b) | |
(IsTuple a, IsFunction b) => IsFunction (:+-> a b) |
type UnknownSize = D99Source
Others
class Pos n => IsPowerOf2 n Source
(LogBase D2 n l, ExpBase D2 l n) => IsPowerOf2 n |
class IsType a => NumberOfElements n a | a -> nSource
Number of elements for instructions that handle both primitive and vector types
Structs
Functions of tuples
TupleFunction is used for distinction of tuple and atomic arguments.
The a function of type a -> b :+-> c -> d
has atomic arguments of type a
and c
and an argument of a type b
that can be a tuple.
If a = (Word8,Int16)
then the corresponding LLVM value is of type Value (Word8,Int16)
.
However, I do not know of a LLVM function that accepts values of this type.
If b = (Word8,Int16)
then the corresponding LLVM value is of type (Value Word8, Value Int16)
.
(IsTuple a, IsFunction b) => IsFunction (:+-> a b) | |
(IsTuple a, IsFunction b) => IsType (:+-> a b) | |
(GenericTuple a, Translatable b) => Translatable (:+-> a b) | |
(MakeValueTuple a a', FunctionArgs b b' r) => FunctionArgs (:+-> a b) (:+-> a' b') r |
IsTuple Bool | |
IsTuple Double | |
IsTuple Float | |
IsTuple Int8 | |
IsTuple Int16 | |
IsTuple Int32 | |
IsTuple Int64 | |
IsTuple Word8 | |
IsTuple Word16 | |
IsTuple Word32 | |
IsTuple Word64 | |
IsTuple () | |
IsTuple FP128 | |
IsTuple (StablePtr a) | |
IsType a => IsTuple (Ptr a) | |
Pos n => IsTuple (WordN n) | |
Pos n => IsTuple (IntN n) | |
(IsTuple a, IsTuple b) => IsTuple (a, b) | |
(IsPowerOf2 n, IsPrimitive a) => IsTuple (Vector n a) | |
(IsTuple a, IsTuple b, IsTuple c) => IsTuple (a, b, c) |
Type tests
Type descriptor, used to convey type information through the LLVM API.
isFloating :: IsArithmetic a => a -> BoolSource
Typeable1 VarArgs | |
IsFirstClass a => IsFunction (VarArgs a) | |
IsType (VarArgs a) | |
CastVarArgs (VarArgs a) (IO a) | |
(IsFirstClass a, CastVarArgs (VarArgs b) c) => CastVarArgs (VarArgs b) (a -> c) |
class CastVarArgs a b Source
Define what vararg types are permissible.
CastVarArgs (VarArgs a) (IO a) | |
(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
.
Typeable1 IntN | |
Pos n => NumberOfElements D1 (IntN n) | |
PosI n => Show (IntN n) | |
Pos n => IsTuple (IntN n) | |
Pos n => IsFirstClass (IntN n) | |
Pos n => IsPrimitive (IntN n) | |
Pos n => IsIntegerOrPointer (IntN n) | |
Pos n => IsInteger (IntN n) | |
Pos n => IsArithmetic (IntN n) | |
Pos n => IsType (IntN n) | |
Pos n => IsSized (IntN n) n | |
Pos n => FunctionArgs (IO (IntN n)) (FA (IntN n)) (FA (IntN n)) |
newtype Pos n => WordN n Source
Variable sized unsigned integer.
The n parameter should belong to PosI
.
Typeable1 WordN | |
Pos n => NumberOfElements D1 (WordN n) | |
PosI n => Show (WordN n) | |
Pos n => IsTuple (WordN n) | |
Pos n => IsFirstClass (WordN n) | |
Pos n => IsPrimitive (WordN n) | |
Pos n => IsIntegerOrPointer (WordN n) | |
Pos n => IsInteger (WordN n) | |
Pos n => IsArithmetic (WordN n) | |
Pos n => IsType (WordN n) | |
Pos n => IsSized (WordN n) n | |
Pos n => FunctionArgs (IO (WordN n)) (FA (WordN n)) (FA (WordN n)) |
128 bit floating point.
newtype Nat n => Array n a Source
Fixed sized arrays, the array size is encoded in the n parameter.
Array [a] |
Typeable2 Array | |
(Show a, NatI n) => Show (Array n a) | |
(Nat n, IsType a, IsSized a s) => IsFirstClass (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 | |
(IsFirstClass a, Nat n) => GetValue (Array n a) Word64 a | |
(IsFirstClass a, Nat n) => GetValue (Array n a) Word32 a | |
(GetElementPtr o i n, IsIndexArg a) => GetElementPtr (Array k o) (a, i) n |
Fixed sized vector, the array size is encoded in the n parameter.
Vector [a] |
data Ptr a
A value of type
represents a pointer to an object, or an
array of objects, which may be marshalled to or from Haskell values
of type Ptr
aa
.
The type a
will often be an instance of class
Foreign.Storable.Storable which provides the marshalling operations.
However this is not essential, and you can provide your own operations
to access the pointer. For example you might write small foreign
functions to get or set the fields of a C struct
.
Typeable1 Ptr | |
Eq (Ptr a) | |
Ord (Ptr a) | |
Show (Ptr a) | |
Storable (Ptr a) | |
IsType a => IsTuple (Ptr a) | |
IsType a => IsFirstClass (Ptr a) | |
IsType a => IsIntegerOrPointer (Ptr a) | |
IsType a => IsType (Ptr a) | |
IsType a => IsConst (Ptr a) | |
GenericTuple (Ptr a) | |
Generic (Ptr a) | |
IsType a => IsSized (Ptr a) PtrSize | |
CmpRet (Ptr a) Bool | |
IsType a => MakeValueTuple (Ptr a) (Value (Ptr a)) | |
IsType a => FunctionArgs (IO (Ptr a)) (FA (Ptr a)) (FA (Ptr a)) |
Label type, produced by a basic block.
Struct types; a list (nested tuple) of component types.
Struct a |
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 | |
(GetField as i a, Nat i) => GetValue (Struct as) i a | |
(GetElementPtr o i n, GetField fs a o, Nat a) => GetElementPtr (Struct fs) (a, i) n |
newtype PackedStruct a Source
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 ConstValue a Source
Typeable1 ConstValue | |
Show (ConstValue a) | |
IsIndexArg (ConstValue Int32) | |
IsIndexArg (ConstValue Int64) | |
IsIndexArg (ConstValue Word32) | |
IsIndexArg (ConstValue Word64) | |
AllocArg (ConstValue Word32) | |
ABinOp (ConstValue a) (ConstValue a) (ConstValue a) | |
ABinOp (ConstValue a) (Value a) (Value a) | |
ABinOp (Value a) (ConstValue a) (Value a) | |
(IsConst a, IsConstStruct cs as) => IsConstStruct (ConstValue a, cs) (a, as) |
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
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.
constStruct :: IsConstStruct c a => c -> ConstValue (Struct a)Source
Make a constant struct.
constPackedStruct :: IsConstStruct c a => c -> ConstValue (PackedStruct a)Source
Make a constant packed struct.
fromVector :: MkVector va n a => Vector n a -> vaSource
vector :: forall a n. Pos n => [a] -> Vector n aSource
Make a constant vector. Replicates or truncates the list to get length n.
This behaviour is consistent with that of LLVM.Core.CodeGen.constVector
.
Code generation
data CodeGenFunction r a Source
Typeable2 CodeGenFunction | |
LiftTuple r b b' => LiftTuple r (CodeGenFunction r a, b) (a, b') | |
Monad (CodeGenFunction r) | |
Functor (CodeGenFunction r) | |
MonadIO (CodeGenFunction r) | |
MonadState (CGFState r) (CodeGenFunction r) | |
CallArgs (IO a) (CodeGenFunction r (Value a)) | |
UncurryN (CodeGenFunction r a) (() -> CodeGenFunction r a) | |
ArithFunction b b' => ArithFunction (CodeGenFunction r a -> b) (a -> b') | |
Ret a r => ArithFunction (CodeGenFunction r a) (CodeGenFunction r ()) |
data CodeGenModule a Source
Functions
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.
:: forall a . IsFunction a | |
=> Linkage | |
-> String | Function name |
-> CodeGenModule (Function a) |
Create a new named function.
:: forall f g r . FunctionArgs f g (CodeGenFunction r ()) | |
=> Function f | Function to define (created by |
-> g | Function body. |
-> CodeGenModule () |
Define a function body. The basic block returned by the function is the function entry point.
:: (IsFunction f, FunctionArgs f g (CodeGenFunction r ())) | |
=> Linkage | |
-> g | Function body. |
-> CodeGenModule (Function f) |
Create a new function with the given body.
:: (IsFunction f, FunctionArgs f g (CodeGenFunction r ())) | |
=> Linkage | |
-> String | |
-> g | Function body. |
-> CodeGenModule (Function f) |
Create a new function with the given body.
type TFunction a = CodeGenModule (Function a)Source
class Undefined a => ValueTuple a whereSource
buildTuple :: FunctionRef -> State Int aSource
ValueTuple () | |
IsFirstClass a => ValueTuple (Value a) | |
(ValueTuple a, ValueTuple b) => ValueTuple (a, b) | |
(ValueTuple a, ValueTuple b, ValueTuple c) => ValueTuple (a, b, c) |
undefTuple :: aSource
class (IsTuple haskellValue, ValueTuple llvmValue) => MakeValueTuple haskellValue llvmValue | haskellValue -> llvmValue whereSource
valueTupleOf :: haskellValue -> llvmValueSource
MakeValueTuple () () | |
MakeValueTuple Bool (Value Bool) | |
MakeValueTuple Double (Value Double) | |
MakeValueTuple Float (Value Float) | |
MakeValueTuple Int8 (Value Int8) | |
MakeValueTuple Int16 (Value Int16) | |
MakeValueTuple Int32 (Value Int32) | |
MakeValueTuple Int64 (Value Int64) | |
MakeValueTuple Word8 (Value Word8) | |
MakeValueTuple Word16 (Value Word16) | |
MakeValueTuple Word32 (Value Word32) | |
MakeValueTuple Word64 (Value Word64) | |
MakeValueTuple (StablePtr a) (Value (StablePtr a)) | |
IsType a => MakeValueTuple (Ptr a) (Value (Ptr a)) | |
(IsPowerOf2 n, IsPrimitive a, IsConst a) => MakeValueTuple (Vector n a) (Value (Vector n a)) | |
(MakeValueTuple ah al, MakeValueTuple bh bl) => MakeValueTuple (ah, bh) (al, bl) | |
(MakeValueTuple ah al, MakeValueTuple bh bl, MakeValueTuple ch cl) => MakeValueTuple (ah, bh, ch) (al, bl, cl) |
Global variable creation
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.
If LLVM cannot resolve its name, then you may try staticFunction
.
staticFunction :: IsFunction f => FunPtr f -> CodeGenFunction r (Function f)Source
Make an external C function with a fixed address callable from LLVM code. This callback function can also be a Haskell function, that was imported like
foreign import ccall "&nextElement" nextElementFunPtr :: FunPtr (StablePtr (IORef [Word32]) -> IO Word32)
See examples/List.hs
.
When you only use externFunction
, then LLVM cannot resolve the name.
(However, I do not know why.)
Thus staticFunction
manages a list of static functions.
This list is automatically installed by ExecutionEngine.simpleFunction
and can be manually obtained by getGlobalMappings
and installed by ExecutionEngine.addGlobalMappings
.
"Installing" means calling LLVM's addGlobalMapping
according to
http://old.nabble.com/jit-with-external-functions-td7769793.html.
data GlobalMappings Source
getGlobalMappings :: CodeGenModule GlobalMappingsSource
Get a list created by calls to staticFunction
that must be passed to the execution engine
via LLVM.ExecutionEngine.addGlobalMappings
.
type TGlobal a = CodeGenModule (Global a)Source
Globals
An enumeration for the kinds of linkage for global values.
ExternalLinkage | Externally visible function |
AvailableExternallyLinkage | |
LinkOnceAnyLinkage | Keep one copy of function when linking (inline) |
LinkOnceODRLinkage | Same, but only replaced by something equivalent. |
WeakAnyLinkage | Keep one copy of named function when linking (weak) |
WeakODRLinkage | Same, but only replaced by something equivalent. |
AppendingLinkage | Special purpose, only applies to global arrays |
InternalLinkage | Rename collisions when linking (static functions) |
PrivateLinkage | Like Internal, but omit from symbol table |
DLLImportLinkage | Function to be imported from DLL |
DLLExportLinkage | Function to be accessible from DLL |
ExternalWeakLinkage | ExternalWeak linkage description |
GhostLinkage | Stand-in functions for streaming fns from BC files |
CommonLinkage | Tentative definitions |
LinkerPrivateLinkage | Like Private, but linker removes. |
Basic blocks
data BasicBlock Source
A basic block is a sequence of non-branching instructions, terminated by a control flow instruction.
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.
castVarArgs :: CastVarArgs a b => Function a -> Function bSource
Convert a varargs function to a regular function.