ddc-core-llvm-0.3.2.1: Disciplined Disciple Compiler LLVM code generator.

Safe HaskellSafe-Inferred

DDC.Llvm.Syntax

Contents

Synopsis

Modules

data Module Source

This is a top level container in LLVM.

Constructors

Module 

Fields

modComments :: [String]

Comments to include at the start of the module.

modAliases :: [TypeAlias]

Alias type definitions.

modGlobals :: [Global]

Global variables to include in the module.

modFwdDecls :: [FunctionDecl]

Functions used in this module but defined in other modules.

modFuncs :: [Function]

Functions defined in this module.

modMDecls :: [MDecl]

Metdata for alias analysis

Instances

Pretty Module

Print out a whole LLVM module.

lookupCallConv :: String -> Module -> Maybe CallConvSource

Lookup the calling convention for this function, using the forward declarations as well as the function definitions.

Global variables

data Global Source

A global mutable variable. Maybe defined or external

Instances

typeOfGlobal :: Global -> TypeSource

Return the LlvmType of the LMGlobal

varOfGlobal :: Global -> VarSource

Return the LlvmVar part of a LMGlobal

Static data

data Static Source

Llvm Static Data. These represent the possible global level variables and constants.

Constructors

StaticComment String

A comment in a static section.

StaticLit Lit

A static variant of a literal value.

StaticUninitType Type

For uninitialised data.

StaticStr String Type

Defines a static LMString.

StaticArray [Static] Type

A static array.

StaticStruct [Static] Type

A static structure type.

StaticPointer Var

A pointer to other data.

StaticBitc Static Type

Pointer to Pointer conversion.

StaticPtoI Static Type

Pointer to Integer conversion.

StaticAdd Static Static

Constant addition operation.

StaticSub Static Static

Constant subtraction operation.

Instances

typeOfStatic :: Static -> TypeSource

Return the LlvmType of the LlvmStatic.

Function declarations

data FunctionDecl Source

An LLVM Function

Constructors

FunctionDecl 

Fields

declName :: String

Unique identifier of the function

declLinkage :: Linkage

LinkageType of the function

declCallConv :: CallConv

The calling convention of the function

declReturnType :: Type

Type of the returned value

declParamListType :: ParamListType

Indicates if this function uses varargs

declParams :: [Param]

Parameter types and attributes

declAlign :: Align

Function align value, must be power of 2

data ParamListType Source

Functions can have a fixed amount of parameters, or a variable amount.

Constructors

FixedArgs

Fixed amount of arguments.

VarArgs

Variable amount of arguments.

data Param Source

Describes a function parameter.

Constructors

Param 

Instances

data Align Source

Alignment.

Instances

Functions

data Function Source

A LLVM Function

Constructors

Function 

Fields

funDecl :: FunctionDecl

The signature of this declared function.

funParams :: [String]

The function parameter names.

funAttrs :: [FuncAttr]

The function attributes.

funSection :: Section

The section to put the function into,

funBlocks :: [Block]

The body of the functions.

Instances

data Section Source

The section name to put the function in.

Constructors

SectionAuto

Let the LLVM decide what section to put this in.

SectionSpecific String

Put it in this specific section.

Instances

Blocks

data Block Source

A block of LLVM code with an optional annotation.

Constructors

Block 

Fields

blockLabel :: Label

The code label for this block

blockInstrs :: Seq AnnotInstr

A list of LlvmStatement's representing the code for this block. This list must end with a control flow statement.

Instances

defVarsOfBlock :: Block -> Set VarSource

Get the set of LLVM variables that this block defines.

Block labels

data Label Source

Block labels.

Constructors

Label String 

Annotated Instructions

data AnnotInstr Source

Instructions annotated with metadata.

Constructors

AnnotInstr 

Fields

annotInstr :: Instr
 
annotMDecl :: [MDecl]
 

annotNil :: Instr -> AnnotInstrSource

Construct an annotated instruction with no annotations.

annotWith :: Instr -> [MDecl] -> AnnotInstrSource

Annotate an instruction with some metadata.

Instructions

data Instr Source

Instructions

Constructors

IComment [String]

Comment meta-instruction.

ISet Var Exp

Set meta instruction v1 = value. This isn't accepted by the real LLVM compiler. ISet instructions are erased by the Clean transform.

