GPipe-2.1.5: Typesafe functional GPU graphics programming

Safe HaskellNone
LanguageHaskell98

Graphics.GPipe.Sampler

Contents

Description

A sampler is a value from which filtered color samples may be taken inside a shader. A sampler is created from a texture and some sampling parameters. There also exist Shadow samplers that doesnt return a sampled color value, but instead compare a reference value to the texture value.

Synopsis

Sampler data types

data Shadow Source

Used instead of Format for shadow samplers. These samplers have specialized sampler values, see sample1DShadow and friends.

Creating samplers

These Shader actions all take a texture and some filtering and edge options from the shader environment, and return a sampler.

newSampler1D :: forall os f s c. ColorSampleable c => (s -> (Texture1D os (Format c), SamplerFilter c, (EdgeMode, BorderColor c))) -> Shader os f s (Sampler1D (Format c)) Source

newSampler2D :: forall os f s c. ColorSampleable c => (s -> (Texture2D os (Format c), SamplerFilter c, (EdgeMode2, BorderColor c))) -> Shader os f s (Sampler2D (Format c)) Source

newSampler3D :: forall os f s c. ColorRenderable c => (s -> (Texture3D os (Format c), SamplerFilter c, (EdgeMode3, BorderColor c))) -> Shader os f s (Sampler3D (Format c)) Source

newSamplerCube :: forall os f s c. ColorSampleable c => (s -> (TextureCube os (Format c), SamplerFilter c)) -> Shader os f s (SamplerCube (Format c)) Source

Types for specifying sampler filter and edge mode

data Filter Source

Constructors

Nearest 
Linear 

data SamplerFilter c where Source

A GADT for sample filters, where SamplerFilter cannot be used for integer textures.

Sampler properties

These functions can be used to get the size of a sampler inside the shader.

sampler2DSize :: Sampler2D f -> S x Level -> V2 (S x Int) Source

sampler3DSize :: Sampler3D f -> S x Level -> V3 (S x Int) Source

Sampling functions

These functions sample a sampler using its filter and edge mode. Besides the sampler and the coordinate, many additional parameters are provided to enable many different variations of sampling. In most cases when sampling in a FragmentStream, use Nothing or SampleAuto to get what you need. Float coordinates are given with components in range [0,1].

sample2D :: forall c x. ColorSampleable c => Sampler2D (Format c) -> SampleLod2 x -> SampleProj x -> SampleOffset2 x -> V2 (S x Float) -> ColorSample x c Source

sample3D :: forall c x. ColorSampleable c => Sampler3D (Format c) -> SampleLod3 x -> SampleProj x -> SampleOffset3 x -> V3 (S x Float) -> ColorSample x c Source

sampleCube :: forall c x. ColorSampleable c => SamplerCube (Format c) -> SampleLod3 x -> V3 (S x Float) -> ColorSample x c Source

The following functions sample a shadow sampler using a ReferenceValue to compare the texture values to. The returned value is a S x Float value in the range [0,1] where 0 means false, 1 means true and any value in between is a fuzzy boolean value indicating how many adjacent texels compared true and how many compared false.

The following functions retrieve a texel value from a samplers texture without using any filtering. Coordinates for these functions are integer texel indices, and not normalized coordinates.

texelFetch1D :: forall c x. ColorSampleable c => Sampler1D (Format c) -> SampleOffset1 x -> S x Level -> S x Int -> ColorSample x c Source

texelFetch2D :: forall c x. ColorSampleable c => Sampler2D (Format c) -> SampleOffset2 x -> S x Level -> V2 (S x Int) -> ColorSample x c Source

texelFetch3D :: forall c x. ColorSampleable c => Sampler3D (Format c) -> SampleOffset3 x -> S x Level -> V3 (S x Int) -> ColorSample x c Source

Sample parameter types

data SampleLod vx x where Source

A GADT to specify where the level of detail and/or partial derivates should be taken from. Some values of this GADT are restricted to only FragmentStreams.

Constructors

SampleAuto :: SampleLod v F 
SampleBias :: FFloat -> SampleLod vx F 
SampleLod :: S x Float -> SampleLod vx x 
SampleGrad :: vx -> vx -> SampleLod vx x 

type SampleLod2 x = SampleLod (V2 (S x Float)) x Source

type SampleLod3 x = SampleLod (V3 (S x Float)) x Source

data SampleLod' vx x where Source

For some reason, OpenGl doesnt allow explicit lod to be specified for some sampler types, hence this extra GADT.

Constructors

SampleAuto' :: SampleLod' v F 
SampleBias' :: FFloat -> SampleLod' vx F 
SampleGrad' :: vx -> vx -> SampleLod' vx x 

type SampleLod2' x = SampleLod' (V2 (S x Float)) x Source

type SampleLod3' x = SampleLod' (V3 (S x Float)) x Source

type ColorSample x f = Color f (S x (ColorElement f)) Source

The type of a color sample made by a texture t