wgpu-hs-0.4.0.0: WGPU
Safe HaskellNone
LanguageHaskell2010

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:

instance ToRaw ApiType WGPUApiType where
  raw ApiType{..} = do
    names_ptr <- rawArrayPtr names
    pure $ 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

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

Instances details
ToRaw Bool CBool Source # 
Instance details

Defined in WGPU.Internal.Memory

Methods

raw :: Bool -> ContT r IO CBool Source #

ToRaw Word32 Word32 Source # 
Instance details

Defined in WGPU.Internal.Memory

Methods

raw :: Word32 -> ContT r IO Word32 Source #

ToRaw ByteSize CSize Source # 
Instance details

Defined in WGPU.Internal.Memory

Methods

raw :: ByteSize -> ContT r IO CSize Source #

ToRaw Instance WGPUHsInstance Source # 
Instance details

Defined in WGPU.Internal.Instance

ToRaw CommandBuffer WGPUCommandBuffer Source # 
Instance details

Defined in WGPU.Internal.CommandBuffer

ToRaw Color WGPUColor Source # 
Instance details

Defined in WGPU.Internal.Color

Methods

raw :: Color -> ContT r IO WGPUColor Source #

ToRaw IndexFormat WGPUIndexFormat Source #

Convert an IndexFormat to its raw value.

Instance details

Defined in WGPU.Internal.Multipurpose

ToRaw TextureDataLayout WGPUTextureDataLayout Source # 
Instance details

Defined in WGPU.Internal.Multipurpose

ToRaw ImageCopyTexture WGPUImageCopyTexture Source # 
Instance details

Defined in WGPU.Internal.Multipurpose

ToRaw TextureAspect WGPUTextureAspect Source # 
Instance details

Defined in WGPU.Internal.Multipurpose

ToRaw Extent3D WGPUExtent3D Source # 
Instance details

Defined in WGPU.Internal.Multipurpose

ToRaw Origin3D WGPUOrigin3D Source # 
Instance details

Defined in WGPU.Internal.Multipurpose

ToRaw CompareFunction WGPUCompareFunction Source #

Convert a CompareFunction to its raw value.

Instance details

Defined in WGPU.Internal.Multipurpose

ToRaw Texture WGPUTexture Source # 
Instance details

Defined in WGPU.Internal.Multipurpose

ToRaw Surface WGPUSurface Source # 
Instance details

Defined in WGPU.Internal.Surface

ToRaw AdapterProperties WGPUAdapterProperties Source # 
Instance details

Defined in WGPU.Internal.Adapter

ToRaw BackendType WGPUBackendType Source # 
Instance details

Defined in WGPU.Internal.Adapter

ToRaw AdapterType WGPUAdapterType Source # 
Instance details

Defined in WGPU.Internal.Adapter

ToRaw Adapter WGPUAdapter Source # 
Instance details

Defined in WGPU.Internal.Adapter

ToRaw DeviceDescriptor WGPUDeviceExtras Source # 
Instance details

Defined in WGPU.Internal.Device

ToRaw Features WGPUNativeFeature Source # 
Instance details

Defined in WGPU.Internal.Device

ToRaw Device WGPUDevice Source # 
Instance details

Defined in WGPU.Internal.Device

ToRaw WGSL WGPUShaderModuleWGSLDescriptor Source # 
Instance details

Defined in WGPU.Internal.Shader

ToRaw SPIRV WGPUShaderModuleSPIRVDescriptor Source # 
Instance details

Defined in WGPU.Internal.Shader

ToRaw ShaderModuleDescriptor WGPUShaderModuleDescriptor Source # 
Instance details

Defined in WGPU.Internal.Shader

ToRaw ShaderModule WGPUShaderModule Source # 
Instance details

Defined in WGPU.Internal.Shader

ToRaw SamplerDescriptor WGPUSamplerDescriptor Source # 
Instance details

Defined in WGPU.Internal.Sampler

ToRaw FilterMode WGPUFilterMode Source # 
Instance details

Defined in WGPU.Internal.Sampler

ToRaw AddressMode WGPUAddressMode Source # 
Instance details

