ghc-8.0.2: The GHC API

Safe HaskellNone
LanguageHaskell2010

Llvm

Contents

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 (http://www.cs.uu.nl/wiki/Ehc/WebHome).

Synopsis

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

data LlvmStatement Source #

Llvm Statements

Constructors

Assignment LlvmVar LlvmExpression

Assign an expression to an 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)]

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

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 an 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, prttoint 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 i1, true if store was successful.

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

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

Atomic operations

data LlvmAtomicOp Source #

LLVM atomic operations. Please see the atomicrmw instruction in the LLVM documentation for a complete description.

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.

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 registerised calling convention.

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 StdCall convention. LLVM includes a specific alias for it rather than just using CC_Ncc.

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.

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 static keyword in C.

LinkOnce

Globals with linkonce linkage are merged with other globals of the same name when linkage occurs. This is typically used to implement inline functions, templates, or other code which must be generated in each translation unit that uses it. Unreferenced linkonce globals are allowed to be discarded.

Weak

weak linkage is exactly the same as linkonce linkage, except that unreferenced weak globals may not be discarded. This is used for globals that may be emitted in multiple translation units, but that are not guaranteed to be emitted into every translation unit that uses them. One example of this are common globals in C, such as int X; at global scope.

Appending

appending linkage may only be applied to global variables of pointer to array type. When two global variables with appending linkage are linked together, the two global arrays are appended together. This is the Llvm, typesafe, equivalent of having the system linker append together sections with identical names when .o files are linked.

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 ExternallyVisible but with explicit textual form in LLVM assembly.

Private

Symbol is private to the module and should not appear in the symbol table

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.

Operations and Comparisons

data LlvmCmpOp Source #

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.

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

Variables and Type System

data LlvmVar Source #

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 LMString

LMStaticArray [LlvmStatic] LlvmType

A static array

LMStaticStruc [LlvmStatic] LlvmType

A static structure type

LMStaticPointer LlvmVar

A pointer to other data

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

data LlvmLit Source #

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.

data LlvmType Source #

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 LlvmType

LMArray Int LlvmType

An array of LlvmType

LMVector Int LlvmType

A vector of LlvmType

LMLabel

A LlvmVar can represent a label (address)

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

type LlvmAlias = (LMString, LlvmType) Source #

A type alias

data LMGlobal Source #

A global mutable variable. Maybe defined or external

Constructors

LMGlobal 

Fields

type LMString = FastString Source #

A String in LLVM

type LMSection = Maybe LMString Source #

An LLVM section definition. If Nothing then let LLVM decide the section

data LMConst Source #

Constructors

Global

Mutable global variable

Constant

Constant global variable

Alias

Alias of another variable

Instances

Eq LMConst # 

Methods

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

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

Some basic types

llvmWord :: DynFlags -> LlvmType Source #

The target architectures word size

llvmWordPtr :: DynFlags -> LlvmType Source #

The target architectures word size

Metadata types

data MetaExpr Source #

LLVM metadata expressions

data MetaAnnot Source #

Associates some metadata with a specific label for attaching to an instruction.

Instances

data MetaDecl Source #

Metadata declarations. Metadata can only be declared in global scope.

Constructors

MetaNamed LMString [Int]

Named metadata. Only used for communicating module information to LLVM. ('!name = !{ [!n] }' form).

MetaUnamed Int MetaExpr

Metadata node declaration. ('!0 = metadata !{ expression }' form).

Operations on the type system.

isGlobal :: LlvmVar -> Bool Source #

Test if a LlvmVar is global.

pVarLift :: LlvmVar -> LlvmVar Source #

Lift a variable to LMPointer type.

pVarLower :: LlvmVar -> LlvmVar Source #

Lower a variable of LMPointer type.

pLift :: LlvmType -> LlvmType Source #

Add a pointer indirection to the supplied type. LMLabel and LMVoid cannot be lifted.

pLower :: LlvmType -> LlvmType Source #

Remove the pointer indirection of the supplied type. Only LMPointer constructors can be lowered.

isInt :: LlvmType -> Bool Source #

Test if the given LlvmType is an integer

isFloat :: LlvmType -> Bool Source #

Test if the given LlvmType is a floating point type

isPointer :: LlvmType -> Bool Source #

Test if the given LlvmType is an LMPointer construct

isVector :: LlvmType -> Bool Source #

Test if the given LlvmType is an LMVector construct

llvmWidthInBits :: DynFlags -> LlvmType -> Int Source #

Width in bits of an LlvmType, returns 0 if not applicable

Pretty Printing

ppLit :: LlvmLit -> SDoc Source #

Print a literal value. No type.

ppName :: LlvmVar -> SDoc Source #

Return the variable name or value of the LlvmVar in Llvm IR textual representation (e.g. @x, %y or 42).

ppPlainName :: LlvmVar -> SDoc Source #

Return the variable name or value of the LlvmVar in a plain textual representation (e.g. x, y or 42).

ppLlvmModule :: 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 :: [LMGlobal] -> SDoc Source #

Print out a list of global mutable variable definitions

ppLlvmGlobal :: 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 :: LlvmFunctions -> SDoc Source #

Print out a list of function definitions.

ppLlvmFunction :: 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 :: [MetaDecl] -> SDoc Source #

Print out a list of LLVM metadata.

ppLlvmMeta :: MetaDecl -> SDoc Source #

Print out an LLVM metadata definition.