{-# LINE 1 "src/Foreign/CUDA/Driver/Context/Base.chs" #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE EmptyCase #-}
module Foreign.CUDA.Driver.Context.Base (
Context(..), ContextFlag(..),
create, destroy, device, pop, push, sync, get, set,
attach, detach,
) where
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Ptr as C2HSImp
{-# LINE 31 "src/Foreign/CUDA/Driver/Context/Base.chs" #-}
import Foreign.CUDA.Driver.Device ( Device(..) )
import Foreign.CUDA.Driver.Error
import Foreign.CUDA.Internal.C2HS
import Foreign
import Foreign.C
import Control.Monad ( liftM )
newtype Context = Context { useContext :: ((C2HSImp.Ptr ()))}
deriving (Eq, Show)
data ContextFlag = SchedAuto
| SchedSpin
| SchedYield
| SchedBlockingSync
| BlockingSync
| SchedMask
| MapHost
| LmemResizeToMax
| FlagsMask
deriving (Eq,Show,Bounded)
instance Enum ContextFlag where
succ SchedAuto = SchedSpin
succ SchedSpin = SchedYield
succ SchedYield = SchedBlockingSync
succ SchedBlockingSync = SchedMask
succ BlockingSync = SchedMask
succ SchedMask = MapHost
succ MapHost = LmemResizeToMax
succ LmemResizeToMax = FlagsMask
succ FlagsMask = error "ContextFlag.succ: FlagsMask has no successor"
pred SchedSpin = SchedAuto
pred SchedYield = SchedSpin
pred SchedBlockingSync = SchedYield
pred BlockingSync = SchedYield
pred SchedMask = SchedBlockingSync
pred MapHost = SchedMask
pred LmemResizeToMax = MapHost
pred FlagsMask = LmemResizeToMax
pred SchedAuto = error "ContextFlag.pred: SchedAuto 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 FlagsMask
fromEnum SchedAuto = 0
fromEnum SchedSpin = 1
fromEnum SchedYield = 2
fromEnum SchedBlockingSync = 4
fromEnum BlockingSync = 4
fromEnum SchedMask = 7
fromEnum MapHost = 8
fromEnum LmemResizeToMax = 16
fromEnum FlagsMask = 31
toEnum 0 = SchedAuto
toEnum 1 = SchedSpin
toEnum 2 = SchedYield
toEnum 4 = SchedBlockingSync
toEnum 7 = SchedMask
toEnum 8 = MapHost
toEnum 16 = LmemResizeToMax
toEnum 31 = FlagsMask
toEnum unmatched = error ("ContextFlag.toEnum: Cannot match " ++ show unmatched)
{-# LINE 60 "src/Foreign/CUDA/Driver/Context/Base.chs" #-}
{-# DEPRECATED attach, detach "as of CUDA-4.0" #-}
{-# DEPRECATED BlockingSync "use SchedBlockingSync instead" #-}
{-# INLINEABLE create #-}
create :: Device -> [ContextFlag] -> IO Context
create !dev !flags = resultIfOk =<< cuCtxCreate flags dev
{-# INLINE cuCtxCreate #-}
cuCtxCreate :: ([ContextFlag]) -> (Device) -> IO ((Status), (Context))
cuCtxCreate a2 a3 =
alloca $ \a1' ->
let {a2' = combineBitMasks a2} in
let {a3' = useDevice a3} in
cuCtxCreate'_ a1' a2' a3' >>= \res ->
let {res' = cToEnum res} in
peekCtx a1'>>= \a1'' ->
return (res', a1'')
{-# LINE 90 "src/Foreign/CUDA/Driver/Context/Base.chs" #-}
where peekCtx = liftM Context . peek
{-# INLINEABLE attach #-}
attach :: Context -> [ContextFlag] -> IO ()
attach !ctx !flags = nothingIfOk =<< cuCtxAttach ctx flags
{-# INLINE cuCtxAttach #-}
cuCtxAttach :: (Context) -> ([ContextFlag]) -> IO ((Status))
cuCtxAttach a1 a2 =
withCtx a1 $ \a1' ->
let {a2' = combineBitMasks a2} in
cuCtxAttach'_ a1' a2' >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 105 "src/Foreign/CUDA/Driver/Context/Base.chs" #-}
where withCtx = with . useContext
{-# INLINEABLE detach #-}
detach :: Context -> IO ()
detach !ctx = nothingIfOk =<< cuCtxDetach ctx
{-# INLINE cuCtxDetach #-}
cuCtxDetach :: (Context) -> IO ((Status))
cuCtxDetach a1 =
let {a1' = useContext a1} in
cuCtxDetach'_ a1' >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 118 "src/Foreign/CUDA/Driver/Context/Base.chs" #-}
{-# INLINEABLE destroy #-}
destroy :: Context -> IO ()
destroy !ctx = nothingIfOk =<< cuCtxDestroy ctx
{-# INLINE cuCtxDestroy #-}
cuCtxDestroy :: (Context) -> IO ((Status))
cuCtxDestroy a1 =
let {a1' = useContext a1} in
cuCtxDestroy'_ a1' >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 136 "src/Foreign/CUDA/Driver/Context/Base.chs" #-}
{-# INLINEABLE get #-}
get :: IO (Maybe Context)
get = resultIfOk =<< cuCtxGetCurrent
{-# INLINE cuCtxGetCurrent #-}
cuCtxGetCurrent :: IO ((Status), (Maybe Context))
cuCtxGetCurrent =
alloca $ \a1' ->
cuCtxGetCurrent'_ a1' >>= \res ->
let {res' = cToEnum res} in
peekCtx a1'>>= \a1'' ->
return (res', a1'')
{-# LINE 155 "src/Foreign/CUDA/Driver/Context/Base.chs" #-}
where peekCtx = liftM (nothingIfNull Context) . peek
{-# INLINEABLE set #-}
set :: Context -> IO ()
set !ctx = nothingIfOk =<< cuCtxSetCurrent ctx
{-# INLINE cuCtxSetCurrent #-}
cuCtxSetCurrent :: (Context) -> IO ((Status))
cuCtxSetCurrent a1 =
let {a1' = useContext a1} in
cuCtxSetCurrent'_ a1' >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 177 "src/Foreign/CUDA/Driver/Context/Base.chs" #-}
{-# INLINEABLE device #-}
device :: IO Device
device = resultIfOk =<< cuCtxGetDevice
{-# INLINE cuCtxGetDevice #-}
cuCtxGetDevice :: IO ((Status), (Device))
cuCtxGetDevice =
alloca $ \a1' ->
cuCtxGetDevice'_ a1' >>= \res ->
let {res' = cToEnum res} in
dev a1'>>= \a1'' ->
return (res', a1'')
{-# LINE 191 "src/Foreign/CUDA/Driver/Context/Base.chs" #-}
where dev = liftM Device . peekIntConv
{-# INLINEABLE pop #-}
pop :: IO Context
pop = resultIfOk =<< cuCtxPopCurrent
{-# INLINE cuCtxPopCurrent #-}
cuCtxPopCurrent :: IO ((Status), (Context))
cuCtxPopCurrent =
alloca $ \a1' ->
cuCtxPopCurrent'_ a1' >>= \res ->
let {res' = cToEnum res} in
peekCtx a1'>>= \a1'' ->
return (res', a1'')
{-# LINE 207 "src/Foreign/CUDA/Driver/Context/Base.chs" #-}
where peekCtx = liftM Context . peek
{-# INLINEABLE push #-}
push :: Context -> IO ()
push !ctx = nothingIfOk =<< cuCtxPushCurrent ctx
{-# INLINE cuCtxPushCurrent #-}
cuCtxPushCurrent :: (Context) -> IO ((Status))
cuCtxPushCurrent a1 =
let {a1' = useContext a1} in
cuCtxPushCurrent'_ a1' >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 224 "src/Foreign/CUDA/Driver/Context/Base.chs" #-}
{-# INLINEABLE sync #-}
sync :: IO ()
sync = nothingIfOk =<< cuCtxSynchronize
{-# INLINE cuCtxSynchronize #-}
cuCtxSynchronize :: IO ((Status))
cuCtxSynchronize =
cuCtxSynchronize'_ >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 240 "src/Foreign/CUDA/Driver/Context/Base.chs" #-}
foreign import ccall unsafe "Foreign/CUDA/Driver/Context/Base.chs.h cuCtxCreate"
cuCtxCreate'_ :: ((C2HSImp.Ptr (C2HSImp.Ptr ())) -> (C2HSImp.CUInt -> (C2HSImp.CInt -> (IO C2HSImp.CInt))))
foreign import ccall unsafe "Foreign/CUDA/Driver/Context/Base.chs.h cuCtxAttach"
cuCtxAttach'_ :: ((C2HSImp.Ptr (C2HSImp.Ptr ())) -> (C2HSImp.CUInt -> (IO C2HSImp.CInt)))
foreign import ccall unsafe "Foreign/CUDA/Driver/Context/Base.chs.h cuCtxDetach"
cuCtxDetach'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall unsafe "Foreign/CUDA/Driver/Context/Base.chs.h cuCtxDestroy"
cuCtxDestroy'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall unsafe "Foreign/CUDA/Driver/Context/Base.chs.h cuCtxGetCurrent"
cuCtxGetCurrent'_ :: ((C2HSImp.Ptr (C2HSImp.Ptr ())) -> (IO C2HSImp.CInt))
foreign import ccall unsafe "Foreign/CUDA/Driver/Context/Base.chs.h cuCtxSetCurrent"
cuCtxSetCurrent'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall unsafe "Foreign/CUDA/Driver/Context/Base.chs.h cuCtxGetDevice"
cuCtxGetDevice'_ :: ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt))
foreign import ccall unsafe "Foreign/CUDA/Driver/Context/Base.chs.h cuCtxPopCurrent"
cuCtxPopCurrent'_ :: ((C2HSImp.Ptr (C2HSImp.Ptr ())) -> (IO C2HSImp.CInt))
foreign import ccall unsafe "Foreign/CUDA/Driver/Context/Base.chs.h cuCtxPushCurrent"
cuCtxPushCurrent'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Foreign/CUDA/Driver/Context/Base.chs.h cuCtxSynchronize"
cuCtxSynchronize'_ :: (IO C2HSImp.CInt)