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


{-# LINE 1 "./Foreign/CUDA/BLAS/Context.chs" #-}
{-# LANGUAGE CPP                      #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE TemplateHaskell          #-}
-- |
-- Module      : Foreign.CUDA.BLAS.Context
-- Copyright   : [2014..2017] Trevor L. McDonell
-- License     : BSD3
--
-- Maintainer  : Trevor L. McDonell <tmcdonell@cse.unsw.edu.au>
-- Stability   : experimental
-- Portability : non-portable (GHC extensions)
--

module Foreign.CUDA.BLAS.Context (

  -- * Context management
  Handle(..),
  create, destroy,

  -- ** Utilities
  PointerMode(..), AtomicsMode(..), MathMode(..),
  setPointerMode,
  getPointerMode,
  setAtomicsMode,
  getAtomicsMode,
  setMathMode,
  getMathMode,

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



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

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



{-# LINE 42 "./Foreign/CUDA/BLAS/Context.chs" #-}



-- | This function initializes the CUBLAS library and creates a handle to an
-- opaque structure holding the CUBLAS library context. It allocates hardware
-- resources on the host and device and must be called prior to making any other
-- CUBLAS library calls.
--
-- <http://docs.nvidia.com/cuda/cublas/index.html#cublascreate>
--
{-# INLINEABLE create #-}
create :: IO ((Handle))
create =
  alloca $ \a1' ->
  create'_ a1' >>= \res ->
  checkStatus res >>
  peekHdl  a1'>>= \a1'' ->
  return (a1'')

{-# LINE 54 "./Foreign/CUDA/BLAS/Context.chs" #-}

  where
    peekHdl = liftM Handle . peek


-- | This function releases hardware resources used by the CUBLAS library. The
-- release of GPU resources may be deferred until the application exits. This
-- function is usually the last call with a particular handle to the CUBLAS
-- library.
--
-- <http://docs.nvidia.com/cuda/cublas/index.html#cublasdestroy>
--
{-# INLINEABLE destroy #-}
destroy :: (Handle) -> IO ((()))
destroy a1 =
  let {a1' = useHandle a1} in
  destroy'_ a1' >>= \res ->
  checkStatus res >>= \res' ->
  return (res')

{-# LINE 68 "./Foreign/CUDA/BLAS/Context.chs" #-}



-- | Set the pointer mode used by cuBLAS library functions. For example, this
-- controls whether the scaling parameters \(\alpha\) and \(\beta\) of the
-- <http://docs.nvidia.com/cuda/cublas/index.html#cublas-lt-t-gt-gemm ?gemm>
-- operation are treated as residing in host or device memory.
--
-- The default mode is for values to be passed by reference from the host.
--
-- <http://docs.nvidia.com/cuda/cublas/index.html#cublassetpointermode>
--
{-# INLINEABLE setPointerMode #-}
setPointerMode :: (Handle) -> (PointerMode) -> IO ((()))
setPointerMode a1 a2 =
  let {a1' = useHandle a1} in
  let {a2' = cFromEnum a2} in
  setPointerMode'_ a1' a2' >>= \res ->
  checkStatus res >>= \res' ->
  return (res')

{-# LINE 85 "./Foreign/CUDA/BLAS/Context.chs" #-}


-- | Get the pointer mode used by cuBLAS library functions to pass scalar
-- arguments.
--
-- <http://docs.nvidia.com/cuda/cublas/index.html#cublasgetpointermode>
--
{-# INLINEABLE getPointerMode #-}
getPointerMode :: (Handle) -> IO ((PointerMode))
getPointerMode a1 =
  let {a1' = useHandle a1} in
  alloca $ \a2' ->
  getPointerMode'_ a1' a2' >>= \res ->
  checkStatus res >>
  peekEnum  a2'>>= \a2'' ->
  return (a2'')

{-# LINE 97 "./Foreign/CUDA/BLAS/Context.chs" #-}



-- | Set whether cuBLAS library functions are allowed to use atomic functions,
-- when available. The implementations are generally faster, but can generate
-- results which are not strictly identical from one run to another.
--
-- <http://docs.nvidia.com/cuda/cublas/index.html#cublassetatomicsmode>
--
{-# INLINEABLE setAtomicsMode #-}
setAtomicsMode :: (Handle) -> (AtomicsMode) -> IO ((()))
setAtomicsMode a1 a2 =
  let {a1' = useHandle a1} in
  let {a2' = cFromEnum a2} in
  setAtomicsMode'_ a1' a2' >>= \res ->
  checkStatus res >>= \res' ->
  return (res')

{-# LINE 111 "./Foreign/CUDA/BLAS/Context.chs" #-}



-- | Determine whether cuBLAS library functions are allowed to use atomic
-- operations.
--
-- <http://docs.nvidia.com/cuda/cublas/index.html#cublasgetatomicsmode>
--
{-# INLINEABLE getAtomicsMode #-}
getAtomicsMode :: (Handle) -> IO ((AtomicsMode))
getAtomicsMode a1 =
  let {a1' = useHandle a1} in
  alloca $ \a2' ->
  getAtomicsMode'_ a1' a2' >>= \res ->
  checkStatus res >>
  peekEnum  a2'>>= \a2'' ->
  return (a2'')

{-# LINE 124 "./Foreign/CUDA/BLAS/Context.chs" #-}



-- | Set whether cuBLAS library functions are allowed to use Tensor Core
-- operations where available.
--
-- <http://docs.nvidia.com/cuda/cublas/index.html#cublassetmathmode>
--
-- @since 0.4.0.0@
--
{-# INLINEABLE setMathMode #-}
setMathMode :: (Handle) -> (MathMode) -> IO ()
setMathMode a1 a2 =
  let {a1' = useHandle a1} in
  let {a2' = cFromEnum a2} in
  setMathMode'_ a1' a2' >>= \res ->
  checkStatus res >>
  return ()

{-# LINE 144 "./Foreign/CUDA/BLAS/Context.chs" #-}



-- | Determine whether cuBLAS library functions are allowed to use Tensor Core
-- operations where available.
--
-- <http://docs.nvidia.com/cuda/cublas/index.html#cublasgetmathmode>
--
-- @since 0.4.0.0@
--
{-# INLINEABLE getMathMode #-}
getMathMode :: (Handle) -> IO ((MathMode))
getMathMode a1 =
  let {a1' = useHandle a1} in
  alloca $ \a2' ->
  getMathMode'_ a1' a2' >>= \res ->
  checkStatus res >>
  peekEnum  a2'>>= \a2'' ->
  return (a2'')

{-# LINE 164 "./Foreign/CUDA/BLAS/Context.chs" #-}


-- TODO: since CUDA-10.0
--  cublasLoggerConfigure
--  cublas[Get,Set]LoggerCallback
--


foreign import ccall unsafe "Foreign/CUDA/BLAS/Context.chs.h cublasCreate_v2"
  create'_ :: ((C2HSImp.Ptr (C2HSImp.Ptr ())) -> (IO C2HSImp.CInt))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Context.chs.h cublasDestroy_v2"
  destroy'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Context.chs.h cublasSetPointerMode_v2"
  setPointerMode'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Context.chs.h cublasGetPointerMode_v2"
  getPointerMode'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt)))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Context.chs.h cublasSetAtomicsMode"
  setAtomicsMode'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Context.chs.h cublasGetAtomicsMode"
  getAtomicsMode'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt)))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Context.chs.h cublasSetMathMode"
  setMathMode'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))

foreign import ccall unsafe "Foreign/CUDA/BLAS/Context.chs.h cublasGetMathMode"
  getMathMode'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt)))