Safe Haskell | None |
---|
- Initialize
- Modules
- Instructions
- ADT representation of IR
- Terminator instructions
- Arithmetic binary operations
- Logical binary operations
- Vector operations
- Aggregate operation
- Memory access
- Conversions
- Comparison
- Fast math
- 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
- setTarget :: String -> CodeGenModule ()
- hostTriple :: String
- data PassManager
- createPassManager :: IO PassManager
- createFunctionPassManager :: Module -> IO PassManager
- writeBitcodeToFile :: String -> Module -> IO ()
- readBitcodeFromFile :: String -> IO Module
- getModuleValues :: Module -> IO [(String, ModuleValue)]
- getFunctions :: Module -> IO [(String, Value)]
- getGlobalVariables :: Module -> IO [(String, Value)]
- data ModuleValue
- castModuleValue :: forall a. IsType a => ModuleValue -> Maybe (Value a)
- data BinOpDesc
- data InstrDesc
- = IDRet TypeDesc ArgDesc
- | IDRetVoid
- | IDBrCond ArgDesc ArgDesc ArgDesc
- | IDBrUncond ArgDesc
- | IDSwitch [(ArgDesc, ArgDesc)]
- | IDIndirectBr
- | IDInvoke
- | IDUnwind
- | IDUnreachable
- | IDBinOp BinOpDesc TypeDesc ArgDesc ArgDesc
- | IDAlloca TypeDesc Int Int
- | IDLoad TypeDesc ArgDesc
- | IDStore TypeDesc ArgDesc ArgDesc
- | IDGetElementPtr TypeDesc [ArgDesc]
- | IDTrunc TypeDesc TypeDesc ArgDesc
- | IDZExt TypeDesc TypeDesc ArgDesc
- | IDSExt TypeDesc TypeDesc ArgDesc
- | IDFPtoUI TypeDesc TypeDesc ArgDesc
- | IDFPtoSI TypeDesc TypeDesc ArgDesc
- | IDUItoFP TypeDesc TypeDesc ArgDesc
- | IDSItoFP TypeDesc TypeDesc ArgDesc
- | IDFPTrunc TypeDesc TypeDesc ArgDesc
- | IDFPExt TypeDesc TypeDesc ArgDesc
- | IDPtrToInt TypeDesc TypeDesc ArgDesc
- | IDIntToPtr TypeDesc TypeDesc ArgDesc
- | IDBitcast TypeDesc TypeDesc ArgDesc
- | IDICmp IntPredicate ArgDesc ArgDesc
- | IDFCmp FPPredicate ArgDesc ArgDesc
- | IDPhi TypeDesc [(ArgDesc, ArgDesc)]
- | IDCall TypeDesc ArgDesc [ArgDesc]
- | IDSelect TypeDesc ArgDesc ArgDesc
- | IDUserOp1
- | IDUserOp2
- | IDVAArg
- | IDExtractElement
- | IDInsertElement
- | IDShuffleVector
- | IDExtractValue
- | IDInsertValue
- | IDInvalidOp
- data ArgDesc
- getInstrDesc :: ValueRef -> IO (String, InstrDesc)
- 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 r => BasicBlock -> BasicBlock -> Function f -> g
- invokeWithConv :: CallArgs f g r => CallingConvention -> BasicBlock -> BasicBlock -> Function f -> g
- invokeFromFunction :: BasicBlock -> BasicBlock -> Function f -> Call f
- invokeWithConvFromFunction :: CallingConvention -> BasicBlock -> BasicBlock -> Function f -> Call f
- unreachable :: CodeGenFunction r Terminate
- add :: (IsArithmetic c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)
- sub :: (IsArithmetic c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)
- mul :: (IsArithmetic c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)
- neg :: (IsArithmetic b, AUnOp a, a ~ v b) => a -> CodeGenFunction r a
- iadd :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)
- isub :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)
- imul :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)
- ineg :: (IsInteger b, AUnOp a, a ~ v b) => a -> CodeGenFunction r a
- fadd :: (IsFloating c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)
- fsub :: (IsFloating c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)
- fmul :: (IsFloating c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)
- fneg :: (IsFloating b, AUnOp a, a ~ v b) => a -> CodeGenFunction r a
- idiv :: forall a b c r v. (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)
- irem :: forall a b c r v. (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)
- udiv :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)
- sdiv :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)
- fdiv :: (IsFloating c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)
- urem :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)
- srem :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)
- frem :: (IsFloating c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)
- shl :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)
- lshr :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)
- ashr :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)
- and :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)
- or :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)
- xor :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)
- inv :: (IsInteger b, AUnOp a, a ~ v b) => a -> CodeGenFunction r a
- extractelement :: Positive n => Value (Vector n a) -> Value Word32 -> CodeGenFunction r (Value a)
- insertelement :: Positive n => Value (Vector n a) -> Value a -> Value Word32 -> CodeGenFunction r (Value (Vector n a))
- shufflevector :: (Positive n, Positive m) => Value (Vector n a) -> Value (Vector n a) -> ConstValue (Vector m Word32) -> CodeGenFunction r (Value (Vector m a))
- extractvalue :: forall r agg i. GetValue agg i => Value agg -> i -> CodeGenFunction r (Value (ValueType agg i))
- insertvalue :: forall r agg i. GetValue agg i => Value agg -> Value (ValueType agg i) -> i -> CodeGenFunction r (Value agg)
- malloc :: forall a r. IsSized a => CodeGenFunction r (Value (Ptr a))
- arrayMalloc :: forall a r s. (IsSized a, AllocArg s) => s -> CodeGenFunction r (Value (Ptr a))
- alloca :: forall a r. IsSized a => CodeGenFunction r (Value (Ptr a))
- arrayAlloca :: forall a r s. (IsSized a, AllocArg s) => s -> CodeGenFunction r (Value (Ptr a))
- free :: IsType a => Value (Ptr a) -> CodeGenFunction r ()
- load :: Value (Ptr a) -> CodeGenFunction r (Value a)
- store :: Value a -> Value (Ptr a) -> CodeGenFunction r ()
- getElementPtr :: forall a o i r. (GetElementPtr o i, IsIndexArg a) => Value (Ptr o) -> (a, i) -> CodeGenFunction r (Value (Ptr (ElementPtrType o i)))
- getElementPtr0 :: GetElementPtr o i => Value (Ptr o) -> i -> CodeGenFunction r (Value (Ptr (ElementPtrType o i)))
- trunc :: (IsInteger a, IsInteger b, NumberOfElements a ~ NumberOfElements b, IsSized a, IsSized b, SizeOf a :>: SizeOf b) => Value a -> CodeGenFunction r (Value b)
- zext :: (IsInteger a, IsInteger b, NumberOfElements a ~ NumberOfElements b, IsSized a, IsSized b, SizeOf a :<: SizeOf b) => Value a -> CodeGenFunction r (Value b)
- sext :: (IsInteger a, IsInteger b, NumberOfElements a ~ NumberOfElements b, IsSized a, IsSized b, SizeOf a :<: SizeOf b) => Value a -> CodeGenFunction r (Value b)
- ext :: forall a b r. (IsInteger a, IsInteger b, NumberOfElements a ~ NumberOfElements b, Signed a ~ Signed b, IsSized a, IsSized b, SizeOf a :<: SizeOf b) => Value a -> CodeGenFunction r (Value b)
- zadapt :: forall a b r. (IsInteger a, IsInteger b, NumberOfElements a ~ NumberOfElements b) => Value a -> CodeGenFunction r (Value b)
- sadapt :: forall a b r. (IsInteger a, IsInteger b, NumberOfElements a ~ NumberOfElements b) => Value a -> CodeGenFunction r (Value b)
- adapt :: forall a b r. (IsInteger a, IsInteger b, NumberOfElements a ~ NumberOfElements b, Signed a ~ Signed b) => Value a -> CodeGenFunction r (Value b)
- fptrunc :: (IsFloating a, IsFloating b, NumberOfElements a ~ NumberOfElements b, IsSized a, IsSized b, SizeOf a :>: SizeOf b) => Value a -> CodeGenFunction r (Value b)
- fpext :: (IsFloating a, IsFloating b, NumberOfElements a ~ NumberOfElements b, IsSized a, IsSized b, SizeOf a :<: SizeOf b) => Value a -> CodeGenFunction r (Value b)
- fptoui :: (IsFloating a, IsInteger b, NumberOfElements a ~ NumberOfElements b) => Value a -> CodeGenFunction r (Value b)
- fptosi :: (IsFloating a, IsInteger b, NumberOfElements a ~ NumberOfElements b) => Value a -> CodeGenFunction r (Value b)
- fptoint :: forall r a b. (IsFloating a, IsInteger b, NumberOfElements a ~ NumberOfElements b) => Value a -> CodeGenFunction r (Value b)
- uitofp :: (IsInteger a, IsFloating b, NumberOfElements a ~ NumberOfElements b) => Value a -> CodeGenFunction r (Value b)
- sitofp :: (IsInteger a, IsFloating b, NumberOfElements a ~ NumberOfElements b) => Value a -> CodeGenFunction r (Value b)
- inttofp :: forall r a b. (IsInteger a, IsFloating b, NumberOfElements a ~ NumberOfElements 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, IsSized b, SizeOf a ~ SizeOf b) => Value a -> CodeGenFunction r (Value b)
- bitcastElements :: (Positive n, IsPrimitive a, IsPrimitive b, IsSized a, IsSized b, SizeOf a ~ SizeOf b) => Value (Vector n a) -> CodeGenFunction r (Value (Vector n b))
- data CmpPredicate
- data IntPredicate
- data FPPredicate
- class CmpRet (CmpType a b) => CmpOp a b
- class CmpRet c where
- type CmpResult c :: *
- type CmpValueResult a b = CmpValue a b (CmpResult (CmpType a b))
- cmp :: forall a b r. CmpOp a b => CmpPredicate -> a -> b -> CodeGenFunction r (CmpValueResult a b)
- pcmp :: (CmpOp a b, Ptr c ~ CmpType a b) => IntPredicate -> a -> b -> CodeGenFunction r (CmpValueResult a b)
- icmp :: (IsIntegerOrPointer c, CmpOp a b, c ~ CmpType a b) => IntPredicate -> a -> b -> CodeGenFunction r (CmpValueResult a b)
- fcmp :: (IsFloating c, CmpOp a b, c ~ CmpType a b) => FPPredicate -> a -> b -> CodeGenFunction r (CmpValueResult a b)
- select :: (IsFirstClass a, CmpRet a) => Value (CmpResult a) -> Value a -> Value a -> CodeGenFunction r (Value a)
- setHasNoNaNs :: IsFloating a => Bool -> Value a -> CodeGenFunction r ()
- setHasNoInfs :: IsFloating a => Bool -> Value a -> CodeGenFunction r ()
- setHasNoSignedZeros :: IsFloating a => Bool -> Value a -> CodeGenFunction r ()
- setHasAllowReciprocal :: IsFloating a => Bool -> Value a -> CodeGenFunction r ()
- setFastMath :: IsFloating a => Bool -> Value a -> CodeGenFunction r ()
- 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 r => Function f -> g
- callWithConv :: CallArgs f g r => CallingConvention -> Function f -> g
- callFromFunction :: Function a -> Call a
- callWithConvFromFunction :: CallingConvention -> Function f -> Call f
- data Call a
- applyCall :: Call (a -> b) -> Value a -> Call b
- runCall :: Call (IO a) -> CodeGenFunction r (Value a)
- type Terminate = ()
- class Ret a r
- class (f ~ CalledFunction g, r ~ CallerResult g, g ~ CallerFunction f r) => CallArgs f g r
- class AUnOp a
- class ABinOp a b where
- type ABinOpResult a b :: *
- class IsConst a
- class IsFunction f => FunctionArgs f where
- type FunctionCodeGen f :: *
- type FunctionResult f :: *
- class AllocArg a
- class GetElementPtr optr ixs where
- type ElementPtrType optr ixs :: *
- class IsIndexArg a
- class GetValue agg ix where
- type ValueType agg ix :: *
- class GetField as i where
- type FieldType as i :: *
- class IsType a where
- class Integer n => Natural n
- class Natural n => Positive n
- class IsFirstClass a => IsArithmetic a where
- data ArithmeticType a
- class (IsArithmetic a, IsIntegerOrPointer a) => IsInteger a where
- type Signed a :: *
- class IsIntegerOrPointer a
- class IsArithmetic a => IsFloating a
- class (IsType a, NumberOfElements a ~ D1) => IsPrimitive a
- class IsType a => IsFirstClass a
- class (IsType a, Natural (SizeOf a)) => IsSized a where
- type SizeOf a :: *
- sizeOf :: TypeDesc -> Integer
- class IsType a => IsFunction a
- class IsType a => IsScalarOrVector a where
- type NumberOfElements a :: *
- class StructFields as
- type UnknownSize = D99
- type :& a as = (a, as)
- (&) :: a -> as -> a :& as
- data TypeDesc
- isFloating :: IsArithmetic a => Proxy a -> Bool
- isSigned :: IsInteger a => Proxy a -> Bool
- typeRef :: IsType a => Proxy a -> IO TypeRef
- unsafeTypeRef :: IsType a => Proxy a -> TypeRef
- typeName :: IsType a => Proxy a -> String
- intrinsicTypeName :: IsType a => Proxy a -> String
- typeDesc2 :: TypeRef -> IO TypeDesc
- data VarArgs a
- class CastVarArgs a b
- newtype IntN n = IntN Integer
- newtype WordN n = WordN Integer
- newtype FP128 = FP128 Rational
- newtype Array n a = Array [a]
- newtype Vector n a = Vector (FixedList (ToUnary n) a)
- data Label
- newtype Struct a = Struct a
- newtype PackedStruct a = PackedStruct a
- type FixedList n = List n
- 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)
- withString :: String -> (forall n. Natural n => Global (Array n Word8) -> CodeGenModule a) -> CodeGenModule a
- withStringNul :: String -> (forall n. Natural n => Global (Array n Word8) -> CodeGenModule a) -> CodeGenModule a
- constVector :: forall a n u. (Positive n, ToUnary n ~ u, Length (FixedList u) ~ u) => FixedList u (ConstValue a) -> ConstValue (Vector n a)
- constArray :: forall a n. (IsSized a, Natural n) => [ConstValue a] -> ConstValue (Array n a)
- constCyclicVector :: forall a n. Positive n => T [] (ConstValue a) -> ConstValue (Vector n a)
- constCyclicArray :: forall a n. (IsSized a, Natural n) => T [] (ConstValue a) -> ConstValue (Vector n a)
- constStruct :: IsConstStruct c => c -> ConstValue (Struct (ConstStructOf c))
- constPackedStruct :: IsConstStruct c => c -> ConstValue (PackedStruct (ConstStructOf c))
- toVector :: MkVector n a => Tuple n a -> Vector n a
- fromVector :: MkVector n a => Vector n a -> Tuple n a
- vector :: Positive n => FixedList (ToUnary n) a -> Vector n a
- cyclicVector :: Positive n => T [] a -> Vector n a
- data CodeGenFunction r a
- data CodeGenModule a
- type Function a = Value (FunPtr a)
- newFunction :: forall a. IsFunction a => Linkage -> CodeGenModule (Function a)
- newNamedFunction :: forall a. IsFunction a => Linkage -> String -> CodeGenModule (Function a)
- defineFunction :: forall f. FunctionArgs f => Function f -> FunctionCodeGen f -> CodeGenModule ()
- createFunction :: FunctionArgs f => Linkage -> FunctionCodeGen f -> CodeGenModule (Function f)
- createNamedFunction :: FunctionArgs f => Linkage -> String -> FunctionCodeGen f -> CodeGenModule (Function f)
- setFuncCallConv :: Function a -> CallingConvention -> CodeGenModule ()
- type TFunction a = CodeGenModule (Function a)
- liftCodeGenModule :: CodeGenModule a -> CodeGenFunction r a
- getParams :: Value -> IO [(String, Value)]
- 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 :: forall f r. IsFunction f => FunPtr f -> CodeGenFunction r (Function f)
- staticNamedFunction :: forall f r. IsFunction f => String -> FunPtr f -> CodeGenFunction r (Function f)
- externGlobal :: forall a r. IsType a => Bool -> String -> CodeGenFunction r (Global a)
- staticGlobal :: forall a r. IsType a => Bool -> Ptr a -> CodeGenFunction r (Global a)
- data GlobalMappings
- getGlobalMappings :: CodeGenModule GlobalMappings
- type TGlobal a = CodeGenModule (Global a)
- data Linkage
- = ExternalLinkage
- | AvailableExternallyLinkage
- | LinkOnceAnyLinkage
- | LinkOnceODRLinkage
- | LinkOnceODRAutoHideLinkage
- | WeakAnyLinkage
- | WeakODRLinkage
- | AppendingLinkage
- | InternalLinkage
- | PrivateLinkage
- | DLLImportLinkage
- | DLLExportLinkage
- | ExternalWeakLinkage
- | GhostLinkage
- | CommonLinkage
- | LinkerPrivateLinkage
- | LinkerPrivateWeakLinkage
- data BasicBlock
- newBasicBlock :: CodeGenFunction r BasicBlock
- newNamedBasicBlock :: String -> CodeGenFunction r BasicBlock
- defineBasicBlock :: BasicBlock -> CodeGenFunction r ()
- createBasicBlock :: CodeGenFunction r BasicBlock
- getCurrentBasicBlock :: CodeGenFunction r BasicBlock
- getBasicBlocks :: Value -> IO [(String, Value)]
- fromLabel :: Value Label -> BasicBlock
- toLabel :: BasicBlock -> Value Label
- getInstructions :: Value -> IO [(String, Value)]
- getOperands :: Value -> IO [(String, Value)]
- hasUsers :: Value -> IO Bool
- getUsers :: [Use] -> IO [(String, Value)]
- getUses :: Value -> IO [Use]
- getUser :: Use -> IO Value
- isChildOf :: BasicBlock -> Value -> IO Bool
- getDep :: Use -> IO (String, String)
- addAttributes :: Value a -> Int -> [Attribute] -> CodeGenFunction r ()
- data Attribute
- = ZExtAttribute
- | SExtAttribute
- | NoReturnAttribute
- | InRegAttribute
- | StructRetAttribute
- | NoUnwindAttribute
- | NoAliasAttribute
- | ByValAttribute
- | NestAttribute
- | ReadNoneAttribute
- | ReadOnlyAttribute
- | NoInlineAttribute
- | AlwaysInlineAttribute
- | OptimizeForSizeAttribute
- | StackProtectAttribute
- | StackProtectReqAttribute
- | NoCaptureAttribute
- | NoRedZoneAttribute
- | NoImplicitFloatAttribute
- | NakedAttribute
- castVarArgs :: CastVarArgs a b => Function a -> Function b
- dumpValue :: Value a -> IO ()
- dumpType :: Value a -> IO ()
- getValueName :: Value a -> IO String
- annotateValueList :: [Value] -> IO [(String, Value)]
Initialize
initializeNativeTarget :: IO ()
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.
setTarget :: String -> CodeGenModule ()Source
hostTriple :: String
createPassManager :: IO PassManagerSource
Create a pass manager.
createFunctionPassManager :: Module -> 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
getFunctions :: Module -> IO [(String, Value)]Source
getGlobalVariables :: Module -> IO [(String, Value)]Source
castModuleValue :: forall a. IsType a => ModuleValue -> Maybe (Value a)Source
Instructions
ADT representation of IR
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 in 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 r | |
=> BasicBlock | Normal return point. |
-> BasicBlock | Exception return point. |
-> Function f | Function to call. |
-> g |
Call a function with exception handling.
:: CallArgs f g r | |
=> CallingConvention | Calling convention |
-> BasicBlock | Normal return point. |
-> BasicBlock | Exception return point. |
-> Function f | Function to call. |
-> g |
Call a function with exception handling. This also sets the calling convention of the call to the function. As LLVM itself defines, if the calling conventions of the calling instruction and the function being called are different, undefined behavior results.
:: BasicBlock | Normal return point. |
-> BasicBlock | Exception return point. |
-> Function f | Function to call. |
-> Call f |
invokeWithConvFromFunctionSource
:: CallingConvention | Calling convention |
-> BasicBlock | Normal return point. |
-> BasicBlock | Exception return point. |
-> Function f | Function to call. |
-> Call f |
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 ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)Source
sub :: (IsArithmetic c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)Source
mul :: (IsArithmetic c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)Source
neg :: (IsArithmetic b, AUnOp a, a ~ v b) => a -> CodeGenFunction r aSource
iadd :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)Source
isub :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)Source
imul :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)Source
ineg :: (IsInteger b, AUnOp a, a ~ v b) => a -> CodeGenFunction r aSource
fadd :: (IsFloating c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)Source
fsub :: (IsFloating c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)Source
fmul :: (IsFloating c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)Source
fneg :: (IsFloating b, AUnOp a, a ~ v b) => a -> CodeGenFunction r aSource
idiv :: forall a b c r v. (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)Source
signed or unsigned integer division depending on the type
irem :: forall a b c r v. (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)Source
signed or unsigned remainder depending on the type
udiv :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)Source
Deprecated: use idiv instead
sdiv :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)Source
Deprecated: use idiv instead
fdiv :: (IsFloating c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)Source
Floating point division.
urem :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)Source
Deprecated: use irem instead
srem :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)Source
Deprecated: use irem instead
frem :: (IsFloating c, ABinOp a b, v c ~ ABinOpResult a b) => 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 ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)Source
lshr :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)Source
ashr :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)Source
and :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)Source
or :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)Source
xor :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c)Source
inv :: (IsInteger b, AUnOp a, a ~ v b) => a -> CodeGenFunction r aSource
Vector operations
:: Positive n | |
=> Value (Vector n a) | Vector |
-> Value Word32 | Index into the vector |
-> CodeGenFunction r (Value a) |
Get a value from a vector.
:: Positive n | |
=> 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 :: (Positive n, Positive m) => Value (Vector n a) -> Value (Vector n a) -> ConstValue (Vector m Word32) -> CodeGenFunction r (Value (Vector m a))Source
Permute vector.
Aggregate operation
:: forall r agg i . GetValue agg i | |
=> Value agg | Aggregate |
-> i | Index into the aggregate |
-> CodeGenFunction r (Value (ValueType agg i)) |
Get a value from an aggregate.
:: forall r agg i . GetValue agg i | |
=> Value agg | Aggregate |
-> Value (ValueType agg i) | Value to insert |
-> i | Index into the aggregate |
-> CodeGenFunction r (Value agg) |
Insert a value into an aggregate, nondestructive.
Memory access
arrayMalloc :: forall a r s. (IsSized a, AllocArg s) => s -> CodeGenFunction r (Value (Ptr a))Source
Allocate heap (array) memory.
arrayAlloca :: forall a r s. (IsSized a, 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.
:: Value a | Value to store. |
-> Value (Ptr a) | Address to store to. |
-> CodeGenFunction r () |
Store a value in memory
getElementPtr :: forall a o i r. (GetElementPtr o i, IsIndexArg a) => Value (Ptr o) -> (a, i) -> CodeGenFunction r (Value (Ptr (ElementPtrType o i)))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 => Value (Ptr o) -> i -> CodeGenFunction r (Value (Ptr (ElementPtrType o i)))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, NumberOfElements a ~ NumberOfElements b, IsSized a, IsSized b, SizeOf a :>: SizeOf b) => Value a -> CodeGenFunction r (Value b)Source
Truncate a value to a shorter bit width.
zext :: (IsInteger a, IsInteger b, NumberOfElements a ~ NumberOfElements b, IsSized a, IsSized b, SizeOf a :<: SizeOf b) => Value a -> CodeGenFunction r (Value b)Source
Zero extend a value to a wider width.
If possible, use ext
that chooses the right padding according to the types
sext :: (IsInteger a, IsInteger b, NumberOfElements a ~ NumberOfElements b, IsSized a, IsSized b, SizeOf a :<: SizeOf b) => Value a -> CodeGenFunction r (Value b)Source
Sign extend a value to wider width.
If possible, use ext
that chooses the right padding according to the types
ext :: forall a b r. (IsInteger a, IsInteger b, NumberOfElements a ~ NumberOfElements b, Signed a ~ Signed b, IsSized a, IsSized b, SizeOf a :<: SizeOf b) => Value a -> CodeGenFunction r (Value b)Source
Extend a value to wider width. If the target type is signed, then preserve the sign, If the target type is unsigned, then extended by zeros.
zadapt :: forall a b r. (IsInteger a, IsInteger b, NumberOfElements a ~ NumberOfElements b) => Value a -> CodeGenFunction r (Value b)Source
sadapt :: forall a b r. (IsInteger a, IsInteger b, NumberOfElements a ~ NumberOfElements b) => Value a -> CodeGenFunction r (Value b)Source
adapt :: forall a b r. (IsInteger a, IsInteger b, NumberOfElements a ~ NumberOfElements b, Signed a ~ Signed b) => Value a -> CodeGenFunction r (Value b)Source
fptrunc :: (IsFloating a, IsFloating b, NumberOfElements a ~ NumberOfElements b, IsSized a, IsSized b, SizeOf a :>: SizeOf b) => Value a -> CodeGenFunction r (Value b)Source
Truncate a floating point value.
fpext :: (IsFloating a, IsFloating b, NumberOfElements a ~ NumberOfElements b, IsSized a, IsSized b, SizeOf a :<: SizeOf b) => Value a -> CodeGenFunction r (Value b)Source
Extend a floating point value.
fptoui :: (IsFloating a, IsInteger b, NumberOfElements a ~ NumberOfElements b) => Value a -> CodeGenFunction r (Value b)Source
Deprecated: use fptoint since it is type-safe with respect to signs
Convert a floating point value to an unsigned integer.
fptosi :: (IsFloating a, IsInteger b, NumberOfElements a ~ NumberOfElements b) => Value a -> CodeGenFunction r (Value b)Source
Deprecated: use fptoint since it is type-safe with respect to signs
Convert a floating point value to a signed integer.
fptoint :: forall r a b. (IsFloating a, IsInteger b, NumberOfElements a ~ NumberOfElements b) => Value a -> CodeGenFunction r (Value b)Source
Convert a floating point value to an integer.
It is mapped to fptosi
or fptoui
depending on the type a
.
uitofp :: (IsInteger a, IsFloating b, NumberOfElements a ~ NumberOfElements b) => Value a -> CodeGenFunction r (Value b)Source
Convert an unsigned integer to a floating point value.
Although inttofp
should be prefered, this function may be useful for conversion from Bool.
sitofp :: (IsInteger a, IsFloating b, NumberOfElements a ~ NumberOfElements b) => Value a -> CodeGenFunction r (Value b)Source
Convert a signed integer to a floating point value.
Although inttofp
should be prefered, this function may be useful for conversion from Bool.
inttofp :: forall r a b. (IsInteger a, IsFloating b, NumberOfElements a ~ NumberOfElements b) => Value a -> CodeGenFunction r (Value b)Source
Convert an integer to a floating point value.
It is mapped to sitofp
or uitofp
depending on the type a
.
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, IsSized b, SizeOf a ~ SizeOf b) => Value a -> CodeGenFunction r (Value b)Source
Convert between to values of the same size by just copying the bit pattern.
bitcastElements :: (Positive n, IsPrimitive a, IsPrimitive b, IsSized a, IsSized b, SizeOf a ~ SizeOf b) => Value (Vector n a) -> CodeGenFunction r (Value (Vector n b))Source
Like bitcast
for vectors but it enforces that the number of elements remains the same.
Comparison
data CmpPredicate Source
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) |
class CmpRet (CmpType a b) => CmpOp a b Source
Acceptable operands to comparison instructions.
CmpRet a => CmpOp (ConstValue a) (ConstValue a) | |
CmpRet a => CmpOp (ConstValue a) (Value a) | |
CmpRet a => CmpOp (Value a) (ConstValue a) | |
CmpRet a => CmpOp (Value a) (Value a) |
type CmpValueResult a b = CmpValue a b (CmpResult (CmpType a b))Source
cmp :: forall a b r. CmpOp a b => CmpPredicate -> a -> b -> CodeGenFunction r (CmpValueResult a b)Source
Compare values of ordered types
and choose predicates according to the compared types.
Floating point numbers are compared in "ordered" mode,
that is NaN
operands yields False
as result.
Pointers are compared unsigned.
These choices are consistent with comparison in plain Haskell.
pcmp :: (CmpOp a b, Ptr c ~ CmpType a b) => IntPredicate -> a -> b -> CodeGenFunction r (CmpValueResult a b)Source
icmp :: (IsIntegerOrPointer c, CmpOp a b, c ~ CmpType a b) => IntPredicate -> a -> b -> CodeGenFunction r (CmpValueResult a b)Source
Deprecated: use cmp or pcmp instead
Compare integers.
fcmp :: (IsFloating c, CmpOp a b, c ~ CmpType a b) => FPPredicate -> a -> b -> CodeGenFunction r (CmpValueResult a b)Source
Compare floating point values.
select :: (IsFirstClass a, CmpRet a) => Value (CmpResult a) -> Value a -> Value a -> CodeGenFunction r (Value a)Source
Select between two values depending on a boolean.
Fast math
setHasNoNaNs :: IsFloating a => Bool -> Value a -> CodeGenFunction r ()Source
setHasNoInfs :: IsFloating a => Bool -> Value a -> CodeGenFunction r ()Source
setHasNoSignedZeros :: IsFloating a => Bool -> Value a -> CodeGenFunction r ()Source
setHasAllowReciprocal :: IsFloating a => Bool -> Value a -> CodeGenFunction r ()Source
setFastMath :: IsFloating a => Bool -> Value a -> CodeGenFunction r ()Source
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 r => 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.
callWithConv :: CallArgs f g r => CallingConvention -> 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.
This also sets the calling convention of the call to the function.
As LLVM itself defines, if the calling conventions of the calling
instruction and the function being called are different, undefined
behavior results.
callFromFunction :: Function a -> Call aSource
callWithConvFromFunction :: CallingConvention -> Function f -> Call fSource
Classes and types
class (f ~ CalledFunction g, r ~ CallerResult g, g ~ CallerFunction f r) => CallArgs f g r Source
Acceptable arguments to call
.
Acceptable arguments to arithmetic unary instructions.
AUnOp (ConstValue a) | |
AUnOp (Value a) |
Acceptable arguments to arithmetic binary instructions.
type ABinOpResult a b :: *Source
ABinOp (ConstValue a) (ConstValue a) | |
ABinOp (ConstValue a) (Value a) | |
ABinOp (Value a) (ConstValue a) | |
ABinOp (Value a) (Value 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) | |
IsFunction a => IsConst (FunPtr a) | |
IsConstFields a => IsConst (PackedStruct a) | |
IsConstFields a => IsConst (Struct a) | |
Positive n => IsConst (WordN n) | |
Positive n => IsConst (IntN n) | |
(IsPrimitive a, IsConst a, Positive n) => IsConst (Vector n a) | |
(IsConst a, IsSized a, Natural n) => IsConst (Array n a) |
class IsFunction f => FunctionArgs f Source
type FunctionCodeGen f :: *Source
type FunctionResult f :: *Source
IsFirstClass a => FunctionArgs (IO a) | |
(FunctionArgs b, IsFirstClass a) => FunctionArgs (a -> b) |
Acceptable argument to array memory allocation.
class GetElementPtr optr ixs Source
Acceptable arguments to getElementPointer
.
type ElementPtrType optr ixs :: *Source
GetElementPtr a () | |
(GetElementPtr (FieldType fs a) i, Natural a) => GetElementPtr (PackedStruct fs) (Proxy a, i) | |
(GetElementPtr (FieldType fs a) i, Natural a) => GetElementPtr (Struct fs) (Proxy a, i) | |
(GetElementPtr o i, IsIndexArg a, Positive k) => GetElementPtr (Vector k o) (a, i) | |
(GetElementPtr o i, IsIndexArg a, Natural k) => GetElementPtr (Array k o) (a, i) |
class IsIndexArg a Source
Acceptable single index to getElementPointer
.
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) | |
IsFunction f => IsType (FunPtr f) | |
StructFields a => IsType (PackedStruct a) | |
StructFields a => IsType (Struct a) | |
Positive n => IsType (WordN n) | |
Positive n => IsType (IntN n) | |
IsType (VarArgs a) | |
(IsFirstClass a, IsFunction b) => IsType (a -> b) | |
(Positive n, IsPrimitive a) => IsType (Vector n a) | |
(Natural n, IsSized a) => IsType (Array n a) |
Special type classifiers
class IsFirstClass a => IsArithmetic a whereSource
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 | |
(Positive n, IsPrimitive a, IsFloating a) => IsFloating (Vector n a) |
class (IsType a, NumberOfElements a ~ D1) => IsPrimitive a Source
Primitive types. class (IsType a) => IsPrimitive a
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) | |
IsFunction a => IsFirstClass (FunPtr a) | |
StructFields as => IsFirstClass (Struct as) | |
Positive n => IsFirstClass (WordN n) | |
Positive n => IsFirstClass (IntN n) | |
(Positive n, IsPrimitive a) => IsFirstClass (Vector n a) | |
(Natural n, IsSized a) => IsFirstClass (Array n a) |
class (IsType a, Natural (SizeOf a)) => IsSized a Source
Types with a fixed size.
IsSized Bool | |
IsSized Double | |
IsSized Float | |
IsSized Int8 | |
IsSized Int16 | |
IsSized Int32 | |
IsSized Int64 | |
IsSized Word8 | |
IsSized Word16 | |
IsSized Word32 | |
IsSized Word64 | |
IsSized FP128 | |
IsSized (StablePtr a) | |
IsType a => IsSized (Ptr a) | |
IsFunction a => IsSized (FunPtr a) | |
StructFields as => IsSized (PackedStruct as) | |
StructFields as => IsSized (Struct as) | |
Positive n => IsSized (WordN n) | |
Positive n => IsSized (IntN n) | |
(Positive n, IsPrimitive a, IsSized a, Natural (:*: n (SizeOf a))) => IsSized (Vector n a) | |
(Natural n, IsSized a, Natural (:*: n (SizeOf a))) => IsSized (Array n a) |
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) |
Others
class IsType a => IsScalarOrVector a Source
Number of elements for instructions that handle both primitive and vector types
type NumberOfElements a :: *Source
class StructFields as Source
StructFields () | |
(IsSized a, StructFields as) => StructFields (:& a as) |
type UnknownSize = D99Source
Structs
Type tests
Type descriptor, used to convey type information through the LLVM API.
isFloating :: IsArithmetic a => Proxy a -> BoolSource
unsafeTypeRef :: IsType a => Proxy a -> TypeRefSource
intrinsicTypeName :: IsType a => Proxy a -> StringSource
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
Variable sized signed integer.
The n parameter should belong to PosI
.
Typeable1 IntN | |
Show (IntN n) | |
Positive n => IsSized (IntN n) | |
Positive n => IsFirstClass (IntN n) | |
Positive n => IsScalarOrVector (IntN n) | |
Positive n => IsPrimitive (IntN n) | |
Positive n => IsIntegerOrPointer (IntN n) | |
Positive n => IsInteger (IntN n) | |
Positive n => IsArithmetic (IntN n) | |
Positive n => IsType (IntN n) | |
Positive n => IsConst (IntN n) | |
Positive n => CmpRet (IntN n) |
Variable sized unsigned integer.
The n parameter should belong to PosI
.
Typeable1 WordN | |
Show (WordN n) | |
Positive n => IsSized (WordN n) | |
Positive n => IsFirstClass (WordN n) | |
Positive n => IsScalarOrVector (WordN n) | |
Positive n => IsPrimitive (WordN n) | |
Positive n => IsIntegerOrPointer (WordN n) | |
Positive n => IsInteger (WordN n) | |
Positive n => IsArithmetic (WordN n) | |
Positive n => IsType (WordN n) | |
Positive n => IsConst (WordN n) | |
Positive n => CmpRet (WordN n) |
128 bit floating point.
Fixed sized arrays, the array size is encoded in the n parameter.
Array [a] |
Typeable2 Array | |
Show a => Show (Array n a) | |
(Natural n, IsSized a, Natural (:*: n (SizeOf a))) => IsSized (Array n a) | |
(Natural n, IsSized a) => IsFirstClass (Array n a) | |
(Natural n, IsSized a) => IsType (Array n a) | |
(IsConst a, IsSized a, Natural n) => IsConst (Array n a) | |
(IsFirstClass a, Natural n) => GetValue (Array n a) Word64 | |
(IsFirstClass a, Natural n) => GetValue (Array n a) Word32 | |
(IsFirstClass a, Natural n, Natural i, :<: i n) => GetValue (Array n a) (Proxy i) | |
(GetElementPtr o i, IsIndexArg a, Natural k) => GetElementPtr (Array k o) (a, i) |
Fixed sized vector, the array size is encoded in the n parameter.
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 => IsSized (Struct as) | |
StructFields as => IsFirstClass (Struct as) | |
StructFields a => IsType (Struct a) | |
IsConstFields a => IsConst (Struct a) | |
(GetField as i, Natural i) => GetValue (Struct as) (Proxy i) | |
(GetElementPtr (FieldType fs a) i, Natural a) => GetElementPtr (Struct fs) (Proxy a, i) |
newtype PackedStruct a Source
Typeable1 PackedStruct | |
Show a => Show (PackedStruct a) | |
StructFields as => IsSized (PackedStruct as) | |
StructFields a => IsType (PackedStruct a) | |
IsConstFields a => IsConst (PackedStruct a) | |
(GetElementPtr (FieldType fs a) i, Natural a) => GetElementPtr (PackedStruct fs) (Proxy a, i) |
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) | |
AUnOp (ConstValue a) | |
CmpRet a => CmpOp (ConstValue a) (ConstValue a) | |
CmpRet a => CmpOp (ConstValue a) (Value a) | |
CmpRet a => CmpOp (Value a) (ConstValue a) | |
ABinOp (ConstValue a) (ConstValue a) | |
ABinOp (ConstValue a) (Value a) | |
ABinOp (Value a) (ConstValue a) | |
(IsConst a, IsConstStruct cs) => IsConstStruct (ConstValue a, cs) |
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
withString :: String -> (forall n. Natural n => Global (Array n Word8) -> CodeGenModule a) -> CodeGenModule aSource
withStringNul :: String -> (forall n. Natural n => Global (Array n Word8) -> CodeGenModule a) -> CodeGenModule aSource
constVector :: forall a n u. (Positive n, ToUnary n ~ u, Length (FixedList u) ~ u) => FixedList u (ConstValue a) -> ConstValue (Vector n a)Source
Make a constant vector.
constArray :: forall a n. (IsSized a, Natural n) => [ConstValue a] -> ConstValue (Array n a)Source
constCyclicVector :: forall a n. Positive n => T [] (ConstValue a) -> ConstValue (Vector n a)Source
Make a constant vector.
Replicates or truncates the list to get length n
.
constCyclicArray :: forall a n. (IsSized a, Natural n) => T [] (ConstValue a) -> ConstValue (Vector n a)Source
Make a constant array.
Replicates or truncates the list to get length n
.
constStruct :: IsConstStruct c => c -> ConstValue (Struct (ConstStructOf c))Source
Make a constant struct.
constPackedStruct :: IsConstStruct c => c -> ConstValue (PackedStruct (ConstStructOf c))Source
Make a constant packed struct.
fromVector :: MkVector n a => Vector n a -> Tuple n aSource
cyclicVector :: Positive n => T [] a -> Vector n aSource
Make a constant vector. Replicates or truncates the list to get length n.
This behaviour is consistent uncurry that of constCyclicVector
.
May be abused for constructing vectors from lists uncurry statically unknown size.
Code generation
data CodeGenFunction r a Source
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 . FunctionArgs f | |
=> Function f | Function to define (created by |
-> FunctionCodeGen f | Function body. |
-> CodeGenModule () |
Define a function body. The basic block returned by the function is the function entry point.
:: FunctionArgs f | |
=> Linkage | |
-> FunctionCodeGen f | Function body. |
-> CodeGenModule (Function f) |
Create a new function with the given body.
:: FunctionArgs f | |
=> Linkage | |
-> String | |
-> FunctionCodeGen f | Function body. |
-> CodeGenModule (Function f) |
Create a new function with the given body.
setFuncCallConv :: Function a -> CallingConvention -> CodeGenModule ()Source
Set the calling convention of a function. By default it is the C calling convention.
type TFunction a = CodeGenModule (Function a)Source
liftCodeGenModule :: CodeGenModule a -> CodeGenFunction r aSource
Allows you to define part of a module while in the middle of defining a function.
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 :: forall f r. 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 simpleFunction
and can be manually obtained by getGlobalMappings
and installed by addGlobalMappings
.
"Installing" means calling LLVM's addGlobalMapping
according to
http://old.nabble.com/jit-with-external-functions-td7769793.html.
staticNamedFunction :: forall f r. IsFunction f => String -> FunPtr f -> CodeGenFunction r (Function f)Source
Due to https://llvm.org/bugs/show_bug.cgi?id=20656 this will fail with MCJIT of LLVM-3.6.
externGlobal :: forall a r. IsType a => Bool -> String -> CodeGenFunction r (Global a)Source
As externFunction
, but for Global
s rather than Function
s
staticGlobal :: forall a r. IsType a => Bool -> Ptr a -> CodeGenFunction r (Global a)Source
As staticFunction
, but for Global
s rather than Function
s
data GlobalMappings Source
Show GlobalMappings | |
Monoid GlobalMappings | |
Semigroup GlobalMappings |
getGlobalMappings :: CodeGenModule GlobalMappingsSource
Get a list created by calls to staticFunction
that must be passed to the execution engine
via addGlobalMappings
.
type TGlobal a = CodeGenModule (Global a)Source
Globals
data Linkage
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. |
LinkOnceODRAutoHideLinkage | Like LinkOnceODR, but possibly hidden. |
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. |
LinkerPrivateWeakLinkage | Like LinkerPrivate, but is weak. |
Basic blocks
data BasicBlock Source
A basic block is a sequence of non-branching instructions, terminated by a control flow instruction.
getBasicBlocks :: Value -> IO [(String, Value)]Source
fromLabel :: Value Label -> BasicBlockSource
toLabel :: BasicBlock -> Value LabelSource
getInstructions :: Value -> IO [(String, Value)]Source
getOperands :: Value -> IO [(String, Value)]Source
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
castVarArgs :: CastVarArgs a b => Function a -> Function bSource
Convert a varargs function to a regular function.
Debugging
annotateValueList :: [Value] -> IO [(String, Value)]Source