{-# LANGUAGE ForeignFunctionInterface #-} -- | Functions for handling the LLVM types module LLVM.General.Internal.FFI.Type where import Foreign.Ptr import Foreign.C import Data.Word import LLVM.General.Internal.FFI.LLVMCTypes import LLVM.General.Internal.FFI.Context import LLVM.General.Internal.FFI.PtrHierarchy -- | foreign import ccall unsafe "LLVMGetTypeKind" getTypeKind :: Ptr Type -> IO TypeKind -- | foreign import ccall unsafe "LLVMGetIntTypeWidth" getIntTypeWidth :: Ptr Type -> IO (CUInt) -- | foreign import ccall unsafe "LLVMIsFunctionVarArg" isFunctionVarArg :: Ptr Type -> IO LLVMBool -- | foreign import ccall unsafe "LLVMGetReturnType" getReturnType :: Ptr Type -> IO (Ptr Type) -- | foreign import ccall unsafe "LLVMCountParamTypes" countParamTypes :: Ptr Type -> IO CUInt -- | foreign import ccall unsafe "LLVMGetParamTypes" getParamTypes :: Ptr Type -> Ptr (Ptr Type) -> IO () -- | foreign import ccall unsafe "LLVMGetElementType" getElementType :: Ptr Type -> IO (Ptr Type) -- | foreign import ccall unsafe "LLVMIntTypeInContext" intTypeInContext :: Ptr Context -> CUInt -> IO (Ptr Type) -- | foreign import ccall unsafe "LLVMFunctionType" functionType' :: Ptr Type -> Ptr (Ptr Type) -> CUInt -> LLVMBool -> IO (Ptr Type) functionType rt (n, ats) va = functionType' rt ats n va newtype AddrSpace = AddrSpace CUInt -- | foreign import ccall unsafe "LLVMPointerType" pointerType :: Ptr Type -> AddrSpace -> IO (Ptr Type) -- | foreign import ccall unsafe "LLVMGetPointerAddressSpace" getPointerAddressSpace :: Ptr Type -> IO AddrSpace -- | foreign import ccall unsafe "LLVMVectorType" vectorType :: Ptr Type -> CUInt -> IO (Ptr Type) -- | what -- | would be if it supported 64-bit array sizes, as the C++ type does. foreign import ccall unsafe "LLVM_General_ArrayType" arrayType :: Ptr Type -> Word64 -> IO (Ptr Type) -- | foreign import ccall unsafe "LLVMStructTypeInContext" structTypeInContext' :: Ptr Context -> Ptr (Ptr Type) -> CUInt -> LLVMBool -> IO (Ptr Type) structTypeInContext ctx (n, ts) p = structTypeInContext' ctx ts n p foreign import ccall unsafe "LLVM_General_StructCreateNamed" structCreateNamed :: Ptr Context -> CString -> IO (Ptr Type) foreign import ccall unsafe "LLVMGetStructName" getStructName :: Ptr Type -> IO CString foreign import ccall unsafe "LLVM_General_StructIsLiteral" structIsLiteral :: Ptr Type -> IO LLVMBool foreign import ccall unsafe "LLVM_General_StructIsOpaque" structIsOpaque :: Ptr Type -> IO LLVMBool -- | foreign import ccall unsafe "LLVMIsPackedStruct" isPackedStruct :: Ptr Type -> IO LLVMBool -- | foreign import ccall unsafe "LLVMCountStructElementTypes" countStructElementTypes :: Ptr Type -> IO CUInt foreign import ccall unsafe "LLVMGetStructElementTypes" getStructElementTypes :: Ptr Type -> Ptr (Ptr Type) -> IO () foreign import ccall unsafe "LLVMStructSetBody" structSetBody' :: Ptr Type -> Ptr (Ptr Type) -> CUInt -> LLVMBool -> IO () structSetBody s (n,ts) p = structSetBody' s ts n p -- | foreign import ccall unsafe "LLVMGetVectorSize" getVectorSize :: Ptr Type -> IO CUInt -- | what -- | would be if it supported 64 bit lengths foreign import ccall unsafe "LLVM_General_GetArrayLength" getArrayLength :: Ptr Type -> IO Word64 -- | foreign import ccall unsafe "LLVMVoidTypeInContext" voidTypeInContext :: Ptr Context -> IO (Ptr Type) -- | foreign import ccall unsafe "LLVMHalfTypeInContext" halfTypeInContext :: Ptr Context -> IO (Ptr Type) -- | foreign import ccall unsafe "LLVMFloatTypeInContext" floatTypeInContext :: Ptr Context -> IO (Ptr Type) -- | foreign import ccall unsafe "LLVMDoubleTypeInContext" doubleTypeInContext :: Ptr Context -> IO (Ptr Type) -- | foreign import ccall unsafe "LLVMX86FP80TypeInContext" x86FP80TypeInContext :: Ptr Context -> IO (Ptr Type) -- | foreign import ccall unsafe "LLVMFP128TypeInContext" fP128TypeInContext :: Ptr Context -> IO (Ptr Type) -- | foreign import ccall unsafe "LLVMPPCFP128TypeInContext" ppcFP128TypeInContext :: Ptr Context -> IO (Ptr Type) -- | foreign import ccall unsafe "LLVM_General_MetadataTypeInContext" metadataTypeInContext :: Ptr Context -> IO (Ptr Type)