{-# LINE 1 "src/Foreign/CUDA/Runtime/Device.chs" #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE EmptyCase #-}
module Foreign.CUDA.Runtime.Device (
Device, DeviceFlag(..), DeviceProperties(..), Compute(..), ComputeMode(..),
choose, get, count, props, set, setFlags, setOrder, reset, sync,
PeerFlag,
accessible, add, remove,
Limit(..),
getLimit, setLimit
) where
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.ForeignPtr as C2HSImp
import qualified Foreign.Ptr as C2HSImp
import qualified Foreign.Storable as C2HSImp
{-# LINE 37 "src/Foreign/CUDA/Runtime/Device.chs" #-}
import Foreign.CUDA.Analysis.Device
import Foreign.CUDA.Runtime.Error
import Foreign.CUDA.Internal.C2HS
import Foreign
import Foreign.C
type Device = Int
{-# LINE 73 "src/Foreign/CUDA/Runtime/Device.chs" #-}
data DeviceFlag = ScheduleAuto
| ScheduleSpin
| ScheduleYield
| BlockingSync
| MapHost
| LMemResizeToMax
deriving (Eq,Show,Bounded)
instance Enum DeviceFlag where
succ ScheduleAuto = ScheduleSpin
succ ScheduleSpin = ScheduleYield
succ ScheduleYield = BlockingSync
succ BlockingSync = MapHost
succ MapHost = LMemResizeToMax
succ LMemResizeToMax = error "DeviceFlag.succ: LMemResizeToMax has no successor"
pred ScheduleSpin = ScheduleAuto
pred ScheduleYield = ScheduleSpin
pred BlockingSync = ScheduleYield
pred MapHost = BlockingSync
pred LMemResizeToMax = MapHost
pred ScheduleAuto = error "DeviceFlag.pred: ScheduleAuto 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 LMemResizeToMax
fromEnum ScheduleAuto = 0
fromEnum ScheduleSpin = 1
fromEnum ScheduleYield = 2
fromEnum BlockingSync = 4
fromEnum MapHost = 8
fromEnum LMemResizeToMax = 16
toEnum 0 = ScheduleAuto
toEnum 1 = ScheduleSpin
toEnum 2 = ScheduleYield
toEnum 4 = BlockingSync
toEnum 8 = MapHost
toEnum 16 = LMemResizeToMax
toEnum unmatched = error ("DeviceFlag.toEnum: Cannot match " ++ show unmatched)
{-# LINE 79 "src/Foreign/CUDA/Runtime/Device.chs" #-}
instance Storable DeviceProperties where
sizeOf _ = 648
{-# LINE 83 "src/Foreign/CUDA/Runtime/Device.chs" #-}
alignment _ = alignment (undefined :: Ptr ())
poke _ _ = error "no instance for Foreign.Storable.poke DeviceProperties"
peek p = do
n <- peekCString =<< (\ptr -> do {return $ ptr `C2HSImp.plusPtr` 0 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p
gm <- cIntConv `fmap` (\ptr -> do {C2HSImp.peekByteOff ptr 256 :: IO C2HSImp.CULong}) p
sm <- cIntConv `fmap` (\ptr -> do {C2HSImp.peekByteOff ptr 264 :: IO C2HSImp.CULong}) p
rb <- cIntConv `fmap` (\ptr -> do {C2HSImp.peekByteOff ptr 272 :: IO C2HSImp.CInt}) p
ws <- cIntConv `fmap` (\ptr -> do {C2HSImp.peekByteOff ptr 276 :: IO C2HSImp.CInt}) p
mp <- cIntConv `fmap` (\ptr -> do {C2HSImp.peekByteOff ptr 280 :: IO C2HSImp.CULong}) p
tb <- cIntConv `fmap` (\ptr -> do {C2HSImp.peekByteOff ptr 288 :: IO C2HSImp.CInt}) p
cl <- cIntConv `fmap` (\ptr -> do {C2HSImp.peekByteOff ptr 316 :: IO C2HSImp.CInt}) p
cm <- cIntConv `fmap` (\ptr -> do {C2HSImp.peekByteOff ptr 320 :: IO C2HSImp.CULong}) p
v1 <- fromIntegral `fmap` (\ptr -> do {C2HSImp.peekByteOff ptr 328 :: IO C2HSImp.CInt}) p
v2 <- fromIntegral `fmap` (\ptr -> do {C2HSImp.peekByteOff ptr 332 :: IO C2HSImp.CInt}) p
ta <- cIntConv `fmap` (\ptr -> do {C2HSImp.peekByteOff ptr 336 :: IO C2HSImp.CULong}) p
ov <- cToBool `fmap` (\ptr -> do {C2HSImp.peekByteOff ptr 352 :: IO C2HSImp.CInt}) p
pc <- cIntConv `fmap` (\ptr -> do {C2HSImp.peekByteOff ptr 356 :: IO C2HSImp.CInt}) p
ke <- cToBool `fmap` (\ptr -> do {C2HSImp.peekByteOff ptr 360 :: IO C2HSImp.CInt}) p
tg <- cToBool `fmap` (\ptr -> do {C2HSImp.peekByteOff ptr 364 :: IO C2HSImp.CInt}) p
hm <- cToBool `fmap` (\ptr -> do {C2HSImp.peekByteOff ptr 368 :: IO C2HSImp.CInt}) p
md <- cToEnum `fmap` (\ptr -> do {C2HSImp.peekByteOff ptr 372 :: IO C2HSImp.CInt}) p
ck <- cToBool `fmap` (\ptr -> do {C2HSImp.peekByteOff ptr 544 :: IO C2HSImp.CInt}) p
u1 <- cIntConv `fmap` (\ptr -> do {C2HSImp.peekByteOff ptr 376 :: IO C2HSImp.CInt}) p
ee <- cToBool `fmap` (\ptr -> do {C2HSImp.peekByteOff ptr 548 :: IO C2HSImp.CInt}) p
ae <- cIntConv `fmap` (\ptr -> do {C2HSImp.peekByteOff ptr 568 :: IO C2HSImp.CInt}) p
l2 <- cIntConv `fmap` (\ptr -> do {C2HSImp.peekByteOff ptr 584 :: IO C2HSImp.CInt}) p
tm <- cIntConv `fmap` (\ptr -> do {C2HSImp.peekByteOff ptr 588 :: IO C2HSImp.CInt}) p
mw <- cIntConv `fmap` (\ptr -> do {C2HSImp.peekByteOff ptr 580 :: IO C2HSImp.CInt}) p
mc <- cIntConv `fmap` (\ptr -> do {C2HSImp.peekByteOff ptr 576 :: IO C2HSImp.CInt}) p
pb <- cIntConv `fmap` (\ptr -> do {C2HSImp.peekByteOff ptr 552 :: IO C2HSImp.CInt}) p
pd <- cIntConv `fmap` (\ptr -> do {C2HSImp.peekByteOff ptr 556 :: IO C2HSImp.CInt}) p
pm <- cIntConv `fmap` (\ptr -> do {C2HSImp.peekByteOff ptr 560 :: IO C2HSImp.CInt}) p
tc <- cToBool `fmap` (\ptr -> do {C2HSImp.peekByteOff ptr 564 :: IO C2HSImp.CInt}) p
ua <- cToBool `fmap` (\ptr -> do {C2HSImp.peekByteOff ptr 572 :: IO C2HSImp.CInt}) p
[t1,t2,t3] <- peekArrayWith cIntConv 3 =<< (\ptr -> do {return $ ptr `C2HSImp.plusPtr` 292 :: IO (C2HSImp.Ptr C2HSImp.CInt)}) p
[g1,g2,g3] <- peekArrayWith cIntConv 3 =<< (\ptr -> do {return $ ptr `C2HSImp.plusPtr` 304 :: IO (C2HSImp.Ptr C2HSImp.CInt)}) p
[u21,u22] <- peekArrayWith cIntConv 2 =<< (\ptr -> do {return $ ptr `C2HSImp.plusPtr` 388 :: IO (C2HSImp.Ptr C2HSImp.CInt)}) p
[u31,u32,u33] <- peekArrayWith cIntConv 3 =<< (\ptr -> do {return $ ptr `C2HSImp.plusPtr` 424 :: IO (C2HSImp.Ptr C2HSImp.CInt)}) p
sp <- cToBool `fmap` (\ptr -> do {C2HSImp.peekByteOff ptr 592 :: IO C2HSImp.CInt}) p
gl1 <- cToBool `fmap` (\ptr -> do {C2HSImp.peekByteOff ptr 596 :: IO C2HSImp.CInt}) p
ll1 <- cToBool `fmap` (\ptr -> do {C2HSImp.peekByteOff ptr 600 :: IO C2HSImp.CInt}) p
mm <- cToBool `fmap` (\ptr -> do {C2HSImp.peekByteOff ptr 620 :: IO C2HSImp.CInt}) p
mg <- cToBool `fmap` (\ptr -> do {C2HSImp.peekByteOff ptr 624 :: IO C2HSImp.CInt}) p
mid <- cIntConv `fmap` (\ptr -> do {C2HSImp.peekByteOff ptr 628 :: IO C2HSImp.CInt}) p
return DeviceProperties
{
deviceName = n
, computeCapability = Compute v1 v2
, totalGlobalMem = gm
, totalConstMem = cm
, sharedMemPerBlock = sm
, regsPerBlock = rb
, warpSize = ws
, maxThreadsPerBlock = tb
, maxBlockSize = (t1,t2,t3)
, maxGridSize = (g1,g2,g3)
, clockRate = cl
, multiProcessorCount = pc
, memPitch = mp
, textureAlignment = ta
, computeMode = md
, deviceOverlap = ov
, kernelExecTimeoutEnabled = ke
, integrated = tg
, canMapHostMemory = hm
, concurrentKernels = ck
, maxTextureDim1D = u1
, maxTextureDim2D = (u21,u22)
, maxTextureDim3D = (u31,u32,u33)
, eccEnabled = ee
, asyncEngineCount = ae
, cacheMemL2 = l2
, maxThreadsPerMultiProcessor = tm
, memBusWidth = mw
, memClockRate = mc
, tccDriverEnabled = tc
, unifiedAddressing = ua
, pciInfo = PCI pb pd pm
, streamPriorities = sp
, globalL1Cache = gl1
, localL1Cache = ll1
, managedMemory = mm
, multiGPUBoard = mg
, multiGPUBoardGroupID = mid
}
{-# INLINEABLE choose #-}
choose :: DeviceProperties -> IO Device
choose !dev = resultIfOk =<< cudaChooseDevice dev
{-# INLINE cudaChooseDevice #-}
cudaChooseDevice :: (DeviceProperties) -> IO ((Status), (Int))
cudaChooseDevice a2 =
alloca $ \a1' ->
withDevProp a2 $ \a2' ->
cudaChooseDevice'_ a1' a2' >>= \res ->
let {res' = cToEnum res} in
peekIntConv a1'>>= \a1'' ->
return (res', a1'')
{-# LINE 213 "src/Foreign/CUDA/Runtime/Device.chs" #-}
where
withDevProp = with
{-# INLINEABLE get #-}
get :: IO Device
get = resultIfOk =<< cudaGetDevice
{-# INLINE cudaGetDevice #-}
cudaGetDevice :: IO ((Status), (Int))
cudaGetDevice =
alloca $ \a1' ->
cudaGetDevice'_ a1' >>= \res ->
let {res' = cToEnum res} in
peekIntConv a1'>>= \a1'' ->
return (res', a1'')
{-# LINE 227 "src/Foreign/CUDA/Runtime/Device.chs" #-}
{-# INLINEABLE count #-}
count :: IO Int
count = resultIfOk =<< cudaGetDeviceCount
{-# INLINE cudaGetDeviceCount #-}
cudaGetDeviceCount :: IO ((Status), (Int))
cudaGetDeviceCount =
alloca $ \a1' ->
cudaGetDeviceCount'_ a1' >>= \res ->
let {res' = cToEnum res} in
peekIntConv a1'>>= \a1'' ->
return (res', a1'')
{-# LINE 240 "src/Foreign/CUDA/Runtime/Device.chs" #-}
{-# INLINEABLE props #-}
props :: Device -> IO DeviceProperties
props !n = resultIfOk =<< cudaGetDeviceProperties n
{-# INLINE cudaGetDeviceProperties #-}
cudaGetDeviceProperties :: (Int) -> IO ((Status), (DeviceProperties))
cudaGetDeviceProperties a2 =
alloca $ \a1' ->
let {a2' = fromIntegral a2} in
cudaGetDeviceProperties'_ a1' a2' >>= \res ->
let {res' = cToEnum res} in
peek a1'>>= \a1'' ->
return (res', a1'')
{-# LINE 253 "src/Foreign/CUDA/Runtime/Device.chs" #-}
{-# INLINEABLE set #-}
set :: Device -> IO ()
set !n = nothingIfOk =<< cudaSetDevice n
{-# INLINE cudaSetDevice #-}
cudaSetDevice :: (Int) -> IO ((Status))
cudaSetDevice a1 =
let {a1' = fromIntegral a1} in
cudaSetDevice'_ a1' >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 265 "src/Foreign/CUDA/Runtime/Device.chs" #-}
{-# INLINEABLE setFlags #-}
setFlags :: [DeviceFlag] -> IO ()
setFlags !f = nothingIfOk =<< cudaSetDeviceFlags (combineBitMasks f)
{-# INLINE cudaSetDeviceFlags #-}
cudaSetDeviceFlags :: (Int) -> IO ((Status))
cudaSetDeviceFlags a1 =
let {a1' = fromIntegral a1} in
cudaSetDeviceFlags'_ a1' >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 277 "src/Foreign/CUDA/Runtime/Device.chs" #-}
{-# INLINEABLE setOrder #-}
setOrder :: [Device] -> IO ()
setOrder !l = nothingIfOk =<< cudaSetValidDevices l (length l)
{-# INLINE cudaSetValidDevices #-}
cudaSetValidDevices :: ([Int]) -> (Int) -> IO ((Status))
cudaSetValidDevices a1 a2 =
withArrayIntConv a1 $ \a1' ->
let {a2' = fromIntegral a2} in
cudaSetValidDevices'_ a1' a2' >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 290 "src/Foreign/CUDA/Runtime/Device.chs" #-}
where
withArrayIntConv = withArray . map cIntConv
{-# INLINEABLE sync #-}
sync :: IO ()
{-# INLINE cudaDeviceSynchronize #-}
sync = nothingIfOk =<< cudaDeviceSynchronize
cudaDeviceSynchronize :: IO ((Status))
cudaDeviceSynchronize =
cudaDeviceSynchronize'_ >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 308 "src/Foreign/CUDA/Runtime/Device.chs" #-}
{-# INLINEABLE reset #-}
reset :: IO ()
{-# INLINE cudaDeviceReset #-}
reset = nothingIfOk =<< cudaDeviceReset
cudaDeviceReset :: IO ((Status))
cudaDeviceReset =
cudaDeviceReset'_ >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 329 "src/Foreign/CUDA/Runtime/Device.chs" #-}
data PeerFlag
instance Enum PeerFlag where
toEnum x = case x of {}
fromEnum x = case x of {}
{-# INLINEABLE accessible #-}
accessible :: Device -> Device -> IO Bool
accessible !dev !peer = resultIfOk =<< cudaDeviceCanAccessPeer dev peer
{-# INLINE cudaDeviceCanAccessPeer #-}
cudaDeviceCanAccessPeer :: (Device) -> (Device) -> IO ((Status), (Bool))
cudaDeviceCanAccessPeer a2 a3 =
alloca $ \a1' ->
let {a2' = cIntConv a2} in
let {a3' = cIntConv a3} in
cudaDeviceCanAccessPeer'_ a1' a2' a3' >>= \res ->
let {res' = cToEnum res} in
peekBool a1'>>= \a1'' ->
return (res', a1'')
{-# LINE 363 "src/Foreign/CUDA/Runtime/Device.chs" #-}
{-# INLINEABLE add #-}
add :: Device -> [PeerFlag] -> IO ()
add !dev !flags = nothingIfOk =<< cudaDeviceEnablePeerAccess dev flags
{-# INLINE cudaDeviceEnablePeerAccess #-}
cudaDeviceEnablePeerAccess :: (Device) -> ([PeerFlag]) -> IO ((Status))
cudaDeviceEnablePeerAccess a1 a2 =
let {a1' = cIntConv a1} in
let {a2' = combineBitMasks a2} in
cudaDeviceEnablePeerAccess'_ a1' a2' >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 381 "src/Foreign/CUDA/Runtime/Device.chs" #-}
{-# INLINEABLE remove #-}
remove :: Device -> IO ()
remove !dev = nothingIfOk =<< cudaDeviceDisablePeerAccess dev
{-# INLINE cudaDeviceDisablePeerAccess #-}
cudaDeviceDisablePeerAccess :: (Device) -> IO ((Status))
cudaDeviceDisablePeerAccess a1 =
let {a1' = cIntConv a1} in
cudaDeviceDisablePeerAccess'_ a1' >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 398 "src/Foreign/CUDA/Runtime/Device.chs" #-}
data Limit = Stacksize
| Printffifosize
| Mallocheapsize
| Devruntimesyncdepth
| Devruntimependinglaunchcount
deriving (Eq,Show)
instance Enum Limit where
succ Stacksize = Printffifosize
succ Printffifosize = Mallocheapsize
succ Mallocheapsize = Devruntimesyncdepth
succ Devruntimesyncdepth = Devruntimependinglaunchcount
succ Devruntimependinglaunchcount = error "Limit.succ: Devruntimependinglaunchcount has no successor"
pred Printffifosize = Stacksize
pred Mallocheapsize = Printffifosize
pred Devruntimesyncdepth = Mallocheapsize
pred Devruntimependinglaunchcount = Devruntimesyncdepth
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 Devruntimependinglaunchcount
fromEnum Stacksize = 0
fromEnum Printffifosize = 1
fromEnum Mallocheapsize = 2
fromEnum Devruntimesyncdepth = 3
fromEnum Devruntimependinglaunchcount = 4
toEnum 0 = Stacksize
toEnum 1 = Printffifosize
toEnum 2 = Mallocheapsize
toEnum 3 = Devruntimesyncdepth
toEnum 4 = Devruntimependinglaunchcount
toEnum unmatched = error ("Limit.toEnum: Cannot match " ++ show unmatched)
{-# LINE 414 "src/Foreign/CUDA/Runtime/Device.chs" #-}
{-# INLINEABLE getLimit #-}
getLimit :: Limit -> IO Int
getLimit !l = resultIfOk =<< cudaDeviceGetLimit l
{-# INLINE cudaDeviceGetLimit #-}
cudaDeviceGetLimit :: (Limit) -> IO ((Status), (Int))
cudaDeviceGetLimit a2 =
alloca $ \a1' ->
let {a2' = cFromEnum a2} in
cudaDeviceGetLimit'_ a1' a2' >>= \res ->
let {res' = cToEnum res} in
peekIntConv a1'>>= \a1'' ->
return (res', a1'')
{-# LINE 438 "src/Foreign/CUDA/Runtime/Device.chs" #-}
{-# INLINEABLE setLimit #-}
setLimit :: Limit -> Int -> IO ()
setLimit !l !n = nothingIfOk =<< cudaDeviceSetLimit l n
{-# INLINE cudaDeviceSetLimit #-}
cudaDeviceSetLimit :: (Limit) -> (Int) -> IO ((Status))
cudaDeviceSetLimit a1 a2 =
let {a1' = cFromEnum a1} in
let {a2' = cIntConv a2} in
cudaDeviceSetLimit'_ a1' a2' >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 462 "src/Foreign/CUDA/Runtime/Device.chs" #-}
foreign import ccall unsafe "Foreign/CUDA/Runtime/Device.chs.h cudaChooseDevice"
cudaChooseDevice'_ :: ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr (DeviceProperties)) -> (IO C2HSImp.CInt)))
foreign import ccall unsafe "Foreign/CUDA/Runtime/Device.chs.h cudaGetDevice"
cudaGetDevice'_ :: ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt))
foreign import ccall unsafe "Foreign/CUDA/Runtime/Device.chs.h cudaGetDeviceCount"
cudaGetDeviceCount'_ :: ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt))
foreign import ccall unsafe "Foreign/CUDA/Runtime/Device.chs.h cudaGetDeviceProperties"
cudaGetDeviceProperties'_ :: ((C2HSImp.Ptr (DeviceProperties)) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))
foreign import ccall unsafe "Foreign/CUDA/Runtime/Device.chs.h cudaSetDevice"
cudaSetDevice'_ :: (C2HSImp.CInt -> (IO C2HSImp.CInt))
foreign import ccall unsafe "Foreign/CUDA/Runtime/Device.chs.h cudaSetDeviceFlags"
cudaSetDeviceFlags'_ :: (C2HSImp.CUInt -> (IO C2HSImp.CInt))
foreign import ccall unsafe "Foreign/CUDA/Runtime/Device.chs.h cudaSetValidDevices"
cudaSetValidDevices'_ :: ((C2HSImp.Ptr C2HSImp.CInt) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))
foreign import ccall safe "Foreign/CUDA/Runtime/Device.chs.h cudaDeviceSynchronize"
cudaDeviceSynchronize'_ :: (IO C2HSImp.CInt)
foreign import ccall unsafe "Foreign/CUDA/Runtime/Device.chs.h cudaDeviceReset"
cudaDeviceReset'_ :: (IO C2HSImp.CInt)
foreign import ccall unsafe "Foreign/CUDA/Runtime/Device.chs.h cudaDeviceCanAccessPeer"
cudaDeviceCanAccessPeer'_ :: ((C2HSImp.Ptr C2HSImp.CInt) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CInt))))
foreign import ccall unsafe "Foreign/CUDA/Runtime/Device.chs.h cudaDeviceEnablePeerAccess"
cudaDeviceEnablePeerAccess'_ :: (C2HSImp.CInt -> (C2HSImp.CUInt -> (IO C2HSImp.CInt)))
foreign import ccall unsafe "Foreign/CUDA/Runtime/Device.chs.h cudaDeviceDisablePeerAccess"
cudaDeviceDisablePeerAccess'_ :: (C2HSImp.CInt -> (IO C2HSImp.CInt))
foreign import ccall unsafe "Foreign/CUDA/Runtime/Device.chs.h cudaDeviceGetLimit"
cudaDeviceGetLimit'_ :: ((C2HSImp.Ptr C2HSImp.CULong) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))
foreign import ccall unsafe "Foreign/CUDA/Runtime/Device.chs.h cudaDeviceSetLimit"
cudaDeviceSetLimit'_ :: (C2HSImp.CInt -> (C2HSImp.CULong -> (IO C2HSImp.CInt)))