| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
GHC.Llvm
Description
This module supplies bindings to generate Llvm IR from Haskell (http://www.llvm.org/docs/LangRef.html).
Note: this module is developed in a demand driven way. It is no complete LLVM binding library in Haskell, but enough to generate code for GHC.
This code is derived from code taken from the Essential Haskell Compiler (EHC) project.
Synopsis
- data LlvmOpts = LlvmOpts {- llvmOptsPlatform :: !Platform
- llvmOptsFillUndefWithGarbage :: !Bool
- llvmOptsSplitSections :: !Bool
 
- initLlvmOpts :: DynFlags -> LlvmOpts
- data LlvmModule = LlvmModule {- modComments :: [LMString]
- modAliases :: [LlvmAlias]
- modMeta :: [MetaDecl]
- modGlobals :: [LMGlobal]
- modFwdDecls :: LlvmFunctionDecls
- modFuncs :: LlvmFunctions
 
- data LlvmFunction = LlvmFunction {}
- data LlvmFunctionDecl = LlvmFunctionDecl {}
- type LlvmFunctions = [LlvmFunction]
- type LlvmFunctionDecls = [LlvmFunctionDecl]
- data LlvmStatement- = Assignment LlvmVar LlvmExpression
- | Fence Bool LlvmSyncOrdering
- | Branch LlvmVar
- | BranchIf LlvmVar LlvmVar LlvmVar
- | Comment [LMString]
- | MkLabel LlvmBlockId
- | Store LlvmVar LlvmVar
- | Switch LlvmVar LlvmVar [(LlvmVar, LlvmVar)]
- | Return (Maybe LlvmVar)
- | Unreachable
- | Expr LlvmExpression
- | Nop
- | MetaStmt [MetaAnnot] LlvmStatement
 
- data LlvmExpression- = Alloca LlvmType Int
- | LlvmOp LlvmMachOp LlvmVar LlvmVar
- | Compare LlvmCmpOp LlvmVar LlvmVar
- | Extract LlvmVar LlvmVar
- | ExtractV LlvmVar Int
- | Insert LlvmVar LlvmVar LlvmVar
- | Malloc LlvmType Int
- | Load LlvmVar
- | ALoad LlvmSyncOrdering SingleThreaded LlvmVar
- | GetElemPtr Bool LlvmVar [LlvmVar]
- | Cast LlvmCastOp LlvmVar LlvmType
- | AtomicRMW LlvmAtomicOp LlvmVar LlvmVar LlvmSyncOrdering
- | CmpXChg LlvmVar LlvmVar LlvmVar LlvmSyncOrdering LlvmSyncOrdering
- | Call LlvmCallType LlvmVar [LlvmVar] [LlvmFuncAttr]
- | CallM LlvmCallType LlvmVar [MetaExpr] [LlvmFuncAttr]
- | Phi LlvmType [(LlvmVar, LlvmVar)]
- | Asm LMString LMString LlvmType [LlvmVar] Bool Bool
- | MExpr [MetaAnnot] LlvmExpression
 
- type LlvmBlocks = [LlvmBlock]
- data LlvmBlock = LlvmBlock {}
- type LlvmBlockId = Unique
- data LlvmParamAttr
- type LlvmParameter = (LlvmType, [LlvmParamAttr])
- data LlvmAtomicOp
- data LlvmSyncOrdering
- data LlvmCallConvention
- data LlvmCallType
- data LlvmParameterListType
- data LlvmLinkageType
- data LlvmFuncAttr
- data LlvmCmpOp
- data LlvmMachOp
- data LlvmCastOp
- data LlvmVar
- data LlvmStatic- = LMComment LMString
- | LMStaticLit LlvmLit
- | LMUninitType LlvmType
- | LMStaticStr LMString LlvmType
- | LMStaticArray [LlvmStatic] LlvmType
- | LMStaticStruc [LlvmStatic] LlvmType
- | LMStaticPointer LlvmVar
- | LMTrunc LlvmStatic LlvmType
- | LMBitc LlvmStatic LlvmType
- | LMPtoI LlvmStatic LlvmType
- | LMAdd LlvmStatic LlvmStatic
- | LMSub LlvmStatic LlvmStatic
 
- data LlvmLit
- data LlvmType
- type LlvmAlias = (LMString, LlvmType)
- data LMGlobal = LMGlobal {}
- type LMString = FastString
- type LMSection = Maybe LMString
- type LMAlign = Maybe Int
- data LMConst
- i64 :: LlvmType
- i32 :: LlvmType
- i16 :: LlvmType
- i8 :: LlvmType
- i1 :: LlvmType
- i8Ptr :: LlvmType
- llvmWord :: Platform -> LlvmType
- llvmWordPtr :: Platform -> LlvmType
- data MetaExpr
- data MetaAnnot = MetaAnnot LMString MetaExpr
- data MetaDecl
- newtype MetaId = MetaId Int
- isGlobal :: LlvmVar -> Bool
- getLitType :: LlvmLit -> LlvmType
- getVarType :: LlvmVar -> LlvmType
- getLink :: LlvmVar -> LlvmLinkageType
- getStatType :: LlvmStatic -> LlvmType
- pVarLift :: LlvmVar -> LlvmVar
- pVarLower :: LlvmVar -> LlvmVar
- pLift :: LlvmType -> LlvmType
- pLower :: LlvmType -> LlvmType
- isInt :: LlvmType -> Bool
- isFloat :: LlvmType -> Bool
- isPointer :: LlvmType -> Bool
- isVector :: LlvmType -> Bool
- llvmWidthInBits :: Platform -> LlvmType -> Int
- ppVar :: LlvmOpts -> LlvmVar -> SDoc
- ppLit :: LlvmOpts -> LlvmLit -> SDoc
- ppTypeLit :: LlvmOpts -> LlvmLit -> SDoc
- ppName :: LlvmOpts -> LlvmVar -> SDoc
- ppPlainName :: LlvmOpts -> LlvmVar -> SDoc
- ppLlvmModule :: LlvmOpts -> LlvmModule -> SDoc
- ppLlvmComments :: [LMString] -> SDoc
- ppLlvmComment :: LMString -> SDoc
- ppLlvmGlobals :: LlvmOpts -> [LMGlobal] -> SDoc
- ppLlvmGlobal :: LlvmOpts -> LMGlobal -> SDoc
- ppLlvmFunctionDecls :: LlvmFunctionDecls -> SDoc
- ppLlvmFunctionDecl :: LlvmFunctionDecl -> SDoc
- ppLlvmFunctions :: LlvmOpts -> LlvmFunctions -> SDoc
- ppLlvmFunction :: LlvmOpts -> LlvmFunction -> SDoc
- ppLlvmAlias :: LlvmAlias -> SDoc
- ppLlvmAliases :: [LlvmAlias] -> SDoc
- ppLlvmMetas :: LlvmOpts -> [MetaDecl] -> SDoc
- ppLlvmMeta :: LlvmOpts -> MetaDecl -> SDoc
Documentation
LLVM code generator options
Constructors
| LlvmOpts | |
| Fields 
 | |
initLlvmOpts :: DynFlags -> LlvmOpts Source #
Get LlvmOptions from DynFlags
Modules, Functions and Blocks
data LlvmModule Source #
An LLVM Module. This is a top level container in LLVM.
Constructors
| LlvmModule | |
| Fields 
 | |
data LlvmFunction Source #
An LLVM Function
Constructors
| LlvmFunction | |
| Fields 
 | |
data LlvmFunctionDecl Source #
An LLVM Function
Constructors
| LlvmFunctionDecl | |
| Fields 
 | |
Instances
| Eq LlvmFunctionDecl Source # | |
| Defined in GHC.Llvm.Types Methods (==) :: LlvmFunctionDecl -> LlvmFunctionDecl -> Bool # (/=) :: LlvmFunctionDecl -> LlvmFunctionDecl -> Bool # | |
| Outputable LlvmFunctionDecl Source # | |
| Defined in GHC.Llvm.Types Methods ppr :: LlvmFunctionDecl -> SDoc | |
type LlvmFunctions = [LlvmFunction] Source #
type LlvmFunctionDecls = [LlvmFunctionDecl] Source #
data LlvmStatement Source #
Llvm Statements
Constructors
| Assignment LlvmVar LlvmExpression | Assign an expression to a variable: * dest: Variable to assign to * source: Source expression | 
| Fence Bool LlvmSyncOrdering | Memory fence operation | 
| Branch LlvmVar | Always branch to the target label | 
| BranchIf LlvmVar LlvmVar LlvmVar | Branch to label targetTrue if cond is true otherwise to label targetFalse * cond: condition that will be tested, must be of type i1 * targetTrue: label to branch to if cond is true * targetFalse: label to branch to if cond is false | 
| Comment [LMString] | Comment Plain comment. | 
| MkLabel LlvmBlockId | Set a label on this position. * name: Identifier of this label, unique for this module | 
| Store LlvmVar LlvmVar | Store variable value in pointer ptr. If value is of type t then ptr must be of type t*. * value: Variable/Constant to store. * ptr: Location to store the value in | 
| Switch LlvmVar LlvmVar [(LlvmVar, LlvmVar)] | Multiway branch * scrutinee: Variable or constant which must be of integer type that is determines which arm is chosen. * def: The default label if there is no match in target. * target: A list of (value,label) where the value is an integer constant and label the corresponding label to jump to if the scrutinee matches the value. | 
| Return (Maybe LlvmVar) | Return a result. * result: The variable or constant to return | 
| Unreachable | An instruction for the optimizer that the code following is not reachable | 
| Expr LlvmExpression | Raise an expression to a statement (if don't want result or want to use Llvm unnamed values. | 
| Nop | A nop LLVM statement. Useful as its often more efficient to use this then to wrap LLvmStatement in a Just or []. | 
| MetaStmt [MetaAnnot] LlvmStatement | A LLVM statement with metadata attached to it. | 
Instances
| Eq LlvmStatement Source # | |
| Defined in GHC.Llvm.Syntax Methods (==) :: LlvmStatement -> LlvmStatement -> Bool # (/=) :: LlvmStatement -> LlvmStatement -> Bool # | |
data LlvmExpression Source #
Llvm Expressions
Constructors
| Alloca LlvmType Int | Allocate amount * sizeof(tp) bytes on the stack * tp: LlvmType to reserve room for * amount: The nr of tp's which must be allocated | 
| LlvmOp LlvmMachOp LlvmVar LlvmVar | Perform the machine operator op on the operands left and right * op: operator * left: left operand * right: right operand | 
| Compare LlvmCmpOp LlvmVar LlvmVar | Perform a compare operation on the operands left and right * op: operator * left: left operand * right: right operand | 
| Extract LlvmVar LlvmVar | Extract a scalar element from a vector * val: The vector * idx: The index of the scalar within the vector | 
| ExtractV LlvmVar Int | Extract a scalar element from a structure * val: The structure * idx: The index of the scalar within the structure Corresponds to "extractvalue" instruction. | 
| Insert LlvmVar LlvmVar LlvmVar | Insert a scalar element into a vector * val: The source vector * elt: The scalar to insert * index: The index at which to insert the scalar | 
| Malloc LlvmType Int | Allocate amount * sizeof(tp) bytes on the heap * tp: LlvmType to reserve room for * amount: The nr of tp's which must be allocated | 
| Load LlvmVar | Load the value at location ptr | 
| ALoad LlvmSyncOrdering SingleThreaded LlvmVar | Atomic load of the value at location ptr | 
| GetElemPtr Bool LlvmVar [LlvmVar] | Navigate in a structure, selecting elements * inbound: Is the pointer inbounds? (computed pointer doesn't overflow) * ptr: Location of the structure * indexes: A list of indexes to select the correct value. | 
| Cast LlvmCastOp LlvmVar LlvmType | Cast the variable from to the to type. This is an abstraction of three cast operators in Llvm, inttoptr, ptrtoint and bitcast. * cast: Cast type * from: Variable to cast * to: type to cast to | 
| AtomicRMW LlvmAtomicOp LlvmVar LlvmVar LlvmSyncOrdering | Atomic read-modify-write operation * op: Atomic operation * addr: Address to modify * operand: Operand to operation * ordering: Ordering requirement | 
| CmpXChg LlvmVar LlvmVar LlvmVar LlvmSyncOrdering LlvmSyncOrdering | Compare-and-exchange operation * addr: Address to modify * old: Expected value * new: New value * suc_ord: Ordering required in success case * fail_ord: Ordering required in failure case, can be no stronger than suc_ord Result is an  | 
| Call LlvmCallType LlvmVar [LlvmVar] [LlvmFuncAttr] | Call a function. The result is the value of the expression. * tailJumps: CallType to signal if the function should be tail called * fnptrval: An LLVM value containing a pointer to a function to be invoked. Can be indirect. Should be LMFunction type. * args: Concrete arguments for the parameters * attrs: A list of function attributes for the call. Only NoReturn, NoUnwind, ReadOnly and ReadNone are valid here. | 
| CallM LlvmCallType LlvmVar [MetaExpr] [LlvmFuncAttr] | Call a function as above but potentially taking metadata as arguments. * tailJumps: CallType to signal if the function should be tail called * fnptrval: An LLVM value containing a pointer to a function to be invoked. Can be indirect. Should be LMFunction type. * args: Arguments that may include metadata. * attrs: A list of function attributes for the call. Only NoReturn, NoUnwind, ReadOnly and ReadNone are valid here. | 
| Phi LlvmType [(LlvmVar, LlvmVar)] | Merge variables from different basic blocks which are predecessors of this basic block in a new variable of type tp. * tp: type of the merged variable, must match the types of the predecessor variables. * predecessors: A list of variables and the basic block that they originate from. | 
| Asm LMString LMString LlvmType [LlvmVar] Bool Bool | Inline assembly expression. Syntax is very similar to the style used by GCC. * assembly: Actual inline assembly code. * constraints: Operand constraints. * return ty: Return type of function. * vars: Any variables involved in the assembly code. * sideeffect: Does the expression have side effects not visible from the constraints list. * alignstack: Should the stack be conservatively aligned before this expression is executed. | 
| MExpr [MetaAnnot] LlvmExpression | A LLVM expression with metadata attached to it. | 
Instances
| Eq LlvmExpression Source # | |
| Defined in GHC.Llvm.Syntax Methods (==) :: LlvmExpression -> LlvmExpression -> Bool # (/=) :: LlvmExpression -> LlvmExpression -> Bool # | |
type LlvmBlocks = [LlvmBlock] Source #
A block of LLVM code.
Constructors
| LlvmBlock | |
| Fields 
 | |
type LlvmBlockId = Unique Source #
Block labels
data LlvmParamAttr Source #
LLVM Parameter Attributes.
Parameter attributes are used to communicate additional information about the result or parameters of a function
Constructors
| ZeroExt | This indicates to the code generator that the parameter or return value should be zero-extended to a 32-bit value by the caller (for a parameter) or the callee (for a return value). | 
| SignExt | This indicates to the code generator that the parameter or return value should be sign-extended to a 32-bit value by the caller (for a parameter) or the callee (for a return value). | 
| InReg | This indicates that this parameter or return value should be treated in a special target-dependent fashion during while emitting code for a function call or return (usually, by putting it in a register as opposed to memory). | 
| ByVal | This indicates that the pointer parameter should really be passed by value to the function. | 
| SRet | This indicates that the pointer parameter specifies the address of a structure that is the return value of the function in the source program. | 
| NoAlias | This indicates that the pointer does not alias any global or any other parameter. | 
| NoCapture | This indicates that the callee does not make any copies of the pointer that outlive the callee itself | 
| Nest | This indicates that the pointer parameter can be excised using the trampoline intrinsics. | 
Instances
| Eq LlvmParamAttr Source # | |
| Defined in GHC.Llvm.Types Methods (==) :: LlvmParamAttr -> LlvmParamAttr -> Bool # (/=) :: LlvmParamAttr -> LlvmParamAttr -> Bool # | |
| Outputable LlvmParamAttr Source # | |
| Defined in GHC.Llvm.Types Methods ppr :: LlvmParamAttr -> SDoc | |
type LlvmParameter = (LlvmType, [LlvmParamAttr]) Source #
Atomic operations
data LlvmAtomicOp Source #
LLVM atomic operations. Please see the atomicrmw instruction in
 the LLVM documentation for a complete description.
Constructors
| LAO_Xchg | |
| LAO_Add | |
| LAO_Sub | |
| LAO_And | |
| LAO_Nand | |
| LAO_Or | |
| LAO_Xor | |
| LAO_Max | |
| LAO_Min | |
| LAO_Umax | |
| LAO_Umin | 
Instances
| Eq LlvmAtomicOp Source # | |
| Defined in GHC.Llvm.Syntax | |
| Show LlvmAtomicOp Source # | |
| Defined in GHC.Llvm.Syntax Methods showsPrec :: Int -> LlvmAtomicOp -> ShowS # show :: LlvmAtomicOp -> String # showList :: [LlvmAtomicOp] -> ShowS # | |
Fence synchronization
data LlvmSyncOrdering Source #
LLVM ordering types for synchronization purposes. (Introduced in LLVM 3.0). Please see the LLVM documentation for a better description.
Constructors
| SyncUnord | Some partial order of operations exists. | 
| SyncMonotonic | A single total order for operations at a single address exists. | 
| SyncAcquire | Acquire synchronization operation. | 
| SyncRelease | Release synchronization operation. | 
| SyncAcqRel | Acquire + Release synchronization operation. | 
| SyncSeqCst | Full sequential Consistency operation. | 
Instances
| Eq LlvmSyncOrdering Source # | |
| Defined in GHC.Llvm.Syntax Methods (==) :: LlvmSyncOrdering -> LlvmSyncOrdering -> Bool # (/=) :: LlvmSyncOrdering -> LlvmSyncOrdering -> Bool # | |
| Show LlvmSyncOrdering Source # | |
| Defined in GHC.Llvm.Syntax Methods showsPrec :: Int -> LlvmSyncOrdering -> ShowS # show :: LlvmSyncOrdering -> String # showList :: [LlvmSyncOrdering] -> ShowS # | |
Call Handling
data LlvmCallConvention Source #
Different calling conventions a function can use.
Constructors
| CC_Ccc | The C calling convention. This calling convention (the default if no other calling convention is specified) matches the target C calling conventions. This calling convention supports varargs function calls and tolerates some mismatch in the declared prototype and implemented declaration of the function (as does normal C). | 
| CC_Fastcc | This calling convention attempts to make calls as fast as possible (e.g. by passing things in registers). This calling convention allows the target to use whatever tricks it wants to produce fast code for the target, without having to conform to an externally specified ABI (Application Binary Interface). Implementations of this convention should allow arbitrary tail call optimization to be supported. This calling convention does not support varargs and requires the prototype of al callees to exactly match the prototype of the function definition. | 
| CC_Coldcc | This calling convention attempts to make code in the caller as efficient as possible under the assumption that the call is not commonly executed. As such, these calls often preserve all registers so that the call does not break any live ranges in the caller side. This calling convention does not support varargs and requires the prototype of all callees to exactly match the prototype of the function definition. | 
| CC_Ghc | The GHC-specific  | 
| CC_Ncc Int | Any calling convention may be specified by number, allowing target-specific calling conventions to be used. Target specific calling conventions start at 64. | 
| CC_X86_Stdcc | X86 Specific  | 
Instances
| Eq LlvmCallConvention Source # | |
| Defined in GHC.Llvm.Types Methods (==) :: LlvmCallConvention -> LlvmCallConvention -> Bool # (/=) :: LlvmCallConvention -> LlvmCallConvention -> Bool # | |
| Outputable LlvmCallConvention Source # | |
| Defined in GHC.Llvm.Types Methods ppr :: LlvmCallConvention -> SDoc | |
data LlvmCallType Source #
Different types to call a function.
Constructors
| StdCall | Normal call, allocate a new stack frame. | 
| TailCall | Tail call, perform the call in the current stack frame. | 
Instances
| Eq LlvmCallType Source # | |
| Defined in GHC.Llvm.Types | |
| Show LlvmCallType Source # | |
| Defined in GHC.Llvm.Types Methods showsPrec :: Int -> LlvmCallType -> ShowS # show :: LlvmCallType -> String # showList :: [LlvmCallType] -> ShowS # | |
data LlvmParameterListType Source #
Functions can have a fixed amount of parameters, or a variable amount.
Instances
| Eq LlvmParameterListType Source # | |
| Defined in GHC.Llvm.Types Methods (==) :: LlvmParameterListType -> LlvmParameterListType -> Bool # (/=) :: LlvmParameterListType -> LlvmParameterListType -> Bool # | |
| Show LlvmParameterListType Source # | |
| Defined in GHC.Llvm.Types Methods showsPrec :: Int -> LlvmParameterListType -> ShowS # show :: LlvmParameterListType -> String # showList :: [LlvmParameterListType] -> ShowS # | |
data LlvmLinkageType Source #
Linkage type of a symbol.
The description of the constructors is copied from the Llvm Assembly Language Reference Manual http://www.llvm.org/docs/LangRef.html#linkage, because they correspond to the Llvm linkage types.
Constructors
| Internal | Global values with internal linkage are only directly accessible by
 objects in the current module. In particular, linking code into a module
 with an internal global value may cause the internal to be renamed as
 necessary to avoid collisions. Because the symbol is internal to the
 module, all references can be updated. This corresponds to the notion
 of the  | 
| LinkOnce | Globals with  | 
| Weak | 
 | 
| Appending | 
 | 
| ExternWeak | The semantics of this linkage follow the ELF model: the symbol is weak until linked, if not linked, the symbol becomes null instead of being an undefined reference. | 
| ExternallyVisible | The symbol participates in linkage and can be used to resolve external symbol references. | 
| External | Alias for  | 
| Private | Symbol is private to the module and should not appear in the symbol table | 
Instances
| Eq LlvmLinkageType Source # | |
| Defined in GHC.Llvm.Types Methods (==) :: LlvmLinkageType -> LlvmLinkageType -> Bool # (/=) :: LlvmLinkageType -> LlvmLinkageType -> Bool # | |
| Outputable LlvmLinkageType Source # | |
| Defined in GHC.Llvm.Types Methods ppr :: LlvmLinkageType -> SDoc | |
data LlvmFuncAttr Source #
Llvm Function Attributes.
Function attributes are set to communicate additional information about a function. Function attributes are considered to be part of the function, not of the function type, so functions with different parameter attributes can have the same function type. Functions can have multiple attributes.
Descriptions taken from http://llvm.org/docs/LangRef.html#fnattrs
Constructors
| AlwaysInline | This attribute indicates that the inliner should attempt to inline this function into callers whenever possible, ignoring any active inlining size threshold for this caller. | 
| InlineHint | This attribute indicates that the source code contained a hint that inlining this function is desirable (such as the "inline" keyword in C/C++). It is just a hint; it imposes no requirements on the inliner. | 
| NoInline | This attribute indicates that the inliner should never inline this function in any situation. This attribute may not be used together with the alwaysinline attribute. | 
| OptSize | This attribute suggests that optimization passes and code generator passes make choices that keep the code size of this function low, and otherwise do optimizations specifically to reduce code size. | 
| NoReturn | This function attribute indicates that the function never returns normally. This produces undefined behavior at runtime if the function ever does dynamically return. | 
| NoUnwind | This function attribute indicates that the function never returns with an unwind or exceptional control flow. If the function does unwind, its runtime behavior is undefined. | 
| ReadNone | This attribute indicates that the function computes its result (or decides to unwind an exception) based strictly on its arguments, without dereferencing any pointer arguments or otherwise accessing any mutable state (e.g. memory, control registers, etc) visible to caller functions. It does not write through any pointer arguments (including byval arguments) and never changes any state visible to callers. This means that it cannot unwind exceptions by calling the C++ exception throwing methods, but could use the unwind instruction. | 
| ReadOnly | This attribute indicates that the function does not write through any pointer arguments (including byval arguments) or otherwise modify any state (e.g. memory, control registers, etc) visible to caller functions. It may dereference pointer arguments and read state that may be set in the caller. A readonly function always returns the same value (or unwinds an exception identically) when called with the same set of arguments and global state. It cannot unwind an exception by calling the C++ exception throwing methods, but may use the unwind instruction. | 
| Ssp | This attribute indicates that the function should emit a stack smashing protector. It is in the form of a "canary"—a random value placed on the stack before the local variables that's checked upon return from the function to see if it has been overwritten. A heuristic is used to determine if a function needs stack protectors or not. If a function that has an ssp attribute is inlined into a function that doesn't have an ssp attribute, then the resulting function will have an ssp attribute. | 
| SspReq | This attribute indicates that the function should always emit a stack smashing protector. This overrides the ssp function attribute. If a function that has an sspreq attribute is inlined into a function that doesn't have an sspreq attribute or which has an ssp attribute, then the resulting function will have an sspreq attribute. | 
| NoRedZone | This attribute indicates that the code generator should not use a red zone, even if the target-specific ABI normally permits it. | 
| NoImplicitFloat | This attributes disables implicit floating point instructions. | 
| Naked | This attribute disables prologue / epilogue emission for the function. This can have very system-specific consequences. | 
Instances
| Eq LlvmFuncAttr Source # | |
| Defined in GHC.Llvm.Types | |
| Outputable LlvmFuncAttr Source # | |
| Defined in GHC.Llvm.Types Methods ppr :: LlvmFuncAttr -> SDoc | |
Operations and Comparisons
Llvm compare operations.
Constructors
| LM_CMP_Eq | Equal (Signed and Unsigned) | 
| LM_CMP_Ne | Not equal (Signed and Unsigned) | 
| LM_CMP_Ugt | Unsigned greater than | 
| LM_CMP_Uge | Unsigned greater than or equal | 
| LM_CMP_Ult | Unsigned less than | 
| LM_CMP_Ule | Unsigned less than or equal | 
| LM_CMP_Sgt | Signed greater than | 
| LM_CMP_Sge | Signed greater than or equal | 
| LM_CMP_Slt | Signed less than | 
| LM_CMP_Sle | Signed less than or equal | 
| LM_CMP_Feq | Float equal | 
| LM_CMP_Fne | Float not equal | 
| LM_CMP_Fgt | Float greater than | 
| LM_CMP_Fge | Float greater than or equal | 
| LM_CMP_Flt | Float less than | 
| LM_CMP_Fle | Float less than or equal | 
data LlvmMachOp Source #
Llvm binary operators machine operations.
Constructors
| LM_MO_Add | add two integer, floating point or vector values. | 
| LM_MO_Sub | subtract two ... | 
| LM_MO_Mul | multiply .. | 
| LM_MO_UDiv | unsigned integer or vector division. | 
| LM_MO_SDiv | signed integer .. | 
| LM_MO_URem | unsigned integer or vector remainder (mod) | 
| LM_MO_SRem | signed ... | 
| LM_MO_FAdd | add two floating point or vector values. | 
| LM_MO_FSub | subtract two ... | 
| LM_MO_FMul | multiply ... | 
| LM_MO_FDiv | divide ... | 
| LM_MO_FRem | remainder ... | 
| LM_MO_Shl | Left shift | 
| LM_MO_LShr | Logical shift right Shift right, filling with zero | 
| LM_MO_AShr | Arithmetic shift right The most significant bits of the result will be equal to the sign bit of the left operand. | 
| LM_MO_And | AND bitwise logical operation. | 
| LM_MO_Or | OR bitwise logical operation. | 
| LM_MO_Xor | XOR bitwise logical operation. | 
Instances
| Eq LlvmMachOp Source # | |
| Defined in GHC.Llvm.Types | |
| Outputable LlvmMachOp Source # | |
| Defined in GHC.Llvm.Types Methods ppr :: LlvmMachOp -> SDoc | |
data LlvmCastOp Source #
Llvm cast operations.
Constructors
| LM_Trunc | Integer truncate | 
| LM_Zext | Integer extend (zero fill) | 
| LM_Sext | Integer extend (sign fill) | 
| LM_Fptrunc | Float truncate | 
| LM_Fpext | Float extend | 
| LM_Fptoui | Float to unsigned Integer | 
| LM_Fptosi | Float to signed Integer | 
| LM_Uitofp | Unsigned Integer to Float | 
| LM_Sitofp | Signed Int to Float | 
| LM_Ptrtoint | Pointer to Integer | 
| LM_Inttoptr | Integer to Pointer | 
| LM_Bitcast | Cast between types where no bit manipulation is needed | 
Instances
| Eq LlvmCastOp Source # | |
| Defined in GHC.Llvm.Types | |
| Outputable LlvmCastOp Source # | |
| Defined in GHC.Llvm.Types Methods ppr :: LlvmCastOp -> SDoc | |
Variables and Type System
LLVM Variables
Constructors
| LMGlobalVar LMString LlvmType LlvmLinkageType LMSection LMAlign LMConst | Variables with a global scope. | 
| LMLocalVar Unique LlvmType | Variables local to a function or parameters. | 
| LMNLocalVar LMString LlvmType | Named local variables. Sometimes we need to be able to explicitly name variables (e.g for function arguments). | 
| LMLitVar LlvmLit | A constant variable | 
data LlvmStatic Source #
Llvm Static Data.
These represent the possible global level variables and constants.
Constructors
| LMComment LMString | A comment in a static section | 
| LMStaticLit LlvmLit | A static variant of a literal value | 
| LMUninitType LlvmType | For uninitialised data | 
| LMStaticStr LMString LlvmType | Defines a static  | 
| LMStaticArray [LlvmStatic] LlvmType | A static array | 
| LMStaticStruc [LlvmStatic] LlvmType | A static structure type | 
| LMStaticPointer LlvmVar | A pointer to other data | 
| LMTrunc LlvmStatic LlvmType | Truncate | 
| LMBitc LlvmStatic LlvmType | Pointer to Pointer conversion | 
| LMPtoI LlvmStatic LlvmType | Pointer to Integer conversion | 
| LMAdd LlvmStatic LlvmStatic | Constant addition operation | 
| LMSub LlvmStatic LlvmStatic | Constant subtraction operation | 
Llvm Literal Data.
These can be used inline in expressions.
Constructors
| LMIntLit Integer LlvmType | Refers to an integer constant (i64 42). | 
| LMFloatLit Double LlvmType | Floating point literal | 
| LMNullLit LlvmType | Literal NULL, only applicable to pointer types | 
| LMVectorLit [LlvmLit] | Vector literal | 
| LMUndefLit LlvmType | Undefined value, random bit pattern. Useful for optimisations. | 
Llvm Types
Constructors
| LMInt Int | An integer with a given width in bits. | 
| LMFloat | 32 bit floating point | 
| LMDouble | 64 bit floating point | 
| LMFloat80 | 80 bit (x86 only) floating point | 
| LMFloat128 | 128 bit floating point | 
| LMPointer LlvmType | A pointer to a  | 
| LMArray Int LlvmType | An array of  | 
| LMVector Int LlvmType | A vector of  | 
| LMLabel | A  | 
| LMVoid | Void type | 
| LMStruct [LlvmType] | Packed structure type | 
| LMStructU [LlvmType] | Unpacked structure type | 
| LMAlias LlvmAlias | A type alias | 
| LMMetadata | LLVM Metadata | 
| LMFunction LlvmFunctionDecl | Function type, used to create pointers to functions | 
A global mutable variable. Maybe defined or external
Constructors
| LMGlobal | |
| Fields 
 | |
type LMSection = Maybe LMString Source #
An LLVM section definition. If Nothing then let LLVM decide the section
Some basic types
llvmWordPtr :: Platform -> LlvmType Source #
The target architectures word size
Metadata types
LLVM metadata expressions
Associates some metadata with a specific label for attaching to an instruction.
Metadata declarations. Metadata can only be declared in global scope.
A reference to an un-named metadata node.
Operations on the type system.
getLink :: LlvmVar -> LlvmLinkageType Source #
Return the LlvmLinkageType for a LlvmVar
getStatType :: LlvmStatic -> LlvmType Source #
Return the LlvmType of the LlvmStatic
pLower :: LlvmType -> LlvmType Source #
Remove the pointer indirection of the supplied type. Only LMPointer
 constructors can be lowered.
llvmWidthInBits :: Platform -> LlvmType -> Int Source #
Width in bits of an LlvmType, returns 0 if not applicable
Pretty Printing
ppName :: LlvmOpts -> LlvmVar -> SDoc Source #
Return the variable name or value of the LlvmVar
 in Llvm IR textual representation (e.g. @x, %y or 42).
ppPlainName :: LlvmOpts -> LlvmVar -> SDoc Source #
Return the variable name or value of the LlvmVar
 in a plain textual representation (e.g. x, y or 42).
ppLlvmModule :: LlvmOpts -> LlvmModule -> SDoc Source #
Print out a whole LLVM module.
ppLlvmComments :: [LMString] -> SDoc Source #
Print out a multi-line comment, can be inside a function or on its own
ppLlvmComment :: LMString -> SDoc Source #
Print out a comment, can be inside a function or on its own
ppLlvmGlobals :: LlvmOpts -> [LMGlobal] -> SDoc Source #
Print out a list of global mutable variable definitions
ppLlvmGlobal :: LlvmOpts -> LMGlobal -> SDoc Source #
Print out a global mutable variable definition
ppLlvmFunctionDecls :: LlvmFunctionDecls -> SDoc Source #
Print out a list of function declaration.
ppLlvmFunctionDecl :: LlvmFunctionDecl -> SDoc Source #
Print out a function declaration. Declarations define the function type but don't define the actual body of the function.
ppLlvmFunctions :: LlvmOpts -> LlvmFunctions -> SDoc Source #
Print out a list of function definitions.
ppLlvmFunction :: LlvmOpts -> LlvmFunction -> SDoc Source #
Print out a function definition.
ppLlvmAlias :: LlvmAlias -> SDoc Source #
Print out an LLVM type alias.
ppLlvmAliases :: [LlvmAlias] -> SDoc Source #
Print out a list of LLVM type aliases.
ppLlvmMetas :: LlvmOpts -> [MetaDecl] -> SDoc Source #
Print out a list of LLVM metadata.
ppLlvmMeta :: LlvmOpts -> MetaDecl -> SDoc Source #
Print out an LLVM metadata definition.