INop

No operation. This isn't accepted by the real LLVM compiler. INop instructions are erased by the Clean transform.

IPhi Var [(Exp, Label)] 
IReturn (Maybe Exp)

Return a result.

IBranch Label

Unconditional branch to the target label.

IBranchIf Exp Label Label

Conditional branch.

ISwitch Exp Label [(Lit, Label)]

Mutliway branch. If scruitniee matches one of the literals in the list then jump to the corresponding label, otherwise jump to the default.

IUnreachable

Informs the optimizer that instructions after this point are unreachable.

IOp Var Op Exp Exp 
IConv Var Conv Exp

Cast the variable from to the to type. This is an abstraction of three cast operators in Llvm, inttoptr, prttoint and bitcast.

ILoad Var Exp

Load a value from memory.

IStore Exp Exp

Store a value to memory. First expression gives the destination pointer.

IICmp Var ICond Exp Exp

Integer comparison.

IFCmp Var FCond Exp Exp

Floating-point comparison.

ICall (Maybe Var) CallType (Maybe CallConv) Type Name [Exp] [FuncAttr]

Call a function. Only NoReturn, NoUnwind and ReadNone attributes are valid.

Instances

branchTargetsOfInstr :: Instr -> Maybe (Set Label)Source

If this instruction can branch to a label then return the possible targets.

defVarOfInstr :: Instr -> Maybe VarSource

Get the LLVM variable that this instruction assigns to, or Nothing if there isn't one.

Metadata

data Metadata Source

Different types of metadata used in LLVM IR e.g. debug, tbaa, range, etc.

Constructors

Tbaa MDNode 
Debug 

data MDecl Source

Maps matadata references to metadata nodes e.g. !2 = !{ metadata id, !0, !i11}

Constructors

MDecl MRef Metadata 

Instances

data MRef Source

Constructors

MRef Int 

Instances

tbaaNodeSource

Arguments

:: String

A unique identifier for the node

-> MRef

The parent node

-> Bool

Whether this node represents a const region

-> Metadata 

Construct a single tbaa node

Expression types

data Type Source

Llvm Types.

Constructors

TVoid

Void type

TInt Integer

An integer with a given width in bits.

TFloat

32-bit floating point

TDouble

64-bit floating point

TFloat80

80 bit (x86 only) floating point

TFloat128

128 bit floating point

TLabel

A block label.

TPointer Type

A pointer to another type of thing.

TArray Integer Type

An array of things.

TStruct [Type]

A structure type.

TAlias TypeAlias

A type alias.

TFunction FunctionDecl

Function type, used to create pointers to functions.

Instances

data TypeAlias Source

A type alias.

Constructors

TypeAlias String Type 

isInt :: Type -> BoolSource

Test if the given LlvmType is an integer

isFloat :: Type -> BoolSource

Test if the given LlvmType is a floating point type

isPointer :: Type -> BoolSource

Test if the given LlvmType is an LMPointer construct

takeBytesOfType :: Integer -> Type -> Maybe IntegerSource

Calculate the size in bytes of a Type, given the size of pointers.

Expressions

data Exp Source

Constructors

XVar Var

Use of a variable.

XLit Lit

A literal.

XUndef Type

An undefined value.

Instances

typeOfExp :: Exp -> TypeSource

Take the type of an expression.

Variables

data Var Source

A variable that can be assigned to.

Constructors

Var Name Type 

Instances

nameOfVar :: Var -> NameSource

Yield the name of a var.

typeOfVar :: Var -> TypeSource

Yield the type of a var.

Names

data Name Source

Names of variables.

Instances

Literals

data Lit Source

Literal data.

Constructors

LitInt Type Integer

An integer literal

LitFloat Type Double

A floating-point literal.

LitNull Type

A null pointer literal. Only applicable to pointer types

LitUndef Type

A completely undefined value.

Instances

typeOfLit :: Lit -> TypeSource

Yield the Type of a Lit.

Primitive operators

data Op Source

Binary arithmetic operators.

Constructors

OpAdd

add two integers, floating point or vector values.

OpSub

subtract two ...

OpMul

multiply ..

OpUDiv

unsigned integer or vector division.

OpSDiv

signed integer ..