Defined in WGPU.Internal.Sampler

ToRaw Sampler WGPUSampler Source # 
Instance details

Defined in WGPU.Internal.Sampler

ToRaw CommandEncoder WGPUCommandEncoder Source # 
Instance details

Defined in WGPU.Internal.CommandEncoder

ToRaw BufferDescriptor WGPUBufferDescriptor Source # 
Instance details

Defined in WGPU.Internal.Buffer

ToRaw BufferUsage Word32 Source # 
Instance details

Defined in WGPU.Internal.Buffer

ToRaw Buffer WGPUBuffer Source # 
Instance details

Defined in WGPU.Internal.Buffer

ToRaw Queue WGPUQueue Source # 
Instance details

Defined in WGPU.Internal.Queue

Methods

raw :: Queue -> ContT r IO WGPUQueue Source #

ToRaw TextureViewDescriptor WGPUTextureViewDescriptor Source # 
Instance details

Defined in WGPU.Internal.Texture

ToRaw TextureDescriptor WGPUTextureDescriptor Source # 
Instance details

Defined in WGPU.Internal.Texture

ToRaw TextureDimension WGPUTextureDimension Source # 
Instance details

Defined in WGPU.Internal.Texture

ToRaw TextureFormat WGPUTextureFormat Source # 
Instance details

Defined in WGPU.Internal.Texture

ToRaw TextureUsage WGPUTextureUsageFlags Source # 
Instance details

Defined in WGPU.Internal.Texture

ToRaw TextureViewDimension WGPUTextureViewDimension Source # 
Instance details

Defined in WGPU.Internal.Texture

ToRaw TextureView WGPUTextureView Source # 
Instance details

Defined in WGPU.Internal.Texture

ToRaw PresentMode WGPUPresentMode Source # 
Instance details

Defined in WGPU.Internal.SwapChain

ToRaw SwapChainDescriptor WGPUSwapChainDescriptor Source # 
Instance details

Defined in WGPU.Internal.SwapChain

ToRaw SwapChain WGPUSwapChain Source # 
Instance details

Defined in WGPU.Internal.SwapChain

ToRaw BufferBindingType WGPUBufferBindingType Source # 
Instance details

Defined in WGPU.Internal.Binding

ToRaw TextureSampleType WGPUTextureSampleType Source # 
Instance details

Defined in WGPU.Internal.Binding

ToRaw StorageTextureAccess WGPUStorageTextureAccess Source # 
Instance details

Defined in WGPU.Internal.Binding

ToRaw StorageTextureBindingLayout WGPUStorageTextureBindingLayout Source # 
Instance details

Defined in WGPU.Internal.Binding

ToRaw TextureBindingLayout WGPUTextureBindingLayout Source # 
Instance details

Defined in WGPU.Internal.Binding

ToRaw SamplerBindingLayout WGPUSamplerBindingLayout Source # 
Instance details

Defined in WGPU.Internal.Binding

ToRaw BufferBindingLayout WGPUBufferBindingLayout Source # 
Instance details

Defined in WGPU.Internal.Binding

ToRaw ShaderStage WGPUShaderStageFlags Source # 
Instance details

Defined in WGPU.Internal.Binding

ToRaw Binding Word32 Source # 
Instance details

Defined in WGPU.Internal.Binding

Methods

raw :: Binding -> ContT r IO Word32 Source #

ToRaw BindGroupLayoutEntry WGPUBindGroupLayoutEntry Source # 
Instance details

Defined in WGPU.Internal.Binding

ToRaw BindGroupLayoutDescriptor WGPUBindGroupLayoutDescriptor Source # 
Instance details

Defined in WGPU.Internal.Binding

ToRaw BindGroupEntry WGPUBindGroupEntry Source # 
Instance details

Defined in WGPU.Internal.Binding

ToRaw BindGroupDescriptor WGPUBindGroupDescriptor Source # 
Instance details

Defined in WGPU.Internal.Binding

ToRaw BindGroupLayout WGPUBindGroupLayout Source # 
Instance details

Defined in WGPU.Internal.Binding

