Copyright | Copyright (C) Jonathan Merritt 2021 |
---|---|
License | BSD-3-Clause |
Maintainer | Jonathan Merritt <j.s.merritt@gmail.com> |
Stability | experimental |
Portability | macOS |
Safe Haskell | None |
Language | Haskell2010 |
WGPU
Description
Layout of this module should be guided by the evolving WebGPU Specification.
Synopsis
- data Instance
- withInstance :: FilePath -> Maybe LogCallback -> (Instance -> IO a) -> IO a
- data Surface
- createGLFWSurface :: Instance -> Window -> IO Surface
- data Adapter
- requestAdapter :: Surface -> IO (Maybe Adapter)
- data Device
- data DeviceDescriptor = DeviceDescriptor {}
- data Limits = Limits {}
- newtype Features = Features {}
- requestDevice :: Adapter -> DeviceDescriptor -> IO (Maybe Device)
- data TextureView
- data TextureViewDimension
- data TextureFormat
- = TextureFormatR8Unorm
- | TextureFormatR8Snorm
- | TextureFormatR8Uint
- | TextureFormatR8Sint
- | TextureFormatR16Uint
- | TextureFormatR16Sint
- | TextureFormatR16Float
- | TextureFormatRG8Unorm
- | TextureFormatRG8Snorm
- | TextureFormatRG8Uint
- | TextureFormatRG8Sint
- | TextureFormatR32Float
- | TextureFormatR32Uint
- | TextureFormatR32Sint
- | TextureFormatRG16Uint
- | TextureFormatRG16Sint
- | TextureFormatRG16Float
- | TextureFormatRGBA8Unorm
- | TextureFormatRGBA8UnormSrgb
- | TextureFormatRGBA8Snorm
- | TextureFormatRGBA8Uint
- | TextureFormatRGBA8Sint
- | TextureFormatBGRA8Unorm
- | TextureFormatBGRA8UnormSrgb
- | TextureFormatRGB10A2Unorm
- | TextureFormatRG11B10Ufloat
- | TextureFormatRGB9E5Ufloat
- | TextureFormatRG32Float
- | TextureFormatRG32Uint
- | TextureFormatRG32Sint
- | TextureFormatRGBA16Uint
- | TextureFormatRGBA16Sint
- | TextureFormatRGBA16Float
- | TextureFormatRGBA32Float
- | TextureFormatRGBA32Uint
- | TextureFormatRGBA32Sint
- | TextureFormatDepth32Float
- | TextureFormatDepth24Plus
- | TextureFormatDepth24PlusStencil8
- | TextureFormatStencil8
- | TextureFormatBC1RGBAUnorm
- | TextureFormatBC1RGBAUnormSrgb
- | TextureFormatBC2RGBAUnorm
- | TextureFormatBC2RGBAUnormSrgb
- | TextureFormatBC3RGBAUnorm
- | TextureFormatBC3RGBAUnormSrgb
- | TextureFormatBC4RUnorm
- | TextureFormatBC4RSnorm
- | TextureFormatBC5RGUnorm
- | TextureFormatBC5RGSnorm
- | TextureFormatBC6HRGBUfloat
- | TextureFormatBC6HRGBFloat
- | TextureFormatBC7RGBAUnorm
- | TextureFormatBC7RGBAUnormSrgb
- data TextureUsage
- data SwapChain
- data SwapChainDescriptor = SwapChainDescriptor {
- swapChainLabel :: !Text
- usage :: !TextureUsage
- swapChainFormat :: !TextureFormat
- width :: !Word32
- height :: !Word32
- presentMode :: !PresentMode
- data PresentMode
- getSwapChainPreferredFormat :: Surface -> Adapter -> IO TextureFormat
- createSwapChain :: Device -> Surface -> SwapChainDescriptor -> IO SwapChain
- getSwapChainCurrentTextureView :: SwapChain -> IO TextureView
- swapChainPresent :: SwapChain -> IO ()
- data BindGroupLayout
- data BindGroupLayoutDescriptor = BindGroupLayoutDescriptor {}
- data BindGroupLayoutEntry = BindGroupLayoutEntry {}
- newtype Binding = Binding {}
- data ShaderStage = ShaderStage {
- stageVertex :: !Bool
- stageFragment :: !Bool
- stageCompute :: !Bool
- data BindingType
- data BufferBindingLayout = BufferBindingLayout {}
- data SamplerBindingLayout
- data TextureBindingLayout = TextureBindingLayout {}
- data StorageTextureBindingLayout = StorageTextureBindingLayout {}
- data StorageTextureAccess
- data TextureSampleType
- data BufferBindingType
- createBindGroupLayout :: Device -> BindGroupLayoutDescriptor -> IO BindGroupLayout
- data ShaderModule
- data ShaderModuleDescriptor = ShaderModuleDescriptor {
- shaderLabel :: !Text
- source :: !ShaderSource
- data ShaderSource
- newtype SPIRV = SPIRV ByteString
- newtype WGSL = WGSL Text
- newtype ShaderEntryPoint = ShaderEntryPoint {}
- createShaderModule :: Device -> ShaderModuleDescriptor -> IO ShaderModule
- createShaderModuleSPIRV :: Device -> Text -> SPIRV -> IO ShaderModule
- createShaderModuleWGSL :: Device -> Text -> WGSL -> IO ShaderModule
- data PipelineLayout
- data RenderPipeline
- data PipelineLayoutDescriptor = PipelineLayoutDescriptor {}
- data RenderPipelineDescriptor = RenderPipelineDescriptor {}
- data VertexFormat
- = VertexFormatUint8x2
- | VertexFormatUint8x4
- | VertexFormatSint8x2
- | VertexFormatSint8x4
- | VertexFormatUnorm8x2
- | VertexFormatUnorm8x4
- | VertexFormatSnorm8x2
- | VertexFormatSnorm8x4
- | VertexFormatUint16x2
- | VertexFormatUint16x4
- | VertexFormatSint16x2
- | VertexFormatSint16x4
- | VertexFormatUnorm16x2
- | VertexFormatUnorm16x4
- | VertexFormatSnorm16x2
- | VertexFormatSnorm16x4
- | VertexFormatFloat16x2
- | VertexFormatFloat16x4
- | VertexFormatFloat32
- | VertexFormatFloat32x2
- | VertexFormatFloat32x3
- | VertexFormatFloat32x4
- | VertexFormatUint32
- | VertexFormatUint32x2
- | VertexFormatUint32x3
- | VertexFormatUint32x4
- | VertexFormatSint32
- | VertexFormatSint32x2
- | VertexFormatSint32x3
- | VertexFormatSint32x4
- data VertexAttribute = VertexAttribute {}
- data InputStepMode
- data VertexBufferLayout = VertexBufferLayout {
- arrayStride :: !Word64
- stepMode :: !InputStepMode
- attributes :: !(Vector VertexAttribute)
- data VertexState = VertexState {}
- data PrimitiveTopology
- data IndexFormat
- data FrontFace
- data CullMode
- data PrimitiveState = PrimitiveState {
- topology :: !PrimitiveTopology
- stripIndexFormat :: !(SMaybe IndexFormat)
- frontFace :: !FrontFace
- cullMode :: !CullMode
- data StencilOperation
- data StencilState = StencilState {
- front :: !StencilFaceState
- back :: !StencilFaceState
- readMask :: !Word8
- writeMask :: !Word8
- data DepthBiasState = DepthBiasState {}
- data DepthStencilState = DepthStencilState {}
- data MultisampleState = MultisampleState {}
- data BlendFactor
- data BlendOperation
- data BlendComponent = BlendComponent {}
- data BlendState = BlendState {}
- data ColorWriteMask = ColorWriteMask {}
- data ColorTargetState = ColorTargetState {}
- data FragmentState = FragmentState {}
- createPipelineLayout :: Device -> PipelineLayoutDescriptor -> IO PipelineLayout
- createRenderPipeline :: Device -> RenderPipelineDescriptor -> IO RenderPipeline
- colorWriteMaskAll :: ColorWriteMask
- data CommandBuffer
- data CommandEncoder
- data RenderPassEncoder
- data Color = Color {}
- 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
- createCommandEncoder :: Device -> Text -> IO CommandEncoder
- commandEncoderFinish :: CommandEncoder -> Text -> IO CommandBuffer
- beginRenderPass :: CommandEncoder -> RenderPassDescriptor -> IO RenderPassEncoder
- renderPassSetPipeline :: RenderPassEncoder -> RenderPipeline -> IO ()
- renderPassDraw :: RenderPassEncoder -> Range Word32 -> Range Word32 -> IO ()
- endRenderPass :: RenderPassEncoder -> IO ()
- data Queue
- getQueue :: Device -> IO Queue
- queueSubmit :: Queue -> Vector CommandBuffer -> IO ()
- data Version = Version {}
- getVersion :: Instance -> IO Version
- versionToText :: Version -> Text
- data LogLevel
- type LogCallback = LogLevel -> Text -> IO ()
- setLogLevel :: Instance -> LogLevel -> IO ()
- logStdout :: LogLevel -> Text -> IO ()
- logLevelToText :: LogLevel -> Text
- data CompareFunction
- data SMaybe a
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 Mozilla-backed WebGPU native implementation, written in Rust, used in the Firefox web browser. This is the binding to which this Haskell library is currently tied.
- dawn: a Google-backed WebGPU native implementation, written in C++, used in the Chrome web browser. In the future, we hope to support this backend too.
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, only macOS (with the Metal backend) is supported. The limitation is not fundamental and only exists because, so far, only macOS surface creation has been implemented. In the future, other backends should be added.
Dependence on GLFW-b
This package currently uses only GLFW-b for windowing and event processing. Clearly, it is undesirable to be tied to only a single library for this purpose, when options like sdl2 are available and might be preferred by many users.
GFLW is used because it is the windowing library used in the C examples from
wgpu-native
and it exposes an API to obtain a pointer to the underlying
windowing system's native window. In the future, other options will be
investigated as time permits.
Structure of Bindings
The bindings to wgpu-native
are structured in three packages:
- The
wgpu-raw-hs-codegen
package is a code generator for the raw bindings. It creates all the packages namedWGPU.Raw.Generated.*
(without exception!), using a custom code generator based on `langage-c`. This package is not in Hackage, since it is only used offline. - The wgpu-raw-hs
package provides raw bindings to
wgpu-native
. These raw bindings are mostly auto-generated, but have some manual curation of top-level types and function aliases. They are "raw" in the sense that they contain raw pointers and are not usable without manual management of memory to construct all the C structs that must be passed to the API. 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. Memory for structs passed to the raw API is managed using a type class (ToRaw
) that encapsulates a mapping between high-level API types and raw types. The possibility to allocate memory as part of this conversion (and later free it) is achieved by embedding conversion to the raw types inside theContT
continuation monad. - There are no callbacks. Several WebGPU native calls use callbacks to
indicate completion rather than blocking. The author decided that, in
the Haskell context, blocking was probably preferable. So,
internally, these calls are converted into a blocking form by waiting
on
MVar
s that are set by the callbacks. - Several parts of the API are tweaked slightly to more closely resemble the Rust API. This is done in cases where, for example, a parameter to the C API is unused except in one branch of a sum type. When this can be done easily enough, it is preferred to using the flattened "union" approach.
- Names are de-duplicated. Where possible, names are identical to the C API (sometimes with prefixes removed). However, where name conflicts exist, names are changed to somewhat-idiomatic Haskell variants.
- There are no more raw
Native Library Handling
The native library for wgpu-native
is not required at compile-time for this
package. Indeed, other packages containing executables that depend on this
one can be compiled without the native library! Instead, the library is
loaded dynamically and its symbols bound at runtime. This has the benefit
that the Haskell tooling need not be concerned with handling a Rust library
(yay!), but it is a point of common failure at runtime. To achieve this
independence, the header files for wgpu-native
are packaged inside
wgpu-raw-hs
. Of course, care should be taken to ensure that a
fully-compatible version of the library is used 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
withInstance
bracketing function:
withInstance
"libwgpu_native.dylib" (JustlogStdout
) $ inst -> do -- set the logging level (optional)setLogLevel
instWarn
-- run the rest of the program...
After creating an Instance
, you may next want to
create a surface.
Instance of the WGPU API.
An instance is loaded from a dynamic library using the withInstance
function.
Arguments
:: FilePath | Name of the |
-> Maybe LogCallback | Optional logging callback. |
-> (Instance -> IO a) | The Program. A function which takes an |
-> IO a | IO action which loads the WGPU |
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. Currently, only GLFW windows are supported for surface creation.
Once you have a GLFW window, you may create a Surface
for it using the
createGLFWSurface
function.
Once you have a Surface
, the next step is usually to
request an adapter that is compatible with it.
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
Eq Surface | |
Show Surface | |
ToRaw Surface WGPUSurface | |
Defined in WGPU.Internal.Surface |
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.
Handle to a physical graphics and/or compute device.
Request an Adapter
for a Surface
using the requestAdapter
function.
Instances
Eq Adapter | |
Show Adapter | |
ToRaw Adapter WGPUAdapter | |
Defined in WGPU.Internal.Adapter |
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.)
An open connection to a graphics and/or compute device.
A Device
may be created using the requestDevice
function.
Instances
Eq Device | |
Show Device | |
ToRaw Device WGPUDevice | |
Defined in WGPU.Internal.Device |
data DeviceDescriptor #
Describes a Device
.
Constructors
DeviceDescriptor | |
Instances
Eq DeviceDescriptor | |
Defined in WGPU.Internal.Device Methods (==) :: DeviceDescriptor -> DeviceDescriptor -> Bool # (/=) :: DeviceDescriptor -> DeviceDescriptor -> Bool # | |
Show DeviceDescriptor | |
Defined in WGPU.Internal.Device Methods showsPrec :: Int -> DeviceDescriptor -> ShowS # show :: DeviceDescriptor -> String # showList :: [DeviceDescriptor] -> ShowS # | |
Default DeviceDescriptor | |
Defined in WGPU.Internal.Device Methods def :: DeviceDescriptor # | |
ToRaw DeviceDescriptor WGPUDeviceExtras | |
Defined in WGPU.Internal.Device Methods raw :: DeviceDescriptor -> ContT c IO WGPUDeviceExtras # |
Device limits.
Represents the set of limits an adapter/device supports.
Constructors
Limits | |
Fields
|
Device features that are not guaranteed to be supported.
- NOTE: The Rust API currently has far more extensive
Features
. Perhaps they have not yet been ported to the C API? https://docs.rs/wgpu-types/0.9.0/wgpu_types/struct.Features.html
Constructors
Features | |
Fields |
Instances
Eq Features | |
Show Features | |
Default Features | |
Defined in WGPU.Internal.Device | |
ToRaw Features WGPUNativeFeature | |
Defined in WGPU.Internal.Device |
Arguments
:: Adapter |
|
-> DeviceDescriptor | The features and limits requested for the device. |
-> IO (Maybe Device) | The returned |
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
Eq TextureView | |
Defined in WGPU.Internal.Texture | |
Show TextureView | |
Defined in WGPU.Internal.Texture Methods showsPrec :: Int -> TextureView -> ShowS # show :: TextureView -> String # showList :: [TextureView] -> ShowS # | |
ToRaw TextureView WGPUTextureView | |
Defined in WGPU.Internal.Texture Methods raw :: TextureView -> ContT c IO WGPUTextureView # |
data TextureViewDimension #
Dimensions of a particular texture view.
Constructors
TextureViewDimension1D | |
TextureViewDimension2D | |
TextureViewDimension2DArray | |
TextureViewDimensionCube | |
TextureViewDimensionCubeArray | |
TextureViewDimension3D |
Instances
Eq TextureViewDimension | |
Defined in WGPU.Internal.Texture Methods (==) :: TextureViewDimension -> TextureViewDimension -> Bool # (/=) :: TextureViewDimension -> TextureViewDimension -> Bool # | |
Show TextureViewDimension | |
Defined in WGPU.Internal.Texture Methods showsPrec :: Int -> TextureViewDimension -> ShowS # show :: TextureViewDimension -> String # showList :: [TextureViewDimension] -> ShowS # | |
ToRaw TextureViewDimension WGPUTextureViewDimension | |
Defined in WGPU.Internal.Texture Methods raw :: TextureViewDimension -> ContT c IO WGPUTextureViewDimension # |
data TextureFormat #
Texture data format.
Constructors
Instances
Eq TextureFormat | |
Defined in WGPU.Internal.Texture Methods (==) :: TextureFormat -> TextureFormat -> Bool # (/=) :: TextureFormat -> TextureFormat -> Bool # | |
Show TextureFormat | |
Defined in WGPU.Internal.Texture Methods showsPrec :: Int -> TextureFormat -> ShowS # show :: TextureFormat -> String # showList :: [TextureFormat] -> ShowS # | |
ToRaw TextureFormat WGPUTextureFormat | |
Defined in WGPU.Internal.Texture Methods raw :: TextureFormat -> ContT c IO WGPUTextureFormat # |
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.
Constructors
TextureUsageCopySrc | |
TextureUsageCopyDst | |
TextureUsageSampled | |
TextureUsageStorage | |
TextureUsageRenderAttachment |
Instances
Eq TextureUsage | |
Defined in WGPU.Internal.Texture | |
Show TextureUsage | |
Defined in WGPU.Internal.Texture Methods showsPrec :: Int -> TextureUsage -> ShowS # show :: TextureUsage -> String # showList :: [TextureUsage] -> ShowS # | |
ToRaw TextureUsage WGPUTextureUsage | |
Defined in WGPU.Internal.Texture Methods raw :: TextureUsage -> ContT c IO WGPUTextureUsage # |
Swapchain
Instances
data SwapChainDescriptor #
Describes a swapchain.
Constructors
SwapChainDescriptor | |
Fields
|
Instances
Eq SwapChainDescriptor | |
Defined in WGPU.Internal.SwapChain Methods (==) :: SwapChainDescriptor -> SwapChainDescriptor -> Bool # (/=) :: SwapChainDescriptor -> SwapChainDescriptor -> Bool # | |
Show SwapChainDescriptor | |
Defined in WGPU.Internal.SwapChain Methods showsPrec :: Int -> SwapChainDescriptor -> ShowS # show :: SwapChainDescriptor -> String # showList :: [SwapChainDescriptor] -> ShowS # | |
ToRaw SwapChainDescriptor WGPUSwapChainDescriptor | |
Defined in WGPU.Internal.SwapChain Methods raw :: SwapChainDescriptor -> ContT c IO WGPUSwapChainDescriptor # |
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
|
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
Eq PresentMode | |
Defined in WGPU.Internal.SwapChain | |
Show PresentMode | |
Defined in WGPU.Internal.SwapChain Methods showsPrec :: Int -> PresentMode -> ShowS # show :: PresentMode -> String # showList :: [PresentMode] -> ShowS # | |
ToRaw PresentMode WGPUPresentMode | |
Defined in WGPU.Internal.SwapChain Methods raw :: PresentMode -> ContT c IO WGPUPresentMode # |
Arguments
:: Surface |
|
-> Adapter |
|
-> IO TextureFormat | IO action which returns the optimal texture format. |
Returns an optimal texture format to use for the swapchain with this adapter and surface.
Arguments
:: Device |
|
-> Surface |
|
-> SwapChainDescriptor | Description of the |
-> IO 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
:: SwapChain | Swap chain from which to fetch the current texture view. |
-> IO TextureView | IO action which returns the current swap chain texture view. |
Get the TextureView
for the current swap chain frame.
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.
Instances
Eq BindGroupLayout | |
Defined in WGPU.Internal.Binding Methods (==) :: BindGroupLayout -> BindGroupLayout -> Bool # (/=) :: BindGroupLayout -> BindGroupLayout -> Bool # | |
Show BindGroupLayout | |
Defined in WGPU.Internal.Binding Methods showsPrec :: Int -> BindGroupLayout -> ShowS # show :: BindGroupLayout -> String # showList :: [BindGroupLayout] -> ShowS # | |
ToRaw BindGroupLayout WGPUBindGroupLayout | |
Defined in WGPU.Internal.Binding Methods raw :: BindGroupLayout -> ContT c IO WGPUBindGroupLayout # |
data BindGroupLayoutDescriptor #
Describes a BindGroupLayout
.
Constructors
BindGroupLayoutDescriptor | |
Fields
|
Instances
Eq BindGroupLayoutDescriptor | |
Defined in WGPU.Internal.Binding Methods (==) :: BindGroupLayoutDescriptor -> BindGroupLayoutDescriptor -> Bool # (/=) :: BindGroupLayoutDescriptor -> BindGroupLayoutDescriptor -> Bool # | |
Show BindGroupLayoutDescriptor | |
Defined in WGPU.Internal.Binding Methods showsPrec :: Int -> BindGroupLayoutDescriptor -> ShowS # show :: BindGroupLayoutDescriptor -> String # showList :: [BindGroupLayoutDescriptor] -> ShowS # | |
ToRaw BindGroupLayoutDescriptor WGPUBindGroupLayoutDescriptor | |
Defined in WGPU.Internal.Binding Methods raw :: BindGroupLayoutDescriptor -> ContT c IO WGPUBindGroupLayoutDescriptor # |
data BindGroupLayoutEntry #
Describes a single binding inside a bind group.
Constructors
BindGroupLayoutEntry | |
Fields
|
Instances
Eq BindGroupLayoutEntry | |
Defined in WGPU.Internal.Binding Methods (==) :: BindGroupLayoutEntry -> BindGroupLayoutEntry -> Bool # (/=) :: BindGroupLayoutEntry -> BindGroupLayoutEntry -> Bool # | |
Show BindGroupLayoutEntry | |
Defined in WGPU.Internal.Binding Methods showsPrec :: Int -> BindGroupLayoutEntry -> ShowS # show :: BindGroupLayoutEntry -> String # showList :: [BindGroupLayoutEntry] -> ShowS # | |
ToRaw BindGroupLayoutEntry WGPUBindGroupLayoutEntry | |
Defined in WGPU.Internal.Binding Methods raw :: BindGroupLayoutEntry -> ContT c IO WGPUBindGroupLayoutEntry # |
Binding index.
This must match a shader index, and be unique inside a binding group layout.
data ShaderStage #
Describes the shader stages from which a binding will be visible.
Constructors
ShaderStage | |
Fields
|
Instances
Eq ShaderStage | |
Defined in WGPU.Internal.Binding | |
Show ShaderStage | |
Defined in WGPU.Internal.Binding Methods showsPrec :: Int -> ShaderStage -> ShowS # show :: ShaderStage -> String # showList :: [ShaderStage] -> ShowS # | |
ToRaw ShaderStage WGPUShaderStageFlags | |
Defined in WGPU.Internal.Binding Methods raw :: ShaderStage -> ContT c IO WGPUShaderStageFlags # |
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
Eq BindingType | |
Defined in WGPU.Internal.Binding | |
Show BindingType | |
Defined in WGPU.Internal.Binding Methods showsPrec :: Int -> BindingType -> ShowS # show :: BindingType -> String # showList :: [BindingType] -> ShowS # |
data BufferBindingLayout #
A buffer binding.
Constructors
BufferBindingLayout | |
Fields
|
Instances
Eq BufferBindingLayout | |
Defined in WGPU.Internal.Binding Methods (==) :: BufferBindingLayout -> BufferBindingLayout -> Bool # (/=) :: BufferBindingLayout -> BufferBindingLayout -> Bool # | |
Show BufferBindingLayout | |
Defined in WGPU.Internal.Binding Methods showsPrec :: Int -> BufferBindingLayout -> ShowS # show :: BufferBindingLayout -> String # showList :: [BufferBindingLayout] -> ShowS # | |
ToRaw BufferBindingLayout WGPUBufferBindingLayout | |
Defined in WGPU.Internal.Binding Methods raw :: BufferBindingLayout -> ContT c IO WGPUBufferBindingLayout # |
data SamplerBindingLayout #
A sampler binding that can be used to sample a texture.
Constructors
SamplerBindingLayoutFiltering | |
SamplerBindingLayoutNonFiltering | |
SamplerBindingLayoutComparison |
Instances
Eq SamplerBindingLayout | |
Defined in WGPU.Internal.Binding Methods (==) :: SamplerBindingLayout -> SamplerBindingLayout -> Bool # (/=) :: SamplerBindingLayout -> SamplerBindingLayout -> Bool # | |
Show SamplerBindingLayout | |
Defined in WGPU.Internal.Binding Methods showsPrec :: Int -> SamplerBindingLayout -> ShowS # show :: SamplerBindingLayout -> String # showList :: [SamplerBindingLayout] -> ShowS # | |
ToRaw SamplerBindingLayout WGPUSamplerBindingLayout | |
Defined in WGPU.Internal.Binding Methods raw :: SamplerBindingLayout -> ContT c IO WGPUSamplerBindingLayout # |
data TextureBindingLayout #
A texture binding.
Constructors
TextureBindingLayout | |
Fields
|
Instances
Eq TextureBindingLayout | |
Defined in WGPU.Internal.Binding Methods (==) :: TextureBindingLayout -> TextureBindingLayout -> Bool # (/=) :: TextureBindingLayout -> TextureBindingLayout -> Bool # | |
Show TextureBindingLayout | |
Defined in WGPU.Internal.Binding Methods showsPrec :: Int -> TextureBindingLayout -> ShowS # show :: TextureBindingLayout -> String # showList :: [TextureBindingLayout] -> ShowS # | |
ToRaw TextureBindingLayout WGPUTextureBindingLayout | |
Defined in WGPU.Internal.Binding Methods raw :: TextureBindingLayout -> ContT c IO WGPUTextureBindingLayout # |
data StorageTextureBindingLayout #
A storage texture binding.
Constructors
StorageTextureBindingLayout | |
Fields
|
Instances
Eq StorageTextureBindingLayout | |
Defined in WGPU.Internal.Binding Methods (==) :: StorageTextureBindingLayout -> StorageTextureBindingLayout -> Bool # (/=) :: StorageTextureBindingLayout -> StorageTextureBindingLayout -> Bool # | |
Show StorageTextureBindingLayout | |
Defined in WGPU.Internal.Binding Methods showsPrec :: Int -> StorageTextureBindingLayout -> ShowS # show :: StorageTextureBindingLayout -> String # showList :: [StorageTextureBindingLayout] -> ShowS # | |
ToRaw StorageTextureBindingLayout WGPUStorageTextureBindingLayout | |
Defined in WGPU.Internal.Binding Methods raw :: StorageTextureBindingLayout -> ContT c IO WGPUStorageTextureBindingLayout # |
data StorageTextureAccess #
Specific method of allowed access to a storage texture.
Constructors
StorageTextureAccessReadOnly | |
StorageTextureAccessWriteOnly | |
StorageTextureAccessReadWrite |
Instances
Eq StorageTextureAccess | |
Defined in WGPU.Internal.Binding Methods (==) :: StorageTextureAccess -> StorageTextureAccess -> Bool # (/=) :: StorageTextureAccess -> StorageTextureAccess -> Bool # | |
Show StorageTextureAccess | |
Defined in WGPU.Internal.Binding Methods showsPrec :: Int -> StorageTextureAccess -> ShowS # show :: StorageTextureAccess -> String # showList :: [StorageTextureAccess] -> ShowS # | |
ToRaw StorageTextureAccess WGPUStorageTextureAccess | |
Defined in WGPU.Internal.Binding Methods raw :: StorageTextureAccess -> ContT c IO WGPUStorageTextureAccess # |
data TextureSampleType #
Specific type of a sample in a texture binding.
Constructors
TextureSampleTypeFloat | |
Fields
| |
TextureSampleTypeDepth | |
TextureSampleTypeSignedInt | |
TextureSampleTypeUnsignedInt |
Instances
Eq TextureSampleType | |
Defined in WGPU.Internal.Binding Methods (==) :: TextureSampleType -> TextureSampleType -> Bool # (/=) :: TextureSampleType -> TextureSampleType -> Bool # | |
Show TextureSampleType | |
Defined in WGPU.Internal.Binding Methods showsPrec :: Int -> TextureSampleType -> ShowS # show :: TextureSampleType -> String # showList :: [TextureSampleType] -> ShowS # | |
ToRaw TextureSampleType WGPUTextureSampleType | |
Defined in WGPU.Internal.Binding Methods raw :: TextureSampleType -> ContT c IO WGPUTextureSampleType # |
data BufferBindingType #
Specific type of a buffer binding.
Instances
Eq BufferBindingType | |
Defined in WGPU.Internal.Binding Methods (==) :: BufferBindingType -> BufferBindingType -> Bool # (/=) :: BufferBindingType -> BufferBindingType -> Bool # | |
Show BufferBindingType | |
Defined in WGPU.Internal.Binding Methods showsPrec :: Int -> BufferBindingType -> ShowS # show :: BufferBindingType -> String # showList :: [BufferBindingType] -> ShowS # | |
ToRaw BufferBindingType WGPUBufferBindingType | |
Defined in WGPU.Internal.Binding Methods raw :: BufferBindingType -> ContT c IO WGPUBufferBindingType # |
Arguments
:: Device | The device for which the bind group layout will be created. |
-> BindGroupLayoutDescriptor | Description of the bind group layout. |
-> IO BindGroupLayout | IO action that creates a bind group layout. |
Creates a BindGroupLayout
.
Shader Modules
data ShaderModule #
Handle to a compiled shader module.
Instances
Eq ShaderModule | |
Defined in WGPU.Internal.Shader | |
Show ShaderModule | |
Defined in WGPU.Internal.Shader Methods showsPrec :: Int -> ShaderModule -> ShowS # show :: ShaderModule -> String # showList :: [ShaderModule] -> ShowS # | |
ToRaw ShaderModule WGPUShaderModule | |
Defined in WGPU.Internal.Shader Methods raw :: ShaderModule -> ContT c IO WGPUShaderModule # |
data ShaderModuleDescriptor #
Descriptor for a shader module.
Constructors
ShaderModuleDescriptor | |
Fields
|
Instances
Eq ShaderModuleDescriptor | |
Defined in WGPU.Internal.Shader Methods (==) :: ShaderModuleDescriptor -> ShaderModuleDescriptor -> Bool # (/=) :: ShaderModuleDescriptor -> ShaderModuleDescriptor -> Bool # | |
Show ShaderModuleDescriptor | |
Defined in WGPU.Internal.Shader Methods showsPrec :: Int -> ShaderModuleDescriptor -> ShowS # show :: ShaderModuleDescriptor -> String # showList :: [ShaderModuleDescriptor] -> ShowS # | |
ToRaw ShaderModuleDescriptor WGPUShaderModuleDescriptor | |
Defined in WGPU.Internal.Shader Methods raw :: ShaderModuleDescriptor -> ContT c IO WGPUShaderModuleDescriptor # |
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
Eq ShaderSource | |
Defined in WGPU.Internal.Shader | |
Show ShaderSource | |
Defined in WGPU.Internal.Shader Methods showsPrec :: Int -> ShaderSource -> ShowS # show :: ShaderSource -> String # showList :: [ShaderSource] -> ShowS # |
Pre-compiled SPIRV module bytes.
Constructors
SPIRV ByteString |
Instances
WGSL shader source code.
Instances
newtype ShaderEntryPoint #
Name of a shader entry point.
Constructors
ShaderEntryPoint | |
Fields |
Instances
Eq ShaderEntryPoint | |
Defined in WGPU.Internal.Shader Methods (==) :: ShaderEntryPoint -> ShaderEntryPoint -> Bool # (/=) :: ShaderEntryPoint -> ShaderEntryPoint -> Bool # | |
Show ShaderEntryPoint | |
Defined in WGPU.Internal.Shader Methods showsPrec :: Int -> ShaderEntryPoint -> ShowS # show :: ShaderEntryPoint -> String # showList :: [ShaderEntryPoint] -> ShowS # | |
IsString ShaderEntryPoint | |
Defined in WGPU.Internal.Shader Methods fromString :: String -> ShaderEntryPoint # | |
ToRawPtr ShaderEntryPoint CChar | |
Defined in WGPU.Internal.Shader |
Arguments
:: Device | Device for the shader. |
-> ShaderModuleDescriptor | Descriptor of the shader module. |
-> IO ShaderModule | IO action producing the shader module. |
Create a shader module from either SPIR-V or WGSL source code.
Arguments
:: Device | Device for which the shader should be created. |
-> Text | Debugging label for the shader. |
-> SPIRV | Shader source code (SPIR-V bytestring). |
-> IO ShaderModule | IO action creating the shader module. |
Create a shader module from SPIR-V source code.
Arguments
:: Device | Device for which the shader should be created. |
-> Text | Debugging label for the shader. |
-> WGSL | Shader source code (WGSL source string). |
-> IO ShaderModule | IO action creating the shader module. |
Create a shader module from WGSL source code.
Pipelines
Compute
Render
data PipelineLayout #
Instances
Eq PipelineLayout | |
Defined in WGPU.Internal.Pipeline Methods (==) :: PipelineLayout -> PipelineLayout -> Bool # (/=) :: PipelineLayout -> PipelineLayout -> Bool # | |
Show PipelineLayout | |
Defined in WGPU.Internal.Pipeline Methods showsPrec :: Int -> PipelineLayout -> ShowS # show :: PipelineLayout -> String # showList :: [PipelineLayout] -> ShowS # | |
ToRaw PipelineLayout WGPUPipelineLayout | |
Defined in WGPU.Internal.Pipeline Methods raw :: PipelineLayout -> ContT c IO WGPUPipelineLayout # |
data RenderPipeline #
Instances
Eq RenderPipeline | |
Defined in WGPU.Internal.RenderPass Methods (==) :: RenderPipeline -> RenderPipeline -> Bool # (/=) :: RenderPipeline -> RenderPipeline -> Bool # | |
Show RenderPipeline | |
Defined in WGPU.Internal.RenderPass Methods showsPrec :: Int -> RenderPipeline -> ShowS # show :: RenderPipeline -> String # showList :: [RenderPipeline] -> ShowS # | |
ToRaw RenderPipeline WGPURenderPipeline | |
Defined in WGPU.Internal.RenderPass Methods raw :: RenderPipeline -> ContT c IO WGPURenderPipeline # |
data PipelineLayoutDescriptor #
Describes a pipeline layout.
Constructors
PipelineLayoutDescriptor | |
Fields
|
Instances
Eq PipelineLayoutDescriptor | |
Defined in WGPU.Internal.Pipeline Methods (==) :: PipelineLayoutDescriptor -> PipelineLayoutDescriptor -> Bool # (/=) :: PipelineLayoutDescriptor -> PipelineLayoutDescriptor -> Bool # | |
Show PipelineLayoutDescriptor | |
Defined in WGPU.Internal.Pipeline Methods showsPrec :: Int -> PipelineLayoutDescriptor -> ShowS # show :: PipelineLayoutDescriptor -> String # showList :: [PipelineLayoutDescriptor] -> ShowS # | |
ToRaw PipelineLayoutDescriptor WGPUPipelineLayoutDescriptor | |
Defined in WGPU.Internal.Pipeline Methods raw :: PipelineLayoutDescriptor -> ContT c IO WGPUPipelineLayoutDescriptor # |
data RenderPipelineDescriptor #
Describes a render (graphics) pipeline.
Constructors
RenderPipelineDescriptor | |
Fields
|
Instances
Eq RenderPipelineDescriptor | |
Defined in WGPU.Internal.Pipeline Methods (==) :: RenderPipelineDescriptor -> RenderPipelineDescriptor -> Bool # (/=) :: RenderPipelineDescriptor -> RenderPipelineDescriptor -> Bool # | |
Show RenderPipelineDescriptor | |
Defined in WGPU.Internal.Pipeline Methods showsPrec :: Int -> RenderPipelineDescriptor -> ShowS # show :: RenderPipelineDescriptor -> String # showList :: [RenderPipelineDescriptor] -> ShowS # | |
ToRaw RenderPipelineDescriptor WGPURenderPipelineDescriptor | |
Defined in WGPU.Internal.Pipeline Methods raw :: RenderPipelineDescriptor -> ContT c IO WGPURenderPipelineDescriptor # |
data VertexFormat #
Vertex format for a vertex attribute.
Constructors
Instances
Eq VertexFormat | |
Defined in WGPU.Internal.Pipeline | |
Show VertexFormat | |
Defined in WGPU.Internal.Pipeline Methods showsPrec :: Int -> VertexFormat -> ShowS # show :: VertexFormat -> String # showList :: [VertexFormat] -> ShowS # | |
ToRaw VertexFormat WGPUVertexFormat | Convert a |
Defined in WGPU.Internal.Pipeline Methods raw :: VertexFormat -> ContT c IO WGPUVertexFormat # |
data VertexAttribute #
Vertex inputs (attributes) to shaders.
Constructors
VertexAttribute | |
Fields
|
Instances
Eq VertexAttribute | |
Defined in WGPU.Internal.Pipeline Methods (==) :: VertexAttribute -> VertexAttribute -> Bool # (/=) :: VertexAttribute -> VertexAttribute -> Bool # | |
Show VertexAttribute | |
Defined in WGPU.Internal.Pipeline Methods showsPrec :: Int -> VertexAttribute -> ShowS # show :: VertexAttribute -> String # showList :: [VertexAttribute] -> ShowS # | |
ToRaw VertexAttribute WGPUVertexAttribute | |
Defined in WGPU.Internal.Pipeline Methods raw :: VertexAttribute -> ContT c IO WGPUVertexAttribute # |
data InputStepMode #
Determines when vertex data is advanced.
Constructors
InputStepModeVertex | Input data is advanced every vertex. |
InputStepModeInstance | Input data is advanced every instance. |
Instances
Eq InputStepMode | |
Defined in WGPU.Internal.Pipeline Methods (==) :: InputStepMode -> InputStepMode -> Bool # (/=) :: InputStepMode -> InputStepMode -> Bool # | |
Show InputStepMode | |
Defined in WGPU.Internal.Pipeline Methods showsPrec :: Int -> InputStepMode -> ShowS # show :: InputStepMode -> String # showList :: [InputStepMode] -> ShowS # | |
ToRaw InputStepMode WGPUInputStepMode | Convert an |
Defined in WGPU.Internal.Pipeline Methods raw :: InputStepMode -> ContT c IO WGPUInputStepMode # |
data VertexBufferLayout #
Describes how a vertex buffer is interpreted.
Constructors
VertexBufferLayout | |
Fields
|
Instances
Eq VertexBufferLayout | |
Defined in WGPU.Internal.Pipeline Methods (==) :: VertexBufferLayout -> VertexBufferLayout -> Bool # (/=) :: VertexBufferLayout -> VertexBufferLayout -> Bool # | |
Show VertexBufferLayout | |
Defined in WGPU.Internal.Pipeline Methods showsPrec :: Int -> VertexBufferLayout -> ShowS # show :: VertexBufferLayout -> String # showList :: [VertexBufferLayout] -> ShowS # | |
ToRaw VertexBufferLayout WGPUVertexBufferLayout | |
Defined in WGPU.Internal.Pipeline Methods raw :: VertexBufferLayout -> ContT c IO WGPUVertexBufferLayout # |
data VertexState #
Describes the vertex process in a render pipeline.
Constructors
VertexState | |
Fields
|
Instances
Eq VertexState | |
Defined in WGPU.Internal.Pipeline | |
Show VertexState | |
Defined in WGPU.Internal.Pipeline Methods showsPrec :: Int -> VertexState -> ShowS # show :: VertexState -> String # showList :: [VertexState] -> ShowS # | |
ToRaw VertexState WGPUVertexState | |
Defined in WGPU.Internal.Pipeline Methods raw :: VertexState -> ContT c IO WGPUVertexState # |
data PrimitiveTopology #
Primitive type out of which an input mesh is composed.
Constructors
PrimitiveTopologyPointList | |
PrimitiveTopologyLineList | |
PrimitiveTopologyLineStrip | |
PrimitiveTopologyTriangleList | |
PrimitiveTopologyTriangleStrip |
Instances
Eq PrimitiveTopology | |
Defined in WGPU.Internal.Pipeline Methods (==) :: PrimitiveTopology -> PrimitiveTopology -> Bool # (/=) :: PrimitiveTopology -> PrimitiveTopology -> Bool # | |
Show PrimitiveTopology | |
Defined in WGPU.Internal.Pipeline Methods showsPrec :: Int -> PrimitiveTopology -> ShowS # show :: PrimitiveTopology -> String # showList :: [PrimitiveTopology] -> ShowS # | |
Default PrimitiveTopology | |
Defined in WGPU.Internal.Pipeline Methods | |
ToRaw PrimitiveTopology WGPUPrimitiveTopology | Convert a |
Defined in WGPU.Internal.Pipeline Methods raw :: PrimitiveTopology -> ContT c IO WGPUPrimitiveTopology # |
data IndexFormat #
Format of indices used within a pipeline.
Constructors
IndexFormatUint16 | Indices are 16-bit unsigned integers ( |
IndexFormatUint32 | Indices are 32-bit unsigned integers ( |
Instances
Eq IndexFormat | |
Defined in WGPU.Internal.Pipeline | |
Show IndexFormat | |
Defined in WGPU.Internal.Pipeline Methods showsPrec :: Int -> IndexFormat -> ShowS # show :: IndexFormat -> String # showList :: [IndexFormat] -> ShowS # | |
ToRaw IndexFormat WGPUIndexFormat | Convert an |
Defined in WGPU.Internal.Pipeline Methods raw :: IndexFormat -> ContT c IO WGPUIndexFormat # |
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
Eq FrontFace | |
Show FrontFace | |
Default FrontFace | |
Defined in WGPU.Internal.Pipeline | |
ToRaw FrontFace WGPUFrontFace | Convert a |
Defined in WGPU.Internal.Pipeline |
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
Eq CullMode | |
Show CullMode | |
Default CullMode | |
Defined in WGPU.Internal.Pipeline | |
ToRaw CullMode WGPUCullMode | Convert a |
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
|
Instances
Eq PrimitiveState | |
Defined in WGPU.Internal.Pipeline Methods (==) :: PrimitiveState -> PrimitiveState -> Bool # (/=) :: PrimitiveState -> PrimitiveState -> Bool # | |
Show PrimitiveState | |
Defined in WGPU.Internal.Pipeline Methods showsPrec :: Int -> PrimitiveState -> ShowS # show :: PrimitiveState -> String # showList :: [PrimitiveState] -> ShowS # | |
Default PrimitiveState | |
Defined in WGPU.Internal.Pipeline Methods def :: PrimitiveState # | |
ToRaw PrimitiveState WGPUPrimitiveState | |
Defined in WGPU.Internal.Pipeline Methods raw :: PrimitiveState -> ContT c IO WGPUPrimitiveState # |
data StencilOperation #
Operation to perform on a stencil value.
Constructors
Instances
Eq StencilOperation | |
Defined in WGPU.Internal.Pipeline Methods (==) :: StencilOperation -> StencilOperation -> Bool # (/=) :: StencilOperation -> StencilOperation -> Bool # | |
Show StencilOperation | |
Defined in WGPU.Internal.Pipeline Methods showsPrec :: Int -> StencilOperation -> ShowS # show :: StencilOperation -> String # showList :: [StencilOperation] -> ShowS # | |
ToRaw StencilOperation WGPUStencilOperation | Convert a |
Defined in WGPU.Internal.Pipeline Methods raw :: StencilOperation -> ContT c IO WGPUStencilOperation # |
data StencilState #
State of the stencil operation (fixed pipeline stage).
Constructors
StencilState | |
Fields
|
Instances
Eq StencilState | |
Defined in WGPU.Internal.Pipeline | |
Show StencilState | |
Defined in WGPU.Internal.Pipeline Methods showsPrec :: Int -> StencilState -> ShowS # show :: StencilState -> String # showList :: [StencilState] -> ShowS # |
data DepthBiasState #
Describes the biasing setting for the depth target.
Constructors
DepthBiasState | |
Instances
Eq DepthBiasState | |
Defined in WGPU.Internal.Pipeline Methods (==) :: DepthBiasState -> DepthBiasState -> Bool # (/=) :: DepthBiasState -> DepthBiasState -> Bool # | |
Show DepthBiasState | |
Defined in WGPU.Internal.Pipeline Methods showsPrec :: Int -> DepthBiasState -> ShowS # show :: DepthBiasState -> String # showList :: [DepthBiasState] -> ShowS # |
data DepthStencilState #
Describes the depth / stencil state of a render pipeline.
Constructors
DepthStencilState | |
Fields
|
Instances
Eq DepthStencilState | |
Defined in WGPU.Internal.Pipeline Methods (==) :: DepthStencilState -> DepthStencilState -> Bool # (/=) :: DepthStencilState -> DepthStencilState -> Bool # | |
Show DepthStencilState | |
Defined in WGPU.Internal.Pipeline Methods showsPrec :: Int -> DepthStencilState -> ShowS # show :: DepthStencilState -> String # showList :: [DepthStencilState] -> ShowS # | |
ToRaw DepthStencilState WGPUDepthStencilState | |
Defined in WGPU.Internal.Pipeline Methods raw :: DepthStencilState -> ContT c IO WGPUDepthStencilState # |
data MultisampleState #
Describes the multi-sampling state of a render pipeline.
Constructors
MultisampleState | |
Fields
|
Instances
Eq MultisampleState | |
Defined in WGPU.Internal.Pipeline Methods (==) :: MultisampleState -> MultisampleState -> Bool # (/=) :: MultisampleState -> MultisampleState -> Bool # | |
Show MultisampleState | |
Defined in WGPU.Internal.Pipeline Methods showsPrec :: Int -> MultisampleState -> ShowS # show :: MultisampleState -> String # showList :: [MultisampleState] -> ShowS # | |
ToRaw MultisampleState WGPUMultisampleState | |
Defined in WGPU.Internal.Pipeline Methods raw :: MultisampleState -> ContT c IO WGPUMultisampleState # |
data BlendFactor #
Alpha blend factor.
Constructors
Instances
Eq BlendFactor | |
Defined in WGPU.Internal.Pipeline | |
Show BlendFactor | |
Defined in WGPU.Internal.Pipeline Methods showsPrec :: Int -> BlendFactor -> ShowS # show :: BlendFactor -> String # showList :: [BlendFactor] -> ShowS # | |
ToRaw BlendFactor WGPUBlendFactor | Convert a |
Defined in WGPU.Internal.Pipeline Methods raw :: BlendFactor -> ContT c IO WGPUBlendFactor # |
data BlendOperation #
Alpha blending operation.
Constructors
BlendOperationAdd | |
BlendOperationSubtract | |
BlendOperationReverseSubtract | |
BlendOperationMin | |
BlendOperationMax |
Instances
Eq BlendOperation | |
Defined in WGPU.Internal.Pipeline Methods (==) :: BlendOperation -> BlendOperation -> Bool # (/=) :: BlendOperation -> BlendOperation -> Bool # | |
Show BlendOperation | |
Defined in WGPU.Internal.Pipeline Methods showsPrec :: Int -> BlendOperation -> ShowS # show :: BlendOperation -> String # showList :: [BlendOperation] -> ShowS # | |
ToRaw BlendOperation WGPUBlendOperation | Convert a |
Defined in WGPU.Internal.Pipeline Methods raw :: BlendOperation -> ContT c IO WGPUBlendOperation # |
data BlendComponent #
Describes the blend component of a pipeline.
Constructors
BlendComponent | |
Fields
|
Instances
Eq BlendComponent | |
Defined in WGPU.Internal.Pipeline Methods (==) :: BlendComponent -> BlendComponent -> Bool # (/=) :: BlendComponent -> BlendComponent -> Bool # | |
Show BlendComponent | |
Defined in WGPU.Internal.Pipeline Methods showsPrec :: Int -> BlendComponent -> ShowS # show :: BlendComponent -> String # showList :: [BlendComponent] -> ShowS # | |
Default BlendComponent | |
Defined in WGPU.Internal.Pipeline Methods def :: BlendComponent # | |
ToRaw BlendComponent WGPUBlendComponent | |
Defined in WGPU.Internal.Pipeline Methods raw :: BlendComponent -> ContT c IO WGPUBlendComponent # |
data BlendState #
Describes the blend state of a render pipeline.
Constructors
BlendState | |
Fields
|
Instances
Eq BlendState | |
Defined in WGPU.Internal.Pipeline | |
Show BlendState | |
Defined in WGPU.Internal.Pipeline Methods showsPrec :: Int -> BlendState -> ShowS # show :: BlendState -> String # showList :: [BlendState] -> ShowS # | |
ToRaw BlendState WGPUBlendState | |
Defined in WGPU.Internal.Pipeline Methods raw :: BlendState -> ContT c IO WGPUBlendState # |
data ColorWriteMask #
Describes which color channels are written.
Constructors
ColorWriteMask | |
Instances
Eq ColorWriteMask | |
Defined in WGPU.Internal.Pipeline Methods (==) :: ColorWriteMask -> ColorWriteMask -> Bool # (/=) :: ColorWriteMask -> ColorWriteMask -> Bool # | |
Show ColorWriteMask | |
Defined in WGPU.Internal.Pipeline Methods showsPrec :: Int -> ColorWriteMask -> ShowS # show :: ColorWriteMask -> String # showList :: [ColorWriteMask] -> ShowS # | |
ToRaw ColorWriteMask WGPUColorWriteMask | |
Defined in WGPU.Internal.Pipeline Methods raw :: ColorWriteMask -> ContT c IO WGPUColorWriteMask # |
data ColorTargetState #
Describes the color state of a render pipeline.
Constructors
ColorTargetState | |
Fields
|
Instances
Eq ColorTargetState | |
Defined in WGPU.Internal.Pipeline Methods (==) :: ColorTargetState -> ColorTargetState -> Bool # (/=) :: ColorTargetState -> ColorTargetState -> Bool # | |
Show ColorTargetState | |
Defined in WGPU.Internal.Pipeline Methods showsPrec :: Int -> ColorTargetState -> ShowS # show :: ColorTargetState -> String # showList :: [ColorTargetState] -> ShowS # | |
ToRaw ColorTargetState WGPUColorTargetState | |
Defined in WGPU.Internal.Pipeline Methods raw :: ColorTargetState -> ContT c IO WGPUColorTargetState # |
data FragmentState #
Describes the fragment processing in a render pipeline.
Constructors
FragmentState | |
Fields
|
Instances
Eq FragmentState | |
Defined in WGPU.Internal.Pipeline Methods (==) :: FragmentState -> FragmentState -> Bool # (/=) :: FragmentState -> FragmentState -> Bool # | |
Show FragmentState | |
Defined in WGPU.Internal.Pipeline Methods showsPrec :: Int -> FragmentState -> ShowS # show :: FragmentState -> String # showList :: [FragmentState] -> ShowS # | |
ToRaw FragmentState WGPUFragmentState | |
Defined in WGPU.Internal.Pipeline Methods raw :: FragmentState -> ContT c IO WGPUFragmentState # |
Arguments
:: Device | The device for which the pipeline layout will be created. |
-> PipelineLayoutDescriptor | Descriptor of the pipeline. |
-> IO PipelineLayout |
Create a pipeline layout.
colorWriteMaskAll :: ColorWriteMask #
A ColorWriteMask
that writes all colors and the alpha value.
Command Buffers
data CommandBuffer #
Instances
Eq CommandBuffer | |
Defined in WGPU.Internal.CommandBuffer Methods (==) :: CommandBuffer -> CommandBuffer -> Bool # (/=) :: CommandBuffer -> CommandBuffer -> Bool # | |
Show CommandBuffer | |
Defined in WGPU.Internal.CommandBuffer Methods showsPrec :: Int -> CommandBuffer -> ShowS # show :: CommandBuffer -> String # showList :: [CommandBuffer] -> ShowS # | |
ToRaw CommandBuffer WGPUCommandBuffer | |
Defined in WGPU.Internal.CommandBuffer Methods raw :: CommandBuffer -> ContT c IO WGPUCommandBuffer # |
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.
Instances
Eq CommandEncoder | |
Defined in WGPU.Internal.CommandEncoder Methods (==) :: CommandEncoder -> CommandEncoder -> Bool # (/=) :: CommandEncoder -> CommandEncoder -> Bool # | |
Show CommandEncoder | |
Defined in WGPU.Internal.CommandEncoder Methods showsPrec :: Int -> CommandEncoder -> ShowS # show :: CommandEncoder -> String # showList :: [CommandEncoder] -> ShowS # | |
ToRaw CommandEncoder WGPUCommandEncoder | |
Defined in WGPU.Internal.CommandEncoder Methods raw :: CommandEncoder -> ContT c IO WGPUCommandEncoder # |
data RenderPassEncoder #
Instances
Eq RenderPassEncoder | |
Defined in WGPU.Internal.RenderPass Methods (==) :: RenderPassEncoder -> RenderPassEncoder -> Bool # (/=) :: RenderPassEncoder -> RenderPassEncoder -> Bool # | |
Show RenderPassEncoder | |
Defined in WGPU.Internal.RenderPass Methods showsPrec :: Int -> RenderPassEncoder -> ShowS # show :: RenderPassEncoder -> String # showList :: [RenderPassEncoder] -> ShowS # | |
ToRaw RenderPassEncoder WGPURenderPassEncoder | |
Defined in WGPU.Internal.RenderPass Methods raw :: RenderPassEncoder -> ContT c IO WGPURenderPassEncoder # |
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. |
Instances
Eq StoreOp | |
Show StoreOp | |
ToRaw StoreOp WGPUStoreOp | |
Defined in WGPU.Internal.RenderPass |
data Operations a #
Constructors
Operations | |
Instances
Eq a => Eq (Operations a) | |
Defined in WGPU.Internal.RenderPass | |
Show a => Show (Operations a) | |
Defined in WGPU.Internal.RenderPass Methods showsPrec :: Int -> Operations a -> ShowS # show :: Operations a -> String # showList :: [Operations a] -> ShowS # |
data RenderPassColorAttachment #
Describes a color attachment to a render pass.
Constructors
RenderPassColorAttachment | |
Fields
|
Instances
Eq RenderPassColorAttachment | |
Defined in WGPU.Internal.RenderPass Methods (==) :: RenderPassColorAttachment -> RenderPassColorAttachment -> Bool # (/=) :: RenderPassColorAttachment -> RenderPassColorAttachment -> Bool # | |
Show RenderPassColorAttachment | |
Defined in WGPU.Internal.RenderPass Methods showsPrec :: Int -> RenderPassColorAttachment -> ShowS # show :: RenderPassColorAttachment -> String # showList :: [RenderPassColorAttachment] -> ShowS # | |
ToRaw RenderPassColorAttachment WGPURenderPassColorAttachment | |
Defined in WGPU.Internal.RenderPass Methods raw :: RenderPassColorAttachment -> ContT c IO WGPURenderPassColorAttachment # |
data RenderPassDepthStencilAttachment #
Describes a depth/stencil attachment to a render pass.
Constructors
RenderPassDepthStencilAttachment | |
Fields
|
Instances
data RenderPassDescriptor #
Describes the attachments of a render pass.
Constructors
RenderPassDescriptor | |
Fields
|
Instances
Eq RenderPassDescriptor | |
Defined in WGPU.Internal.RenderPass Methods (==) :: RenderPassDescriptor -> RenderPassDescriptor -> Bool # (/=) :: RenderPassDescriptor -> RenderPassDescriptor -> Bool # | |
Show RenderPassDescriptor | |
Defined in WGPU.Internal.RenderPass Methods showsPrec :: Int -> RenderPassDescriptor -> ShowS # show :: RenderPassDescriptor -> String # showList :: [RenderPassDescriptor] -> ShowS # | |
ToRaw RenderPassDescriptor WGPURenderPassDescriptor | |
Defined in WGPU.Internal.RenderPass Methods raw :: RenderPassDescriptor -> ContT c IO WGPURenderPassDescriptor # |
Half open range. It includes the start
value but not the end
value.
Constructors
Range | |
Fields
|
Arguments
:: Device | Device for which to create the command encoder. |
-> Text | Debug label for the command encoder. |
-> IO CommandEncoder | IO action that returns the command encoder. |
Create an empty command encoder.
Arguments
:: CommandEncoder | Command encoder to finish. |
-> Text | Debugging label for the command buffer. |
-> IO CommandBuffer | IO action which returns the command buffer. |
Finish encoding commands, returning a command buffer.
Arguments
:: CommandEncoder |
|
-> RenderPassDescriptor | Description of the render pass. |
-> IO RenderPassEncoder | IO action which returns the render pass encoder. |
Begins recording of a render pass.
Arguments
:: RenderPassEncoder | Render pass encoder on which to act. |
-> RenderPipeline | Render pipeline to set active. |
-> IO () | IO action which sets the active render pipeline. |
Sets the active render pipeline.
Subsequent draw calls will exhibit the behaviour defined by the pipeline.
Arguments
:: RenderPassEncoder | Render pass encoder on which to act. |
-> Range Word32 | Range of vertices to draw. |
-> Range Word32 | Range of instances to draw. |
-> IO () | IO action which stores the draw command. |
Draws primitives from the active vertex buffers.
Arguments
:: RenderPassEncoder | Render pass encoder on which to finish recording. |
-> IO () | IO action that finishes recording. |
Finish recording of a render pass.
Queue
queueSubmit :: Queue -> Vector CommandBuffer -> IO () #
Submit a list of command buffers to a device queue.
Version
Version of WGPU native.
getVersion :: Instance -> IO 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
Logging level.
type LogCallback = LogLevel -> Text -> IO () #
Logging callback function.
setLogLevel :: Instance -> LogLevel -> IO () #
Set the current logging level for the instance.
logStdout :: LogLevel -> Text -> IO () #
A logging function which prints to stdout
.
This logging function can be supplied to withInstance
to print logging
messages to stdout
for debugging purposes.
logLevelToText :: LogLevel -> Text #
Convert a LogLevel
to a text string.
Multipurpose
data CompareFunction #
Comparison function used for depth and stencil operations.
Constructors
CompareFunctionNever | |
CompareFunctionLess | |
CompareFunctionEqual | |
CompareFunctionLessEqual | |
CompareFunctionGreater | |
CompareFunctionNotEqual | |
CompareFunctionGreaterEqual | |
CompareFunctionAlways |
Instances
Eq CompareFunction | |
Defined in WGPU.Internal.Multipurpose Methods (==) :: CompareFunction -> CompareFunction -> Bool # (/=) :: CompareFunction -> CompareFunction -> Bool # | |
Show CompareFunction | |
Defined in WGPU.Internal.Multipurpose Methods showsPrec :: Int -> CompareFunction -> ShowS # show :: CompareFunction -> String # showList :: [CompareFunction] -> ShowS # | |
ToRaw CompareFunction WGPUCompareFunction | Convert a |
Defined in WGPU.Internal.Multipurpose Methods raw :: CompareFunction -> ContT c IO WGPUCompareFunction # |