{-# LANGUAGE ForeignFunctionInterface #-}
module Torch.FFI.THC.CachingAllocator where
import Foreign
import Foreign.C.Types
import Data.Word
import Data.Int
import Torch.Types.TH
import Torch.Types.THC
foreign import ccall "THCCachingAllocator.h THCCachingAllocator_getBaseAllocation"
c_THCCachingAllocator_getBaseAllocation :: Ptr () -> Ptr CSize -> IO (Ptr ())
foreign import ccall "THCCachingAllocator.h THCCachingAllocator_recordStream"
c_THCCachingAllocator_recordStream :: Ptr () -> Ptr C'THCStream -> IO ()
foreign import ccall "THCCachingAllocator.h THCCachingAllocator_currentMemoryAllocated"
c_THCCachingAllocator_currentMemoryAllocated :: CInt -> IO CULong
foreign import ccall "THCCachingAllocator.h THCCachingAllocator_maxMemoryAllocated"
c_THCCachingAllocator_maxMemoryAllocated :: CInt -> IO CULong
foreign import ccall "THCCachingAllocator.h THCCachingAllocator_currentMemoryCached"
c_THCCachingAllocator_currentMemoryCached :: CInt -> IO CULong
foreign import ccall "THCCachingAllocator.h THCCachingAllocator_maxMemoryCached"
c_THCCachingAllocator_maxMemoryCached :: CInt -> IO CULong
foreign import ccall "THCCachingAllocator.h &THCCachingAllocator_getBaseAllocation"
p_THCCachingAllocator_getBaseAllocation :: FunPtr (Ptr () -> Ptr CSize -> IO (Ptr ()))
foreign import ccall "THCCachingAllocator.h &THCCachingAllocator_recordStream"
p_THCCachingAllocator_recordStream :: FunPtr (Ptr () -> Ptr C'THCStream -> IO ())
foreign import ccall "THCCachingAllocator.h &THCCachingAllocator_currentMemoryAllocated"
p_THCCachingAllocator_currentMemoryAllocated :: FunPtr (CInt -> IO CULong)
foreign import ccall "THCCachingAllocator.h &THCCachingAllocator_maxMemoryAllocated"
p_THCCachingAllocator_maxMemoryAllocated :: FunPtr (CInt -> IO CULong)
foreign import ccall "THCCachingAllocator.h &THCCachingAllocator_currentMemoryCached"
p_THCCachingAllocator_currentMemoryCached :: FunPtr (CInt -> IO CULong)
foreign import ccall "THCCachingAllocator.h &THCCachingAllocator_maxMemoryCached"
p_THCCachingAllocator_maxMemoryCached :: FunPtr (CInt -> IO CULong)