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

CopyrightBryan O'Sullivan 2007, 2008
LicenseBSD-style (see the file LICENSE)
Maintainerbos@serpentine.com
Stabilityexperimental
Portabilityrequires GHC 6.8, LLVM
Safe HaskellSafe
LanguageHaskell98

LLVM.FFI.Core

Contents

Description

This module provides direct access to the LLVM C bindings.

Synopsis

Documentation

Error handling

Context functions

data Context Source

Instances

getMDKindID :: CString -> CUInt -> IO CUInt Source

Modules

data Module Source

Instances

Module providers

Types

data Type Source

Instances

Integer types

Real types

Function types

functionType Source

Arguments

:: TypeRef

return type

-> Ptr TypeRef

array of argument types

-> CUInt

number of elements in array

-> CInt

non-zero if function is varargs

-> IO TypeRef 

Create a function type.

isFunctionVarArg :: TypeRef -> IO CInt Source

Indicate whether a function takes varargs.

getReturnType :: TypeRef -> IO TypeRef Source

Give a function's return type.

countParamTypes :: TypeRef -> IO CUInt Source

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

structType :: Ptr TypeRef -> CUInt -> CInt -> IO TypeRef Source

structSetBody :: TypeRef -> Ptr TypeRef -> CUInt -> CInt -> IO () Source

Array, pointer, and vector types

arrayType Source

Arguments

:: TypeRef

element type

-> CUInt

element count

-> IO TypeRef 

pointerType Source

Arguments

:: TypeRef

pointed-to type

-> CUInt

address space

-> IO TypeRef 

vectorType Source

Arguments

:: TypeRef

element type

-> CUInt

element count

-> IO TypeRef 

getElementType :: TypeRef -> IO TypeRef Source

Get the type of a sequential type's elements.

Other types

Values

data Value Source

Instances

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

Uses

Users

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

Constants

Metadata

Scalar constants

constInt :: TypeRef -> CULLong -> CInt -> IO ValueRef Source

Composite constants

constString :: CString -> CUInt -> CInt -> IO ValueRef Source

constStruct :: Ptr ValueRef -> CUInt -> CInt -> IO ValueRef Source

Constant Expressions

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.

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.

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 -> CUInt -> IO () Source

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

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

Global variables

setThreadLocal :: ValueRef -> CInt -> IO () Source

Aliases

Parameter passing

fromAttribute :: Attribute -> CAttribute Source

toAttribute :: CAttribute -> Attribute Source

Calling conventions

Functions

addFunction Source

Arguments

:: ModuleRef

module

-> CString

name

-> TypeRef

type

-> IO ValueRef 

getNamedFunction Source

Arguments

:: ModuleRef

module

-> CString

name

-> IO ValueRef

function (nullPtr if not found)

deleteFunction Source

Arguments

:: ValueRef

function

-> IO () 

getIntrinsicID Source

Arguments

:: ValueRef

function

-> IO CUInt 

getFunctionCallConv Source

Arguments

:: ValueRef

function

-> IO CUInt 

setFunctionCallConv Source

Arguments

:: ValueRef

function

-> CUInt 
-> IO () 

addFunctionAttr :: ValueRef -> CAttribute -> IO () Source

removeFunctionAttr :: ValueRef -> CAttribute -> IO () Source

Parameters

countParams Source

Arguments

:: ValueRef

function

-> IO CUInt 

getParams Source

Arguments

:: ValueRef

function

-> Ptr ValueRef

array to fill out

-> IO () 

getParam Source

Arguments

:: ValueRef

function

-> CUInt

offset into array

-> IO ValueRef 

addAttribute :: ValueRef -> CAttribute -> IO () Source

removeAttribute :: ValueRef -> CAttribute -> IO () Source

Basic blocks

countBasicBlocks Source

Arguments

:: ValueRef

function

-> IO CUInt 

getBasicBlocks Source

Arguments

:: ValueRef

function

-> Ptr BasicBlockRef

array to fill out

-> IO () 

appendBasicBlock Source

Arguments

:: ValueRef

function

-> CString

name for label

-> IO BasicBlockRef 

insertBasicBlock Source

Arguments

:: BasicBlockRef

insert before this one

-> CString

name for label

-> IO BasicBlockRef 

Instructions

Call Sites

addInstrAttribute :: ValueRef -> CUInt -> CAttribute -> IO () Source

removeInstrAttribute :: ValueRef -> CUInt -> CAttribute -> IO () Source

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

Call Instructions (only)

setTailCall :: ValueRef -> CInt -> IO () Source

Switch Instructions (only)

Phi nodes

Instruction building

data Builder Source

Instances

Metadata

Terminators

setCleanup :: ValueRef -> CInt -> IO () Source

Arithmetic

Memory

Casts

Comparisons

Miscellaneous instructions

Memory buffers

PassRegistry

Pass manager

Functions from extras.cpp