-- GENERATED by C->Haskell Compiler, version 0.28.3 Switcheroo, 25 November 2017 (Haskell)
-- Edit the ORIGNAL .chs file instead!


{-# LINE 1 "src/Foreign/CUDA/Runtime/Stream.chs" #-}
{-# LANGUAGE BangPatterns             #-}
{-# LANGUAGE ForeignFunctionInterface #-}
--------------------------------------------------------------------------------
-- |
-- Module    : Foreign.CUDA.Runtime.Stream
-- Copyright : [2009..2017] Trevor L. McDonell
-- License   : BSD
--
-- Stream management routines
--
--------------------------------------------------------------------------------

module Foreign.CUDA.Runtime.Stream (

  -- * Stream Management
  Stream(..),
  create, destroy, finished, block, defaultStream

) where
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Ptr as C2HSImp





{-# LINE 22 "src/Foreign/CUDA/Runtime/Stream.chs" #-}


-- Friends
import Foreign.CUDA.Types
import Foreign.CUDA.Runtime.Error
import Foreign.CUDA.Internal.C2HS

-- System
import Foreign
import Foreign.C
import Control.Monad                                    ( liftM )
import Control.Exception                                ( throwIO )


--------------------------------------------------------------------------------
-- Functions
--------------------------------------------------------------------------------

-- |
-- Create a new asynchronous stream
--
{-# INLINEABLE create #-}
create :: IO Stream
create = resultIfOk =<< cudaStreamCreate

{-# INLINE cudaStreamCreate #-}
cudaStreamCreate :: IO ((Status), (Stream))
cudaStreamCreate =
  alloca $ \a1' -> 
  cudaStreamCreate'_ a1' >>= \res ->
  let {res' = cToEnum res} in
  peekStream  a1'>>= \a1'' -> 
  return (res', a1'')

{-# LINE 49 "src/Foreign/CUDA/Runtime/Stream.chs" #-}



-- |
-- Destroy and clean up an asynchronous stream
--
{-# INLINEABLE destroy #-}
destroy :: Stream -> IO ()
destroy !s = nothingIfOk =<< cudaStreamDestroy s

{-# INLINE cudaStreamDestroy #-}
cudaStreamDestroy :: (Stream) -> IO ((Status))
cudaStreamDestroy a1 =
  let {a1' = useStream a1} in 
  cudaStreamDestroy'_ a1' >>= \res ->
  let {res' = cToEnum res} in
  return (res')

{-# LINE 61 "src/Foreign/CUDA/Runtime/Stream.chs" #-}



-- |
-- Determine if all operations in a stream have completed
--
{-# INLINEABLE finished #-}
finished :: Stream -> IO Bool
finished !s =
  cudaStreamQuery s >>= \rv -> do
  case rv of
      Success  -> return True
      NotReady -> return False
      _        -> throwIO (ExitCode rv)

{-# INLINE cudaStreamQuery #-}
cudaStreamQuery :: (Stream) -> IO ((Status))
cudaStreamQuery a1 =
  let {a1' = useStream a1} in 
  cudaStreamQuery'_ a1' >>= \res ->
  let {res' = cToEnum res} in
  return (res')

{-# LINE 78 "src/Foreign/CUDA/Runtime/Stream.chs" #-}



-- |
-- Block until all operations in a Stream have been completed
--
{-# INLINEABLE block #-}
block :: Stream -> IO ()
block !s = nothingIfOk =<< cudaStreamSynchronize s

{-# INLINE cudaStreamSynchronize #-}
cudaStreamSynchronize :: (Stream) -> IO ((Status))
cudaStreamSynchronize a1 =
  let {a1' = useStream a1} in 
  cudaStreamSynchronize'_ a1' >>= \res ->
  let {res' = cToEnum res} in
  return (res')

{-# LINE 90 "src/Foreign/CUDA/Runtime/Stream.chs" #-}



-- |
-- The main execution stream (0)
--
-- {-# INLINE defaultStream #-}
-- defaultStream :: Stream
-- #if CUDART_VERSION < 3010
-- defaultStream = Stream 0
-- #else
-- defaultStream = Stream nullPtr
-- #endif

--------------------------------------------------------------------------------
-- Internal
--------------------------------------------------------------------------------

{-# INLINE peekStream #-}
peekStream :: Ptr ((C2HSImp.Ptr ())) -> IO Stream
peekStream = liftM Stream . peek


foreign import ccall unsafe "Foreign/CUDA/Runtime/Stream.chs.h cudaStreamCreate"
  cudaStreamCreate'_ :: ((C2HSImp.Ptr (C2HSImp.Ptr ())) -> (IO C2HSImp.CInt))

foreign import ccall unsafe "Foreign/CUDA/Runtime/Stream.chs.h cudaStreamDestroy"
  cudaStreamDestroy'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall unsafe "Foreign/CUDA/Runtime/Stream.chs.h cudaStreamQuery"
  cudaStreamQuery'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Foreign/CUDA/Runtime/Stream.chs.h cudaStreamSynchronize"
  cudaStreamSynchronize'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))