llvm-ffi-9.1.0.1: FFI bindings to the LLVM compiler toolkit.

Safe HaskellSafe

LLVM.FFI.Core

Contents

Synopsis

Documentation

version :: IntSource

Version of LLVM we have linked to.

Boolean values

newtype Bool Source

Constructors

Bool Int32 

Instances

Error handling

Raw.Context functions

getMDKindID :: CString -> CUInt -> IO CUIntSource

Modules

data Module Source

Instances

Types

data Type Source

Instances

Integer types

Real types

Function types

functionTypeSource

Arguments

:: TypeRef

return type

-> Ptr TypeRef

array of argument types

-> CUInt

number of elements in array

-> Bool

non-zero if function is varargs

-> IO TypeRef 

Create a function type.

isFunctionVarArg :: TypeRef -> IO BoolSource

Indicate whether a function takes varargs.

getReturnType :: TypeRef -> IO TypeRefSource

Give a function's return type.

countParamTypes :: TypeRef -> IO CUIntSource

Give the number of fixed parameters that a function takes.

getParamTypes :: TypeRef -> Ptr TypeRef -> IO ()Source

Fill out an array with the types of a function's fixed parameters.

Struct types

Array, pointer, and vector types

arrayTypeSource

Arguments

:: TypeRef

element type

-> CUInt

element count

-> IO TypeRef 

pointerTypeSource

Arguments

:: TypeRef

pointed-to type

-> CUInt

address space

-> IO TypeRef 

vectorTypeSource

Arguments

:: TypeRef

element type

-> CUInt

element count

-> IO TypeRef 

getElementType :: TypeRef -> IO TypeRefSource

Get the type of a sequential type's elements.

Other types

Values

data Value Source

Instances

Uses

Users

Constants

Metadata

Scalar constants

constInt :: TypeRef -> CULLong -> Bool -> IO ValueRefSource

Composite constants

Constant Expressions

constICmp :: IntPredicate -> ValueRef -> ValueRef -> IO ValueRefSource

constFCmp :: RealPredicate -> ValueRef -> ValueRef -> IO ValueRefSource

Comparison predicates

data IntPredicate Source

Constructors

IntEQ

equal

IntNE

not equal

IntUGT

unsigned greater than

IntUGE

unsigned greater or equal

IntULT

unsigned less than

IntULE

unsigned less or equal

IntSGT

signed greater than

IntSGE

signed greater or equal

IntSLT

signed less than

IntSLE

signed less or equal

data FPPredicate Source

Constructors

FPFalse

Always false (always folded)

FPOEQ

True if ordered and equal

FPOGT

True if ordered and greater than

FPOGE

True if ordered and greater than or equal

FPOLT

True if ordered and less than

FPOLE

True if ordered and less than or equal

FPONE

True if ordered and operands are unequal

FPORD

True if ordered (no nans)

FPUNO

True if unordered: isnan(X) | isnan(Y)

FPUEQ

True if unordered or equal

FPUGT

True if unordered or greater than

FPUGE

True if unordered, greater than, or equal

FPULT

True if unordered or less than

FPULE

True if unordered, less than, or equal

FPUNE

True if unordered or not equal

FPTrue

Always true (always folded)

Floating point attributes

Support operations and types

data Linkage Source

An enumeration for the kinds of linkage for global values.

Constructors

ExternalLinkage

Externally visible function

AvailableExternallyLinkage 
LinkOnceAnyLinkage

Keep one copy of function when linking (inline)

LinkOnceODRLinkage

Same, but only replaced by something equivalent.

LinkOnceODRAutoHideLinkage

Like LinkOnceODR, but possibly hidden.

WeakAnyLinkage

Keep one copy of named function when linking (weak)

WeakODRLinkage

Same, but only replaced by something equivalent.

AppendingLinkage

Special purpose, only applies to global arrays

InternalLinkage

Rename collisions when linking (static functions)

PrivateLinkage

Like Internal, but omit from symbol table

DLLImportLinkage

Function to be imported from DLL

DLLExportLinkage

Function to be accessible from DLL

ExternalWeakLinkage

ExternalWeak linkage description

GhostLinkage

Stand-in functions for streaming fns from BC files

CommonLinkage

Tentative definitions

LinkerPrivateLinkage

Like Private, but linker removes.

LinkerPrivateWeakLinkage

Like LinkerPrivate, but is weak.

toLinkage :: Linkage -> LinkageSource

data Visibility Source

An enumeration for the kinds of visibility of global values.

Constructors

DefaultVisibility

The GV is visible

HiddenVisibility

The GV is hidden

ProtectedVisibility

The GV is protected

Global variables, functions, and aliases (globals)

setLinkage :: ValueRef -> Linkage -> IO ()Source

setVisibility :: ValueRef -> Visibility -> IO ()Source

Global variables

Aliases

Parameter passing

newtype AttributeKind Source

Constructors

AttributeKind CUInt 

Calling conventions

Functions

addFunction :: ModuleRef -> CString -> TypeRef -> IO FunctionRefSource

deleteFunction :: FunctionRef -> IO ()Source

getIntrinsicID :: FunctionRef -> IO CUIntSource

getFunctionCallConv :: FunctionRef -> IO CallingConventionSource

setFunctionCallConv :: FunctionRef -> CallingConvention -> IO ()Source

Parameters

countParams :: FunctionRef -> IO CUIntSource

getParamsSource

Arguments

:: FunctionRef 
-> Ptr ValueRef

array to fill out

-> IO () 

getParamSource

Arguments

:: FunctionRef 
-> CUInt

offset into array

-> IO ValueRef 

Basic blocks

countBasicBlocksSource

Arguments

:: ValueRef

function

-> IO CUInt 

getBasicBlocksSource

Arguments

:: ValueRef

function

-> Ptr BasicBlockRef

array to fill out

-> IO () 

appendBasicBlockSource

Arguments

:: ValueRef

function

-> CString

name for label

-> IO BasicBlockRef 

insertBasicBlockSource

Arguments

:: BasicBlockRef

insert before this one

-> CString

name for label

-> IO BasicBlockRef 

Instructions

Call Sites

getInstructionCallConv :: ValueRef -> IO CallingConventionSource

setInstructionCallConv :: ValueRef -> CallingConvention -> IO ()Source

setInstrParamAlignment :: ValueRef -> CUInt -> CUInt -> IO ()Source

Call Instructions (only)

Switch Instructions (only)

Phi nodes

Instruction building

Metadata

Terminators

Arithmetic

Memory

Casts

Comparisons

Miscellaneous instructions

Memory buffers

Raw.PassRegistry

Pass manager

Functions from extras.cpp