ghc-7.8.4: The GHC API

Safe HaskellNone
LanguageHaskell98

Llvm.Types

Contents

Description

The LLVM Type System.

Synopsis

LLVM Basic Types and Variables

data LMGlobal Source

A global mutable variable. Maybe defined or external

Constructors

LMGlobal 

Fields

getGlobalVar :: LlvmVar

Returns the variable of the LMGlobal

getGlobalValue :: Maybe LlvmStatic

Return the value of the LMGlobal

type LMString = FastString Source

A String in LLVM

type LlvmAlias = (LMString, LlvmType) Source

A type alias

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]

Structure type

LMAlias LlvmAlias

A type alias

LMMetadata

LLVM Metadata

LMFunction LlvmFunctionDecl

Function type, used to create pointers to functions

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

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

Operations on LLVM Basic Types and Variables

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

ppLit :: LlvmLit -> SDoc Source

Print a literal value. No type.

pLift :: LlvmType -> LlvmType Source

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

pVarLift :: LlvmVar -> LlvmVar Source

Lower a variable of LMPointer type.

pLower :: LlvmType -> LlvmType Source

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

pVarLower :: LlvmVar -> LlvmVar Source

Lower a variable of LMPointer type.

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

isGlobal :: LlvmVar -> Bool Source

Test if a LlvmVar is global.

llvmWidthInBits :: DynFlags -> LlvmType -> Int Source

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

Shortcut for Common Types

llvmWord :: DynFlags -> LlvmType Source

The target architectures word size

llvmWordPtr :: DynFlags -> LlvmType Source

The target architectures word size

LLVM Function Types

data LlvmFunctionDecl Source

An LLVM Function

Constructors

LlvmFunctionDecl 

Fields

decName :: LMString

Unique identifier of the function

funcLinkage :: LlvmLinkageType

LinkageType of the function

funcCc :: LlvmCallConvention

The calling convention of the function

decReturnType :: LlvmType

Type of the returned value

decVarargs :: LlvmParameterListType

Indicates if this function uses varargs

decParams :: [LlvmParameter]

Parameter types and attributes

funcAlign :: LMAlign

Function align value, must be power of 2

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.

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.

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 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_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 LlvmParameterListType Source

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

Constructors

FixedArgs 
VarArgs 

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

LLVM Operations

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

Floating point conversion

ppDouble :: Double -> SDoc Source

Convert a Haskell Double to an LLVM hex encoded floating point form. In Llvm float literals can be printed in a big-endian hexadecimal format, regardless of underlying architecture.

See Note [LLVM Float Types].

fixEndian :: [a] -> [a] Source

Reverse or leave byte data alone to fix endianness on this target.

Misc functions