Copyright | [2016..2017] Trevor L. McDonell |
---|---|
License | BSD3 |
Maintainer | Trevor L. McDonell <tmcdonell@cse.unsw.edu.au> |
Stability | experimental |
Portability | non-portable (GHC extensions) |
Safe Haskell | None |
Language | Haskell2010 |
- data ForeignAcc f where
- ForeignAcc :: String -> (Stream -> a -> LLVM PTX b) -> ForeignAcc (a -> b)
- data ForeignExp f where
- ForeignExp :: String -> IRFun1 PTX () (x -> y) -> ForeignExp (x -> y)
- data LLVM target a :: * -> * -> *
- data PTX = PTX {
- ptxContext :: !Context
- ptxMemoryTable :: !MemoryTable
- ptxKernelTable :: !KernelTable
- ptxStreamReservoir :: !Reservoir
- fillP :: !Executable
- data Context = Context {
- deviceProperties :: !DeviceProperties
- deviceContext :: !(Lifetime Context)
- liftIO :: MonadIO m => forall a. IO a -> m a
- withDevicePtr :: (ArrayElt e, ArrayPtrs e ~ Ptr a, Typeable e, Typeable a, Storable a) => ArrayData e -> (DevicePtr a -> LLVM PTX (Maybe Event, r)) -> LLVM PTX r
- module Data.Array.Accelerate.LLVM.Array.Data
- copyToHostLazy :: Arrays arrs => arrs -> LLVM PTX arrs
- cloneArrayAsync :: (Shape sh, Elt e) => Stream -> Array sh e -> LLVM PTX (Array sh e)
- type Async a = AsyncR PTX a
- type Stream = Lifetime Stream
- type Event = Lifetime Event
- module Data.Array.Accelerate.LLVM.Execute.Async
Documentation
data ForeignAcc f where Source #
ForeignAcc :: String -> (Stream -> a -> LLVM PTX b) -> ForeignAcc (a -> b) |
Foreign ForeignAcc Source # | |
data ForeignExp f where Source #
ForeignExp :: String -> IRFun1 PTX () (x -> y) -> ForeignExp (x -> y) |
Foreign ForeignExp Source # | |
data LLVM target a :: * -> * -> * #
The LLVM monad, for executing array computations. This consists of a stack
for the LLVM execution context as well as the per-execution target specific
state target
.
MonadState target (LLVM target) | |
Execute arch => ExecuteAfun arch (LLVM arch b) | |
Monad (LLVM target) | |
Functor (LLVM target) | |
Applicative (LLVM target) | |
MonadIO (LLVM target) | |
MonadThrow (LLVM target) | |
MonadCatch (LLVM target) | |
MonadMask (LLVM target) | |
type ExecAfunR arch (LLVM arch b) | |
type RemotePtr (LLVM PTX) | |
The PTX execution target for NVIDIA GPUs.
The execution target carries state specific for the current execution context. The data here --- device memory and execution streams --- are implicitly tied to this CUDA execution context.
Don't store anything here that is independent of the context, for example state related to [persistent] kernel caching should _not_ go here.
PTX | |
|
An execution context, which is tied to a specific device and CUDA execution context.
Context | |
|
withDevicePtr :: (ArrayElt e, ArrayPtrs e ~ Ptr a, Typeable e, Typeable a, Storable a) => ArrayData e -> (DevicePtr a -> LLVM PTX (Maybe Event, r)) -> LLVM PTX r Source #
Lookup the device memory associated with a given host array and do something with it.
copyToHostLazy :: Arrays arrs => arrs -> LLVM PTX arrs Source #
Copy an array from the remote device to the host. Although the Accelerate program is hyper-strict and will evaluate the computation as soon as any part of it is demanded, the individual array payloads are copied back to the host _only_ as they are demanded by the Haskell program. This has several consequences:
- If the device has multiple memcpy engines, only one will be used. The transfers are however associated with a non-default stream.
- Using
seq
to force an Array to head-normal form will initiate the computation, but not transfer the results back to the host. Requesting an array element or usingdeepseq
to force to normal form is required to actually transfer the data.
cloneArrayAsync :: (Shape sh, Elt e) => Stream -> Array sh e -> LLVM PTX (Array sh e) Source #
Clone an array into a newly allocated array on the device.
type Event = Lifetime Event Source #
Events can be used for efficient device-side synchronisation between execution streams and between the host.