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

Safe HaskellSafe
LanguageHaskell2010

LLVM.FFI.Core

Contents

Description

Raw.Module: LLVM.FFI.Core Copyright: Bryan O'Sullivan 2007, 2008 License: BSD-style (see the file LICENSE)

Maintainer: bos@serpentine.com Stability: experimental Portability: requires GHC 6.8, LLVM

This module provides direct access to the LLVM C bindings.

Synopsis

Documentation

version :: Int Source #

Version of LLVM we have linked to.

Boolean values

newtype Bool Source #

Constructors

Bool Int32 
Instances
Enum Bool Source # 
Instance details

Defined in LLVM.FFI.Base

Methods

succ :: Bool -> Bool #

pred :: Bool -> Bool #

toEnum :: Int -> Bool #

fromEnum :: Bool -> Int #

enumFrom :: Bool -> [Bool] #

enumFromThen :: Bool -> Bool -> [Bool] #

enumFromTo :: Bool -> Bool -> [Bool] #

enumFromThenTo :: Bool -> Bool -> Bool -> [Bool] #

Eq Bool Source # 
Instance details

Defined in LLVM.FFI.Base

Methods

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

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

Show Bool Source # 
Instance details

Defined in LLVM.FFI.Base

Methods

showsPrec :: Int -> Bool -> ShowS #

show :: Bool -> String #

showList :: [Bool] -> ShowS #

Error handling

Raw.Context functions

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

Modules

Types

data TypeKind Source #

Integer types

Real types

Function types

functionType Source #

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

structSetBody :: TypeRef -> Ptr TypeRef -> CUInt -> Bool -> 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

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

Uses

Users

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

Constants

Metadata

Scalar constants

constInt :: TypeRef -> CULLong -> Bool -> IO ValueRef Source #

constReal :: TypeRef -> CDouble -> IO ValueRef Source #

Composite constants

Constant Expressions

constICmp :: IntPredicate -> ValueRef -> ValueRef -> IO ValueRef Source #

constFCmp :: RealPredicate -> ValueRef -> ValueRef -> IO ValueRef Source #

constExtractValue :: ValueRef -> Ptr CUInt -> CUInt -> IO ValueRef Source #

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

toIntPredicate :: IntPredicate -> IntPredicate Source #

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)

toRealPredicate :: RealPredicate -> FPPredicate Source #

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.

Instances
Enum Linkage Source # 
Instance details

Defined in LLVM.FFI.Core

Eq Linkage Source # 
Instance details

Defined in LLVM.FFI.Core

Methods

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

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

Ord Linkage Source # 
Instance details

Defined in LLVM.FFI.Core

Show Linkage Source # 
Instance details

Defined in LLVM.FFI.Core

fromLinkage :: Linkage -> Linkage Source #

toLinkage :: Linkage -> Linkage Source #

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

toVisibility :: Visibility -> Visibility Source #

Global variables, functions, and aliases (globals)

getLinkage :: ValueRef -> IO Linkage Source #

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

getVisibility :: ValueRef -> IO Visibility Source #

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

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

Global variables

Aliases

Parameter passing

newtype AttributeKind Source #

Constructors

AttributeKind CUInt 

Calling conventions

data CallingConvention Source #

Constructors

C 
Fast 
Cold 
X86StdCall 
X86FastCall 
GHC 
Instances
Bounded CallingConvention Source # 
Instance details

Defined in LLVM.FFI.Core

Enum CallingConvention Source # 
Instance details

Defined in LLVM.FFI.Core

Eq CallingConvention Source # 
Instance details

Defined in LLVM.FFI.Core

Ord CallingConvention Source # 
Instance details

Defined in LLVM.FFI.Core

Show CallingConvention Source # 
Instance details

Defined in LLVM.FFI.Core

Functions

addFunction :: ModuleRef -> CString -> TypeRef -> IO FunctionRef Source #

deleteFunction :: FunctionRef -> IO () Source #

getIntrinsicID :: FunctionRef -> IO CUInt Source #

getFunctionCallConv :: FunctionRef -> IO CallingConvention Source #

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

Parameters

countParams :: FunctionRef -> IO CUInt Source #

getParams Source #

Arguments

:: FunctionRef 
-> Ptr ValueRef

array to fill out

-> IO () 

getParam Source #

Arguments

:: FunctionRef 
-> CUInt

offset into array

-> IO ValueRef 

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

getICmpPredicate :: ValueRef -> IO IntPredicate Source #

Call Sites

getInstructionCallConv :: ValueRef -> IO CallingConvention Source #

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

buildFCmp :: BuilderRef -> RealPredicate -> ValueRef -> ValueRef -> CString -> IO ValueRef Source #

Miscellaneous instructions

Memory buffers

Raw.PassRegistry

Pass manager

Functions from extras.cpp