{-# LINE 1 "src/Foreign/CUDA/Driver/Profiler.chs" #-}
{-# LANGUAGE ForeignFunctionInterface #-}
module Foreign.CUDA.Driver.Profiler (
OutputMode(..),
initialise,
start, stop,
) where
import qualified Foreign.C.String as C2HSImp
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Ptr as C2HSImp
{-# LINE 21 "src/Foreign/CUDA/Driver/Profiler.chs" #-}
import Foreign.CUDA.Driver.Error
import Foreign.CUDA.Internal.C2HS
import Foreign
import Foreign.C
data OutputMode = KeyValuePair
| CSV
deriving (Eq,Show)
instance Enum OutputMode where
succ KeyValuePair = CSV
succ CSV = error "OutputMode.succ: CSV has no successor"
pred CSV = KeyValuePair
pred KeyValuePair = error "OutputMode.pred: KeyValuePair has no predecessor"
enumFromTo from to = go from
where
end = fromEnum to
go v = case compare (fromEnum v) end of
LT -> v : go (succ v)
EQ -> [v]
GT -> []
enumFrom from = enumFromTo from CSV
fromEnum KeyValuePair = 0
fromEnum CSV = 1
toEnum 0 = KeyValuePair
toEnum 1 = CSV
toEnum unmatched = error ("OutputMode.toEnum: Cannot match " ++ show unmatched)
{-# LINE 37 "src/Foreign/CUDA/Driver/Profiler.chs" #-}
{-# INLINEABLE initialise #-}
initialise
:: FilePath
-> FilePath
-> OutputMode
-> IO ()
initialise config output mode
= nothingIfOk =<< cuProfilerInitialize config output mode
{-# INLINE cuProfilerInitialize #-}
cuProfilerInitialize :: (String) -> (String) -> (OutputMode) -> IO ((Status))
cuProfilerInitialize a1 a2 a3 =
C2HSImp.withCString a1 $ \a1' ->
C2HSImp.withCString a2 $ \a2' ->
let {a3' = cFromEnum a3} in
cuProfilerInitialize'_ a1' a2' a3' >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 66 "src/Foreign/CUDA/Driver/Profiler.chs" #-}
{-# INLINEABLE start #-}
start :: IO ()
start = nothingIfOk =<< cuProfilerStart
{-# INLINE cuProfilerStart #-}
cuProfilerStart :: IO ((Status))
cuProfilerStart =
cuProfilerStart'_ >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 84 "src/Foreign/CUDA/Driver/Profiler.chs" #-}
{-# INLINEABLE stop #-}
stop :: IO ()
stop = nothingIfOk =<< cuProfilerStop
{-# INLINE cuProfilerStop #-}
cuProfilerStop :: IO ((Status))
cuProfilerStop =
cuProfilerStop'_ >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 99 "src/Foreign/CUDA/Driver/Profiler.chs" #-}
foreign import ccall unsafe "Foreign/CUDA/Driver/Profiler.chs.h cuProfilerInitialize"
cuProfilerInitialize'_ :: ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CInt -> (IO C2HSImp.CInt))))
foreign import ccall unsafe "Foreign/CUDA/Driver/Profiler.chs.h cuProfilerStart"
cuProfilerStart'_ :: (IO C2HSImp.CInt)
foreign import ccall unsafe "Foreign/CUDA/Driver/Profiler.chs.h cuProfilerStop"
cuProfilerStop'_ :: (IO C2HSImp.CInt)