Copyright | (C) 2015, 2016 Dimitri Sabadie |
---|---|
License | BSD3 |
Maintainer | Dimitri Sabadie <dimitri.sabadie@gmail.com> |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Graphics.Luminance.Texture
Contents
Description
- class Texture t where
- type TextureSize t :: *
- type TextureOffset t :: *
- createTexture :: forall m t. (MonadIO m, MonadResource m, Texture t) => TextureSize t -> Natural -> Sampling -> m t
- data Sampling = Sampling {}
- defaultSampling :: Sampling
- data Filter
- data Wrap
- data CompareFunc
- = Never
- | Less
- | Equal
- | LessOrEqual
- | Greater
- | GreaterOrEqual
- | NotEqual
- | Always
- uploadSub :: forall a m t. (MonadIO m, Storable a, Texture t) => t -> TextureOffset t -> TextureSize t -> Bool -> Vector a -> m ()
- fillSub :: forall a m t. (MonadIO m, Storable a, Texture t) => t -> TextureOffset t -> TextureSize t -> Bool -> Vector a -> m ()
- data Texture1D f
- texture1DW :: Texture1D f -> Natural
- data Texture1DArray n f
- texture1DArrayW :: Texture1DArray n f -> Natural
- data Texture2D f
- texture2DW :: Texture2D f -> Natural
- texture2DH :: Texture2D f -> Natural
- data Texture2DArray n f
- texture2DArrayW :: Texture2DArray n f -> Natural
- data Texture3D f
- texture3DW :: Texture3D f -> Natural
- texture3DH :: Texture3D f -> Natural
- texture3DD :: Texture3D f -> Natural
- data Cubemap f
- data CubeFace
- cubemapSize :: Cubemap f -> Natural
- data CubemapArray n f
- cubemapArraySize :: CubemapArray n f -> Natural
- module Graphics.Luminance.Pixel
Texture information and creation
Class of all textures.
Minimal complete definition
fromBaseTexture, toBaseTexture, textureTypeEnum, textureSize, textureStorage, transferTexelsSub, fillTextureSub
Associated Types
type TextureSize t :: * Source #
Size of a texture. This is an associated type – type family – because the dimensionality of a texture relies on its type.
type TextureOffset t :: * Source #
In order to index regions of texels in texture, we need another associated type – for the same
dimensionality reason as for TextureSize
.
Instances
Pixel f => Texture (Cubemap f) Source # | |
Pixel f => Texture (Texture1D f) Source # | |
Pixel f => Texture (Texture2D f) Source # | |
Pixel f => Texture (Texture3D f) Source # | |
(KnownNat n, Pixel f) => Texture (CubemapArray n f) Source # | |
(KnownNat n, Pixel f) => Texture (Texture1DArray n f) Source # | |
(KnownNat n, Pixel f) => Texture (Texture2DArray n f) Source # | |
createTexture :: forall m t. (MonadIO m, MonadResource m, Texture t) => TextureSize t -> Natural -> Sampling -> m t Source #
'createTexture w h levels sampling' a new 'w'*'h' texture with levels
levels. The format is
set through the type.
Sampling
A sampling configuration type.
Constructors
Sampling | |
Fields |
defaultSampling :: Sampling Source #
Default Sampling
for convenience.
defaultSampling = Sampling { samplingWrapS = ClampToEdge , samplingWrapT = ClampToEdge , samplingWrapR = ClampToEdge , samplingMinFilter = Linear , samplingMagFilter = Linear , samplingCompareFunction = Nothing }
Texture sampler customization
Wrap texture parameter. Such an object is used to tell how to sampling is performed when going out of the texture coordinates.
ClampToEdge
will clamp the texture coordinates between in '[0,1]'. If you pass '1.1' or
'31.456', in both cases you’ll end up with '1'. Same thing for negative values clamped to '0'.
Repeat
will clamp the texture in '[0,1]' after applying a fract
on the value, yielding a
a repeated '[0,1]' pattern.
Constructors
ClampToEdge | |
Repeat | ClampToBorder |
MirroredRepeat |
data CompareFunc Source #
For textures that might require depth comparison, that type defines all the possible cases for comparison.
Constructors
Never | |
Less | |
Equal | |
LessOrEqual | |
Greater | |
GreaterOrEqual | |
NotEqual | |
Always |
Instances
Texture operations
uploadSub :: forall a m t. (MonadIO m, Storable a, Texture t) => t -> TextureOffset t -> TextureSize t -> Bool -> Vector a -> m () Source #
fillSub :: forall a m t. (MonadIO m, Storable a, Texture t) => t -> TextureOffset t -> TextureSize t -> Bool -> Vector a -> m () Source #
Fill a subpart of the texture’s storage with a given value.
Available textures
1D textures
A 1D texture.
texture1DW :: Texture1D f -> Natural Source #
Array texture
data Texture1DArray n f Source #
A 1D texture array.
Instances
Eq (Texture1DArray n f) Source # | |
Show (Texture1DArray n f) Source # | |
(KnownNat n, Pixel f) => Texture (Texture1DArray n f) Source # | |
type TextureSize (Texture1DArray n f) Source # | |
type TextureOffset (Texture1DArray n f) Source # | |
texture1DArrayW :: Texture1DArray n f -> Natural Source #
2D textures
A 2D texture.
texture2DW :: Texture2D f -> Natural Source #
texture2DH :: Texture2D f -> Natural Source #
Array texture
data Texture2DArray n f Source #
A 2D texture array.
Instances
Eq (Texture2DArray n f) Source # | |
Show (Texture2DArray n f) Source # | |
(KnownNat n, Pixel f) => Texture (Texture2DArray n f) Source # | |
type TextureSize (Texture2DArray n f) Source # | |
type TextureOffset (Texture2DArray n f) Source # | |
texture2DArrayW :: Texture2DArray n f -> Natural Source #
3D textures
A 3D texture.
texture3DW :: Texture3D f -> Natural Source #
texture3DH :: Texture3D f -> Natural Source #
texture3DD :: Texture3D f -> Natural Source #
Cubemaps
A cubemap.
Face of a Cubemap
.
cubemapSize :: Cubemap f -> Natural Source #
Array textures
data CubemapArray n f Source #
A cubemap array.
Instances
Eq (CubemapArray n f) Source # | |
Show (CubemapArray n f) Source # | |
(KnownNat n, Pixel f) => Texture (CubemapArray n f) Source # | |
type TextureSize (CubemapArray n f) Source # | |
type TextureOffset (CubemapArray n f) Source # | |
cubemapArraySize :: CubemapArray n f -> Natural Source #
Pixel formats
module Graphics.Luminance.Pixel