Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Texture a = Texture {
- tFormat :: Format
- tMipLevels :: Word32
- tLayers :: Word32
- tAllocatedImage :: AllocatedImage
- destroy :: (MonadIO io, HasVulkan context) => context -> Texture a -> io ()
- data TextureError
- data Flat
- data CubeMap
- data ArrayOf (layers :: Nat)
- class TextureLayers a where
- allocateCollectionWith :: (MonadResource m, MonadVulkan env m, Traversable t) => TextureLoaderAction src m layers -> t src -> m (ReleaseKey, t (Texture layers))
- allocateTextureWith :: (MonadResource m, MonadVulkan env m) => TextureLoaderAction src m layers -> src -> m (ReleaseKey, Texture layers)
- debugNameCollection :: (Traversable t, MonadVulkan env m, HasLogFunc env, HasCallStack) => t (Texture layers) -> t FilePath -> m ()
- type TextureLoader m layers = Format -> Queues CommandPool -> FilePath -> m (Texture layers)
- createImageView :: (MonadIO io, HasVulkan context) => context -> Image -> Format -> ("mip levels" ::: Word32) -> ("array layers" ::: Word32) -> io ImageView
- imageCI :: Format -> Extent3D -> Word32 -> Word32 -> ImageCreateInfo '[]
- imageAllocationCI :: AllocationCreateInfo
- stageBufferCI :: Integral a => a -> BufferCreateInfo '[]
- stageAllocationCI :: AllocationCreateInfo
Documentation
Texture | |
|
data TextureError Source #
Instances
Exception TextureError Source # | |
Defined in Resource.Texture | |
Show TextureError Source # | |
Defined in Resource.Texture showsPrec :: Int -> TextureError -> ShowS # show :: TextureError -> String # showList :: [TextureError] -> ShowS # | |
Eq TextureError Source # | |
Defined in Resource.Texture (==) :: TextureError -> TextureError -> Bool # (/=) :: TextureError -> TextureError -> Bool # | |
Ord TextureError Source # | |
Defined in Resource.Texture compare :: TextureError -> TextureError -> Ordering # (<) :: TextureError -> TextureError -> Bool # (<=) :: TextureError -> TextureError -> Bool # (>) :: TextureError -> TextureError -> Bool # (>=) :: TextureError -> TextureError -> Bool # max :: TextureError -> TextureError -> TextureError # min :: TextureError -> TextureError -> TextureError # |
Texture types
Instances
TextureLayers Flat Source # | |
Defined in Resource.Texture |
Instances
TextureLayers CubeMap Source # | |
Defined in Resource.Texture |
data ArrayOf (layers :: Nat) Source #
Instances
KnownNat n => TextureLayers (ArrayOf n) Source # | |
Defined in Resource.Texture |
class TextureLayers a where Source #
Number of expected texture layers to load from resource.
Instances
TextureLayers CubeMap Source # | |
Defined in Resource.Texture | |
TextureLayers Flat Source # | |
Defined in Resource.Texture | |
KnownNat n => TextureLayers (ArrayOf n) Source # | |
Defined in Resource.Texture |
Utilities
allocateCollectionWith :: (MonadResource m, MonadVulkan env m, Traversable t) => TextureLoaderAction src m layers -> t src -> m (ReleaseKey, t (Texture layers)) Source #
allocateTextureWith :: (MonadResource m, MonadVulkan env m) => TextureLoaderAction src m layers -> src -> m (ReleaseKey, Texture layers) Source #
debugNameCollection :: (Traversable t, MonadVulkan env m, HasLogFunc env, HasCallStack) => t (Texture layers) -> t FilePath -> m () Source #
type TextureLoader m layers = Format -> Queues CommandPool -> FilePath -> m (Texture layers) Source #
createImageView :: (MonadIO io, HasVulkan context) => context -> Image -> Format -> ("mip levels" ::: Word32) -> ("array layers" ::: Word32) -> io ImageView Source #
imageAllocationCI :: AllocationCreateInfo Source #
stageBufferCI :: Integral a => a -> BufferCreateInfo '[] Source #
stageAllocationCI :: AllocationCreateInfo Source #