-- GENERATED by C->Haskell Compiler, version 0.28.6 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..2018] 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 =  resultIfOk =<< cuDriverGetVersion

{-# INLINE cuDriverGetVersion #-}
cuDriverGetVersion :: IO ((Status), (Int))
cuDriverGetVersion =
  alloca $ \a1' ->
  cuDriverGetVersion'_ a1' >>= \res ->
  let {res' = cToEnum res} in
  peekIntConv  a1'>>= \a1'' ->
  return (res', 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 = 10000
{-# 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))