module Foreign.CUDA.Driver.Module.Query (
  
  getFun, getPtr, getTex,
) where
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 )
getFun :: Module -> String -> IO Fun
getFun !mdl !fn = resultIfFound "function" fn =<< cuModuleGetFunction mdl fn
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'')
  where peekFun = liftM Fun . peek
getPtr :: Module -> String -> IO (DevicePtr a, Int)
getPtr !mdl !name = do
  (!status,!dptr,!bytes) <- cuModuleGetGlobal mdl name
  resultIfFound "global" name (status,(dptr,bytes))
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'')
getTex :: Module -> String -> IO Texture
getTex !mdl !name = resultIfFound "texture" name =<< cuModuleGetTexRef mdl name
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'')
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'_ :: ((Ptr (Ptr ())) -> ((Ptr ()) -> ((Ptr CChar) -> (IO CInt))))
foreign import ccall unsafe "Foreign/CUDA/Driver/Module/Query.chs.h cuModuleGetGlobal"
  cuModuleGetGlobal'_ :: ((Ptr CULLong) -> ((Ptr CULong) -> ((Ptr ()) -> ((Ptr CChar) -> (IO CInt)))))
foreign import ccall unsafe "Foreign/CUDA/Driver/Module/Query.chs.h cuModuleGetTexRef"
  cuModuleGetTexRef'_ :: ((Ptr (Ptr ())) -> ((Ptr ()) -> ((Ptr CChar) -> (IO CInt))))