{-# LANGUAGE BangPatterns #-} {-# LANGUAGE CPP #-} {-# LANGUAGE EmptyDataDecls #-} {-# LANGUAGE ForeignFunctionInterface #-} {-# LANGUAGE TemplateHaskell #-} #ifdef USE_EMPTY_CASE {-# LANGUAGE EmptyCase #-} #endif -------------------------------------------------------------------------------- -- | -- Module : Foreign.CUDA.Driver.Context.Peer -- Copyright : [2009..2015] Trevor L. McDonell -- License : BSD -- -- Direct peer context access functions for the low-level driver interface. -- -- Since: CUDA-4.0 -- -------------------------------------------------------------------------------- module Foreign.CUDA.Driver.Context.Peer ( -- * Peer Access PeerFlag, accessible, add, remove, ) where #include "cbits/stubs.h" {# context lib="cuda" #} -- Friends import Foreign.CUDA.Driver.Context.Base ( Context(..) ) import Foreign.CUDA.Driver.Device ( Device(..) ) import Foreign.CUDA.Driver.Error import Foreign.CUDA.Internal.C2HS -- System import Foreign import Foreign.C -------------------------------------------------------------------------------- -- Data Types -------------------------------------------------------------------------------- -- | -- Possible option values for direct peer memory access -- data PeerFlag instance Enum PeerFlag where #ifdef USE_EMPTY_CASE toEnum x = case x of {} fromEnum x = case x of {} #endif -------------------------------------------------------------------------------- -- Peer access -------------------------------------------------------------------------------- -- | -- Queries if the first device can directly access the memory of the second. If -- direct access is possible, it can then be enabled with 'add'. -- -- Requires CUDA-4.0. -- -- -- {-# INLINEABLE accessible #-} accessible :: Device -> Device -> IO Bool #if CUDA_VERSION < 4000 accessible _ _ = requireSDK 'accessible 4.0 #else accessible !dev !peer = resultIfOk =<< cuDeviceCanAccessPeer dev peer {-# INLINE cuDeviceCanAccessPeer #-} {# fun unsafe cuDeviceCanAccessPeer { alloca- `Bool' peekBool* , useDevice `Device' , useDevice `Device' } -> `Status' cToEnum #} #endif -- | -- If the devices of both the current and supplied contexts support unified -- addressing, then enable allocations in the supplied context to be accessible -- by the current context. -- -- Note that access is unidirectional, and in order to access memory in the -- current context from the peer context, a separate symmetric call to -- 'add' is required. -- -- Requires CUDA-4.0. -- -- -- {-# INLINEABLE add #-} add :: Context -> [PeerFlag] -> IO () #if CUDA_VERSION < 4000 add _ _ = requireSDK 'add 4.0 #else add !ctx !flags = nothingIfOk =<< cuCtxEnablePeerAccess ctx flags {-# INLINE cuCtxEnablePeerAccess #-} {# fun unsafe cuCtxEnablePeerAccess { useContext `Context' , combineBitMasks `[PeerFlag]' } -> `Status' cToEnum #} #endif -- | -- Disable direct memory access from the current context to the supplied -- peer context, and unregisters any registered allocations. -- -- Requires CUDA-4.0. -- -- -- {-# INLINEABLE remove #-} remove :: Context -> IO () #if CUDA_VERSION < 4000 remove _ = requireSDK 'remave 4.0 #else remove !ctx = nothingIfOk =<< cuCtxDisablePeerAccess ctx {-# INLINE cuCtxDisablePeerAccess #-} {# fun unsafe cuCtxDisablePeerAccess { useContext `Context' } -> `Status' cToEnum #} #endif