luminance-0.11.0.4: Type-safe, type-level and stateless graphics framework

Copyright(C) 2015, 2016 Dimitri Sabadie
LicenseBSD3
MaintainerDimitri Sabadie <dimitri.sabadie@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Graphics.Luminance.Texture

Contents

Description

 

Synopsis

Texture information and creation

class Texture t Source #

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 # 

Associated Types

type TextureSize (Cubemap f) :: * Source #

type TextureOffset (Cubemap f) :: * Source #

Methods

fromBaseTexture :: BaseTexture -> TextureSize (Cubemap f) -> Cubemap f

toBaseTexture :: Cubemap f -> BaseTexture

textureTypeEnum :: proxy (Cubemap f) -> GLenum

textureSize :: Cubemap f -> TextureSize (Cubemap f)

textureStorage :: proxy (Cubemap f) -> GLuint -> GLint -> TextureSize (Cubemap f) -> IO ()

transferTexelsSub :: Storable a => proxy (Cubemap f) -> GLuint -> TextureOffset (Cubemap f) -> TextureSize (Cubemap f) -> Vector a -> IO ()

fillTextureSub :: Storable a => proxy (Cubemap f) -> GLuint -> TextureOffset (Cubemap f) -> TextureSize (Cubemap f) -> Vector a -> IO ()

Pixel f => Texture (Texture1D f) Source # 

Associated Types

type TextureSize (Texture1D f) :: * Source #

type TextureOffset (Texture1D f) :: * Source #

Pixel f => Texture (Texture2D f) Source # 

Associated Types

type TextureSize (Texture2D f) :: * Source #

type TextureOffset (Texture2D f) :: * Source #

Pixel f => Texture (Texture3D f) Source # 

Associated Types

type TextureSize (Texture3D f) :: * Source #

type TextureOffset (Texture3D f) :: * Source #

(KnownNat n, Pixel f) => Texture (CubemapArray n f) Source # 

Associated Types

type TextureSize (CubemapArray n f) :: * Source #

type TextureOffset (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

defaultSampling :: Sampling Source #

Default Sampling for convenience.

  defaultSampling = Sampling {
      samplingWrapS           = ClampToEdge
    , samplingWrapT           = ClampToEdge
    , samplingWrapR           = ClampToEdge
    , samplingMinFilter       = Linear
    , samplingMagFilter       = Linear
    , samplingCompareFunction = Nothing
    }

Texture sampler customization

data Filter Source #

Sampling filter. Nearest will sample the nearest texel at the sampling coordinates whilst Linear will perform linear interpolation with the texels nearby.

Constructors

Nearest 
Linear 

Instances

data Wrap Source #

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 

Instances

Eq Wrap Source # 

Methods

(==) :: Wrap -> Wrap -> Bool #

(/=) :: Wrap -> Wrap -> Bool #

Show Wrap Source # 

Methods

showsPrec :: Int -> Wrap -> ShowS #

show :: Wrap -> String #

showList :: [Wrap] -> ShowS #

data CompareFunc Source #

For textures that might require depth comparison, that type defines all the possible cases for comparison.

Texture operations

uploadSub :: forall a m t. (MonadIO m, Storable a, Texture t) => t -> TextureOffset t -> TextureSize t -> Bool -> Vector a -> m () Source #

uploadSub tex offset size autolvl texels uploads data to a subpart of the texture’s storage. The offset is given with origin at upper-left corner, and size is the size of the area to upload to. autolvl is a Bool that can be used to automatically generate mipmaps.

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

data Texture1D f Source #

A 1D texture.

Array texture

2D textures

data Texture2D f Source #

A 2D texture.

Array texture

data Texture2DArray n f Source #

A 2D texture array.

3D textures

Cubemaps

data Cubemap f Source #

A cubemap.

Instances

Eq (Cubemap f) Source # 

Methods

(==) :: Cubemap f -> Cubemap f -> Bool #

(/=) :: Cubemap f -> Cubemap f -> Bool #

Show (Cubemap f) Source # 

Methods

showsPrec :: Int -> Cubemap f -> ShowS #

show :: Cubemap f -> String #

showList :: [Cubemap f] -> ShowS #

Pixel f => Texture (Cubemap f) Source # 

Associated Types

type TextureSize (Cubemap f) :: * Source #

type TextureOffset (Cubemap f) :: * Source #

Methods

fromBaseTexture :: BaseTexture -> TextureSize (Cubemap f) -> Cubemap f

toBaseTexture :: Cubemap f -> BaseTexture

textureTypeEnum :: proxy (Cubemap f) -> GLenum

textureSize :: Cubemap f -> TextureSize (Cubemap f)

textureStorage :: proxy (Cubemap f) -> GLuint -> GLint -> TextureSize (Cubemap f) -> IO ()

transferTexelsSub :: Storable a => proxy (Cubemap f) -> GLuint -> TextureOffset (Cubemap f) -> TextureSize (Cubemap f) -> Vector a -> IO ()

fillTextureSub :: Storable a => proxy (Cubemap f) -> GLuint -> TextureOffset (Cubemap f) -> TextureSize (Cubemap f) -> Vector a -> IO ()

Pixel f => Uniform (Cubemap f) Source # 

Methods

toU :: Monad m => GLuint -> GLint -> UniformInterface m (U (Cubemap f))

type TextureSize (Cubemap f) Source # 
type TextureOffset (Cubemap f) Source # 

Array textures

Pixel formats