-- GENERATED by C->Haskell Compiler, version 0.28.2 Switcheroo, 1 April 2016 (Haskell) -- Edit the ORIGNAL .chs file instead! {-# LINE 1 "src/Foreign/CUDA/Driver/IPC/Event.chs" #-} {-# LANGUAGE BangPatterns #-} {-# LANGUAGE CPP #-} {-# LANGUAGE ForeignFunctionInterface #-} {-# LANGUAGE TemplateHaskell #-} -------------------------------------------------------------------------------- -- | -- Module : Foreign.CUDA.Driver.IPC.Event -- Copyright : [2009..2017] Trevor L. McDonell -- License : BSD -- -- IPC event management for low-level driver interface. -- -- Restricted to devices which support unified addressing on Linux -- operating systems. -- -- Since CUDA-4.1. -- -------------------------------------------------------------------------------- module Foreign.CUDA.Driver.IPC.Event ( IPCEvent, export, open, ) where import qualified Foreign.C.Types as C2HSImp import qualified Foreign.Ptr as C2HSImp {-# LINE 28 "src/Foreign/CUDA/Driver/IPC/Event.chs" #-} -- Friends import Foreign.CUDA.Driver.Error import Foreign.CUDA.Driver.Event import Foreign.CUDA.Internal.C2HS -- System import Control.Monad import Prelude import Foreign.C import Foreign.Ptr import Foreign.ForeignPtr import Foreign.Marshal import Foreign.Storable -------------------------------------------------------------------------------- -- Data Types -------------------------------------------------------------------------------- -- | -- A CUDA inter-process event handle. -- newtype IPCEvent = IPCEvent { useIPCEvent :: IPCEventHandle } deriving (Eq, Show) -------------------------------------------------------------------------------- -- IPC event management -------------------------------------------------------------------------------- -- | -- Create an inter-process event handle for a previously allocated event. -- The event must be created with the 'Interprocess' and 'DisableTiming' -- event flags. The returned handle may then be sent to another process and -- 'open'ed to allow efficient hardware synchronisation between GPU work in -- other processes. -- -- After the event has been opened in the importing process, 'record', -- 'block', 'wait', 'query' may be used in either process. -- -- Performing operations on the imported event after the event has been -- 'destroy'ed in the exporting process is undefined. -- -- Requires CUDA-4.0. -- -- <http://docs.nvidia.com/cuda/cuda-driver-api/group__CUDA__MEM.html#group__CUDA__MEM_1gea02eadd12483de5305878b13288a86c> -- {-# INLINEABLE export #-} export :: Event -> IO IPCEvent export !ev = do h <- newIPCEventHandle r <- cuIpcGetEventHandle h ev resultIfOk (r, IPCEvent h) {-# INLINE cuIpcGetEventHandle #-} cuIpcGetEventHandle :: (IPCEventHandle) -> (Event) -> IO ((Status)) cuIpcGetEventHandle a1 a2 = withForeignPtr a1 $ \a1' -> let {a2' = useEvent a2} in cuIpcGetEventHandle'_ a1' a2' >>= \res -> let {res' = cToEnum res} in return (res') {-# LINE 94 "src/Foreign/CUDA/Driver/IPC/Event.chs" #-} -- | -- Open an inter-process event handle for use in the current process, -- returning an event that can be used in the current process and behaving -- as a locally created event with the 'DisableTiming' flag specified. -- -- The event must be freed with 'destroy'. Performing operations on the -- imported event after the exported event has been 'destroy'ed in the -- exporting process is undefined. -- -- Requires CUDA-4.0. -- -- <http://docs.nvidia.com/cuda/cuda-driver-api/group__CUDA__MEM.html#group__CUDA__MEM_1gf1d525918b6c643b99ca8c8e42e36c2e> -- {-# INLINEABLE open #-} open :: IPCEvent -> IO Event open !ev = resultIfOk =<< cuIpcOpenEventHandle (useIPCEvent ev) {-# INLINE cuIpcOpenEventHandle #-} cuIpcOpenEventHandle :: (IPCEventHandle) -> IO ((Status), (Event)) cuIpcOpenEventHandle a2 = alloca $ \a1' -> withForeignPtr a2 $ \a2' -> cuIpcOpenEventHandle'_ a1' a2' >>= \res -> let {res' = cToEnum res} in peekEvent a1'>>= \a1'' -> return (res', a1'') {-# LINE 122 "src/Foreign/CUDA/Driver/IPC/Event.chs" #-} where peekEvent = liftM Event . peek -------------------------------------------------------------------------------- -- Internal -------------------------------------------------------------------------------- type IPCEventHandle = ForeignPtr () newIPCEventHandle :: IO IPCEventHandle newIPCEventHandle = mallocForeignPtrBytes 64 {-# LINE 139 "src/Foreign/CUDA/Driver/IPC/Event.chs" #-} foreign import ccall unsafe "Foreign/CUDA/Driver/IPC/Event.chs.h cuIpcGetEventHandle" cuIpcGetEventHandle'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))) foreign import ccall unsafe "Foreign/CUDA/Driver/IPC/Event.chs.h cuIpcOpenEventHandle" cuIpcOpenEventHandle'_ :: ((C2HSImp.Ptr (C2HSImp.Ptr ())) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))