module LLVM.FFI.Core
(
Module
, ModuleRef
, moduleCreateWithName
, disposeModule
, ptrDisposeModule
, getDataLayout
, setDataLayout
, getTarget
, setTarget
, ModuleProvider
, ModuleProviderRef
, createModuleProviderForExistingModule
, ptrDisposeModuleProvider
, Type
, TypeRef
, addTypeName
, deleteTypeName
, getTypeKind
, TypeKind(..)
, int1Type
, int8Type
, int16Type
, int32Type
, int64Type
, integerType
, getIntTypeWidth
, floatType
, doubleType
, x86FP80Type
, fp128Type
, ppcFP128Type
, functionType
, isFunctionVarArg
, getReturnType
, countParamTypes
, getParamTypes
, voidType
, labelType
, opaqueType
, arrayType
, pointerType
, vectorType
, getElementType
, getArrayLength
, getPointerAddressSpace
, getVectorSize
, structType
, countStructElementTypes
, getStructElementTypes
, isPackedStruct
, createTypeHandle
, refineType
, resolveTypeHandle
, disposeTypeHandle
, Value
, ValueRef
, typeOf
, getValueName
, setValueName
, dumpValue
, constNull
, constAllOnes
, getUndef
, isConstant
, isNull
, isUndef
, Linkage
, Visibility
, isDeclaration
, getLinkage
, setLinkage
, getSection
, setSection
, getVisibility
, setVisibility
, getAlignment
, setAlignment
, addGlobal
, getNamedGlobal
, deleteGlobal
, getInitializer
, setInitializer
, isThreadLocal
, setThreadLocal
, isGlobalConstant
, setGlobalConstant
, getFirstGlobal
, getNextGlobal
, getPreviousGlobal
, getLastGlobal
, getGlobalParent
, addFunction
, getNamedFunction
, deleteFunction
, countParams
, getParams
, getParam
, getIntrinsicID
, getGC
, setGC
, getFirstFunction
, getNextFunction
, getPreviousFunction
, getLastFunction
, getFirstParam
, getNextParam
, getPreviousParam
, getLastParam
, getParamParent
, isTailCall
, setTailCall
, addIncoming
, countIncoming
, getIncomingValue
, getIncomingBlock
, CallingConvention(..)
, fromCallingConvention
, toCallingConvention
, getFunctionCallConv
, setFunctionCallConv
, getInstructionCallConv
, setInstructionCallConv
, constInt
, constReal
, constArray
, constString
, constStruct
, constVector
, sizeOf
, constNeg
, constNot
, constAdd
, constSub
, constMul
, constUDiv
, constSDiv
, constFDiv
, constURem
, constSRem
, constFRem
, constAnd
, constOr
, constXor
, constICmp
, constFCmp
, constShl
, constLShr
, constAShr
, constGEP
, constTrunc
, constSExt
, constZExt
, constFPTrunc
, constFPExt
, constUIToFP
, constSIToFP
, constFPToUI
, constFPToSI
, constPtrToInt
, constIntToPtr
, constBitCast
, constSelect
, constExtractElement
, constInsertElement
, constShuffleVector
, constRealOfString
, BasicBlock
, BasicBlockRef
, basicBlockAsValue
, valueIsBasicBlock
, valueAsBasicBlock
, countBasicBlocks
, getBasicBlocks
, getEntryBasicBlock
, appendBasicBlock
, insertBasicBlock
, deleteBasicBlock
, getFirstBasicBlock
, getNextBasicBlock
, getPreviousBasicBlock
, getLastBasicBlock
, getInsertBlock
, getBasicBlockParent
, Builder
, BuilderRef
, createBuilder
, ptrDisposeBuilder
, positionBuilder
, positionBefore
, positionAtEnd
, getFirstInstruction
, getNextInstruction
, getPreviousInstruction
, getLastInstruction
, getInstructionParent
, buildRetVoid
, buildRet
, buildBr
, buildCondBr
, buildSwitch
, buildInvoke
, buildUnwind
, buildUnreachable
, buildAdd
, buildSub
, buildMul
, buildUDiv
, buildSDiv
, buildFDiv
, buildURem
, buildSRem
, buildFRem
, buildShl
, buildLShr
, buildAShr
, buildAnd
, buildOr
, buildXor
, buildNeg
, buildNot
, buildMalloc
, buildArrayMalloc
, buildAlloca
, buildArrayAlloca
, buildFree
, buildLoad
, buildStore
, buildGEP
, buildTrunc
, buildZExt
, buildSExt
, buildFPToUI
, buildFPToSI
, buildUIToFP
, buildSIToFP
, buildFPTrunc
, buildFPExt
, buildPtrToInt
, buildIntToPtr
, buildBitCast
, buildICmp
, buildFCmp
, buildPhi
, buildCall
, buildSelect
, buildVAArg
, buildExtractElement
, buildInsertElement
, buildShuffleVector
, addCase
, MemoryBuffer
, MemoryBufferRef
, createMemoryBufferWithContentsOfFile
, createMemoryBufferWithSTDIN
, disposeMemoryBuffer
, disposeMessage
, addInstrAttribute
, addAttribute
, removeInstrAttribute
, removeAttribute
, setInstrParamAlignment
, setParamAlignment
, Attribute(..)
, fromAttribute
, toAttribute
, PassManager
, PassManagerRef
, createFunctionPassManager
, createPassManager
, ptrDisposePassManager
, finalizeFunctionPassManager
, initializeFunctionPassManager
, runFunctionPassManager
, runPassManager
, dumpModule
) where
import Foreign.C.String (CString)
import Foreign.C.Types (CDouble, CInt, CUInt, CULLong)
import Foreign.Ptr (Ptr, FunPtr)
data Module
type ModuleRef = Ptr Module
foreign import ccall unsafe "LLVMModuleCreateWithName" moduleCreateWithName
:: CString -> IO ModuleRef
foreign import ccall unsafe "LLVMDisposeModule" disposeModule
:: ModuleRef -> IO ()
foreign import ccall unsafe "&LLVMDisposeModule" ptrDisposeModule
:: FunPtr (ModuleRef -> IO ())
foreign import ccall unsafe "LLVMGetDataLayout" getDataLayout
:: ModuleRef -> IO CString
foreign import ccall unsafe "LLVMSetDataLayout" setDataLayout
:: ModuleRef -> CString -> IO ()
data ModuleProvider
type ModuleProviderRef = Ptr ModuleProvider
foreign import ccall unsafe "LLVMCreateModuleProviderForExistingModule"
createModuleProviderForExistingModule
:: ModuleRef -> IO ModuleProviderRef
foreign import ccall unsafe "&LLVMDisposeModuleProvider" ptrDisposeModuleProvider
:: FunPtr (ModuleProviderRef -> IO ())
data Type
type TypeRef = Ptr Type
foreign import ccall unsafe "LLVMInt1Type" int1Type :: TypeRef
foreign import ccall unsafe "LLVMInt8Type" int8Type :: TypeRef
foreign import ccall unsafe "LLVMInt16Type" int16Type :: TypeRef
foreign import ccall unsafe "LLVMInt32Type" int32Type :: TypeRef
foreign import ccall unsafe "LLVMInt64Type" int64Type :: TypeRef
foreign import ccall unsafe "LLVMIntType" integerType
:: CUInt
-> TypeRef
foreign import ccall unsafe "LLVMFloatType" floatType :: TypeRef
foreign import ccall unsafe "LLVMDoubleType" doubleType :: TypeRef
foreign import ccall unsafe "LLVMX86FP80Type" x86FP80Type :: TypeRef
foreign import ccall unsafe "LLVMFP128Type" fp128Type :: TypeRef
foreign import ccall unsafe "LLVMPPCFP128Type" ppcFP128Type :: TypeRef
foreign import ccall unsafe "LLVMVoidType" voidType :: TypeRef
foreign import ccall unsafe "LLVMFunctionType" functionType
:: TypeRef
-> Ptr TypeRef
-> CUInt
-> CInt
-> TypeRef
foreign import ccall unsafe "LLVMIsFunctionVarArg" isFunctionVarArg
:: TypeRef -> IO CInt
foreign import ccall unsafe "LLVMGetReturnType" getReturnType
:: TypeRef -> IO TypeRef
foreign import ccall unsafe "LLVMCountParamTypes" countParamTypes
:: TypeRef -> IO CUInt
foreign import ccall unsafe "LLVMGetParamTypes" getParamTypes
:: TypeRef -> Ptr TypeRef -> IO ()
foreign import ccall unsafe "LLVMArrayType" arrayType
:: TypeRef
-> CUInt
-> TypeRef
foreign import ccall unsafe "LLVMPointerType" pointerType
:: TypeRef
-> CUInt
-> TypeRef
foreign import ccall unsafe "LLVMVectorType" vectorType
:: TypeRef
-> CUInt
-> TypeRef
foreign import ccall unsafe "LLVMAddTypeName" addTypeName
:: ModuleRef -> CString -> TypeRef -> IO CInt
foreign import ccall unsafe "LLVMDeleteTypeName" deleteTypeName
:: ModuleRef -> CString -> IO ()
foreign import ccall unsafe "LLVMGetElementType" getElementType
:: TypeRef -> IO TypeRef
data Value
type ValueRef = Ptr Value
foreign import ccall unsafe "LLVMAddGlobal" addGlobal
:: ModuleRef -> TypeRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMDeleteGlobal" deleteGlobal
:: ValueRef -> IO ()
foreign import ccall unsafe "LLVMSetInitializer" setInitializer
:: ValueRef -> ValueRef -> IO ()
foreign import ccall unsafe "LLVMGetNamedGlobal" getNamedGlobal
:: ModuleRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMGetInitializer" getInitializer
:: ValueRef -> IO ValueRef
foreign import ccall unsafe "LLVMIsThreadLocal" isThreadLocal
:: ValueRef -> IO CInt
foreign import ccall unsafe "LLVMSetThreadLocal" setThreadLocal
:: ValueRef -> CInt -> IO ()
foreign import ccall unsafe "LLVMIsGlobalConstant" isGlobalConstant
:: ValueRef -> IO CInt
foreign import ccall unsafe "LLVMSetGlobalConstant" setGlobalConstant
:: ValueRef -> CInt -> IO ()
foreign import ccall unsafe "LLVMTypeOf" typeOf
:: ValueRef -> IO TypeRef
foreign import ccall unsafe "LLVMGetValueName" getValueName
:: ValueRef -> IO CString
foreign import ccall unsafe "LLVMSetValueName" setValueName
:: ValueRef -> CString -> IO ()
foreign import ccall unsafe "LLVMDumpValue" dumpValue
:: ValueRef -> IO ()
foreign import ccall unsafe "LLVMConstAllOnes" constAllOnes
:: TypeRef -> ValueRef
foreign import ccall unsafe "LLVMConstArray" constArray
:: TypeRef -> Ptr ValueRef -> CUInt -> ValueRef
foreign import ccall unsafe "LLVMConstNull" constNull
:: TypeRef -> ValueRef
foreign import ccall unsafe "LLVMIsConstant" isConstant
:: ValueRef -> IO CInt
foreign import ccall unsafe "LLVMGetUndef" getUndef
:: TypeRef -> ValueRef
foreign import ccall unsafe "LLVMIsNull" isNull
:: ValueRef -> IO CInt
foreign import ccall unsafe "LLVMIsUndef" isUndef
:: ValueRef -> IO CInt
foreign import ccall unsafe "LLVMGetNamedFunction" getNamedFunction
:: ModuleRef
-> CString
-> IO ValueRef
foreign import ccall unsafe "LLVMAddFunction" addFunction
:: ModuleRef
-> CString
-> TypeRef
-> IO ValueRef
foreign import ccall unsafe "LLVMDeleteFunction" deleteFunction
:: ValueRef
-> IO ()
foreign import ccall unsafe "LLVMCountParams" countParams
:: ValueRef
-> CUInt
foreign import ccall unsafe "LLVMGetParam" getParam
:: ValueRef
-> CUInt
-> ValueRef
foreign import ccall unsafe "LLVMGetParams" getParams
:: ValueRef
-> Ptr ValueRef
-> IO ()
foreign import ccall unsafe "LLVMGetIntrinsicID" getIntrinsicID
:: ValueRef
-> CUInt
data CallingConvention = C
| Fast
| Cold
| X86StdCall
| X86FastCall
deriving (Show, Eq, Ord, Enum, Bounded)
fromCallingConvention :: CallingConvention -> CUInt
fromCallingConvention C = (0)
fromCallingConvention Fast = (8)
fromCallingConvention Cold = (9)
fromCallingConvention X86StdCall = (65)
fromCallingConvention X86FastCall = (64)
toCallingConvention :: CUInt -> CallingConvention
toCallingConvention c | c == (0) = C
toCallingConvention c | c == (8) = Fast
toCallingConvention c | c == (9) = Cold
toCallingConvention c | c == (64) = X86StdCall
toCallingConvention c | c == (65) = X86FastCall
toCallingConvention c = error $ "LLVM.Core.FFI.toCallingConvention: " ++
"unsupported calling convention" ++ show c
foreign import ccall unsafe "LLVMGetFunctionCallConv" getFunctionCallConv
:: ValueRef
-> IO CUInt
foreign import ccall unsafe "LLVMSetFunctionCallConv" setFunctionCallConv
:: ValueRef
-> CUInt
-> IO ()
foreign import ccall unsafe "LLVMGetGC" getGC
:: ValueRef -> IO CString
foreign import ccall unsafe "LLVMSetGC" setGC
:: ValueRef -> CString -> IO ()
foreign import ccall unsafe "LLVMIsDeclaration" isDeclaration
:: ValueRef -> IO CInt
type Linkage = CUInt
foreign import ccall unsafe "LLVMGetLinkage" getLinkage
:: ValueRef -> IO Linkage
foreign import ccall unsafe "LLVMSetLinkage" setLinkage
:: ValueRef -> Linkage -> IO ()
foreign import ccall unsafe "LLVMGetSection" getSection
:: ValueRef -> IO CString
foreign import ccall unsafe "LLVMSetSection" setSection
:: ValueRef -> CString -> IO ()
type Visibility = CUInt
foreign import ccall unsafe "LLVMGetVisibility" getVisibility
:: ValueRef -> IO Visibility
foreign import ccall unsafe "LLVMSetVisibility" setVisibility
:: ValueRef -> Visibility -> IO ()
foreign import ccall unsafe "LLVMGetAlignment" getAlignment
:: ValueRef -> IO CUInt
foreign import ccall unsafe "LLVMSetAlignment" setAlignment
:: ValueRef -> CUInt -> IO ()
foreign import ccall unsafe "LLVMConstInt" constInt
:: TypeRef -> CULLong -> CInt -> ValueRef
foreign import ccall unsafe "LLVMConstReal" constReal
:: TypeRef -> CDouble -> ValueRef
foreign import ccall unsafe "LLVMConstString" constString
:: CString -> CUInt -> CInt -> ValueRef
foreign import ccall unsafe "LLVMConstStruct" constStruct
:: Ptr ValueRef -> CUInt -> CInt -> ValueRef
foreign import ccall unsafe "LLVMConstVector" constVector
:: Ptr ValueRef -> CUInt -> ValueRef
foreign import ccall unsafe "LLVMConstNeg" constNeg
:: ValueRef -> ValueRef
foreign import ccall unsafe "LLVMConstNot" constNot
:: ValueRef -> ValueRef
foreign import ccall unsafe "LLVMConstAdd" constAdd
:: ValueRef -> ValueRef -> ValueRef
foreign import ccall unsafe "LLVMConstSub" constSub
:: ValueRef -> ValueRef -> ValueRef
foreign import ccall unsafe "LLVMConstMul" constMul
:: ValueRef -> ValueRef -> ValueRef
foreign import ccall unsafe "LLVMConstUDiv" constUDiv
:: ValueRef -> ValueRef -> ValueRef
foreign import ccall unsafe "LLVMConstSDiv" constSDiv
:: ValueRef -> ValueRef -> ValueRef
foreign import ccall unsafe "LLVMConstFDiv" constFDiv
:: ValueRef -> ValueRef -> ValueRef
foreign import ccall unsafe "LLVMConstURem" constURem
:: ValueRef -> ValueRef -> ValueRef
foreign import ccall unsafe "LLVMConstSRem" constSRem
:: ValueRef -> ValueRef -> ValueRef
foreign import ccall unsafe "LLVMConstFRem" constFRem
:: ValueRef -> ValueRef -> ValueRef
foreign import ccall unsafe "LLVMConstAnd" constAnd
:: ValueRef -> ValueRef -> ValueRef
foreign import ccall unsafe "LLVMConstOr" constOr
:: ValueRef -> ValueRef -> ValueRef
foreign import ccall unsafe "LLVMConstXor" constXor
:: ValueRef -> ValueRef -> ValueRef
foreign import ccall unsafe "LLVMConstICmp" constICmp
:: CInt -> ValueRef -> ValueRef -> ValueRef
foreign import ccall unsafe "LLVMConstFCmp" constFCmp
:: CInt -> ValueRef -> ValueRef -> ValueRef
foreign import ccall unsafe "LLVMConstShl" constShl
:: ValueRef -> ValueRef -> ValueRef
foreign import ccall unsafe "LLVMConstLShr" constLShr
:: ValueRef -> ValueRef -> ValueRef
foreign import ccall unsafe "LLVMConstAShr" constAShr
:: ValueRef -> ValueRef -> ValueRef
foreign import ccall unsafe "LLVMConstGEP" constGEP
:: ValueRef -> Ptr ValueRef -> CUInt -> ValueRef
foreign import ccall unsafe "LLVMConstTrunc" constTrunc
:: ValueRef -> TypeRef -> ValueRef
foreign import ccall unsafe "LLVMConstSExt" constSExt
:: ValueRef -> TypeRef -> ValueRef
foreign import ccall unsafe "LLVMConstZExt" constZExt
:: ValueRef -> TypeRef -> ValueRef
foreign import ccall unsafe "LLVMConstFPTrunc" constFPTrunc
:: ValueRef -> TypeRef -> ValueRef
foreign import ccall unsafe "LLVMConstFPExt" constFPExt
:: ValueRef -> TypeRef -> ValueRef
foreign import ccall unsafe "LLVMConstUIToFP" constUIToFP
:: ValueRef -> TypeRef -> ValueRef
foreign import ccall unsafe "LLVMConstSIToFP" constSIToFP
:: ValueRef -> TypeRef -> ValueRef
foreign import ccall unsafe "LLVMConstFPToUI" constFPToUI
:: ValueRef -> TypeRef -> ValueRef
foreign import ccall unsafe "LLVMConstFPToSI" constFPToSI
:: ValueRef -> TypeRef -> ValueRef
foreign import ccall unsafe "LLVMConstPtrToInt" constPtrToInt
:: ValueRef -> TypeRef -> ValueRef
foreign import ccall unsafe "LLVMConstIntToPtr" constIntToPtr
:: ValueRef -> TypeRef -> ValueRef
foreign import ccall unsafe "LLVMConstBitCast" constBitCast
:: ValueRef -> TypeRef -> ValueRef
foreign import ccall unsafe "LLVMConstSelect" constSelect
:: ValueRef -> ValueRef -> ValueRef -> ValueRef
foreign import ccall unsafe "LLVMConstExtractElement" constExtractElement
:: ValueRef -> ValueRef -> ValueRef
foreign import ccall unsafe "LLVMConstInsertElement" constInsertElement
:: ValueRef -> ValueRef -> ValueRef -> ValueRef
foreign import ccall unsafe "LLVMConstShuffleVector" constShuffleVector
:: ValueRef -> ValueRef -> ValueRef -> ValueRef
type BasicBlock = Value
type BasicBlockRef = Ptr BasicBlock
foreign import ccall unsafe "LLVMBasicBlockAsValue" basicBlockAsValue
:: BasicBlockRef -> ValueRef
foreign import ccall unsafe "LLVMValueIsBasicBlock" valueIsBasicBlock
:: ValueRef -> Bool
foreign import ccall unsafe "LLVMValueAsBasicBlock" valueAsBasicBlock
:: ValueRef
-> BasicBlockRef
foreign import ccall unsafe "LLVMCountBasicBlocks" countBasicBlocks
:: ValueRef
-> IO CUInt
foreign import ccall unsafe "LLVMGetBasicBlocks" getBasicBlocks
:: ValueRef
-> Ptr BasicBlockRef
-> IO ()
foreign import ccall unsafe "LLVMGetEntryBasicBlock" getEntryBasicBlock
:: ValueRef
-> IO BasicBlockRef
foreign import ccall unsafe "LLVMAppendBasicBlock" appendBasicBlock
:: ValueRef
-> CString
-> IO BasicBlockRef
foreign import ccall unsafe "LLVMInsertBasicBlock" insertBasicBlock
:: BasicBlockRef
-> CString
-> IO BasicBlockRef
foreign import ccall unsafe "LLVMDeleteBasicBlock" deleteBasicBlock
:: BasicBlockRef -> IO ()
data Builder
type BuilderRef = Ptr Builder
foreign import ccall unsafe "LLVMCreateBuilder" createBuilder
:: IO BuilderRef
foreign import ccall unsafe "&LLVMDisposeBuilder" ptrDisposeBuilder
:: FunPtr (BuilderRef -> IO ())
foreign import ccall unsafe "LLVMPositionBuilderBefore" positionBefore
:: BuilderRef -> ValueRef -> IO ()
foreign import ccall unsafe "LLVMPositionBuilderAtEnd" positionAtEnd
:: BuilderRef -> BasicBlockRef -> IO ()
foreign import ccall unsafe "LLVMBuildRetVoid" buildRetVoid
:: BuilderRef -> IO ValueRef
foreign import ccall unsafe "LLVMBuildRet" buildRet
:: BuilderRef -> ValueRef -> IO ValueRef
foreign import ccall unsafe "LLVMBuildBr" buildBr
:: BuilderRef -> BasicBlockRef -> IO ValueRef
foreign import ccall unsafe "LLVMBuildCondBr" buildCondBr
:: BuilderRef -> ValueRef -> BasicBlockRef -> BasicBlockRef -> IO ValueRef
foreign import ccall unsafe "LLVMBuildSwitch" buildSwitch
:: BuilderRef -> ValueRef -> BasicBlockRef -> CUInt -> IO ValueRef
foreign import ccall unsafe "LLVMBuildInvoke" buildInvoke
:: BuilderRef -> ValueRef -> Ptr ValueRef -> CUInt
-> BasicBlockRef -> BasicBlockRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildUnwind" buildUnwind
:: BuilderRef -> IO ValueRef
foreign import ccall unsafe "LLVMBuildUnreachable" buildUnreachable
:: BuilderRef -> IO ValueRef
foreign import ccall unsafe "LLVMBuildAdd" buildAdd
:: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildSub" buildSub
:: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildMul" buildMul
:: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildUDiv" buildUDiv
:: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildSDiv" buildSDiv
:: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildFDiv" buildFDiv
:: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildURem" buildURem
:: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildSRem" buildSRem
:: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildFRem" buildFRem
:: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildShl" buildShl
:: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildLShr" buildLShr
:: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildAShr" buildAShr
:: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildAnd" buildAnd
:: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildOr" buildOr
:: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildXor" buildXor
:: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildNeg" buildNeg
:: BuilderRef -> ValueRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildNot" buildNot
:: BuilderRef -> ValueRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildMalloc" buildMalloc
:: BuilderRef -> TypeRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildArrayMalloc" buildArrayMalloc
:: BuilderRef -> TypeRef -> ValueRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildAlloca" buildAlloca
:: BuilderRef -> TypeRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildArrayAlloca" buildArrayAlloca
:: BuilderRef -> TypeRef -> ValueRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildFree" buildFree
:: BuilderRef -> ValueRef -> IO ValueRef
foreign import ccall unsafe "LLVMBuildLoad" buildLoad
:: BuilderRef -> ValueRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildStore" buildStore
:: BuilderRef -> ValueRef -> ValueRef -> IO ValueRef
foreign import ccall unsafe "LLVMBuildGEP" buildGEP
:: BuilderRef -> ValueRef -> Ptr ValueRef -> CUInt -> CString
-> IO ValueRef
foreign import ccall unsafe "LLVMBuildTrunc" buildTrunc
:: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildZExt" buildZExt
:: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildSExt" buildSExt
:: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildFPToUI" buildFPToUI
:: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildFPToSI" buildFPToSI
:: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildUIToFP" buildUIToFP
:: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildSIToFP" buildSIToFP
:: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildFPTrunc" buildFPTrunc
:: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildFPExt" buildFPExt
:: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildPtrToInt" buildPtrToInt
:: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildIntToPtr" buildIntToPtr
:: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildBitCast" buildBitCast
:: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildICmp" buildICmp
:: BuilderRef -> CInt -> ValueRef -> ValueRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildFCmp" buildFCmp
:: BuilderRef -> CInt -> ValueRef -> ValueRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildPhi" buildPhi
:: BuilderRef -> TypeRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildCall" buildCall
:: BuilderRef -> ValueRef -> Ptr ValueRef -> CUInt -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildSelect" buildSelect
:: BuilderRef -> ValueRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildVAArg" buildVAArg
:: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildExtractElement" buildExtractElement
:: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildInsertElement" buildInsertElement
:: BuilderRef -> ValueRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMBuildShuffleVector" buildShuffleVector
:: BuilderRef -> ValueRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMAddCase" addCase
:: ValueRef -> ValueRef -> BasicBlockRef -> IO ()
foreign import ccall unsafe "LLVMCountIncoming" countIncoming
:: ValueRef -> IO CUInt
foreign import ccall unsafe "LLVMAddIncoming" addIncoming
:: ValueRef -> Ptr ValueRef -> Ptr ValueRef -> CUInt -> IO ()
foreign import ccall unsafe "LLVMGetIncomingValue" getIncomingValue
:: ValueRef -> CUInt -> IO ValueRef
foreign import ccall unsafe "LLVMGetIncomingBlock" getIncomingBlock
:: ValueRef -> CUInt -> IO BasicBlockRef
foreign import ccall unsafe "LLVMGetInstructionCallConv" getInstructionCallConv
:: ValueRef -> IO CUInt
foreign import ccall unsafe "LLVMSetInstructionCallConv" setInstructionCallConv
:: ValueRef -> CUInt -> IO ()
foreign import ccall unsafe "LLVMStructType" structType
:: (Ptr TypeRef) -> CUInt -> CInt -> IO TypeRef
foreign import ccall unsafe "LLVMCountStructElementTypes"
countStructElementTypes :: TypeRef -> IO CUInt
foreign import ccall unsafe "LLVMGetStructElementTypes" getStructElementTypes
:: TypeRef -> (Ptr TypeRef) -> IO ()
foreign import ccall unsafe "LLVMIsPackedStruct" isPackedStruct
:: TypeRef -> IO CInt
data MemoryBuffer
type MemoryBufferRef = Ptr MemoryBuffer
data TypeHandle
type TypeHandleRef = Ptr TypeHandle
data TypeKind
= VoidTypeKind
| FloatTypeKind
| DoubleTypeKind
| X86_FP80TypeKind
| FP128TypeKind
| PPC_FP128TypeKind
| LabelTypeKind
| IntegerTypeKind
| FunctionTypeKind
| StructTypeKind
| ArrayTypeKind
| PointerTypeKind
| OpaqueTypeKind
| VectorTypeKind
deriving (Eq, Ord, Enum, Bounded, Show, Read)
getTypeKind :: TypeRef -> IO TypeKind
getTypeKind = fmap (toEnum . fromIntegral) . getTypeKindCUInt
foreign import ccall unsafe "LLVMCreateMemoryBufferWithContentsOfFile" createMemoryBufferWithContentsOfFile
:: CString -> Ptr MemoryBufferRef -> Ptr CString -> IO CInt
foreign import ccall unsafe "LLVMCreateMemoryBufferWithSTDIN" createMemoryBufferWithSTDIN
:: Ptr MemoryBufferRef -> Ptr CString -> IO CInt
foreign import ccall unsafe "LLVMCreateTypeHandle" createTypeHandle
:: TypeRef -> IO TypeHandleRef
foreign import ccall unsafe "LLVMDisposeMemoryBuffer" disposeMemoryBuffer
:: MemoryBufferRef -> IO ()
foreign import ccall unsafe "LLVMDisposeMessage" disposeMessage
:: CString -> IO ()
foreign import ccall unsafe "LLVMDisposeTypeHandle" disposeTypeHandle
:: TypeHandleRef -> IO ()
foreign import ccall unsafe "LLVMGetArrayLength" getArrayLength
:: TypeRef -> IO CUInt
foreign import ccall unsafe "LLVMGetIntTypeWidth" getIntTypeWidth
:: TypeRef -> IO CUInt
foreign import ccall unsafe "LLVMGetPointerAddressSpace" getPointerAddressSpace
:: TypeRef -> IO CUInt
foreign import ccall unsafe "LLVMGetTarget" getTarget
:: ModuleRef -> IO CString
foreign import ccall unsafe "LLVMGetTypeKind" getTypeKindCUInt
:: TypeRef -> IO CUInt
foreign import ccall unsafe "LLVMGetVectorSize" getVectorSize
:: TypeRef -> IO CUInt
foreign import ccall unsafe "LLVMRefineType" refineType
:: TypeRef -> TypeRef -> IO ()
foreign import ccall unsafe "LLVMResolveTypeHandle" resolveTypeHandle
:: TypeHandleRef -> IO TypeRef
foreign import ccall unsafe "LLVMSetTarget" setTarget
:: ModuleRef -> CString -> IO ()
foreign import ccall unsafe "LLVMSizeOf" sizeOf
:: TypeRef -> IO ValueRef
data Attribute
= ZExtAttribute
| SExtAttribute
| NoReturnAttribute
| InRegAttribute
| StructRetAttribute
| NoUnwindAttribute
| NoAliasAttribute
| ByValAttribute
| NestAttribute
| ReadNoneAttribute
| ReadOnlyAttribute
deriving (Show, Eq, Ord, Enum, Bounded)
fromAttribute :: Attribute -> CAttribute
fromAttribute ZExtAttribute = (1)
fromAttribute SExtAttribute = (2)
fromAttribute NoReturnAttribute = (4)
fromAttribute InRegAttribute = (8)
fromAttribute StructRetAttribute = (16)
fromAttribute NoUnwindAttribute = (32)
fromAttribute NoAliasAttribute = (64)
fromAttribute ByValAttribute = (128)
fromAttribute NestAttribute = (256)
fromAttribute ReadNoneAttribute = (512)
fromAttribute ReadOnlyAttribute = (1024)
toAttribute :: CAttribute -> Attribute
toAttribute c | c == (1) = ZExtAttribute
toAttribute c | c == (2) = SExtAttribute
toAttribute c | c == (4) = NoReturnAttribute
toAttribute c | c == (8) = InRegAttribute
toAttribute c | c == (16) = StructRetAttribute
toAttribute c | c == (32) = NoUnwindAttribute
toAttribute c | c == (64) = NoAliasAttribute
toAttribute c | c == (128) = ByValAttribute
toAttribute c | c == (256) = NestAttribute
toAttribute c | c == (512) = ReadNoneAttribute
toAttribute c | c == (1024) = ReadOnlyAttribute
toAttribute _ = error "toAttribute: bad value"
type CAttribute = CInt
data PassManager
type PassManagerRef = Ptr PassManager
foreign import ccall unsafe "LLVMConstRealOfString" constRealOfString
:: TypeRef -> CString -> IO ValueRef
foreign import ccall unsafe "LLVMCreateFunctionPassManager" createFunctionPassManager
:: ModuleProviderRef -> IO PassManagerRef
foreign import ccall unsafe "LLVMCreatePassManager" createPassManager
:: IO PassManagerRef
foreign import ccall unsafe "&LLVMDisposePassManager" ptrDisposePassManager
:: FunPtr (PassManagerRef -> IO ())
foreign import ccall unsafe "LLVMDumpModule" dumpModule
:: ModuleRef -> IO ()
foreign import ccall unsafe "LLVMFinalizeFunctionPassManager" finalizeFunctionPassManager
:: PassManagerRef -> IO CInt
foreign import ccall unsafe "LLVMGetBasicBlockParent" getBasicBlockParent
:: BasicBlockRef -> IO ValueRef
foreign import ccall unsafe "LLVMGetFirstBasicBlock" getFirstBasicBlock
:: ValueRef -> IO BasicBlockRef
foreign import ccall unsafe "LLVMGetFirstFunction" getFirstFunction
:: ModuleRef -> IO ValueRef
foreign import ccall unsafe "LLVMGetFirstGlobal" getFirstGlobal
:: ModuleRef -> IO ValueRef
foreign import ccall unsafe "LLVMGetFirstInstruction" getFirstInstruction
:: BasicBlockRef -> IO ValueRef
foreign import ccall unsafe "LLVMGetFirstParam" getFirstParam
:: ValueRef -> IO ValueRef
foreign import ccall unsafe "LLVMGetGlobalParent" getGlobalParent
:: ValueRef -> IO ModuleRef
foreign import ccall unsafe "LLVMGetInsertBlock" getInsertBlock
:: BuilderRef -> IO BasicBlockRef
foreign import ccall unsafe "LLVMGetInstructionParent" getInstructionParent
:: ValueRef -> IO BasicBlockRef
foreign import ccall unsafe "LLVMGetLastBasicBlock" getLastBasicBlock
:: ValueRef -> IO BasicBlockRef
foreign import ccall unsafe "LLVMGetLastFunction" getLastFunction
:: ModuleRef -> IO ValueRef
foreign import ccall unsafe "LLVMGetLastGlobal" getLastGlobal
:: ModuleRef -> IO ValueRef
foreign import ccall unsafe "LLVMGetLastInstruction" getLastInstruction
:: BasicBlockRef -> IO ValueRef
foreign import ccall unsafe "LLVMGetLastParam" getLastParam
:: ValueRef -> IO ValueRef
foreign import ccall unsafe "LLVMGetNextBasicBlock" getNextBasicBlock
:: BasicBlockRef -> IO BasicBlockRef
foreign import ccall unsafe "LLVMGetNextFunction" getNextFunction
:: ValueRef -> IO ValueRef
foreign import ccall unsafe "LLVMGetNextGlobal" getNextGlobal
:: ValueRef -> IO ValueRef
foreign import ccall unsafe "LLVMGetNextInstruction" getNextInstruction
:: ValueRef -> IO ValueRef
foreign import ccall unsafe "LLVMGetNextParam" getNextParam
:: ValueRef -> IO ValueRef
foreign import ccall unsafe "LLVMGetParamParent" getParamParent
:: ValueRef -> IO ValueRef
foreign import ccall unsafe "LLVMGetPreviousBasicBlock" getPreviousBasicBlock
:: BasicBlockRef -> IO BasicBlockRef
foreign import ccall unsafe "LLVMGetPreviousFunction" getPreviousFunction
:: ValueRef -> IO ValueRef
foreign import ccall unsafe "LLVMGetPreviousGlobal" getPreviousGlobal
:: ValueRef -> IO ValueRef
foreign import ccall unsafe "LLVMGetPreviousInstruction" getPreviousInstruction
:: ValueRef -> IO ValueRef
foreign import ccall unsafe "LLVMGetPreviousParam" getPreviousParam
:: ValueRef -> IO ValueRef
foreign import ccall unsafe "LLVMInitializeFunctionPassManager" initializeFunctionPassManager
:: PassManagerRef -> IO CInt
foreign import ccall unsafe "LLVMLabelType" labelType
:: TypeRef
foreign import ccall unsafe "LLVMOpaqueType" opaqueType
:: TypeRef
foreign import ccall unsafe "LLVMPositionBuilder" positionBuilder
:: BuilderRef -> BasicBlockRef -> ValueRef -> IO ()
foreign import ccall unsafe "LLVMRunFunctionPassManager" runFunctionPassManager
:: PassManagerRef -> ValueRef -> IO CInt
foreign import ccall unsafe "LLVMRunPassManager" runPassManager
:: PassManagerRef -> ModuleRef -> IO CInt
foreign import ccall unsafe "LLVMSetInstrParamAlignment" setInstrParamAlignment
:: ValueRef -> CUInt -> CUInt -> IO ()
foreign import ccall unsafe "LLVMSetParamAlignment" setParamAlignment
:: ValueRef -> CUInt -> IO ()
foreign import ccall unsafe "LLVMAddAttribute" addAttribute
:: ValueRef -> CAttribute -> IO ()
foreign import ccall unsafe "LLVMAddInstrAttribute" addInstrAttribute
:: ValueRef -> CUInt -> CAttribute -> IO ()
foreign import ccall unsafe "LLVMIsTailCall" isTailCall
:: ValueRef -> IO CInt
foreign import ccall unsafe "LLVMRemoveAttribute" removeAttribute
:: ValueRef -> CAttribute -> IO ()
foreign import ccall unsafe "LLVMRemoveInstrAttribute" removeInstrAttribute
:: ValueRef -> CUInt -> CAttribute -> IO ()
foreign import ccall unsafe "LLVMSetTailCall" setTailCall
:: ValueRef -> CInt -> IO ()