OpURem

unsigned integer or vector remainder

OpSRem

signed ...

OpFAdd

add two floating point or vector values.

OpFSub

subtract two ...

OpFMul

multiply ...

OpFDiv

divide ...

OpFRem

remainder ...

OpShl

Left shift.

OpLShr

Logical shift right

OpAShr

Arithmetic shift right. The most significant bits of the result will be equal to the sign bit of the left operand.

OpAnd

AND bitwise logical operation.

OpOr

OR bitwise logical operation.

OpXor

XOR bitwise logical operation.

Instances

data ICond Source

Integer comparison.

Constructors

ICondEq

Equal (Signed and Unsigned)

ICondNe

Not equal (Signed and Unsigned)

ICondUgt

Unsigned greater than

ICondUge

Unsigned greater than or equal

ICondUlt

Unsigned less than

ICondUle

Unsigned less than or equal

ICondSgt

Signed greater than

ICondSge

Signed greater than or equal

ICondSlt

Signed less than

ICondSle

Signed less than or equal

Instances

data FCond Source

Floating point comparison.

Constructors

FCondFalse

Always yields false, regardless of operands.

FCondOeq

Both operands are not a QNAN and op1 is equal to op2.

FCondOgt

Both operands are not a QNAN and op1 is greater than op2.

FCondOge

Both operands are not a QNAN and op1 is greater than or equal to op2.

FCondOlt

Both operands are not a QNAN and op1 is less than op2.

FCondOle

Both operands are not a QNAN and op1 is less than or equal to op2.

FCondOne

Both operands are not a QNAN and op1 is not equal to op2.

FCondOrd

Both operands are not a QNAN.

FCondUeq

Either operand is a QNAN or op1 is equal to op2.

FCondUgt

Either operand is a QNAN or op1 is greater than op2.

FCondUge

Either operand is a QNAN or op1 is greater than or equal to op2.

FCondUlt

Either operand is a QNAN or op1 is less than op2.

FCondUle

Either operand is a QNAN or op1 is less than or equal to op2.

FCondUne

Either operand is a QNAN or op1 is not equal to op2.

FCondUno

Either operand is a QNAN.

FCondTrue

Always yields true, regardless of operands.

Instances

data Conv Source

Conversion Operations

Constructors

ConvTrunc

Integer truncate

ConvZext

Integer extend (zero fill)

ConvSext

Integer extend (sign fill)

ConvFptrunc

Float truncate

ConvFpext

Float extend

ConvFptoui

Float to unsigned Integer

ConvFptosi

Float to signed Integer

ConvUintofp

Unsigned Integer to Float

ConvSintofp

Signed Int to Float

ConvPtrtoint

Pointer to Integer

ConvInttoptr

Integer to Pointer

ConvBitcast

Cast between types where no bit manipulation is needed

Instances

Attributes

data FuncAttr Source

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

The inliner should attempt to inline this function into callers whenever possible, ignoring any active inlining size threshold for this caller.

InlineHint

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

The inliner should never inline this function in any situation. This attribute may not be used together with the alwaysinline attribute.

OptSize

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

The function never returns normally. This produces undefined behavior at runtime if the function ever does dynamically return.

NoUnwind

The function never returns with an unwind or exceptional control flow. If the function does unwind, its runtime behavior is undefined.

ReadNone

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

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

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

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

The code generator should not use a red zone, even if the target-specific ABI normally permits it.

NoImplicitFloat

Disables implicit floating point instructions.

Naked

Disables prologue / epilogue emission for the function. This can have very system-specific consequences.

data ParamAttr Source

Parameter attributes are used to communicate additional information about the result or parameters of a function

Constructors

ZeroExt

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

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

The 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

The pointer parameter should really be passed by value to the function.

SRet

The pointer parameter specifies the address of a structure that is the return value of the function in the source program.

NoAlias

The pointer does not alias any global or any other parameter.

NoCapture

The callee does not make any copies of the pointer that outlive the callee itself.

Nest

The pointer parameter can be excised using the trampoline intrinsics.

data CallConv 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_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 CallType Source

Different ways to call a function.

Constructors

CallTypeStd

Normal call, allocate a new stack frame.

CallTypeTail

Tail call, perform the call in the current stack frame.

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