ToRaw BindGroup WGPUBindGroup Source # 
Instance details

Defined in WGPU.Internal.Binding

ToRaw RenderPassDescriptor WGPURenderPassDescriptor Source # 
Instance details

Defined in WGPU.Internal.RenderPass

ToRaw RenderPassDepthStencilAttachment WGPURenderPassDepthStencilAttachment Source # 
Instance details

Defined in WGPU.Internal.RenderPass

ToRaw RenderPassColorAttachment WGPURenderPassColorAttachment Source # 
Instance details

Defined in WGPU.Internal.RenderPass

ToRaw StoreOp WGPUStoreOp Source # 
Instance details

Defined in WGPU.Internal.RenderPass

ToRaw RenderPassEncoder WGPURenderPassEncoder Source # 
Instance details

Defined in WGPU.Internal.RenderPass

ToRaw RenderPipeline WGPURenderPipeline Source # 
Instance details

Defined in WGPU.Internal.RenderPass

ToRaw RenderPipelineDescriptor WGPURenderPipelineDescriptor Source # 
Instance details

Defined in WGPU.Internal.Pipeline

ToRaw FragmentState WGPUFragmentState Source # 
Instance details

Defined in WGPU.Internal.Pipeline

ToRaw ColorTargetState WGPUColorTargetState Source # 
Instance details

Defined in WGPU.Internal.Pipeline

ToRaw ColorWriteMask WGPUColorWriteMask Source # 
Instance details

Defined in WGPU.Internal.Pipeline

ToRaw BlendState WGPUBlendState Source # 
Instance details

Defined in WGPU.Internal.Pipeline

ToRaw BlendComponent WGPUBlendComponent Source # 
Instance details

Defined in WGPU.Internal.Pipeline

ToRaw BlendOperation WGPUBlendOperation Source #

Convert a BlendOperation to its raw value.

Instance details

Defined in WGPU.Internal.Pipeline

ToRaw BlendFactor WGPUBlendFactor Source #

Convert a BlendFactor to its raw value.

Instance details

Defined in WGPU.Internal.Pipeline

ToRaw MultisampleState WGPUMultisampleState Source # 
Instance details

Defined in WGPU.Internal.Pipeline

ToRaw DepthStencilState WGPUDepthStencilState Source # 
Instance details

Defined in WGPU.Internal.Pipeline

ToRaw StencilFaceState WGPUStencilFaceState Source # 
Instance details

Defined in WGPU.Internal.Pipeline

ToRaw StencilOperation WGPUStencilOperation Source #

Convert a StencilOperation to its raw value.

Instance details

Defined in WGPU.Internal.Pipeline

ToRaw PrimitiveState WGPUPrimitiveState Source # 
Instance details

Defined in WGPU.Internal.Pipeline

ToRaw CullMode WGPUCullMode Source #

Convert a CullMode to its raw value.

Instance details

Defined in WGPU.Internal.Pipeline

ToRaw FrontFace WGPUFrontFace Source #

Convert a FrontFace to its raw value.

Instance details

Defined in WGPU.Internal.Pipeline

ToRaw PrimitiveTopology WGPUPrimitiveTopology Source #

Convert a PrimitiveTopology to its raw value.

Instance details

Defined in WGPU.Internal.Pipeline

ToRaw VertexState WGPUVertexState Source # 
Instance details

Defined in WGPU.Internal.Pipeline

ToRaw VertexBufferLayout WGPUVertexBufferLayout Source # 
Instance details

Defined in WGPU.Internal.Pipeline

ToRaw InputStepMode WGPUInputStepMode Source #

Convert an InputStepMode to its raw value.

Instance details

Defined in WGPU.Internal.Pipeline

ToRaw VertexAttribute WGPUVertexAttribute Source # 
Instance details

Defined in WGPU.Internal.Pipeline

ToRaw VertexFormat WGPUVertexFormat Source #

Convert a VertexFormat to its raw representation.

Instance details

Defined in WGPU.Internal.Pipeline

ToRaw PipelineLayoutDescriptor WGPUPipelineLayoutDescriptor Source # 
Instance details

Defined in WGPU.Internal.Pipeline

ToRaw PipelineLayout WGPUPipelineLayout Source # 
Instance details

Defined in WGPU.Internal.Pipeline

ToRaw (ChainedStruct a) WGPUChainedStruct Source # 
Instance details

Defined in WGPU.Internal.ChainedStruct

class FromRaw b a | a -> b where Source #

Represents a type a that can be read from a raw value b.

Methods

fromRaw :: MonadIO m => b -> m a 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 (Ptr b) around the continuation. In particular, the memory allocated for (Ptr b) must be allocated before the continuation is called, and freed afterward.

Methods

rawPtr :: a -> ContT r IO (Ptr b) Source #

Instances

Instances details
(Storable b, ToRaw a b) => ToRawPtr a b Source # 
Instance details

Defined in WGPU.Internal.Memory

Methods

rawPtr :: a -> ContT r IO (Ptr b) Source #

ToRawPtr ByteString Word8 Source # 
Instance details

Defined in WGPU.Internal.Memory

ToRawPtr Text CChar Source # 
Instance details

Defined in WGPU.Internal.Memory

Methods

rawPtr :: Text -> ContT r IO (Ptr CChar) Source #

ToRawPtr ShaderEntryPoint CChar Source # 
Instance details

Defined in WGPU.Internal.Shader

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

Instances details
(Storable b, FromRaw b a) => FromRawPtr b a Source # 
Instance details

Defined in WGPU.Internal.Memory

Methods

fromRawPtr :: MonadIO m => Ptr b -> m a Source #

class ReadableMemoryBuffer a where Source #

Region of memory that is read-only for WGPU.

A ReadableMemoryBuffer represents a contiguous region of memory that WGPU may read from, but not write to. It has a pointer to the start of the region, and a size in bytes.

When the caller of WGPU supplies a ReadableMemoryBuffer, it commits to keeping the buffer alive for the period of the call to withReadablePtr. WGPU commits to not mutating the data.

If it is necessary to refer to slices within a buffer, it is up to the type a to store those offsets and account for them in the two functions required by the API. (For example, Vector does this.)

Methods

withReadablePtr :: a -> (Ptr () -> IO b) -> IO b Source #

Perform an action with the memory buffer.

readableMemoryBufferSize :: a -> ByteSize Source #

The size of the buffer, in number of bytes.

Instances

Instances details
Storable a => ReadableMemoryBuffer a Source # 
Instance details

Defined in WGPU.Internal.Memory

Methods

withReadablePtr :: a -> (Ptr () -> IO b) -> IO b Source #

readableMemoryBufferSize :: a -> ByteSize Source #

Storable a => ReadableMemoryBuffer (Vector a) Source # 
Instance details

Defined in WGPU.Internal.Memory

Types

newtype ByteSize Source #

Size, in number of bytes.

Constructors

ByteSize 

Fields

Instances

Instances details
Enum ByteSize Source # 
Instance details

Defined in WGPU.Internal.Memory

Eq ByteSize Source # 
Instance details

Defined in WGPU.Internal.Memory

Integral ByteSize Source # 
Instance details

Defined in WGPU.Internal.Memory

Num ByteSize Source # 
Instance details

Defined in WGPU.Internal.Memory

Ord ByteSize Source # 
Instance details

Defined in WGPU.Internal.Memory

Real ByteSize Source # 
Instance details

Defined in WGPU.Internal.Memory

Show ByteSize Source # 
Instance details

Defined in WGPU.Internal.Memory

ToRaw ByteSize CSize Source # 
Instance details

Defined in WGPU.Internal.Memory

Methods

raw :: ByteSize -> ContT r IO CSize Source #

Functions

Internal

evalContT :: Monad m => ContT a m a -> m a Source #

rawArrayPtr Source #

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.

showWithPtr Source #

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

takeMVar :: MonadIO m => MVar a -> m a Source #

putMVar :: MonadIO m => MVar a -> a -> m () Source #

poke :: (MonadIO m, Storable a) => Ptr a -> a -> m () Source #