- data Buffer a
- castBuffer :: Buffer a -> Buffer b
- bufferSize :: forall e. Storable e => Buffer e -> Int
- mallocBuffer :: forall a m. (Storable a, MonadQueue m) => MemAccessFlag -> MemInitFlag a -> Int -> m (Buffer a)
- freeBuffer :: MonadIO m => Buffer a -> m ()
- allocaBuffer :: (Storable a, MonadQueue m) => MemAccessFlag -> MemInitFlag a -> Int -> (Buffer a -> m b) -> m b
- class CopyTo a b where
- class BufferLike b where
- data Slice e
- slice :: Storable e => BufferLike b => Int -> Int -> b e -> Slice e
- sizeS :: Slice e -> Int
- data SlicedPtr a = SlicedPtr {}
- copyToVector :: (Storable e, MonadQueue m, BufferLike b) => b e -> m (Vector e)
- data IsBlocking
- = Blocking
- | NonBlocking
- readBuffer :: forall a. Storable a => Buffer a -> IsBlocking -> Int -> Int -> Ptr a -> Command
- writeBuffer :: forall a. Storable a => Buffer a -> IsBlocking -> Int -> Int -> Ptr a -> Command
- copyBuffer :: forall a. Storable a => Buffer a -> Buffer a -> Int -> Int -> Int -> Command
- class MemObject m
- data MemAccessFlag
- data MemInitFlag a
- = NoHostPtr
- | UseHostPtr (Ptr a)
- | CopyHostPtr (Ptr a)
- | AllocHostPtr
- | CopyAllocHostPtr (Ptr a)
- memFlags :: MemObject m => m -> (MemAccessFlag, MemInitFlag a)
- memSize :: MemObject m => m -> Int
- memContext :: MemObject m => m -> Context
Buffers
data Buffer a
A region of memory on an OpenCL device.
castBuffer :: Buffer a -> Buffer b
bufferSize :: forall e. Storable e => Buffer e -> Int
Number of elements in the buffer.
:: forall a m . (Storable a, MonadQueue m) | |
=> MemAccessFlag | |
-> MemInitFlag a | |
-> Int | The number of elements in the buffer. |
-> m (Buffer a) |
Allocate memory on the device associated with this queue. The returned Buffer
must later be released with freeBuffer
.
freeBuffer :: MonadIO m => Buffer a -> m ()
:: (Storable a, MonadQueue m) | |
=> MemAccessFlag | |
-> MemInitFlag a | |
-> Int | The number of elements in the buffer. |
-> (Buffer a -> m b) | |
-> m b |
Reading, writing and copying
class CopyTo a b where
Reads, writes and copies between device and host memory can all be performed using
the CopyTo
class.
For example, if a :: Buffer Float
and c :: Ptr Float
, then waitForCommand (a := c)
copies bufferSize a
elements (i.e., Float
s) from c
to a
.
This class can also be used to copy to/from subregions of device memory. For example,
waitForCommand (slice 2 10 a =: slice 0 10 b)
copies the first 10 elements of b
into
indices [2..11]
of a
.
All CopyTo
operations are unblocking. As a result, when QueueOutOfOrderExecModeEnable
has been set, the runtime may copy data simultaneously or out of order from other
Command
s.
The module System.HsOpenCL.Instances.CArray exports instances for copying to and from
CArray
s, which may be more convenient to use than pointers.
(=:) :: Storable e => a e -> b e -> Command
A copy between host and device memory, or between two device memory objects.
BufferLike b => CopyTo Ptr b | |
BufferLike b => CopyTo b Vector | |
BufferLike b => CopyTo b IOVector | |
BufferLike b => CopyTo b SlicedPtr | |
(BufferLike b1, BufferLike b2) => CopyTo b1 b2 | |
BufferLike b => CopyTo b Ptr | |
BufferLike b => CopyTo IOVector b | |
BufferLike b => CopyTo SlicedPtr b |
class BufferLike b where
data SlicedPtr a
A slice of the data contained in a ForeignPtr. The CopyTo
instance for this type
ensures that the ForeignPtr
will be retained until the copy has completed.
An error will be thrown when copying between a SlicedPtr and a Buffer of unequal sizes.
BufferLike b => CopyTo b SlicedPtr | |
BufferLike b => CopyTo SlicedPtr b |
copyToVector :: (Storable e, MonadQueue m, BufferLike b) => b e -> m (Vector e)
Buffer operations
This section provides an API for buffer operations which is closer to the actual OpenCL API.
Properties
data MemInitFlag a
NoHostPtr | |
UseHostPtr (Ptr a) | |
CopyHostPtr (Ptr a) | |
AllocHostPtr | |
CopyAllocHostPtr (Ptr a) |
Eq (MemInitFlag a) | |
Show (MemInitFlag a) |
memFlags :: MemObject m => m -> (MemAccessFlag, MemInitFlag a)
memContext :: MemObject m => m -> Context