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


{-# LINE 1 "src/Foreign/CUDA/Driver/Utils.chs" #-}
{-# LANGUAGE ForeignFunctionInterface #-}
--------------------------------------------------------------------------------
-- |
-- Module    : Foreign.CUDA.Driver.Utils
-- Copyright : [2009..2023] Trevor L. McDonell
-- License   : BSD
--
-- Utility functions
--
--------------------------------------------------------------------------------

module Foreign.CUDA.Driver.Utils (

  driverVersion,
  libraryVersion,

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





{-# LINE 20 "src/Foreign/CUDA/Driver/Utils.chs" #-}


-- Friends
import Foreign.CUDA.Driver.Error
import Foreign.CUDA.Internal.C2HS

-- System
import Foreign
import Foreign.C


-- |
-- Return the version number of the installed CUDA driver.
--
{-# INLINEABLE driverVersion #-}
driverVersion :: IO Int
driverVersion :: IO Int
driverVersion =  (Status, Int) -> IO Int
forall a. (Status, a) -> IO a
resultIfOk ((Status, Int) -> IO Int) -> IO (Status, Int) -> IO Int
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IO (Status, Int)
cuDriverGetVersion

{-# INLINE cuDriverGetVersion #-}
cuDriverGetVersion :: IO ((Status), (Int))
cuDriverGetVersion :: IO (Status, Int)
cuDriverGetVersion =
  (Ptr CInt -> IO (Status, Int)) -> IO (Status, Int)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CInt -> IO (Status, Int)) -> IO (Status, Int))
-> (Ptr CInt -> IO (Status, Int)) -> IO (Status, Int)
forall a b. (a -> b) -> a -> b
$ \Ptr CInt
a1' -> 
  Ptr CInt -> IO CInt
cuDriverGetVersion'_ Ptr CInt
a1' IO CInt -> (CInt -> IO (Status, Int)) -> IO (Status, Int)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \CInt
res ->
  let {res' :: Status
res' = CInt -> Status
forall i e. (Integral i, Enum e) => i -> e
cToEnum CInt
res} in
  Ptr CInt -> IO Int
forall a b. (Storable a, Integral a, Integral b) => Ptr a -> IO b
peekIntConv  Ptr CInt
a1'IO Int -> (Int -> IO (Status, Int)) -> IO (Status, Int)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Int
a1'' -> 
  (Status, Int) -> IO (Status, Int)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Status
res', Int
a1'')

{-# LINE 40 "src/Foreign/CUDA/Driver/Utils.chs" #-}



-- |
-- Return the version number of the CUDA library (API) that this package was
-- compiled against.
--
{-# INLINEABLE libraryVersion #-}
libraryVersion :: Int
libraryVersion :: Int
libraryVersion = Int
11080
{-# LINE 49 "src/Foreign/CUDA/Driver/Utils.chs" #-}



foreign import ccall unsafe "Foreign/CUDA/Driver/Utils.chs.h cuDriverGetVersion"
  cuDriverGetVersion'_ :: ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt))