| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
WGPU.Internal.RenderPass
Description
Synopsis
- newtype RenderPipeline = RenderPipeline {}
- data RenderPassEncoder
- data LoadOp a
- = LoadOpClear !a
- | LoadOpLoad
- data StoreOp
- data Operations a = Operations {}
- data RenderPassColorAttachment = RenderPassColorAttachment {
- colorView :: !TextureView
- resolveTarget :: !(SMaybe TextureView)
- operations :: !(Operations Color)
- data RenderPassDepthStencilAttachment = RenderPassDepthStencilAttachment {
- depthStencilView :: !TextureView
- depthOps :: !(SMaybe (Operations Float))
- stencilOps :: !(SMaybe (Operations Word32))
- data RenderPassDescriptor = RenderPassDescriptor {}
- data Range a = Range {
- rangeStart :: !a
- rangeLength :: !a
- beginRenderPass :: MonadIO m => CommandEncoder -> RenderPassDescriptor -> m RenderPassEncoder
- renderPassSetPipeline :: MonadIO m => RenderPassEncoder -> RenderPipeline -> m ()
- renderPassSetBindGroup :: MonadIO m => RenderPassEncoder -> Word32 -> BindGroup -> Vector Word32 -> m ()
- renderPassSetIndexBuffer :: MonadIO m => RenderPassEncoder -> Buffer -> IndexFormat -> Word64 -> Word64 -> m ()
- renderPassSetVertexBuffer :: MonadIO m => RenderPassEncoder -> Word32 -> Buffer -> Word64 -> Word64 -> m ()
- renderPassDraw :: MonadIO m => RenderPassEncoder -> Range Word32 -> Range Word32 -> m ()
- renderPassDrawIndexed :: MonadIO m => RenderPassEncoder -> Range Word32 -> Int32 -> Range Word32 -> m ()
- endRenderPass :: MonadIO m => RenderPassEncoder -> m ()
Types
newtype RenderPipeline Source #
Constructors
| RenderPipeline | |
Fields | |
Instances
| Eq RenderPipeline Source # | |
Defined in WGPU.Internal.RenderPass Methods (==) :: RenderPipeline -> RenderPipeline -> Bool # (/=) :: RenderPipeline -> RenderPipeline -> Bool # | |
| Show RenderPipeline Source # | |
Defined in WGPU.Internal.RenderPass Methods showsPrec :: Int -> RenderPipeline -> ShowS # show :: RenderPipeline -> String # showList :: [RenderPipeline] -> ShowS # | |
| ToRaw RenderPipeline WGPURenderPipeline Source # | |
Defined in WGPU.Internal.RenderPass Methods raw :: RenderPipeline -> ContT r IO WGPURenderPipeline Source # | |
data RenderPassEncoder Source #
Instances
| Eq RenderPassEncoder Source # | |
Defined in WGPU.Internal.RenderPass Methods (==) :: RenderPassEncoder -> RenderPassEncoder -> Bool # (/=) :: RenderPassEncoder -> RenderPassEncoder -> Bool # | |
| Show RenderPassEncoder Source # | |
Defined in WGPU.Internal.RenderPass Methods showsPrec :: Int -> RenderPassEncoder -> ShowS # show :: RenderPassEncoder -> String # showList :: [RenderPassEncoder] -> ShowS # | |
| ToRaw RenderPassEncoder WGPURenderPassEncoder Source # | |
Defined in WGPU.Internal.RenderPass Methods raw :: RenderPassEncoder -> ContT r IO WGPURenderPassEncoder Source # | |
Operation to perform to the output attachment at the start of a render pass.
Constructors
| LoadOpClear !a | Clear with the specified color value. |
| LoadOpLoad | Load from memory. |
Operation to perform to the output attachment at the end of the render pass.
Constructors
| StoreOpStore | Store the result. |
| StoreOpClear | Discard the result. |
data Operations a Source #
Constructors
| Operations | |
Instances
| Eq a => Eq (Operations a) Source # | |
Defined in WGPU.Internal.RenderPass | |
| Show a => Show (Operations a) Source # | |
Defined in WGPU.Internal.RenderPass Methods showsPrec :: Int -> Operations a -> ShowS # show :: Operations a -> String # showList :: [Operations a] -> ShowS # | |
data RenderPassColorAttachment Source #
Describes a color attachment to a render pass.
Constructors
| RenderPassColorAttachment | |
Fields
| |
Instances
| Eq RenderPassColorAttachment Source # | |
Defined in WGPU.Internal.RenderPass Methods (==) :: RenderPassColorAttachment -> RenderPassColorAttachment -> Bool # (/=) :: RenderPassColorAttachment -> RenderPassColorAttachment -> Bool # | |
| Show RenderPassColorAttachment Source # | |
Defined in WGPU.Internal.RenderPass Methods showsPrec :: Int -> RenderPassColorAttachment -> ShowS # show :: RenderPassColorAttachment -> String # showList :: [RenderPassColorAttachment] -> ShowS # | |
| ToRaw RenderPassColorAttachment WGPURenderPassColorAttachment Source # | |
Defined in WGPU.Internal.RenderPass Methods raw :: RenderPassColorAttachment -> ContT r IO WGPURenderPassColorAttachment Source # | |
data RenderPassDepthStencilAttachment Source #
Describes a depth/stencil attachment to a render pass.
Constructors
| RenderPassDepthStencilAttachment | |
Fields
| |
Instances
data RenderPassDescriptor Source #
Describes the attachments of a render pass.
Constructors
| RenderPassDescriptor | |
Fields
| |
Instances
| Eq RenderPassDescriptor Source # | |
Defined in WGPU.Internal.RenderPass Methods (==) :: RenderPassDescriptor -> RenderPassDescriptor -> Bool # (/=) :: RenderPassDescriptor -> RenderPassDescriptor -> Bool # | |
| Show RenderPassDescriptor Source # | |
Defined in WGPU.Internal.RenderPass Methods showsPrec :: Int -> RenderPassDescriptor -> ShowS # show :: RenderPassDescriptor -> String # showList :: [RenderPassDescriptor] -> ShowS # | |
| ToRaw RenderPassDescriptor WGPURenderPassDescriptor Source # | |
Defined in WGPU.Internal.RenderPass Methods raw :: RenderPassDescriptor -> ContT r IO WGPURenderPassDescriptor Source # | |
Half open range. It includes the start value but not the end value.
Constructors
| Range | |
Fields
| |
Functions
Arguments
| :: MonadIO m | |
| => CommandEncoder |
|
| -> RenderPassDescriptor | Description of the render pass. |
| -> m RenderPassEncoder | IO action which returns the render pass encoder. |
Begins recording of a render pass.
renderPassSetPipeline Source #
Arguments
| :: MonadIO m | |
| => RenderPassEncoder | Render pass encoder on which to act. |
| -> RenderPipeline | Render pipeline to set active. |
| -> m () | IO action which sets the active render pipeline. |
Sets the active render pipeline.
Subsequent draw calls will exhibit the behaviour defined by the pipeline.
renderPassSetBindGroup :: MonadIO m => RenderPassEncoder -> Word32 -> BindGroup -> Vector Word32 -> m () Source #
Sets the active bind group for a given bind group index.
renderPassSetIndexBuffer :: MonadIO m => RenderPassEncoder -> Buffer -> IndexFormat -> Word64 -> Word64 -> m () Source #
Sets the active index buffer.
renderPassSetVertexBuffer :: MonadIO m => RenderPassEncoder -> Word32 -> Buffer -> Word64 -> Word64 -> m () Source #
Assign a vertex buffer to a slot.
Arguments
| :: MonadIO m | |
| => RenderPassEncoder | Render pass encoder on which to act. |
| -> Range Word32 | Range of vertices to draw. |
| -> Range Word32 | Range of instances to draw. |
| -> m () | IO action which stores the draw command. |
Draws primitives from the active vertex buffers.
renderPassDrawIndexed :: MonadIO m => RenderPassEncoder -> Range Word32 -> Int32 -> Range Word32 -> m () Source #
Arguments
| :: MonadIO m | |
| => RenderPassEncoder | Render pass encoder on which to finish recording. |
| -> m () | IO action that finishes recording. |
Finish recording of a render pass.