Copyright | Copyright (C) Jonathan Merritt 2021 |
---|---|
License | BSD-3-Clause |
Maintainer | Jonathan Merritt <j.s.merritt@gmail.com> |
Stability | experimental |
Portability | macOS, Linux, Windows |
Safe Haskell | None |
Language | Haskell2010 |
WGPU
Description
Layout of this module should be guided by the evolving WebGPU Specification.
Synopsis
- data Instance
- withPlatformInstance :: MonadIO m => (m Instance -> (Instance -> m ()) -> r) -> r
- withInstance :: MonadIO m => FilePath -> (m Instance -> (Instance -> m ()) -> r) -> r
- data Surface
- data Adapter
- data AdapterType
- data BackendType
- data AdapterProperties = AdapterProperties {
- deviceID :: !Word32
- vendorID :: !Word32
- adapterName :: !Text
- driverDescription :: !Text
- adapterType :: !AdapterType
- backendType :: !BackendType
- requestAdapter :: MonadIO m => Surface -> m (Maybe Adapter)
- getAdapterProperties :: MonadIO m => Adapter -> m AdapterProperties
- adapterPropertiesToText :: AdapterProperties -> Text
- data Device
- data DeviceDescriptor = DeviceDescriptor {}
- data Limits = Limits {}
- newtype Features = Features {}
- requestDevice :: MonadIO m => Adapter -> DeviceDescriptor -> m (Maybe Device)
- data Buffer
- data BufferDescriptor = BufferDescriptor {
- bufferLabel :: !Text
- bufferSize :: !ByteSize
- bufferUsage :: !BufferUsage
- mappedAtCreation :: Bool
- data BufferUsage = BufferUsage {
- bufMapRead :: !Bool
- bufMapWrite :: !Bool
- bufCopySrc :: !Bool
- bufCopyDst :: !Bool
- bufIndex :: !Bool
- bufVertex :: !Bool
- bufUniform :: !Bool
- bufStorage :: !Bool
- bufIndirect :: !Bool
- createBuffer :: MonadIO m => Device -> BufferDescriptor -> m Buffer
- createBufferInit :: forall a m. (MonadIO m, ReadableMemoryBuffer a) => Device -> Text -> BufferUsage -> a -> m Buffer
- data Texture
- 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 = TextureUsage {
- texCopySrc :: !Bool
- texCopyDst :: !Bool
- texSampled :: !Bool
- texStorage :: !Bool
- texRenderAttachment :: !Bool
- data Extent3D = Extent3D {}
- data TextureDimension
- data TextureDescriptor = TextureDescriptor {
- textureLabel :: !Text
- textureSize :: !Extent3D
- mipLevelCount :: !Word32
- sampleCount :: !Word32
- dimension :: !TextureDimension
- format :: !TextureFormat
- textureUsage :: !TextureUsage
- data Origin3D = Origin3D {}
- data TextureAspect
- data ImageCopyTexture = ImageCopyTexture {}
- data TextureDataLayout = TextureDataLayout {
- textureOffset :: !Word64
- bytesPerRow :: !Word32
- rowsPerImage :: !Word32
- data TextureViewDescriptor = TextureViewDescriptor {}
- createTexture :: MonadIO m => Device -> TextureDescriptor -> m Texture
- createView :: MonadIO m => Texture -> TextureViewDescriptor -> m TextureView
- data SwapChain
- data SwapChainDescriptor = SwapChainDescriptor {}
- data PresentMode
- getSwapChainPreferredFormat :: MonadIO m => Surface -> Adapter -> m TextureFormat
- createSwapChain :: MonadIO m => Device -> Surface -> SwapChainDescriptor -> m SwapChain
- getSwapChainCurrentTextureView :: MonadIO m => SwapChain -> m TextureView
- swapChainPresent :: MonadIO m => SwapChain -> m ()
- data Sampler
- data AddressMode
- data FilterMode
- data SamplerDescriptor = SamplerDescriptor {}
- createSampler :: MonadIO m => Device -> SamplerDescriptor -> m Sampler
- data BindGroup
- data BindGroupLayout
- data BindGroupDescriptor = BindGroupDescriptor {}
- data BindGroupEntry = BindGroupEntry {
- binding :: !Binding
- resource :: !BindingResource
- 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
- data BindingResource
- data BufferBinding = BufferBinding {}
- createBindGroup :: MonadIO m => Device -> BindGroupDescriptor -> m BindGroup
- createBindGroupLayout :: MonadIO m => Device -> BindGroupLayoutDescriptor -> m BindGroupLayout
- data ShaderModule
- data ShaderModuleDescriptor = ShaderModuleDescriptor {
- shaderLabel :: !Text
- source :: !ShaderSource
- data ShaderSource
- newtype SPIRV = SPIRV ByteString
- newtype WGSL = WGSL Text
- newtype ShaderEntryPoint = ShaderEntryPoint {}
- createShaderModule :: MonadIO m => Device -> ShaderModuleDescriptor -> m ShaderModule
- createShaderModuleSPIRV :: MonadIO m => Device -> Text -> SPIRV -> m ShaderModule
- createShaderModuleWGSL :: MonadIO m => Device -> Text -> WGSL -> m 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 :: MonadIO m => Device -> PipelineLayoutDescriptor -> m PipelineLayout
- createRenderPipeline :: MonadIO m => Device -> RenderPipelineDescriptor -> m 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 :: MonadIO m => Device -> Text -> m CommandEncoder
- commandEncoderFinish :: MonadIO m => CommandEncoder -> Text -> m CommandBuffer
- 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 ()
- data Queue
- getQueue :: MonadIO m => Device -> m Queue
- queueSubmit :: MonadIO m => Queue -> Vector CommandBuffer -> m ()
- queueWriteTexture :: (MonadIO m, ReadableMemoryBuffer a) => Queue -> ImageCopyTexture -> TextureDataLayout -> Extent3D -> a -> m ()
- queueWriteBuffer :: (MonadIO m, ReadableMemoryBuffer a) => Queue -> Buffer -> a -> m ()
- data Version = Version {}
- getVersion :: MonadIO m => Instance -> m Version
- versionToText :: Version -> Text
- data LogLevel
- connectLog :: MonadIO m => Instance -> m ()
- disconnectLog :: MonadIO m => Instance -> m ()
- setLogLevel :: MonadIO m => Instance -> LogLevel -> m ()
- data CompareFunction
- data SMaybe a
- fromSMaybe :: a -> SMaybe a -> a
- class ReadableMemoryBuffer a where
- withReadablePtr :: a -> (Ptr () -> IO b) -> IO b
- readableMemoryBufferSize :: a -> ByteSize
- newtype ByteSize = ByteSize {
- unByteSize :: Word64
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:
- The
wgpu-raw-hs-codegen
package is a code generator for the raw bindings. It creates all the packages namedWGPU.Raw.Generated.*
(without exception!). - 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. 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.
- There are no more raw
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
instsetLogLevel
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
:: MonadIO m | |
=> (m Instance -> (Instance -> m ()) -> r) | Bracketing function.
This can (for example) be something like |
-> 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
.
Arguments
:: MonadIO m | |
=> FilePath | Name of the |
-> (m Instance -> (Instance -> m ()) -> r) | Bracketing function.
This can (for example) be something like |
-> 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 createSurface
(GLFW) or
createSurface
(SDL2).
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
.
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.
data AdapterType #
Physical device type.
Instances
Eq AdapterType | |
Defined in WGPU.Internal.Adapter | |
Show AdapterType | |
Defined in WGPU.Internal.Adapter Methods showsPrec :: Int -> AdapterType -> ShowS # show :: AdapterType -> String # showList :: [AdapterType] -> ShowS # | |
ToRaw AdapterType WGPUAdapterType | |
Defined in WGPU.Internal.Adapter Methods raw :: AdapterType -> ContT r IO WGPUAdapterType # | |
FromRaw WGPUAdapterType AdapterType | |
Defined in WGPU.Internal.Adapter Methods fromRaw :: MonadIO m => WGPUAdapterType -> m AdapterType # |
data BackendType #
Backends supported by WGPU.
Constructors
BackendTypeNull | |
BackendTypeD3D11 | |
BackendTypeD3D12 | |
BackendTypeMetal | |
BackendTypeVulkan | |
BackendTypeOpenGL | |
BackendTypeOpenGLES |
Instances
Eq BackendType | |
Defined in WGPU.Internal.Adapter | |
Show BackendType | |
Defined in WGPU.Internal.Adapter Methods showsPrec :: Int -> BackendType -> ShowS # show :: BackendType -> String # showList :: [BackendType] -> ShowS # | |
ToRaw BackendType WGPUBackendType | |
Defined in WGPU.Internal.Adapter Methods raw :: BackendType -> ContT r IO WGPUBackendType # | |
FromRaw WGPUBackendType BackendType | |
Defined in WGPU.Internal.Adapter Methods fromRaw :: MonadIO m => WGPUBackendType -> m BackendType # |
data AdapterProperties #
Constructors
AdapterProperties | |
Fields
|
Instances
Eq AdapterProperties | |
Defined in WGPU.Internal.Adapter Methods (==) :: AdapterProperties -> AdapterProperties -> Bool # (/=) :: AdapterProperties -> AdapterProperties -> Bool # | |
Show AdapterProperties | |
Defined in WGPU.Internal.Adapter Methods showsPrec :: Int -> AdapterProperties -> ShowS # show :: AdapterProperties -> String # showList :: [AdapterProperties] -> ShowS # | |
ToRaw AdapterProperties WGPUAdapterProperties | |
Defined in WGPU.Internal.Adapter Methods raw :: AdapterProperties -> ContT r IO WGPUAdapterProperties # | |
FromRaw WGPUAdapterProperties AdapterProperties | |
Defined in WGPU.Internal.Adapter Methods fromRaw :: MonadIO m => WGPUAdapterProperties -> m AdapterProperties # |
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.)
An open connection to a graphics and/or compute device.
A Device
may be created using the requestDevice
function.
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 r 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
:: MonadIO m | |
=> Adapter |
|
-> DeviceDescriptor | The features and limits requested for the device. |
-> m (Maybe Device) | The returned |
Requests a connection to a physical device, creating a logical device.
This action blocks until an available device is returned.
Buffers
Handle to a buffer.
Instances
Eq Buffer | |
Show Buffer | |
ToRaw Buffer WGPUBuffer | |
Defined in WGPU.Internal.Buffer |
data BufferDescriptor #
Describes a Buffer
.
Constructors
BufferDescriptor | |
Fields
|
Instances
Eq BufferDescriptor | |
Defined in WGPU.Internal.Buffer Methods (==) :: BufferDescriptor -> BufferDescriptor -> Bool # (/=) :: BufferDescriptor -> BufferDescriptor -> Bool # | |
Show BufferDescriptor | |
Defined in WGPU.Internal.Buffer Methods showsPrec :: Int -> BufferDescriptor -> ShowS # show :: BufferDescriptor -> String # showList :: [BufferDescriptor] -> ShowS # | |
ToRaw BufferDescriptor WGPUBufferDescriptor | |
Defined in WGPU.Internal.Buffer Methods raw :: BufferDescriptor -> ContT r IO WGPUBufferDescriptor # |
data BufferUsage #
Different ways you can use a buffer.
Constructors
BufferUsage | |
Fields
|
Instances
Eq BufferUsage | |
Defined in WGPU.Internal.Buffer | |
Show BufferUsage | |
Defined in WGPU.Internal.Buffer Methods showsPrec :: Int -> BufferUsage -> ShowS # show :: BufferUsage -> String # showList :: [BufferUsage] -> ShowS # | |
Default BufferUsage | |
Defined in WGPU.Internal.Buffer Methods def :: BufferUsage # | |
ToRaw BufferUsage Word32 | |
Defined in WGPU.Internal.Buffer |
createBuffer :: MonadIO m => Device -> BufferDescriptor -> m Buffer #
Create a Buffer
.
Arguments
:: forall a m. (MonadIO m, ReadableMemoryBuffer a) | |
=> Device | Device for which to create the buffer. |
-> Text | Debugging label for the buffer. |
-> BufferUsage | Usage for the buffer. |
-> a | Data to initialize the buffer with. |
-> m Buffer | Buffer created with the specified data. |
Create a Buffer
with data to initialize it.
Textures and Views
Handle to a texture.
Instances
Eq Texture | |
Show Texture | |
ToRaw Texture WGPUTexture | |
Defined in WGPU.Internal.Multipurpose |
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 r 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 r 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 r 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
TextureUsage | |
Fields
|
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 # | |
Default TextureUsage | |
Defined in WGPU.Internal.Texture Methods def :: TextureUsage # | |
ToRaw TextureUsage WGPUTextureUsageFlags | |
Defined in WGPU.Internal.Texture Methods raw :: TextureUsage -> ContT r IO WGPUTextureUsageFlags # |
Extent of a texture or texture-related operation.
Constructors
Extent3D | |
Fields
|
Instances
data TextureDimension #
Dimensionality of a texture.
Constructors
TextureDimension1D | |
TextureDimension2D | |
TextureDimension3D |
Instances
Eq TextureDimension | |
Defined in WGPU.Internal.Texture Methods (==) :: TextureDimension -> TextureDimension -> Bool # (/=) :: TextureDimension -> TextureDimension -> Bool # | |
Show TextureDimension | |
Defined in WGPU.Internal.Texture Methods showsPrec :: Int -> TextureDimension -> ShowS # show :: TextureDimension -> String # showList :: [TextureDimension] -> ShowS # | |
ToRaw TextureDimension WGPUTextureDimension | |
Defined in WGPU.Internal.Texture Methods raw :: TextureDimension -> ContT r IO WGPUTextureDimension # |
data TextureDescriptor #
Describes a Texture
.
Constructors
TextureDescriptor | |
Fields
|
Instances
Eq TextureDescriptor | |
Defined in WGPU.Internal.Texture Methods (==) :: TextureDescriptor -> TextureDescriptor -> Bool # (/=) :: TextureDescriptor -> TextureDescriptor -> Bool # | |
Show TextureDescriptor | |
Defined in WGPU.Internal.Texture Methods showsPrec :: Int -> TextureDescriptor -> ShowS # show :: TextureDescriptor -> String # showList :: [TextureDescriptor] -> ShowS # | |
ToRaw TextureDescriptor WGPUTextureDescriptor | |
Defined in WGPU.Internal.Texture Methods raw :: TextureDescriptor -> ContT r IO WGPUTextureDescriptor # |
Origin of a copy to/from a texture.
Instances
data TextureAspect #
Kind of data a texture holds.
Instances
Eq TextureAspect | |
Defined in WGPU.Internal.Multipurpose Methods (==) :: TextureAspect -> TextureAspect -> Bool # (/=) :: TextureAspect -> TextureAspect -> Bool # | |
Show TextureAspect | |
Defined in WGPU.Internal.Multipurpose Methods showsPrec :: Int -> TextureAspect -> ShowS # show :: TextureAspect -> String # showList :: [TextureAspect] -> ShowS # | |
ToRaw TextureAspect WGPUTextureAspect | |
Defined in WGPU.Internal.Multipurpose Methods raw :: TextureAspect -> ContT r IO WGPUTextureAspect # |
data ImageCopyTexture #
View of a texture which can be used to copy tofrom a buffertexture.
Constructors
ImageCopyTexture | |
Instances
ToRaw ImageCopyTexture WGPUImageCopyTexture | |
Defined in WGPU.Internal.Multipurpose Methods raw :: ImageCopyTexture -> ContT r IO WGPUImageCopyTexture # |
data TextureDataLayout #
Layout of a texture in a buffer's memory.
Constructors
TextureDataLayout | |
Fields
|
Instances
Eq TextureDataLayout | |
Defined in WGPU.Internal.Multipurpose Methods (==) :: TextureDataLayout -> TextureDataLayout -> Bool # (/=) :: TextureDataLayout -> TextureDataLayout -> Bool # | |
Show TextureDataLayout | |
Defined in WGPU.Internal.Multipurpose Methods showsPrec :: Int -> TextureDataLayout -> ShowS # show :: TextureDataLayout -> String # showList :: [TextureDataLayout] -> ShowS # | |
ToRaw TextureDataLayout WGPUTextureDataLayout | |
Defined in WGPU.Internal.Multipurpose Methods raw :: TextureDataLayout -> ContT r IO WGPUTextureDataLayout # |
data TextureViewDescriptor #
Describes a TextureView
.
Constructors
TextureViewDescriptor | |
Instances
Eq TextureViewDescriptor | |
Defined in WGPU.Internal.Texture Methods (==) :: TextureViewDescriptor -> TextureViewDescriptor -> Bool # (/=) :: TextureViewDescriptor -> TextureViewDescriptor -> Bool # | |
Show TextureViewDescriptor | |
Defined in WGPU.Internal.Texture Methods showsPrec :: Int -> TextureViewDescriptor -> ShowS # show :: TextureViewDescriptor -> String # showList :: [TextureViewDescriptor] -> ShowS # | |
ToRaw TextureViewDescriptor WGPUTextureViewDescriptor | |
Defined in WGPU.Internal.Texture Methods raw :: TextureViewDescriptor -> ContT r IO WGPUTextureViewDescriptor # |
Arguments
:: MonadIO m | |
=> Device | Device for which to create the texture. |
-> TextureDescriptor | Description of the texture to create. |
-> m Texture | Action to create the texture. |
Create a texture.
Arguments
:: MonadIO m | |
=> Texture | Texture for which the view should be created. |
-> TextureViewDescriptor | Description of the texture view. |
-> m TextureView | Created texture view. |
Create a view of a texture.
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 r 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 r IO WGPUPresentMode # |
Arguments
:: MonadIO m | |
=> Surface |
|
-> Adapter |
|
-> 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.
Arguments
:: MonadIO m | |
=> Device |
|
-> Surface |
|
-> SwapChainDescriptor | Description of the |
-> 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.
Arguments
:: MonadIO m | |
=> SwapChain | Swap chain to present. |
-> m () | IO action which presents the swap chain image. |
Present the latest swap chain image.
Samplers
Handle to a Sampler
.
A Sampler
defines how a pipeline will sample from a TextureView
.
Samplers define image filters (include anisotropy) and address (wrapping)
modes, among other things.
Instances
Eq Sampler | |
Show Sampler | |
ToRaw Sampler WGPUSampler | |
Defined in WGPU.Internal.Sampler |
data AddressMode #
How edges should be handled in texture addressing.
Instances
Eq AddressMode | |
Defined in WGPU.Internal.Sampler | |
Show AddressMode | |
Defined in WGPU.Internal.Sampler Methods showsPrec :: Int -> AddressMode -> ShowS # show :: AddressMode -> String # showList :: [AddressMode] -> ShowS # | |
ToRaw AddressMode WGPUAddressMode | |
Defined in WGPU.Internal.Sampler Methods raw :: AddressMode -> ContT r IO WGPUAddressMode # |
data FilterMode #
Texel mixing mode when sampling between texels.
Constructors
FilterModeNearest | |
FilterModeLinear |
Instances
Eq FilterMode | |
Defined in WGPU.Internal.Sampler | |
Show FilterMode | |
Defined in WGPU.Internal.Sampler Methods showsPrec :: Int -> FilterMode -> ShowS # show :: FilterMode -> String # showList :: [FilterMode] -> ShowS # | |
ToRaw FilterMode WGPUFilterMode | |
Defined in WGPU.Internal.Sampler Methods raw :: FilterMode -> ContT r IO WGPUFilterMode # |
data SamplerDescriptor #
Describes a Sampler
.
Constructors
SamplerDescriptor | |
Fields
|
Instances
Eq SamplerDescriptor | |
Defined in WGPU.Internal.Sampler Methods (==) :: SamplerDescriptor -> SamplerDescriptor -> Bool # (/=) :: SamplerDescriptor -> SamplerDescriptor -> Bool # | |
Show SamplerDescriptor | |
Defined in WGPU.Internal.Sampler Methods showsPrec :: Int -> SamplerDescriptor -> ShowS # show :: SamplerDescriptor -> String # showList :: [SamplerDescriptor] -> ShowS # | |
ToRaw SamplerDescriptor WGPUSamplerDescriptor | |
Defined in WGPU.Internal.Sampler Methods raw :: SamplerDescriptor -> ContT r IO WGPUSamplerDescriptor # |
Arguments
:: MonadIO m | |
=> Device | Device for which to create the sampler. |
-> SamplerDescriptor | Description of the sampler to create. |
-> m Sampler | Action to create the sampler. |
Create a Sampler
.
Resource Binding
Binding group.
Represents the set of resources bound to the bindings described by a
BindGroupLayout
.
Instances
Eq BindGroup | |
Show BindGroup | |
ToRaw BindGroup WGPUBindGroup | |
Defined in WGPU.Internal.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 r IO WGPUBindGroupLayout # |
data BindGroupDescriptor #
Describes a BindGroup
.
Constructors
BindGroupDescriptor | |
Fields |
Instances
Eq BindGroupDescriptor | |
Defined in WGPU.Internal.Binding Methods (==) :: BindGroupDescriptor -> BindGroupDescriptor -> Bool # (/=) :: BindGroupDescriptor -> BindGroupDescriptor -> Bool # | |
Show BindGroupDescriptor | |
Defined in WGPU.Internal.Binding Methods showsPrec :: Int -> BindGroupDescriptor -> ShowS # show :: BindGroupDescriptor -> String # showList :: [BindGroupDescriptor] -> ShowS # | |
ToRaw BindGroupDescriptor WGPUBindGroupDescriptor | |
Defined in WGPU.Internal.Binding Methods raw :: BindGroupDescriptor -> ContT r IO WGPUBindGroupDescriptor # |
data BindGroupEntry #
Entry in a bind group.
Constructors
BindGroupEntry | |
Fields
|
Instances
Eq BindGroupEntry | |
Defined in WGPU.Internal.Binding Methods (==) :: BindGroupEntry -> BindGroupEntry -> Bool # (/=) :: BindGroupEntry -> BindGroupEntry -> Bool # | |
Show BindGroupEntry | |
Defined in WGPU.Internal.Binding Methods showsPrec :: Int -> BindGroupEntry -> ShowS # show :: BindGroupEntry -> String # showList :: [BindGroupEntry] -> ShowS # | |
ToRaw BindGroupEntry WGPUBindGroupEntry | |
Defined in WGPU.Internal.Binding Methods raw :: BindGroupEntry -> ContT r IO WGPUBindGroupEntry # |
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 r 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 r 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 # | |
Default ShaderStage | |
Defined in WGPU.Internal.Binding Methods def :: ShaderStage # | |
ToRaw ShaderStage WGPUShaderStageFlags | |
Defined in WGPU.Internal.Binding Methods raw :: ShaderStage -> ContT r 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 r 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 r 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 r 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 r 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 r 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 r 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 r IO WGPUBufferBindingType # |
data BindingResource #
Resource that can be bound to a pipeline.
Constructors
BindingResourceBuffer !BufferBinding | |
BindingResourceSampler !Sampler | |
BindingResourceTextureView !TextureView |
Instances
Eq BindingResource | |
Defined in WGPU.Internal.Binding Methods (==) :: BindingResource -> BindingResource -> Bool # (/=) :: BindingResource -> BindingResource -> Bool # | |
Show BindingResource | |
Defined in WGPU.Internal.Binding Methods showsPrec :: Int -> BindingResource -> ShowS # show :: BindingResource -> String # showList :: [BindingResource] -> ShowS # |
data BufferBinding #
A buffer binding.
Constructors
BufferBinding | |
Fields
|
Instances
Eq BufferBinding | |
Defined in WGPU.Internal.Binding Methods (==) :: BufferBinding -> BufferBinding -> Bool # (/=) :: BufferBinding -> BufferBinding -> Bool # | |
Show BufferBinding | |
Defined in WGPU.Internal.Binding Methods showsPrec :: Int -> BufferBinding -> ShowS # show :: BufferBinding -> String # showList :: [BufferBinding] -> ShowS # |
Arguments
:: MonadIO m | |
=> Device | Device for which to create the bind group. |
-> BindGroupDescriptor | Description of the bind group. |
-> m BindGroup | Action to create the bind group. |
Create a bind group.
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
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 r 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 r 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
:: 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.
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.
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 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 r 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 r 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 r 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 r 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 r 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 r 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 r 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 r 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 r 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 r 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.Multipurpose | |
Show IndexFormat | |
Defined in WGPU.Internal.Multipurpose Methods showsPrec :: Int -> IndexFormat -> ShowS # show :: IndexFormat -> String # showList :: [IndexFormat] -> ShowS # | |
ToRaw IndexFormat WGPUIndexFormat | Convert an |
Defined in WGPU.Internal.Multipurpose Methods raw :: IndexFormat -> ContT r 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 r 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 r 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 r 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 r 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 r 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 r 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 r 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 r 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 r 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 r 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 r IO WGPUFragmentState # |
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.
createRenderPipeline :: MonadIO m => Device -> RenderPipelineDescriptor -> m RenderPipeline #
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 r 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 r 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 r 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 r 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 r IO WGPURenderPassDescriptor # |
Half open range. It includes the start
value but not the end
value.
Constructors
Range | |
Fields
|
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.
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.
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.
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 () #
Sets the active bind group for a given bind group index.
renderPassSetIndexBuffer :: MonadIO m => RenderPassEncoder -> Buffer -> IndexFormat -> Word64 -> Word64 -> m () #
Sets the active index buffer.
renderPassSetVertexBuffer :: MonadIO m => RenderPassEncoder -> Word32 -> Buffer -> Word64 -> Word64 -> m () #
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 () #
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
queueSubmit :: MonadIO m => Queue -> Vector CommandBuffer -> m () #
Submit a list of command buffers to a device queue.
Arguments
:: (MonadIO m, ReadableMemoryBuffer a) | |
=> Queue | Queue to which the texture write will be submitted. |
-> ImageCopyTexture | View of a texture which will be copied. |
-> TextureDataLayout | Layout of the texture in a buffer's memory. |
-> Extent3D | Extent of the texture operation. |
-> a | A |
-> m () | Action to copy the texture |
Schedule a data write into a texture.
Arguments
:: (MonadIO m, ReadableMemoryBuffer a) | |
=> Queue | Queue to which the buffer write will be submitted. |
-> Buffer | Buffer in which to write. |
-> a | A |
-> m () | Action which copies the buffer data. |
Schedule a data write into a buffer.
Version
Version of WGPU native.
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
Logging level.
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
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 r IO WGPUCompareFunction # |
Extras
Strict Maybe
Additional Classes
class ReadableMemoryBuffer a where #
Region of memory that is read-only for WGPU.
A ReadableMemoryBuffer
represents a contiguous region of memory that WGPU
may read from, but not write to. It has a pointer to the start of the region,
and a size in bytes.
When the caller of WGPU supplies a ReadableMemoryBuffer
, it commits to
keeping the buffer alive for the period of the call to withReadablePtr
.
WGPU commits to not mutating the data.
If it is necessary to refer to slices within a buffer, it is up to the type
a
to store those offsets and account for them in the two functions required
by the API. (For example, Vector
does this.)
Methods
withReadablePtr :: a -> (Ptr () -> IO b) -> IO b #
Perform an action with the memory buffer.
readableMemoryBufferSize :: a -> ByteSize #
The size of the buffer, in number of bytes.
Instances
Storable a => ReadableMemoryBuffer a | |
Defined in WGPU.Internal.Memory Methods withReadablePtr :: a -> (Ptr () -> IO b) -> IO b # readableMemoryBufferSize :: a -> ByteSize # | |
Storable a => ReadableMemoryBuffer (Vector a) | |
Defined in WGPU.Internal.Memory Methods withReadablePtr :: Vector a -> (Ptr () -> IO b) -> IO b # readableMemoryBufferSize :: Vector a -> ByteSize # |
Additional Types
Size, in number of bytes.
Constructors
ByteSize | |
Fields
|
Instances
Enum ByteSize | |
Defined in WGPU.Internal.Memory | |
Eq ByteSize | |
Integral ByteSize | |
Defined in WGPU.Internal.Memory | |
Num ByteSize | |
Ord ByteSize | |
Defined in WGPU.Internal.Memory | |
Real ByteSize | |
Defined in WGPU.Internal.Memory Methods toRational :: ByteSize -> Rational # | |
Show ByteSize | |
ToRaw ByteSize CSize | |