| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
WGPU.Internal.Memory
Description
This module contains type classes used to manage marshalling of objects into memory before calling C functions.
Motivation
In many locations in the API, we have:
A type (example only) which contains a nice Haskell representation of some data:
data ApiType = ApiType { things :: Vector Thing }
and a raw type which is required for a C function:
data WGPUApiType = WGPUApiType
{ thingsCount :: Word8, -- this is an array length
things :: Ptr WGPUApiThing -- this is a pointer to an array
}
This type class constraint represents the ability to encode ApiType as
WGPUApiType, performing any necessary memory allocation and freeing:
ToRaw ApiType WGPUApiType
ToRaw uses the ContT monad so that bracketing of the memory resources
can be performed around some continuation that uses the memory.
In the example above, we could write a ToRaw instance as follows:
instanceToRawApiType WGPUApiType whererawApiType{..} = do names_ptr <-rawArrayPtrnamespure$ WGPUApiType { namesCount = fromIntegral . length $ names, names = names_ptr }
The ToRawPtr type class represents similar functionality, except that it
creates a pointer to a value. Thus it does both raw conversion and storing
the raw value in allocated memory. It exists as a separate type class so
that library types (eg. Text and ByteString) can be marshalled into
pointers more easily.
Synopsis
- class ToRaw a b | a -> b where
- class FromRaw b a | a -> b where
- class ToRawPtr a b where
- class FromRawPtr b a where
- fromRawPtr :: MonadIO m => Ptr b -> m a
- evalContT :: Monad m => ContT a m a -> m a
- allocaC :: Storable a => ContT r IO (Ptr a)
- rawArrayPtr :: forall v r a b. (ToRaw a b, Storable b, Vector v a) => v a -> ContT r IO (Ptr b)
- showWithPtr :: String -> Ptr a -> String
- withCZeroingAfter :: Storable a => a -> ContT r IO (Ptr a)
- newEmptyMVar :: MonadIO m => m (MVar a)
- takeMVar :: MonadIO m => MVar a -> m a
- putMVar :: MonadIO m => MVar a -> a -> m ()
- freeHaskellFunPtr :: MonadIO m => FunPtr a -> m ()
- poke :: (MonadIO m, Storable a) => Ptr a -> a -> m ()
Classes
class ToRaw a b | a -> b where Source #
Represents a value of type a that can be stored as type b in the
ContT monad.
Implementations of this type class should bracket any resource management for
creating the b value around the continuation. For example. memory to hold
elements of b should be allocated and freed in a bracketed fashion.
Methods
raw :: a -> ContT r IO b Source #
Convert a value to a raw representation, bracketing any resource management.
Instances
class FromRaw b a | a -> b where Source #
Represents a type a that can be read from a raw value b.
Instances
| FromRaw WGPUAdapterProperties AdapterProperties Source # | |
Defined in WGPU.Internal.Adapter Methods fromRaw :: MonadIO m => WGPUAdapterProperties -> m AdapterProperties Source # | |
| FromRaw WGPUBackendType BackendType Source # | |
Defined in WGPU.Internal.Adapter Methods fromRaw :: MonadIO m => WGPUBackendType -> m BackendType Source # | |
| FromRaw WGPUAdapterType AdapterType Source # | |
Defined in WGPU.Internal.Adapter Methods fromRaw :: MonadIO m => WGPUAdapterType -> m AdapterType Source # | |
| FromRaw (Ptr CChar) Text Source # | |
class ToRawPtr a b where Source #
Represents a value of type a that can be stored as type (Ptr b) in the
ContT monad.
Implementations of this type class should bracket resource management for
creating ( around the continuation. In particular, the memory
allocated for Ptr b)( must be allocated before the continuation is
called, and freed afterward.Ptr b)
class FromRawPtr b a where Source #
Represents a type a that can be read from a raw pointer b.
Methods
fromRawPtr :: MonadIO m => Ptr b -> m a Source #
Instances
| (Storable b, FromRaw b a) => FromRawPtr b a Source # | |
Defined in WGPU.Internal.Memory Methods fromRawPtr :: MonadIO m => Ptr b -> m a Source # | |
Functions
Internal
Arguments
| :: forall v r a b. (ToRaw a b, Storable b, Vector v a) | |
| => v a | Vector of values to store in a C array. |
| -> ContT r IO (Ptr b) | Pointer to the array with raw values stored in it. |
Return a pointer to an allocated array, populated with raw values from a vector.
Arguments
| :: String | Name of the type. |
| -> Ptr a | Opaque pointer that the type contains. |
| -> String | Final show string. |
Formatter for Show instances for opaque pointers.
Displays a name and a corresponding opaque pointer.
Lifted to MonadIO
newEmptyMVar :: MonadIO m => m (MVar a) Source #
freeHaskellFunPtr :: MonadIO m => FunPtr a -> m () Source #