wgpu-hs-0.3.0.0: WGPU
CopyrightCopyright (C) Jonathan Merritt 2021
LicenseBSD-3-Clause
MaintainerJonathan Merritt <j.s.merritt@gmail.com>
Stabilityexperimental
PortabilitymacOS, Linux, Windows
Safe HaskellNone
LanguageHaskell2010

WGPU

Description

Layout of this module should be guided by the evolving WebGPU Specification.

Synopsis

Introduction

Introduction to WebGPU

WebGPU is a future web standard for graphics and compute, developed by the W3C. It is currently (August 2021) an emerging technology, and not yet stable. In addition to its JavaScript API, there are also early attempts to create a native binding (ie. a C language binding). Two implementations of the native binding are:

  • wgpu-native: a Rust implementation used in the Firefox web browser.
  • dawn: a C++ implementation,used in the Chrome web browser.

The native bindings to WebGPU have the potential to become a portable, next-generation GPU API which is easy to use. Vulkan is also currently available across platforms, but it is very low-level. In the opinion of the author of this package, Vulkan is very difficult to use directly from Haskell. It would benefit greatly from a shim layer which performs common tasks and streamlines many operations. Not unexpectedly, that is exactly the role that WebGPU native can play.

Platform Support

Currently, macOS (Metal), Windows and Linux are supported.

Windowing System Support

The bindings support both GLFW-b and SDL as windowing systems on macOS, Windows and Linux. The windowing system bindings are somewhat hacky (due to the early stage of WebGPU Native), but they work.

Structure of Bindings

The bindings to wgpu-native are structured in three packages:

  1. The wgpu-raw-hs-codegen package is a code generator for the raw bindings. It creates all the packages named WGPU.Raw.Generated.* (without exception!).
  2. The wgpu-raw-hs package provides raw bindings to wgpu-native. They are "raw" in the sense that they contain raw pointers and are not usable without manual construction of the C structs that must be passed to the API.
  3. The wgpu-hs package (this one) provides high-level bindings. These bindings are written manually. They are improvements on the raw bindings in the following ways:

    • There are no more raw Ptr types.
    • There are no callbacks.
    • Several parts of the API are tweaked slightly to more closely resemble the Rust API.
    • Names are de-duplicated.

Native Library Handling

The native library for wgpu-native is not required at compile-time for this package. The library is loaded dynamically at runtime.

Initialization

The first step in using these Haskell bindings is to obtain an Instance. This acts as a handle to the rest of the API. An Instance is obtained at runtime by loading a dynamic library containing the WGPU binding symbols. Currently, only the C/Rust library from wgpu-native is supported.

To load the dynamic library and obtain an instance, use the withPlatformInstance or withInstance bracketing functions. These functions take a function that performs bracketing.

withPlatformInstance bracket $ inst -> do
  -- attach the logger and set the logging level (optional)
  connectLog inst
  setLogLevel inst Warn
  -- run the rest of the program...

After creating an Instance, you may next want to create a surface.

data Instance #

Instance of the WGPU API.

An instance is loaded from a dynamic library using the withInstance function.

Instances

Instances details
Show Instance 
Instance details

Defined in WGPU.Internal.Instance

Has Instance Resources Source # 
Instance details

Defined in WGPU.BoneYard.SimpleSDL

ToRaw Instance WGPUHsInstance 
Instance details

Defined in WGPU.Internal.Instance

withPlatformInstance #

Arguments

:: MonadIO m 
=> (m Instance -> (Instance -> m ()) -> r)

Bracketing function. This can (for example) be something like bracket.

-> r

Usage or action component of the bracketing function.

Load the WGPU API from a dynamic library and supply an Instance to a program.

This is the same as withInstance, except that it uses a default, per-platform name for the library, based on the value returned by os.

withInstance #

Arguments

:: MonadIO m 
=> FilePath

Name of the wgpu-native dynamic library, or a complete path to it.

-> (m Instance -> (Instance -> m ()) -> r)

Bracketing function. This can (for example) be something like bracket.

