{-# LINE 1 "src/Foreign/CUDA/Driver/Context/Config.chs" #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE EmptyCase #-}
module Foreign.CUDA.Driver.Context.Config (
getFlags,
Limit(..),
getLimit, setLimit,
Cache(..),
getCache, setCache,
SharedMem(..),
getSharedMem, setSharedMem,
StreamPriority,
getStreamPriorityRange,
) where
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Ptr as C2HSImp
{-# LINE 43 "src/Foreign/CUDA/Driver/Context/Config.chs" #-}
import Foreign.CUDA.Driver.Context.Base
import Foreign.CUDA.Driver.Error
import Foreign.CUDA.Internal.C2HS
import Foreign.CUDA.Types
import Control.Monad
import Foreign
import Foreign.C
data Limit = StackSize
| PrintfFifoSize
| MallocHeapSize
| DevRuntimeSyncDepth
| DevRuntimePendingLaunchCount
| Max
deriving (Eq,Show)
instance Enum Limit where
succ StackSize = PrintfFifoSize
succ PrintfFifoSize = MallocHeapSize
succ MallocHeapSize = DevRuntimeSyncDepth
succ DevRuntimeSyncDepth = DevRuntimePendingLaunchCount
succ DevRuntimePendingLaunchCount = Max
succ Max = error "Limit.succ: Max has no successor"
pred PrintfFifoSize = StackSize
pred MallocHeapSize = PrintfFifoSize
pred DevRuntimeSyncDepth = MallocHeapSize
pred DevRuntimePendingLaunchCount = DevRuntimeSyncDepth
pred Max = DevRuntimePendingLaunchCount
pred StackSize = error "Limit.pred: StackSize 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 Max
fromEnum StackSize = 0
fromEnum PrintfFifoSize = 1
fromEnum MallocHeapSize = 2
fromEnum DevRuntimeSyncDepth = 3
fromEnum DevRuntimePendingLaunchCount = 4
fromEnum Max = 5
toEnum 0 = StackSize
toEnum 1 = PrintfFifoSize
toEnum 2 = MallocHeapSize
toEnum 3 = DevRuntimeSyncDepth
toEnum 4 = DevRuntimePendingLaunchCount
toEnum 5 = Max
toEnum unmatched = error ("Limit.toEnum: Cannot match " ++ show unmatched)
{-# LINE 70 "src/Foreign/CUDA/Driver/Context/Config.chs" #-}
data Cache = PreferNone
| PreferShared
| PreferL1
| PreferEqual
deriving (Eq,Show)
instance Enum Cache where
succ PreferNone = PreferShared
succ PreferShared = PreferL1
succ PreferL1 = PreferEqual
succ PreferEqual = error "Cache.succ: PreferEqual has no successor"
pred PreferShared = PreferNone
pred PreferL1 = PreferShared
pred PreferEqual = PreferL1
pred PreferNone = error "Cache.pred: PreferNone 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 PreferEqual
fromEnum PreferNone = 0
fromEnum PreferShared = 1
fromEnum PreferL1 = 2
fromEnum PreferEqual = 3
toEnum 0 = PreferNone
toEnum 1 = PreferShared
toEnum 2 = PreferL1
toEnum 3 = PreferEqual
toEnum unmatched = error ("Cache.toEnum: Cannot match " ++ show unmatched)
{-# LINE 82 "src/Foreign/CUDA/Driver/Context/Config.chs" #-}
data SharedMem = DefaultBankSize
| FourByteBankSize
| EightByteBankSize
deriving (Eq,Show)
instance Enum SharedMem where
succ DefaultBankSize = FourByteBankSize
succ FourByteBankSize = EightByteBankSize
succ EightByteBankSize = error "SharedMem.succ: EightByteBankSize has no successor"
pred FourByteBankSize = DefaultBankSize
pred EightByteBankSize = FourByteBankSize
pred DefaultBankSize = error "SharedMem.pred: DefaultBankSize 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 EightByteBankSize
fromEnum DefaultBankSize = 0
fromEnum FourByteBankSize = 1
fromEnum EightByteBankSize = 2
toEnum 0 = DefaultBankSize
toEnum 1 = FourByteBankSize
toEnum 2 = EightByteBankSize
toEnum unmatched = error ("SharedMem.toEnum: Cannot match " ++ show unmatched)
{-# LINE 94 "src/Foreign/CUDA/Driver/Context/Config.chs" #-}
{-# INLINEABLE getFlags #-}
getFlags :: IO [ContextFlag]
getFlags = resultIfOk =<< cuCtxGetFlags
{-# INLINE cuCtxGetFlags #-}
cuCtxGetFlags :: IO ((Status), ([ContextFlag]))
cuCtxGetFlags =
alloca $ \a1' ->
cuCtxGetFlags'_ a1' >>= \res ->
let {res' = cToEnum res} in
peekFlags a1'>>= \a1'' ->
return (res', a1'')
{-# LINE 117 "src/Foreign/CUDA/Driver/Context/Config.chs" #-}
where
peekFlags = liftM extractBitMasks . peek
{-# INLINEABLE getLimit #-}
getLimit :: Limit -> IO Int
getLimit !l = resultIfOk =<< cuCtxGetLimit l
{-# INLINE cuCtxGetLimit #-}
cuCtxGetLimit :: (Limit) -> IO ((Status), (Int))
cuCtxGetLimit a2 =
alloca $ \a1' ->
let {a2' = cFromEnum a2} in
cuCtxGetLimit'_ a1' a2' >>= \res ->
let {res' = cToEnum res} in
peekIntConv a1'>>= \a1'' ->
return (res', a1'')
{-# LINE 141 "src/Foreign/CUDA/Driver/Context/Config.chs" #-}
{-# INLINEABLE setLimit #-}
setLimit :: Limit -> Int -> IO ()
setLimit !l !n = nothingIfOk =<< cuCtxSetLimit l n
{-# INLINE cuCtxSetLimit #-}
cuCtxSetLimit :: (Limit) -> (Int) -> IO ((Status))
cuCtxSetLimit a1 a2 =
let {a1' = cFromEnum a1} in
let {a2' = cIntConv a2} in
cuCtxSetLimit'_ a1' a2' >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 162 "src/Foreign/CUDA/Driver/Context/Config.chs" #-}
{-# INLINEABLE getCache #-}
getCache :: IO Cache
getCache = resultIfOk =<< cuCtxGetCacheConfig
{-# INLINE cuCtxGetCacheConfig #-}
cuCtxGetCacheConfig :: IO ((Status), (Cache))
cuCtxGetCacheConfig =
alloca $ \a1' ->
cuCtxGetCacheConfig'_ a1' >>= \res ->
let {res' = cToEnum res} in
peekEnum a1'>>= \a1'' ->
return (res', a1'')
{-# LINE 184 "src/Foreign/CUDA/Driver/Context/Config.chs" #-}
{-# INLINEABLE setCache #-}
setCache :: Cache -> IO ()
setCache !c = nothingIfOk =<< cuCtxSetCacheConfig c
{-# INLINE cuCtxSetCacheConfig #-}
cuCtxSetCacheConfig :: (Cache) -> IO ((Status))
cuCtxSetCacheConfig a1 =
let {a1' = cFromEnum a1} in
cuCtxSetCacheConfig'_ a1' >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 210 "src/Foreign/CUDA/Driver/Context/Config.chs" #-}
{-# INLINEABLE getSharedMem #-}
getSharedMem :: IO SharedMem
getSharedMem = resultIfOk =<< cuCtxGetSharedMemConfig
{-# INLINE cuCtxGetSharedMemConfig #-}
cuCtxGetSharedMemConfig :: IO ((Status), (SharedMem))
cuCtxGetSharedMemConfig =
alloca $ \a1' ->
cuCtxGetSharedMemConfig'_ a1' >>= \res ->
let {res' = cToEnum res} in
peekEnum a1'>>= \a1'' ->
return (res', a1'')
{-# LINE 236 "src/Foreign/CUDA/Driver/Context/Config.chs" #-}
{-# INLINEABLE setSharedMem #-}
setSharedMem :: SharedMem -> IO ()
setSharedMem !c = nothingIfOk =<< cuCtxSetSharedMemConfig c
{-# INLINE cuCtxSetSharedMemConfig #-}
cuCtxSetSharedMemConfig :: (SharedMem) -> IO ((Status))
cuCtxSetSharedMemConfig a1 =
let {a1' = cFromEnum a1} in
cuCtxSetSharedMemConfig'_ a1' >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 266 "src/Foreign/CUDA/Driver/Context/Config.chs" #-}
{-# INLINEABLE getStreamPriorityRange #-}
getStreamPriorityRange :: IO (StreamPriority, StreamPriority)
getStreamPriorityRange = do
(r,l,h) <- cuCtxGetStreamPriorityRange
resultIfOk (r, (h,l))
{-# INLINE cuCtxGetStreamPriorityRange #-}
cuCtxGetStreamPriorityRange :: IO ((Status), (Int), (Int))
cuCtxGetStreamPriorityRange =
alloca $ \a1' ->
alloca $ \a2' ->
cuCtxGetStreamPriorityRange'_ a1' a2' >>= \res ->
let {res' = cToEnum res} in
peekIntConv a1'>>= \a1'' ->
peekIntConv a2'>>= \a2'' ->
return (res', a1'', a2'')
{-# LINE 296 "src/Foreign/CUDA/Driver/Context/Config.chs" #-}
foreign import ccall unsafe "Foreign/CUDA/Driver/Context/Config.chs.h cuCtxGetFlags"
cuCtxGetFlags'_ :: ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO C2HSImp.CInt))
foreign import ccall unsafe "Foreign/CUDA/Driver/Context/Config.chs.h cuCtxGetLimit"
cuCtxGetLimit'_ :: ((C2HSImp.Ptr C2HSImp.CULong) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))
foreign import ccall unsafe "Foreign/CUDA/Driver/Context/Config.chs.h cuCtxSetLimit"
cuCtxSetLimit'_ :: (C2HSImp.CInt -> (C2HSImp.CULong -> (IO C2HSImp.CInt)))
foreign import ccall unsafe "Foreign/CUDA/Driver/Context/Config.chs.h cuCtxGetCacheConfig"
cuCtxGetCacheConfig'_ :: ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt))
foreign import ccall unsafe "Foreign/CUDA/Driver/Context/Config.chs.h cuCtxSetCacheConfig"
cuCtxSetCacheConfig'_ :: (C2HSImp.CInt -> (IO C2HSImp.CInt))
foreign import ccall unsafe "Foreign/CUDA/Driver/Context/Config.chs.h cuCtxGetSharedMemConfig"
cuCtxGetSharedMemConfig'_ :: ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt))
foreign import ccall unsafe "Foreign/CUDA/Driver/Context/Config.chs.h cuCtxSetSharedMemConfig"
cuCtxSetSharedMemConfig'_ :: (C2HSImp.CInt -> (IO C2HSImp.CInt))
foreign import ccall unsafe "Foreign/CUDA/Driver/Context/Config.chs.h cuCtxGetStreamPriorityRange"
cuCtxGetStreamPriorityRange'_ :: ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt)))