| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
WGPU.BoneYard.SimpleSDL
Description
This is a kind of skeleton for a very simple SDL app. It is intended for bootstrapping development. A common use case is when you want a window to draw in with everything configured. This provides a version of that functionality that can later be replaced or refined (easily) by the app developer if necessary.
Synopsis
- data SwapChainState
- emptySwapChainState :: MonadResource m => m SwapChainState
- withSwapChain :: forall r m a. (HasDevice r m, HasSurface r m, HasAdapter r m, Has Window r, Has SwapChainState r) => ReaderT (SwapChain, r) m a -> m a
- data Buffers
- data BufferName
- emptyBuffers :: MonadResource m => m Buffers
- createBuffer :: (MonadIO m, HasDevice r m, Has Buffers r) => BufferName -> ByteSize -> BufferUsage -> m Buffer
- createBufferInit :: (MonadIO m, HasDevice r m, Has Buffers r, ReadableMemoryBuffer a) => BufferName -> BufferUsage -> a -> m Buffer
- getBuffer :: (MonadIO m, Has Buffers r, MonadReader r m, MonadThrow m) => BufferName -> m Buffer
- data Textures
- data TextureName
- emptyTextures :: MonadResource m => m Textures
- createTexture :: (MonadIO m, HasDevice r m, Has Textures r) => TextureName -> Extent3D -> Word32 -> Word32 -> TextureDimension -> TextureFormat -> TextureUsage -> m Texture
- getTexture :: (MonadIO m, Has Textures r, MonadReader r m, MonadThrow m) => TextureName -> m Texture
- data BindGroups
- data BindGroupName
- emptyBindGroups :: MonadResource m => m BindGroups
- createBindGroup :: (MonadIO m, HasDevice r m, Has BindGroups r) => BindGroupName -> BindGroupDescriptor -> m BindGroup
- getBindGroup :: (MonadIO m, Has BindGroups r, MonadReader r m, MonadThrow m) => BindGroupName -> m BindGroup
- data RenderPipelineName
- data RenderPipelines
- emptyRenderPipelines :: MonadResource m => m RenderPipelines
- createRenderPipeline :: (MonadIO m, HasDevice r m, Has RenderPipelines r) => RenderPipelineName -> RenderPipelineDescriptor -> m RenderPipeline
- getRenderPipeline :: (Has RenderPipelines r, MonadReader r m, MonadIO m, MonadThrow m) => RenderPipelineName -> m RenderPipeline
- data ShaderName
- data Shaders
- emptyShaders :: MonadResource m => m Shaders
- compileWGSL :: (Has Device r, Has Shaders r, MonadReader r m, MonadResource m) => ShaderName -> WGSL -> m ShaderModule
- compileWGSL_ :: (Has Device r, Has Shaders r, MonadReader r m, MonadResource m) => ShaderName -> WGSL -> m ()
- getShader :: (Has Shaders r, MonadReader r m, MonadIO m, MonadThrow m) => ShaderName -> m ShaderModule
- data Params = Params {
- title :: !Text
- mDeviceDescriptor :: !(SMaybe DeviceDescriptor)
- data Resources = Resources {}
- loadResources :: forall m. (MonadResource m, MonadThrow m) => Params -> m Resources
- getWindow :: (Has Window r, MonadReader r m) => m Window
- getDrawableSize :: (Has Window r, MonadReader r m, MonadIO m) => m (Int, Int)
- data AppException
Swap Chain
Types
data SwapChainState Source #
Contains mutable state to manage the swap chain.
Functions
emptySwapChainState :: MonadResource m => m SwapChainState Source #
Initialize a new SwapChainState.
withSwapChain :: forall r m a. (HasDevice r m, HasSurface r m, HasAdapter r m, Has Window r, Has SwapChainState r) => ReaderT (SwapChain, r) m a -> m a Source #
Buffers
Types
Container for buffers (map of BufferName to Buffer).
data BufferName Source #
Name of a buffer.
Instances
| Eq BufferName Source # | |
Defined in WGPU.BoneYard.SimpleSDL | |
| Ord BufferName Source # | |
Defined in WGPU.BoneYard.SimpleSDL Methods compare :: BufferName -> BufferName -> Ordering # (<) :: BufferName -> BufferName -> Bool # (<=) :: BufferName -> BufferName -> Bool # (>) :: BufferName -> BufferName -> Bool # (>=) :: BufferName -> BufferName -> Bool # max :: BufferName -> BufferName -> BufferName # min :: BufferName -> BufferName -> BufferName # | |
| Show BufferName Source # | |
Defined in WGPU.BoneYard.SimpleSDL Methods showsPrec :: Int -> BufferName -> ShowS # show :: BufferName -> String # showList :: [BufferName] -> ShowS # | |
| IsString BufferName Source # | |
Defined in WGPU.BoneYard.SimpleSDL Methods fromString :: String -> BufferName # | |
Functions
emptyBuffers :: MonadResource m => m Buffers Source #
Create an empty Buffers collection.
Arguments
| :: (MonadIO m, HasDevice r m, Has Buffers r) | |
| => BufferName | Name of the buffer. |
| -> ByteSize | Size of the buffer in bytes. |
| -> BufferUsage | Usage of the buffer. |
| -> m Buffer | Action which creates the buffer. |
Create an uninitialized Buffer.
Arguments
| :: (MonadIO m, HasDevice r m, Has Buffers r, ReadableMemoryBuffer a) | |
| => BufferName | Name of the buffer. |
| -> BufferUsage | Usage of the buffer. |
| -> a | Contents of the buffer. |
| -> m Buffer | Action which creates the buffer. |
getBuffer :: (MonadIO m, Has Buffers r, MonadReader r m, MonadThrow m) => BufferName -> m Buffer Source #
Fetch a buffer that was previously created.
If the buffer pipeline is not available, this function throws an exception of
type AppException.
Textures
Types
Container for textures (map of TextureName to Texture).
data TextureName Source #
Name of a texture.
Instances
| Eq TextureName Source # | |
Defined in WGPU.BoneYard.SimpleSDL | |
| Ord TextureName Source # | |
Defined in WGPU.BoneYard.SimpleSDL Methods compare :: TextureName -> TextureName -> Ordering # (<) :: TextureName -> TextureName -> Bool # (<=) :: TextureName -> TextureName -> Bool # (>) :: TextureName -> TextureName -> Bool # (>=) :: TextureName -> TextureName -> Bool # max :: TextureName -> TextureName -> TextureName # min :: TextureName -> TextureName -> TextureName # | |
| Show TextureName Source # | |
Defined in WGPU.BoneYard.SimpleSDL Methods showsPrec :: Int -> TextureName -> ShowS # show :: TextureName -> String # showList :: [TextureName] -> ShowS # | |
| IsString TextureName Source # | |
Defined in WGPU.BoneYard.SimpleSDL Methods fromString :: String -> TextureName # | |
Functions
emptyTextures :: MonadResource m => m Textures Source #
Create an empty Textures collection.
Arguments
| :: (MonadIO m, HasDevice r m, Has Textures r) | |
| => TextureName | Name of the texture to create. |
| -> Extent3D | Extent / size of the texture. |
| -> Word32 | Mip level count. |
| -> Word32 | Sample count. |
| -> TextureDimension | Dimension (1D, 2D, 3D) of the texture. |
| -> TextureFormat | Format of an element of the texture. |
| -> TextureUsage | Usages of the texture. |
| -> m Texture | Action to create the texture. |
Arguments
| :: (MonadIO m, Has Textures r, MonadReader r m, MonadThrow m) | |
| => TextureName | Name of the texture to fetch. |
| -> m Texture | Action which fetches the texture. |
Fetch a texture that was previously created using createTexture.
If the texture is not available, this function throws an exception of type
AppException.
Bind Groups
Types
data BindGroups Source #
Container for bind groups that contains a map of bind groups.
data BindGroupName Source #
Name of a bind group.
Instances
| Eq BindGroupName Source # | |
Defined in WGPU.BoneYard.SimpleSDL Methods (==) :: BindGroupName -> BindGroupName -> Bool # (/=) :: BindGroupName -> BindGroupName -> Bool # | |
| Ord BindGroupName Source # | |
Defined in WGPU.BoneYard.SimpleSDL Methods compare :: BindGroupName -> BindGroupName -> Ordering # (<) :: BindGroupName -> BindGroupName -> Bool # (<=) :: BindGroupName -> BindGroupName -> Bool # (>) :: BindGroupName -> BindGroupName -> Bool # (>=) :: BindGroupName -> BindGroupName -> Bool # max :: BindGroupName -> BindGroupName -> BindGroupName # min :: BindGroupName -> BindGroupName -> BindGroupName # | |
| Show BindGroupName Source # | |
Defined in WGPU.BoneYard.SimpleSDL Methods showsPrec :: Int -> BindGroupName -> ShowS # show :: BindGroupName -> String # showList :: [BindGroupName] -> ShowS # | |
| IsString BindGroupName Source # | |
Defined in WGPU.BoneYard.SimpleSDL Methods fromString :: String -> BindGroupName # | |
Functions
emptyBindGroups :: MonadResource m => m BindGroups Source #
Create an empty BindGroups collection.
createBindGroup :: (MonadIO m, HasDevice r m, Has BindGroups r) => BindGroupName -> BindGroupDescriptor -> m BindGroup Source #
Create a new BindGroup, adding it to the BindGroups collection.
getBindGroup :: (MonadIO m, Has BindGroups r, MonadReader r m, MonadThrow m) => BindGroupName -> m BindGroup Source #
Fetch a BindGroup that was previously created using createBindGroup.
If the bind group is not available, this function throws an exception of type
AppException.
Render Pipelines
Types
data RenderPipelineName Source #
Name of a render pipeline.
Instances
data RenderPipelines Source #
Container for mutable state that contains a map of render pipelines.
Functions
emptyRenderPipelines :: MonadResource m => m RenderPipelines Source #
Create an empty RenderPipelines.
Arguments
| :: (MonadIO m, HasDevice r m, Has RenderPipelines r) | |
| => RenderPipelineName | Name of the render pipeline. |
| -> RenderPipelineDescriptor | Descriptor of the render pipeline. |
| -> m RenderPipeline | The created render pipeline. |
Create a RenderPipeline, storing it in the RenderPipelines map.
A RenderPipeline created this way can be fetched using
getRenderPipeline. This calls createRenderPipeline under the hood.
Arguments
| :: (Has RenderPipelines r, MonadReader r m, MonadIO m, MonadThrow m) | |
| => RenderPipelineName | Name of the render pipeline to fetch. |
| -> m RenderPipeline | The render pipeline. |
Fetch a render pipeline that was previously created using
createRenderPipeline.
If the render pipeline is not available, this function throws an exception
of type AppException.
Shaders
Types
data ShaderName Source #
Name of a shader.
Instances
| Eq ShaderName Source # | |
Defined in WGPU.BoneYard.SimpleSDL | |
| Ord ShaderName Source # | |
Defined in WGPU.BoneYard.SimpleSDL Methods compare :: ShaderName -> ShaderName -> Ordering # (<) :: ShaderName -> ShaderName -> Bool # (<=) :: ShaderName -> ShaderName -> Bool # (>) :: ShaderName -> ShaderName -> Bool # (>=) :: ShaderName -> ShaderName -> Bool # max :: ShaderName -> ShaderName -> ShaderName # min :: ShaderName -> ShaderName -> ShaderName # | |
| Show ShaderName Source # | |
Defined in WGPU.BoneYard.SimpleSDL Methods showsPrec :: Int -> ShaderName -> ShowS # show :: ShaderName -> String # showList :: [ShaderName] -> ShowS # | |
| IsString ShaderName Source # | |
Defined in WGPU.BoneYard.SimpleSDL Methods fromString :: String -> ShaderName # | |
Functions
emptyShaders :: MonadResource m => m Shaders Source #
Create an empty Shaders.
Arguments
| :: (Has Device r, Has Shaders r, MonadReader r m, MonadResource m) | |
| => ShaderName | Name of the shader. |
| -> WGSL | Shader source code. |
| -> m ShaderModule | Action that returns the compiled shader module, after adding it to the
|
Compile a WGSL shader, adding it to the Shaders map, and returning the
compiled ShaderModule.
Arguments
| :: (Has Device r, Has Shaders r, MonadReader r m, MonadResource m) | |
| => ShaderName | Name of the shader. |
| -> WGSL | Shader source code. |
| -> m () | Action that compiles the shader and adds it to the |
Compile a WGSL shader, adding it to the Shaders map.
Arguments
| :: (Has Shaders r, MonadReader r m, MonadIO m, MonadThrow m) | |
| => ShaderName | Name of the shader to fetch. |
| -> m ShaderModule | The shader module. |
Fetch a shader that was previously compiled.
If the shader is not available, this function throws an exception of type
AppException.
Resources
Types
Parameters for initialization.
Constructors
| Params | |
Fields
| |
Resources for the app.
Constructors
| Resources | |
Instances
Functions
Arguments
| :: forall m. (MonadResource m, MonadThrow m) | |
| => Params | Initialization parameters. |
| -> m Resources | Created application resources. |
getDrawableSize :: (Has Window r, MonadReader r m, MonadIO m) => m (Int, Int) Source #
Exceptions
data AppException Source #
Exceptions from SimpleSDL.
Constructors
| AdapterRequestFailed | Requesting an adapter failed. |
| DeviceRequestFailed | Requesting a device failed. |
| UnknownShaderName ShaderName | Requesting a shader failed. |
| UnknownRenderPipelineName RenderPipelineName | Requesting a render pipeline failed. |
| UnknownBufferName BufferName | Requesting a buffer failed. |
| UnknownTextureName TextureName | Requesting a texture failed. |
| UnknownBindGroupName BindGroupName | Requesting a bind group failed. |
Instances
| Show AppException Source # | |
Defined in WGPU.BoneYard.SimpleSDL Methods showsPrec :: Int -> AppException -> ShowS # show :: AppException -> String # showList :: [AppException] -> ShowS # | |
| Exception AppException Source # | |
Defined in WGPU.BoneYard.SimpleSDL Methods toException :: AppException -> SomeException # fromException :: SomeException -> Maybe AppException # displayException :: AppException -> String # | |