-> r

Usage or action component of the bracketing function.

Load the WGPU API from a dynamic library and supply an Instance to a program.

Surface

A Surface is a handle to a platform-specific presentable surface, like a window. First, create either a GLFW or SDL window, and then create a surface using either createGLFWSurface or createSDLSurface.

Once you have a Surface, the next step is usually to request an adapter that is compatible with it.

data Surface #

Handle to a presentable surface.

A Surface presents a platform-specific surface (eg. a window) on to which rendered images may be presented. A Surface can be created for a GLFW window using createGLFWSurface.

Instances

Instances details
Eq Surface 
Instance details

Defined in WGPU.Internal.Surface

Methods

(==) :: Surface -> Surface -> Bool #

(/=) :: Surface -> Surface -> Bool #

Show Surface 
Instance details

Defined in WGPU.Internal.Surface

Has Surface Resources Source # 
Instance details

Defined in WGPU.BoneYard.SimpleSDL

ToRaw Surface WGPUSurface 
Instance details

Defined in WGPU.Internal.Surface

Methods

raw :: Surface -> ContT r IO WGPUSurface #

Adapter

An Adapter is a handle to a physical device. For example, a physical display adaptor (GPU) or a software renderer. Currently you obtain an adapter using requestAdapter, which requests an adapter that is compatible with an existing Surface.

After obtaining an adapter, you will typically want to request a device.

data Adapter #

Handle to a physical graphics and/or compute device.

Request an Adapter for a Surface using the requestAdapter function.

Instances

Instances details
Eq Adapter 
Instance details

Defined in WGPU.Internal.Adapter

Methods

(==) :: Adapter -> Adapter -> Bool #

(/=) :: Adapter -> Adapter -> Bool #

Show Adapter 
Instance details

Defined in WGPU.Internal.Adapter

Has Adapter Resources Source # 
Instance details

Defined in WGPU.BoneYard.SimpleSDL

ToRaw Adapter WGPUAdapter 
Instance details

Defined in WGPU.Internal.Adapter

Methods

raw :: Adapter -> ContT r IO WGPUAdapter #

requestAdapter #

Arguments

:: MonadIO m 
=> Surface

Existing surface for which to request an Adapter.

-> m (Maybe Adapter)

The returned Adapter, if it could be retrieved.

Request an Adapter that is compatible with a given Surface.

This action blocks until an available adapter is returned.

getAdapterProperties :: MonadIO m => Adapter -> m AdapterProperties #

Get information about an adapter.

adapterPropertiesToText :: AdapterProperties -> Text #

Format adapter properties into a multi-line block of text.

This can be useful for debugging purposes.

Device

A Device is an open connection to a graphics and/or compute device. A Device is created using the requestDevice function.

