{-# LANGUAGE ForeignFunctionInterface #-}
module Torch.FFI.THC.Half where
import Foreign
import Foreign.C.Types
import Data.Word
import Data.Int
import Torch.Types.TH
import Torch.Types.THC
foreign import ccall "THCHalf.h THC_nativeHalfInstructions"
c_THC_nativeHalfInstructions :: Ptr C'THCState -> IO CInt
foreign import ccall "THCHalf.h THC_fastHalfInstructions"
c_THC_fastHalfInstructions :: Ptr C'THCState -> IO CInt
foreign import ccall "THCHalf.h &THC_nativeHalfInstructions"
p_THC_nativeHalfInstructions :: FunPtr (Ptr C'THCState -> IO CInt)
foreign import ccall "THCHalf.h &THC_fastHalfInstructions"
p_THC_fastHalfInstructions :: FunPtr (Ptr C'THCState -> IO CInt)