{-# LINE 1 "src/Foreign/CUDA/Driver/Module/Query.chs" #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE ForeignFunctionInterface #-}
module Foreign.CUDA.Driver.Module.Query (
getFun, getPtr, getTex,
) where
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Ptr as C2HSImp
{-# LINE 21 "src/Foreign/CUDA/Driver/Module/Query.chs" #-}
import Foreign.CUDA.Driver.Error
import Foreign.CUDA.Driver.Exec
import Foreign.CUDA.Driver.Marshal ( peekDeviceHandle )
import Foreign.CUDA.Driver.Module.Base
import Foreign.CUDA.Driver.Texture
import Foreign.CUDA.Internal.C2HS
import Foreign.CUDA.Ptr
import Foreign
import Foreign.C
import Control.Exception ( throwIO )
import Control.Monad ( liftM )
{-# INLINEABLE getFun #-}
getFun :: Module -> String -> IO Fun
getFun !mdl !fn = resultIfFound "function" fn =<< cuModuleGetFunction mdl fn
{-# INLINE cuModuleGetFunction #-}
cuModuleGetFunction :: (Module) -> (String) -> IO ((Status), (Fun))
cuModuleGetFunction a2 a3 =
alloca $ \a1' ->
let {a2' = useModule a2} in
withCString a3 $ \a3' ->
cuModuleGetFunction'_ a1' a2' a3' >>= \res ->
let {res' = cToEnum res} in
peekFun a1'>>= \a1'' ->
return (res', a1'')
{-# LINE 56 "src/Foreign/CUDA/Driver/Module/Query.chs" #-}
where peekFun = liftM Fun . peek
{-# INLINEABLE getPtr #-}
getPtr :: Module -> String -> IO (DevicePtr a, Int)
getPtr !mdl !name = do
(!status,!dptr,!bytes) <- cuModuleGetGlobal mdl name
resultIfFound "global" name (status,(dptr,bytes))
{-# INLINE cuModuleGetGlobal #-}
cuModuleGetGlobal :: (Module) -> (String) -> IO ((Status), (DevicePtr a), (Int))
cuModuleGetGlobal a3 a4 =
alloca $ \a1' ->
alloca $ \a2' ->
let {a3' = useModule a3} in
withCString a4 $ \a4' ->
cuModuleGetGlobal'_ a1' a2' a3' a4' >>= \res ->
let {res' = cToEnum res} in
peekDeviceHandle a1'>>= \a1'' ->
peekIntConv a2'>>= \a2'' ->
return (res', a1'', a2'')
{-# LINE 76 "src/Foreign/CUDA/Driver/Module/Query.chs" #-}
{-# INLINEABLE getTex #-}
getTex :: Module -> String -> IO Texture
getTex !mdl !name = resultIfFound "texture" name =<< cuModuleGetTexRef mdl name
{-# INLINE cuModuleGetTexRef #-}
cuModuleGetTexRef :: (Module) -> (String) -> IO ((Status), (Texture))
cuModuleGetTexRef a2 a3 =
alloca $ \a1' ->
let {a2' = useModule a2} in
withCString a3 $ \a3' ->
cuModuleGetTexRef'_ a1' a2' a3' >>= \res ->
let {res' = cToEnum res} in
peekTex a1'>>= \a1'' ->
return (res', a1'')
{-# LINE 94 "src/Foreign/CUDA/Driver/Module/Query.chs" #-}
{-# INLINE resultIfFound #-}
resultIfFound :: String -> String -> (Status, a) -> IO a
resultIfFound kind name (!status,!result) =
case status of
Success -> return result
NotFound -> cudaError (kind ++ ' ' : describe status ++ ": " ++ name)
_ -> throwIO (ExitCode status)
foreign import ccall unsafe "Foreign/CUDA/Driver/Module/Query.chs.h cuModuleGetFunction"
cuModuleGetFunction'_ :: ((C2HSImp.Ptr (C2HSImp.Ptr ())) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (IO C2HSImp.CInt))))
foreign import ccall unsafe "Foreign/CUDA/Driver/Module/Query.chs.h cuModuleGetGlobal"
cuModuleGetGlobal'_ :: ((C2HSImp.Ptr C2HSImp.CULLong) -> ((C2HSImp.Ptr C2HSImp.CULong) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (IO C2HSImp.CInt)))))
foreign import ccall unsafe "Foreign/CUDA/Driver/Module/Query.chs.h cuModuleGetTexRef"
cuModuleGetTexRef'_ :: ((C2HSImp.Ptr (C2HSImp.Ptr ())) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (IO C2HSImp.CInt))))