{-# LANGUAGE ForeignFunctionInterface, EmptyDataDecls, MultiParamTypeClasses, FlexibleContexts, FlexibleInstances, UndecidableInstances, OverlappingInstances #-} -- | FFI functions for handling the LLVM Value class module LLVM.General.Internal.FFI.Value where import Foreign.Ptr import Foreign.C import LLVM.General.Internal.FFI.LLVMCTypes import LLVM.General.Internal.FFI.Type import LLVM.General.Internal.FFI.PtrHierarchy -- | foreign import ccall unsafe "LLVMTypeOf" typeOf :: Ptr Value -> IO (Ptr Type) -- | foreign import ccall unsafe "LLVMGetValueName" getValueName :: Ptr Value -> IO CString -- | foreign import ccall unsafe "LLVMSetValueName" setValueName :: Ptr Value -> CString -> IO () -- | This function exposes the ID returned by llvm::Value::getValueID() -- | . foreign import ccall unsafe "LLVM_General_GetValueSubclassId" getValueSubclassId :: Ptr Value -> IO ValueSubclassId foreign import ccall unsafe "LLVMReplaceAllUsesWith" replaceAllUsesWith :: Ptr Value -> Ptr Value -> IO ()