(According to the WebGPU API documentation, a Device may also be "lost". However, it's not yet clear how that event will be signalled to the C API, nor how to handle it.)

data Device #

An open connection to a graphics and/or compute device.

A Device may be created using the requestDevice function.

Instances

Instances details
Eq Device 
Instance details

Defined in WGPU.Internal.Device

Methods

(==) :: Device -> Device -> Bool #

(/=) :: Device -> Device -> Bool #

Show Device 
Instance details

Defined in WGPU.Internal.Device

Has Device Resources Source # 
Instance details

Defined in WGPU.BoneYard.SimpleSDL

ToRaw Device WGPUDevice 
Instance details

Defined in WGPU.Internal.Device

Methods

raw :: Device -> ContT r IO WGPUDevice #

data DeviceDescriptor #

Describes a Device.

Constructors

DeviceDescriptor 

Fields

data Limits #

Device limits.

Represents the set of limits an adapter/device supports.

Constructors

Limits 

Fields

Instances

Instances details
Eq Limits 
Instance details

Defined in WGPU.Internal.Device

Methods

(==) :: Limits -> Limits -> Bool #

(/=) :: Limits -> Limits -> Bool #

Show Limits 
Instance details

Defined in WGPU.Internal.Device

Default Limits 
Instance details

Defined in WGPU.Internal.Device

Methods

def :: Limits #

newtype Features #

Device features that are not guaranteed to be supported.

Instances

Instances details
Eq Features 
Instance details

Defined in WGPU.Internal.Device

Show Features 
Instance details

Defined in WGPU.Internal.Device

Default Features 
Instance details

Defined in WGPU.Internal.Device

Methods

def :: Features #

ToRaw Features WGPUNativeFeature 
Instance details

Defined in WGPU.Internal.Device

requestDevice #

Arguments

:: MonadIO m 
=> Adapter

Adapter for which the device will be returned.

-> DeviceDescriptor

The features and limits requested for the device.

-> m (Maybe Device)

The returned Device, if it could be retrieved.

Requests a connection to a physical device, creating a logical device.

This action blocks until an available device is returned.

Textures and Views

data TextureView #

Handle to a texture view.

A TextureView describes a texture and associated metadata needed by a rendering pipeline or bind group.

Instances

Instances details
Eq TextureView 
Instance details

Defined in WGPU.Internal.Texture

Show TextureView 
Instance details

Defined in WGPU.Internal.Texture

ToRaw TextureView WGPUTextureView 
Instance details

Defined in WGPU.Internal.Texture

data TextureFormat #

Texture data format.

Instances

Instances details
Eq TextureFormat 
Instance details

Defined in WGPU.Internal.Texture

Show TextureFormat 
Instance details

Defined in WGPU.Internal.Texture

ToRaw TextureFormat WGPUTextureFormat 
Instance details

Defined in WGPU.Internal.Texture

data TextureUsage #

Different ways you can use a texture.

The usages determine from what kind of memory the texture is allocated, and in what actions the texture can partake.

Instances

Instances details
Eq TextureUsage 
Instance details

Defined in WGPU.Internal.Texture

Show TextureUsage 
Instance details

Defined in WGPU.Internal.Texture

ToRaw TextureUsage WGPUTextureUsage 
Instance details

Defined in WGPU.Internal.Texture

Swapchain

data SwapChain #

Instances

Instances details
Eq SwapChain 
Instance details

Defined in WGPU.Internal.SwapChain

Show SwapChain 
Instance details

Defined in WGPU.Internal.SwapChain

ToRaw SwapChain WGPUSwapChain 
Instance details

Defined in WGPU.Internal.SwapChain

data SwapChainDescriptor #

Describes a swapchain.

Constructors

SwapChainDescriptor 

Fields

data PresentMode #

Behaviour of the presentation engine based on frame rate.

Constructors

PresentModeImmediate

The presentation engine does not wait for a vertical blanking period and the request is presented immediately. This is a low-latency presentation mode, but visible tearing may be observed. Will fallback to Fifo if unavailable on the selected platform and backend. Not optimal for mobile.

PresentModeMailbox

The presentation engine waits for the next vertical blanking period to update the current image, but frames may be submitted without delay. This is a low-latency presentation mode and visible tearing will not be observed. Will fallback to Fifo if unavailable on the selected platform and backend. Not optimal for mobile.

PresentModeFifo

The presentation engine waits for the next vertical blanking period to update the current image. The framerate will be capped at the display refresh rate, corresponding to the VSync. Tearing cannot be observed. Optimal for mobile.

Instances

Instances details
Eq PresentMode 
Instance details

Defined in WGPU.Internal.SwapChain

Show PresentMode 
Instance details

Defined in WGPU.Internal.SwapChain

ToRaw PresentMode WGPUPresentMode 
Instance details

Defined in WGPU.Internal.SwapChain

getSwapChainPreferredFormat #

Arguments

:: MonadIO m 
=> Surface

Surface for which to obtain an optimal texture format.

-> Adapter

Adapter for which to obtain an optimal texture format.

-> m TextureFormat

IO action which returns the optimal texture format.

Returns an optimal texture format to use for the swapchain with this adapter and surface.

createSwapChain #

Arguments

:: MonadIO m 
=> Device

Device for which the SwapChain will be created.

-> Surface

Surface for which the SwapChain will be created.

-> SwapChainDescriptor

Description of the SwapChain to be created.

-> m SwapChain

IO action which creates the swap chain.

Createa a new SwapChain which targets a Surface.

To determine the preferred TextureFormat for the Surface, use the getSwapChainPreferredFormat function.

getSwapChainCurrentTextureView #

Arguments

:: MonadIO m 
=> SwapChain

Swap chain from which to fetch the current texture view.

-> m TextureView

IO action which returns the current swap chain texture view.

Get the TextureView for the current swap chain frame.

swapChainPresent #

Arguments

:: MonadIO m 
=> SwapChain

Swap chain to present.

-> m ()

IO action which presents the swap chain image.

Present the latest swap chain image.

Samplers

Resource Binding

data BindGroupLayout #

Handle to a binding group layout.

A BindGroupLayout is a handle to the GPU-side layout of a binding group.

data BindGroupLayoutEntry #

Describes a single binding inside a bind group.

Constructors

BindGroupLayoutEntry 

Fields

newtype Binding #

Binding index.

This must match a shader index, and be unique inside a binding group layout.

Constructors

Binding 

Fields

Instances

Instances details
Eq Binding 
Instance details

Defined in WGPU.Internal.Binding

Methods

(==) :: Binding -> Binding -> Bool #

(/=) :: Binding -> Binding -> Bool #

Show Binding 
Instance details

Defined in WGPU.Internal.Binding

ToRaw Binding Word32 
Instance details

Defined in WGPU.Internal.Binding

Methods

raw :: Binding -> ContT r IO Word32 #

data ShaderStage #

Describes the shader stages from which a binding will be visible.

Constructors

ShaderStage 

Fields

  • stageVertex :: !Bool

    Binding is visible from the vertex shader of a render pipeline.

  • stageFragment :: !Bool

    Binding is visible from the fragment shader of a render pipeline.

  • stageCompute :: !Bool

    Binding is visible from the compute shader of a compute pipeline.

Instances

Instances details
Eq ShaderStage 
Instance details

Defined in WGPU.Internal.Binding

Show ShaderStage 
Instance details

Defined in WGPU.Internal.Binding

ToRaw ShaderStage WGPUShaderStageFlags 
Instance details

Defined in WGPU.Internal.Binding

data BindingType #

Specifies type of a binding.

Constructors

BindingTypeBuffer !BufferBindingLayout

A buffer binding.

BindingTypeSampler !SamplerBindingLayout

A sampler that can be used to sample a texture.

BindingTypeTexture !TextureBindingLayout

A texture binding.

BindingTypeStorageTexture !StorageTextureBindingLayout

A storage texture.

Instances

Instances details
Eq BindingType 
Instance details

Defined in WGPU.Internal.Binding

Show BindingType 
Instance details

Defined in WGPU.Internal.Binding

data BufferBindingLayout #

A buffer binding.

Constructors

BufferBindingLayout 

Fields

data TextureBindingLayout #

A texture binding.

Constructors

TextureBindingLayout 

Fields

data BufferBindingType #

Specific type of a buffer binding.

Constructors

Uniform 
Storage 

Fields

createBindGroupLayout #

Arguments

:: MonadIO m 
=> Device

The device for which the bind group layout will be created.

-> BindGroupLayoutDescriptor

Description of the bind group layout.

-> m BindGroupLayout

MonadIO action that creates a bind group layout.

Creates a BindGroupLayout.

Shader Modules

data ShaderModule #

Handle to a compiled shader module.

Instances

Instances details
Eq ShaderModule 
Instance details

Defined in WGPU.Internal.Shader

Show ShaderModule 
Instance details

Defined in WGPU.Internal.Shader

ToRaw ShaderModule WGPUShaderModule 
Instance details

Defined in WGPU.Internal.Shader

data ShaderSource #

Source for a shader module.

Constructors

ShaderSourceSPIRV !SPIRV

Use shader source from a SPIRV module (pre-compiled).

ShaderSourceWGSL !WGSL

Use shader source from WGSL string.

Instances

Instances details
Eq ShaderSource 
Instance details

Defined in WGPU.Internal.Shader

Show ShaderSource 
Instance details

Defined in WGPU.Internal.Shader

newtype SPIRV #

Pre-compiled SPIRV module bytes.

Constructors

SPIRV ByteString 

Instances

Instances details
Eq SPIRV 
Instance details

Defined in WGPU.Internal.Shader

Methods

(==) :: SPIRV -> SPIRV -> Bool #

(/=) :: SPIRV -> SPIRV -> Bool #

Show SPIRV 
Instance details

Defined in WGPU.Internal.Shader

Methods

showsPrec :: Int -> SPIRV -> ShowS #

show :: SPIRV -> String #

showList :: [SPIRV] -> ShowS #

ToRaw SPIRV WGPUShaderModuleSPIRVDescriptor 
Instance details

Defined in WGPU.Internal.Shader

newtype WGSL #

WGSL shader source code.

Constructors

WGSL Text 

Instances

Instances details
Eq WGSL 
Instance details

Defined in WGPU.Internal.Shader

Methods

(==) :: WGSL -> WGSL -> Bool #

(/=) :: WGSL -> WGSL -> Bool #

Show WGSL 
Instance details

Defined in WGPU.Internal.Shader

Methods

showsPrec :: Int -> WGSL -> ShowS #

show :: WGSL -> String #

showList :: [WGSL] -> ShowS #

ToRaw WGSL WGPUShaderModuleWGSLDescriptor 
Instance details

Defined in WGPU.Internal.Shader

newtype ShaderEntryPoint #

Name of a shader entry point.

Constructors

ShaderEntryPoint 

createShaderModule #

Arguments

:: MonadIO m 
=> Device

Device for the shader.

-> ShaderModuleDescriptor

Descriptor of the shader module.

-> m ShaderModule

IO action producing the shader module.

Create a shader module from either SPIR-V or WGSL source code.

createShaderModuleSPIRV #

Arguments

:: MonadIO m 
=> Device

Device for which the shader should be created.

-> Text

Debugging label for the shader.

-> SPIRV

Shader source code (SPIR-V bytestring).

-> m ShaderModule

IO action creating the shader module.

Create a shader module from SPIR-V source code.

createShaderModuleWGSL #

Arguments

:: MonadIO m 
=> Device

Device for which the shader should be created.

-> Text

Debugging label for the shader.

-> WGSL

Shader source code (WGSL source string).

-> m ShaderModule

IO action creating the shader module.

Create a shader module from WGSL source code.

Pipelines

Compute

Render

data RenderPipelineDescriptor #

Describes a render (graphics) pipeline.

Constructors

RenderPipelineDescriptor 

Fields

data VertexAttribute #

Vertex inputs (attributes) to shaders.

Constructors

VertexAttribute 

Fields

data InputStepMode #

Determines when vertex data is advanced.

Constructors

InputStepModeVertex

Input data is advanced every vertex.

InputStepModeInstance

Input data is advanced every instance.

Instances

Instances details
Eq InputStepMode 
Instance details

Defined in WGPU.Internal.Pipeline

Show InputStepMode 
Instance details

Defined in WGPU.Internal.Pipeline

ToRaw InputStepMode WGPUInputStepMode

Convert an InputStepMode to its raw value.

Instance details

Defined in WGPU.Internal.Pipeline

data VertexBufferLayout #

Describes how a vertex buffer is interpreted.

Constructors

VertexBufferLayout 

Fields

data VertexState #

Describes the vertex process in a render pipeline.

Constructors

VertexState 

Fields

Instances

Instances details
Eq VertexState 
Instance details

Defined in WGPU.Internal.Pipeline

Show VertexState 
Instance details

Defined in WGPU.Internal.Pipeline

ToRaw VertexState WGPUVertexState 
Instance details

Defined in WGPU.Internal.Pipeline

data IndexFormat #

Format of indices used within a pipeline.

Constructors

IndexFormatUint16

Indices are 16-bit unsigned integers (Word16)

IndexFormatUint32

Indices are 32-bit unsigned integers (Word32)

Instances

Instances details
Eq IndexFormat 
Instance details

Defined in WGPU.Internal.Pipeline

Show IndexFormat 
Instance details

Defined in WGPU.Internal.Pipeline

ToRaw IndexFormat WGPUIndexFormat

Convert an IndexFormat to its raw value.

Instance details

Defined in WGPU.Internal.Pipeline

data FrontFace #

Winding order which classifies the "front" face.

Constructors

FrontFaceCCW

Triangles with counter-clockwise vertices are the front face.

FrontFaceCW

Triangles with clockwise vertices are the front face.

Instances

Instances details
Eq FrontFace 
Instance details

Defined in WGPU.Internal.Pipeline

Show FrontFace 
Instance details

Defined in WGPU.Internal.Pipeline

Default FrontFace 
Instance details

Defined in WGPU.Internal.Pipeline

Methods

def :: FrontFace #

ToRaw FrontFace WGPUFrontFace

Convert a FrontFace to its raw value.

Instance details

Defined in WGPU.Internal.Pipeline

data CullMode #

Whether to cull the face of a vertex.

Constructors

CullModeFront

Cull the front face.

CullModeBack

Cull the back face.

CullModeNone

Do not cull either face.

Instances

Instances details
Eq CullMode 
Instance details

Defined in WGPU.Internal.Pipeline

Show CullMode 
Instance details

Defined in WGPU.Internal.Pipeline

Default CullMode 
Instance details

Defined in WGPU.Internal.Pipeline

Methods

def :: CullMode #

ToRaw CullMode WGPUCullMode

Convert a CullMode to its raw value.

Instance details

Defined in WGPU.Internal.Pipeline

data PrimitiveState #

Describes the state of primitive assembly and rasterization in a render pipeline.

Differences between this and the Rust API: - no clamp_depth member - no polygon_mode member - no conservative member

Constructors

PrimitiveState 

Fields

data StencilState #

State of the stencil operation (fixed pipeline stage).

Constructors

StencilState 

Fields

Instances

Instances details
Eq StencilState 
Instance details

Defined in WGPU.Internal.Pipeline

Show StencilState 
Instance details

Defined in WGPU.Internal.Pipeline

data DepthBiasState #

Describes the biasing setting for the depth target.

Constructors

DepthBiasState 

Fields

Instances

Instances details
Eq DepthBiasState 
Instance details

Defined in WGPU.Internal.Pipeline

Show DepthBiasState 
Instance details

Defined in WGPU.Internal.Pipeline

data DepthStencilState #

Describes the depth / stencil state of a render pipeline.

Constructors

DepthStencilState 

Fields

data MultisampleState #

Describes the multi-sampling state of a render pipeline.

Constructors

MultisampleState 

Fields

  • count :: Word32

    Number of samples calculated per pixel (for MSAA). For non-multisampled textures, this should be 1.

  • mask :: Word32

    Bitmask that restricts the samples of a pixel modified by this pipeline. All samples can be enabled by using 0XFFFFFFFF (ie. zero complement).

  • alphaToCoverageEnabled :: Bool

    When enabled, produces another sample mask per pixel based on the alpha output value, and that is AND-ed with the sample mask and the primitive coverage to restrict the set of samples affected by a primitive.

data BlendComponent #

Describes the blend component of a pipeline.

Constructors

BlendComponent 

Fields

data BlendState #

Describes the blend state of a render pipeline.

Constructors

BlendState 

Fields

Instances

Instances details
Eq BlendState 
Instance details

Defined in WGPU.Internal.Pipeline

Show BlendState 
Instance details

Defined in WGPU.Internal.Pipeline

ToRaw BlendState WGPUBlendState 
Instance details

Defined in WGPU.Internal.Pipeline

data ColorWriteMask #

Describes which color channels are written.

Constructors

ColorWriteMask 

Fields

data ColorTargetState #

Describes the color state of a render pipeline.

Constructors

ColorTargetState 

Fields

data FragmentState #

Describes the fragment processing in a render pipeline.

Constructors

FragmentState 

Fields

createPipelineLayout #

Arguments

:: MonadIO m 
=> Device

The device for which the pipeline layout will be created.

-> PipelineLayoutDescriptor

Descriptor of the pipeline.

-> m PipelineLayout 

Create a pipeline layout.

colorWriteMaskAll :: ColorWriteMask #

A ColorWriteMask that writes all colors and the alpha value.

Command Buffers

Command Encoding

data CommandEncoder #

Handle to an encoder for a series of GPU operations.

A command encoder can record render passes, compute passes, and transfer operations between driver-managed resources like buffers and textures.

data Color #

RGBA double-precision color.

Constructors

Color 

Fields

Instances

Instances details
Eq Color 
Instance details

Defined in WGPU.Internal.Color

Methods

(==) :: Color -> Color -> Bool #

(/=) :: Color -> Color -> Bool #

Show Color 
Instance details

Defined in WGPU.Internal.Color

Methods

showsPrec :: Int -> Color -> ShowS #

show :: Color -> String #

showList :: [Color] -> ShowS #

ToRaw Color WGPUColor 
Instance details

Defined in WGPU.Internal.Color

Methods

raw :: Color -> ContT r IO WGPUColor #

data LoadOp a #

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.

Instances

Instances details
Eq a => Eq (LoadOp a) 
Instance details

Defined in WGPU.Internal.RenderPass

Methods

(==) :: LoadOp a -> LoadOp a -> Bool #

(/=) :: LoadOp a -> LoadOp a -> Bool #

Show a => Show (LoadOp a) 
Instance details

Defined in WGPU.Internal.RenderPass

Methods

showsPrec :: Int -> LoadOp a -> ShowS #

show :: LoadOp a -> String #

showList :: [LoadOp a] -> ShowS #

data StoreOp #

Operation to perform to the output attachment at the end of the render pass.

Constructors

StoreOpStore

Store the result.

StoreOpClear

Discard the result.

Instances

Instances details
Eq StoreOp 
Instance details

Defined in WGPU.Internal.RenderPass

Methods

(==) :: StoreOp -> StoreOp -> Bool #

(/=) :: StoreOp -> StoreOp -> Bool #

Show StoreOp 
Instance details

Defined in WGPU.Internal.RenderPass

ToRaw StoreOp WGPUStoreOp 
Instance details

Defined in WGPU.Internal.RenderPass

Methods

raw :: StoreOp -> ContT r IO WGPUStoreOp #

data Operations a #

Constructors

Operations 

Fields

Instances

Instances details
Eq a => Eq (Operations a) 
Instance details

Defined in WGPU.Internal.RenderPass

Methods

(==) :: Operations a -> Operations a -> Bool #

(/=) :: Operations a -> Operations a -> Bool #

Show a => Show (Operations a) 
Instance details

Defined in WGPU.Internal.RenderPass

data RenderPassColorAttachment #

Describes a color attachment to a render pass.

Constructors

RenderPassColorAttachment 

Fields

data RenderPassDescriptor #

Describes the attachments of a render pass.

Constructors

RenderPassDescriptor 

Fields

data Range a #

Half open range. It includes the start value but not the end value.

Constructors

Range 

Fields

Instances

Instances details
Eq a => Eq (Range a) 
Instance details

Defined in WGPU.Internal.RenderPass

Methods

(==) :: Range a -> Range a -> Bool #

(/=) :: Range a -> Range a -> Bool #

Show a => Show (Range a) 
Instance details

Defined in WGPU.Internal.RenderPass

Methods

showsPrec :: Int -> Range a -> ShowS #

show :: Range a -> String #

showList :: [Range a] -> ShowS #

createCommandEncoder #

Arguments

:: MonadIO m 
=> Device

Device for which to create the command encoder.

-> Text

Debug label for the command encoder.

-> m CommandEncoder

IO action that returns the command encoder.

Create an empty command encoder.

commandEncoderFinish #

Arguments

:: MonadIO m 
=> CommandEncoder

Command encoder to finish.

-> Text

Debugging label for the command buffer.

-> m CommandBuffer

IO action which returns the command buffer.

Finish encoding commands, returning a command buffer.

beginRenderPass #

Arguments

:: MonadIO m 
=> CommandEncoder

CommandEncoder to contain the render pass.

-> RenderPassDescriptor

Description of the render pass.

-> m RenderPassEncoder

IO action which returns the render pass encoder.

Begins recording of a render pass.

renderPassSetPipeline #

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.

renderPassDraw #

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.

endRenderPass #

Arguments

:: MonadIO m 
=> RenderPassEncoder

Render pass encoder on which to finish recording.

-> m ()

IO action that finishes recording.

Finish recording of a render pass.

Queue

data Queue #

Instances

Instances details
Eq Queue 
Instance details

Defined in WGPU.Internal.Queue

Methods

(==) :: Queue -> Queue -> Bool #

(/=) :: Queue -> Queue -> Bool #

Show Queue 
Instance details

Defined in WGPU.Internal.Queue

Methods

showsPrec :: Int -> Queue -> ShowS #

show :: Queue -> String #

showList :: [Queue] -> ShowS #

Has Queue Resources Source # 
Instance details

Defined in WGPU.BoneYard.SimpleSDL

ToRaw Queue WGPUQueue 
Instance details

Defined in WGPU.Internal.Queue

Methods

raw :: Queue -> ContT r IO WGPUQueue #

getQueue :: MonadIO m => Device -> m Queue #

Get the queue for a device.

queueSubmit :: MonadIO m => Queue -> Vector CommandBuffer -> m () #

Submit a list of command buffers to a device queue.

Version

data Version #

Version of WGPU native.

Constructors

Version 

Fields

Instances

Instances details
Eq Version 
Instance details

Defined in WGPU.Internal.Instance

Methods

(==) :: Version -> Version -> Bool #

(/=) :: Version -> Version -> Bool #

Show Version 
Instance details

Defined in WGPU.Internal.Instance

getVersion :: MonadIO m => Instance -> m Version #

Return the exact version of the WGPU native instance.

versionToText :: Version -> Text #

Convert a Version value to a text string.

>>> versionToText (Version 0 9 2 2)
"v0.9.2.2"

Logging

data LogLevel #

Logging level.

Constructors

Trace 
Debug 
Info 
Warn 
Error 

Instances

Instances details
Eq LogLevel 
Instance details

Defined in WGPU.Internal.Instance

Show LogLevel 
Instance details

Defined in WGPU.Internal.Instance

connectLog :: MonadIO m => Instance -> m () #

Connect a stdout logger to the instance.

disconnectLog :: MonadIO m => Instance -> m () #

Disconnect a stdout logger from the instance.

setLogLevel :: MonadIO m => Instance -> LogLevel -> m () #

Set the current logging level for the instance.

Multipurpose

Extras

Strict Maybe

data SMaybe a #

Strict version of the Maybe type.

Constructors

SNothing 
SJust !a 

Instances

Instances details
Eq a => Eq (SMaybe a) 
Instance details

Defined in WGPU.Internal.SMaybe

Methods

(==) :: SMaybe a -> SMaybe a -> Bool #

(/=) :: SMaybe a -> SMaybe a -> Bool #

Show a => Show (SMaybe a) 
Instance details

Defined in WGPU.Internal.SMaybe

Methods

showsPrec :: Int -> SMaybe a -> ShowS #

show :: SMaybe a -> String #

showList :: [SMaybe a] -> ShowS #

fromSMaybe #

Arguments

:: a

Default value.

-> SMaybe a

SMaybe from which to return the SJust value if possible.

-> a

SJust value, if present, or the default value, if not.

Return a value from an SMaybe with a default.

This function returns the SJust value from an SMaybe, or the default value if the SMaybe is SNothing.