Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- data Sampler1D f
- data Sampler1DArray f
- data Sampler2D f
- data Sampler2DArray f
- data Sampler3D f
- data SamplerCube f
- data Shadow
- newSampler1D :: forall os s c. ColorSampleable c => (s -> (Texture1D os (Format c), SamplerFilter c, (EdgeMode, BorderColor c))) -> Shader os s (Sampler1D (Format c))
- newSampler1DArray :: forall os s c. ColorSampleable c => (s -> (Texture1DArray os (Format c), SamplerFilter c, (EdgeMode, BorderColor c))) -> Shader os s (Sampler1DArray (Format c))
- newSampler2D :: forall os s c. ColorSampleable c => (s -> (Texture2D os (Format c), SamplerFilter c, (EdgeMode2, BorderColor c))) -> Shader os s (Sampler2D (Format c))
- newSampler2DArray :: forall os s c. ColorSampleable c => (s -> (Texture2DArray os (Format c), SamplerFilter c, (EdgeMode2, BorderColor c))) -> Shader os s (Sampler2DArray (Format c))
- newSampler3D :: forall os s c. ColorRenderable c => (s -> (Texture3D os (Format c), SamplerFilter c, (EdgeMode3, BorderColor c))) -> Shader os s (Sampler3D (Format c))
- newSamplerCube :: forall os s c. ColorSampleable c => (s -> (TextureCube os (Format c), SamplerFilter c)) -> Shader os s (SamplerCube (Format c))
- newSampler1DShadow :: forall os s d. DepthRenderable d => (s -> (Texture1D os (Format d), SamplerFilter d, (EdgeMode, BorderColor d), ComparisonFunction)) -> Shader os s (Sampler1D Shadow)
- newSampler1DArrayShadow :: forall os s d. DepthRenderable d => (s -> (Texture1DArray os (Format d), SamplerFilter d, (EdgeMode, BorderColor d), ComparisonFunction)) -> Shader os s (Sampler1DArray Shadow)
- newSampler2DShadow :: forall os s d. DepthRenderable d => (s -> (Texture2D os d, SamplerFilter (Format d), (EdgeMode2, BorderColor d), ComparisonFunction)) -> Shader os s (Sampler2D Shadow)
- newSampler2DArrayShadow :: forall os s d. DepthRenderable d => (s -> (Texture2DArray os (Format d), SamplerFilter d, (EdgeMode2, BorderColor d), ComparisonFunction)) -> Shader os s (Sampler2DArray Shadow)
- newSamplerCubeShadow :: forall os s d. DepthRenderable d => (s -> (TextureCube os (Format d), SamplerFilter d, ComparisonFunction)) -> Shader os s (SamplerCube Shadow)
- data Filter
- data EdgeMode
- type EdgeMode2 = V2 EdgeMode
- type EdgeMode3 = V3 EdgeMode
- type BorderColor c = Color c (ColorElement c)
- type Anisotropy = Maybe Float
- type MinFilter = Filter
- type MagFilter = Filter
- type LodFilter = Filter
- data SamplerFilter c where
- SamplerFilter :: ColorElement c ~ Float => MagFilter -> MinFilter -> LodFilter -> Anisotropy -> SamplerFilter c
- SamplerNearest :: SamplerFilter c
- data ComparisonFunction
- sampler1DSize :: Sampler1D f -> S x Level -> S x Int
- sampler1DArraySize :: Sampler1DArray f -> S x Level -> V2 (S x Int)
- sampler2DSize :: Sampler2D f -> S x Level -> V2 (S x Int)
- sampler2DArraySize :: Sampler2DArray f -> S x Level -> V3 (S x Int)
- sampler3DSize :: Sampler3D f -> S x Level -> V3 (S x Int)
- samplerCubeSize :: SamplerCube f -> S x Level -> S x Int
- sample1D :: forall c x. ColorSampleable c => Sampler1D (Format c) -> SampleLod1 x -> SampleProj x -> SampleOffset1 x -> S x Float -> ColorSample x c
- sample1DArray :: forall c x. ColorSampleable c => Sampler1DArray (Format c) -> SampleLod1 x -> SampleOffset1 x -> V2 (S x Float) -> ColorSample x c
- sample2D :: forall c x. ColorSampleable c => Sampler2D (Format c) -> SampleLod2 x -> SampleProj x -> SampleOffset2 x -> V2 (S x Float) -> ColorSample x c
- sample2DArray :: forall c x. ColorSampleable c => Sampler2DArray (Format c) -> SampleLod2 x -> SampleOffset2 x -> V3 (S x Float) -> ColorSample x c
- sample3D :: forall c x. ColorSampleable c => Sampler3D (Format c) -> SampleLod3 x -> SampleProj x -> SampleOffset3 x -> V3 (S x Float) -> ColorSample x c
- sampleCube :: forall c x. ColorSampleable c => SamplerCube (Format c) -> SampleLod3 x -> V3 (S x Float) -> ColorSample x c
- sample1DShadow :: forall x. Sampler1D Shadow -> SampleLod1 x -> SampleProj x -> SampleOffset1 x -> ReferenceValue x -> S x Float -> S x Float
- sample1DArrayShadow :: forall x. Sampler1DArray Shadow -> SampleLod1 x -> SampleOffset1 x -> ReferenceValue x -> V2 (S x Float) -> S x Float
- sample2DShadow :: forall x. Sampler2D Shadow -> SampleLod2 x -> SampleProj x -> SampleOffset2 x -> ReferenceValue x -> V2 (S x Float) -> S x Float
- sample2DArrayShadow :: forall x. Sampler2DArray Shadow -> SampleLod2' x -> SampleOffset2 x -> ReferenceValue x -> V3 (S x Float) -> S x Float
- sampleCubeShadow :: forall x. SamplerCube Shadow -> SampleLod3' x -> ReferenceValue x -> V3 (S x Float) -> S x Float
- texelFetch1D :: forall c x. ColorSampleable c => Sampler1D (Format c) -> SampleOffset1 x -> S x Level -> S x Int -> ColorSample x c
- texelFetch1DArray :: forall c x. ColorSampleable c => Sampler1DArray (Format c) -> SampleOffset1 x -> S x Level -> V2 (S x Int) -> ColorSample x c
- texelFetch2D :: forall c x. ColorSampleable c => Sampler2D (Format c) -> SampleOffset2 x -> S x Level -> V2 (S x Int) -> ColorSample x c
- texelFetch2DArray :: forall c x. ColorSampleable c => Sampler2DArray (Format c) -> SampleOffset2 x -> S x Level -> V3 (S x Int) -> ColorSample x c
- texelFetch3D :: forall c x. ColorSampleable c => Sampler3D (Format c) -> SampleOffset3 x -> S x Level -> V3 (S x Int) -> ColorSample x c
- data SampleLod vx x where
- SampleAuto :: SampleLod v F
- SampleBias :: FFloat -> SampleLod vx F
- SampleLod :: S x Float -> SampleLod vx x
- SampleGrad :: vx -> vx -> SampleLod vx x
- type SampleLod1 x = SampleLod (S x Float) x
- type SampleLod2 x = SampleLod (V2 (S x Float)) x
- type SampleLod3 x = SampleLod (V3 (S x Float)) x
- data SampleLod' vx x where
- SampleAuto' :: SampleLod' v F
- SampleBias' :: FFloat -> SampleLod' vx F
- SampleGrad' :: vx -> vx -> SampleLod' vx x
- type SampleLod2' x = SampleLod' (V2 (S x Float)) x
- type SampleLod3' x = SampleLod' (V3 (S x Float)) x
- fromLod' :: SampleLod' v x -> SampleLod v x
- type SampleProj x = Maybe (S x Float)
- type SampleOffset1 x = Maybe Int
- type SampleOffset2 x = Maybe (V2 Int)
- type SampleOffset3 x = Maybe (V3 Int)
- type ReferenceValue x = S x Float
- type ColorSample x f = Color f (S x (ColorElement f))
Sampler data types
data Sampler1DArray f Source #
data Sampler2DArray f Source #
data SamplerCube f 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 s c. ColorSampleable c => (s -> (Texture1D os (Format c), SamplerFilter c, (EdgeMode, BorderColor c))) -> Shader os s (Sampler1D (Format c)) Source #
newSampler1DArray :: forall os s c. ColorSampleable c => (s -> (Texture1DArray os (Format c), SamplerFilter c, (EdgeMode, BorderColor c))) -> Shader os s (Sampler1DArray (Format c)) Source #
newSampler2D :: forall os s c. ColorSampleable c => (s -> (Texture2D os (Format c), SamplerFilter c, (EdgeMode2, BorderColor c))) -> Shader os s (Sampler2D (Format c)) Source #
newSampler2DArray :: forall os s c. ColorSampleable c => (s -> (Texture2DArray os (Format c), SamplerFilter c, (EdgeMode2, BorderColor c))) -> Shader os s (Sampler2DArray (Format c)) Source #
newSampler3D :: forall os s c. ColorRenderable c => (s -> (Texture3D os (Format c), SamplerFilter c, (EdgeMode3, BorderColor c))) -> Shader os s (Sampler3D (Format c)) Source #
newSamplerCube :: forall os s c. ColorSampleable c => (s -> (TextureCube os (Format c), SamplerFilter c)) -> Shader os s (SamplerCube (Format c)) Source #
newSampler1DShadow :: forall os s d. DepthRenderable d => (s -> (Texture1D os (Format d), SamplerFilter d, (EdgeMode, BorderColor d), ComparisonFunction)) -> Shader os s (Sampler1D Shadow) Source #
newSampler1DArrayShadow :: forall os s d. DepthRenderable d => (s -> (Texture1DArray os (Format d), SamplerFilter d, (EdgeMode, BorderColor d), ComparisonFunction)) -> Shader os s (Sampler1DArray Shadow) Source #
newSampler2DShadow :: forall os s d. DepthRenderable d => (s -> (Texture2D os d, SamplerFilter (Format d), (EdgeMode2, BorderColor d), ComparisonFunction)) -> Shader os s (Sampler2D Shadow) Source #
newSampler2DArrayShadow :: forall os s d. DepthRenderable d => (s -> (Texture2DArray os (Format d), SamplerFilter d, (EdgeMode2, BorderColor d), ComparisonFunction)) -> Shader os s (Sampler2DArray Shadow) Source #
newSamplerCubeShadow :: forall os s d. DepthRenderable d => (s -> (TextureCube os (Format d), SamplerFilter d, ComparisonFunction)) -> Shader os s (SamplerCube Shadow) Source #
Types for specifying sampler filter and edge mode
Instances
Enum EdgeMode Source # | |
Defined in Graphics.GPipe.Internal.Texture | |
Eq EdgeMode Source # | |
type BorderColor c = Color c (ColorElement c) Source #
type Anisotropy = Maybe Float Source #
data SamplerFilter c where Source #
A GADT for sample filters, where SamplerFilter
cannot be used for integer textures.
SamplerFilter :: ColorElement c ~ Float => MagFilter -> MinFilter -> LodFilter -> Anisotropy -> SamplerFilter c | |
SamplerNearest :: SamplerFilter c |
data ComparisonFunction Source #
Instances
Eq ComparisonFunction Source # | |
Defined in Graphics.GPipe.Internal.Texture (==) :: ComparisonFunction -> ComparisonFunction -> Bool # (/=) :: ComparisonFunction -> ComparisonFunction -> Bool # | |
Ord ComparisonFunction Source # | |
Defined in Graphics.GPipe.Internal.Texture compare :: ComparisonFunction -> ComparisonFunction -> Ordering # (<) :: ComparisonFunction -> ComparisonFunction -> Bool # (<=) :: ComparisonFunction -> ComparisonFunction -> Bool # (>) :: ComparisonFunction -> ComparisonFunction -> Bool # (>=) :: ComparisonFunction -> ComparisonFunction -> Bool # max :: ComparisonFunction -> ComparisonFunction -> ComparisonFunction # min :: ComparisonFunction -> ComparisonFunction -> ComparisonFunction # | |
Show ComparisonFunction Source # | |
Defined in Graphics.GPipe.Internal.Texture showsPrec :: Int -> ComparisonFunction -> ShowS # show :: ComparisonFunction -> String # showList :: [ComparisonFunction] -> ShowS # |
Sampler properties
These functions can be used to get the size of a sampler inside the shader.
sampler1DArraySize :: Sampler1DArray f -> S x Level -> V2 (S x Int) Source #
sampler2DArraySize :: Sampler2DArray f -> S x Level -> V3 (S x Int) Source #
samplerCubeSize :: SamplerCube f -> S x Level -> 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].
sample1D :: forall c x. ColorSampleable c => Sampler1D (Format c) -> SampleLod1 x -> SampleProj x -> SampleOffset1 x -> S x Float -> ColorSample x c Source #
sample1DArray :: forall c x. ColorSampleable c => Sampler1DArray (Format c) -> SampleLod1 x -> SampleOffset1 x -> V2 (S x Float) -> ColorSample x c Source #
sample2D :: forall c x. ColorSampleable c => Sampler2D (Format c) -> SampleLod2 x -> SampleProj x -> SampleOffset2 x -> V2 (S x Float) -> ColorSample x c Source #
sample2DArray :: forall c x. ColorSampleable c => Sampler2DArray (Format c) -> SampleLod2 x -> SampleOffset2 x -> V3 (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.
sample1DShadow :: forall x. Sampler1D Shadow -> SampleLod1 x -> SampleProj x -> SampleOffset1 x -> ReferenceValue x -> S x Float -> S x Float Source #
sample1DArrayShadow :: forall x. Sampler1DArray Shadow -> SampleLod1 x -> SampleOffset1 x -> ReferenceValue x -> V2 (S x Float) -> S x Float Source #
sample2DShadow :: forall x. Sampler2D Shadow -> SampleLod2 x -> SampleProj x -> SampleOffset2 x -> ReferenceValue x -> V2 (S x Float) -> S x Float Source #
sample2DArrayShadow :: forall x. Sampler2DArray Shadow -> SampleLod2' x -> SampleOffset2 x -> ReferenceValue x -> V3 (S x Float) -> S x Float Source #
sampleCubeShadow :: forall x. SamplerCube Shadow -> SampleLod3' x -> ReferenceValue x -> V3 (S x Float) -> S x Float Source #
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 #
texelFetch1DArray :: forall c x. ColorSampleable c => Sampler1DArray (Format c) -> SampleOffset1 x -> S x Level -> V2 (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 #
texelFetch2DArray :: forall c x. ColorSampleable c => Sampler2DArray (Format c) -> SampleOffset2 x -> S x Level -> V3 (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 FragmentStream
s.
SampleAuto :: SampleLod v F | |
SampleBias :: FFloat -> SampleLod vx F | |
SampleLod :: S x Float -> SampleLod vx x | |
SampleGrad :: vx -> vx -> SampleLod vx x |
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.
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 #
fromLod' :: SampleLod' v x -> SampleLod v x Source #
type SampleOffset1 x = Maybe Int Source #
type ReferenceValue x = S x Float Source #
type ColorSample x f = Color f (S x (ColorElement f)) Source #
The type of a color sample made by a texture t