Safe Haskell | None |
---|---|
Language | Haskell98 |
Graphics.GPipe.FrameBuffer
Contents
Description
This module defines all functions and types for drawing into a context window
or texture from a Shader
.
- drawContextColor :: forall os s c ds. ContextColorFormat c => (s -> ContextColorOption c) -> FragmentStream (FragColor c) -> Shader os (ContextFormat c ds) s ()
- drawContextDepth :: forall os s c ds. DepthRenderable ds => (s -> DepthOption) -> FragmentStream FragDepth -> Shader os (ContextFormat c ds) s ()
- drawContextColorDepth :: forall os s c ds. (ContextColorFormat c, DepthRenderable ds) => (s -> (ContextColorOption c, DepthOption)) -> FragmentStream (FragColor c, FragDepth) -> Shader os (ContextFormat c ds) s ()
- drawContextStencil :: forall os s c ds. StencilRenderable ds => (s -> StencilOptions) -> FragmentStream () -> Shader os (ContextFormat c ds) s ()
- drawContextColorStencil :: forall os s c ds. (ContextColorFormat c, StencilRenderable ds) => (s -> (ContextColorOption c, StencilOptions)) -> FragmentStream (FragColor c) -> Shader os (ContextFormat c ds) s ()
- drawContextDepthStencil :: forall os s c ds. (DepthRenderable ds, StencilRenderable ds) => (s -> DepthStencilOption) -> FragmentStream FragDepth -> Shader os (ContextFormat c ds) s ()
- drawContextColorDepthStencil :: forall os s c ds. (ContextColorFormat c, DepthRenderable ds, StencilRenderable ds) => (s -> (ContextColorOption c, DepthStencilOption)) -> FragmentStream (FragColor c, FragDepth) -> Shader os (ContextFormat c ds) s ()
- draw :: forall a os f s. (s -> Blending) -> FragmentStream a -> (a -> DrawColors os s ()) -> Shader os f s ()
- drawDepth :: forall a os f s d. DepthRenderable d => (s -> (Blending, Image (Format d), DepthOption)) -> FragmentStream (a, FragDepth) -> (a -> DrawColors os s ()) -> Shader os f s ()
- drawStencil :: forall a os f s st. StencilRenderable st => (s -> (Blending, Image (Format st), StencilOptions)) -> FragmentStream a -> (a -> DrawColors os s ()) -> Shader os f s ()
- drawDepthStencil :: forall a os f s d st. (DepthRenderable d, StencilRenderable st) => (s -> (Blending, Image (Format d), Image (Format st), DepthStencilOption)) -> FragmentStream (a, FragDepth) -> (a -> DrawColors os s ()) -> Shader os f s ()
- drawColor :: forall c s os. ColorRenderable c => (s -> (Image (Format c), ColorMask c, UseBlending)) -> FragColor c -> DrawColors os s ()
- data DrawColors os s a
- data Image f
- imageEquals :: Image a -> Image b -> Bool
- imageSize :: Image f -> V2 Int
- getTexture1DImage :: Texture1D os f -> Level -> Render os f' (Image f)
- getTexture1DArrayImage :: Texture1DArray os f -> Level -> Int -> Render os f' (Image f)
- getTexture2DImage :: Texture2D os f -> Level -> Render os f' (Image f)
- getTexture2DArrayImage :: Texture2DArray os f -> Level -> Int -> Render os f' (Image f)
- getTexture3DImage :: Texture3D os f -> Level -> Int -> Render os f' (Image f)
- getTextureCubeImage :: TextureCube os f -> Level -> CubeSide -> Render os f' (Image f)
- clearContextColor :: forall os c ds. ContextColorFormat c => Color c Float -> Render os (ContextFormat c ds) ()
- clearContextDepth :: DepthRenderable ds => Float -> Render os (ContextFormat c ds) ()
- clearContextStencil :: StencilRenderable ds => Int -> Render os (ContextFormat c ds) ()
- clearContextDepthStencil :: Float -> Int -> Render os (ContextFormat c DepthStencil) ()
- clearColorImage :: forall c os f. ColorRenderable c => Image c -> Color c (ColorElement c) -> Render os f ()
- clearDepthImage :: DepthRenderable d => Image d -> Float -> Render os f ()
- clearStencilImage :: StencilRenderable s => Image s -> Int -> Render os f ()
- clearDepthStencilImage :: Image DepthStencil -> Float -> Int -> Render os f ()
- type FragColor c = Color c (S F (ColorElement c))
- data ContextColorOption f = ContextColorOption Blending (ColorMask f)
- type ColorMask f = Color f Bool
- type UseBlending = Bool
- data Blending
- type ConstantColor = V4 Float
- data BlendingFactors = BlendingFactors {}
- data BlendEquation
- data BlendingFactor
- data LogicOp
- = Clear
- | And
- | AndReverse
- | Copy
- | AndInverted
- | Noop
- | Xor
- | Or
- | Nor
- | Equiv
- | Invert
- | OrReverse
- | CopyInverted
- | OrInverted
- | Nand
- | Set
- type FragDepth = FFloat
- data DepthOption = DepthOption DepthFunction DepthMask
- type DepthMask = Bool
- type DepthFunction = ComparisonFunction
- type StencilOptions = FrontBack StencilOption
- data StencilOption = StencilOption {}
- data DepthStencilOption = DepthStencilOption {}
- data FrontBack a = FrontBack {}
- data StencilOp
- = OpZero
- | OpKeep
- | OpReplace
- | OpIncr
- | OpIncrWrap
- | OpDecr
- | OpDecrWrap
- | OpInvert
Draw into the context window
drawContextColor :: forall os s c ds. ContextColorFormat c => (s -> ContextColorOption c) -> FragmentStream (FragColor c) -> Shader os (ContextFormat c ds) s () Source
Draw color values from a FragmentStream
into the context window.
drawContextDepth :: forall os s c ds. DepthRenderable ds => (s -> DepthOption) -> FragmentStream FragDepth -> Shader os (ContextFormat c ds) s () Source
Perform a depth test for each fragment from a FragmentStream
in the context window. This doesn't draw any color values and only affects the depth buffer.
drawContextColorDepth :: forall os s c ds. (ContextColorFormat c, DepthRenderable ds) => (s -> (ContextColorOption c, DepthOption)) -> FragmentStream (FragColor c, FragDepth) -> Shader os (ContextFormat c ds) s () Source
Perform a depth test for each fragment from a FragmentStream
and write a color value from each fragment that passes the test into the context window.
drawContextStencil :: forall os s c ds. StencilRenderable ds => (s -> StencilOptions) -> FragmentStream () -> Shader os (ContextFormat c ds) s () Source
Perform a stencil test for each fragment from a FragmentStream
in the context window. This doesn't draw any color values and only affects the stencil buffer.
drawContextColorStencil :: forall os s c ds. (ContextColorFormat c, StencilRenderable ds) => (s -> (ContextColorOption c, StencilOptions)) -> FragmentStream (FragColor c) -> Shader os (ContextFormat c ds) s () Source
Perform a stencil test for each fragment from a FragmentStream
and write a color value from each fragment that passes the test into the context window.
drawContextDepthStencil :: forall os s c ds. (DepthRenderable ds, StencilRenderable ds) => (s -> DepthStencilOption) -> FragmentStream FragDepth -> Shader os (ContextFormat c ds) s () Source
Perform a stencil test and depth test (in that order) for each fragment from a FragmentStream
in the context window. This doesnt draw any color values and only affects the depth and stencil buffer.
drawContextColorDepthStencil :: forall os s c ds. (ContextColorFormat c, DepthRenderable ds, StencilRenderable ds) => (s -> (ContextColorOption c, DepthStencilOption)) -> FragmentStream (FragColor c, FragDepth) -> Shader os (ContextFormat c ds) s () Source
Perform a stencil test and depth test (in that order) for each fragment from a FragmentStream
and write a color value from each fragment that passes the tests into the context window.
Draw into one or more texture images
draw :: forall a os f s. (s -> Blending) -> FragmentStream a -> (a -> DrawColors os s ()) -> Shader os f s () Source
Draw all fragments in a FragmentStream
using the provided function that passes each fragment value into a DrawColors
monad. The first argument is a function
that retrieves a Blending
setting from the shader environment, which will be used for all drawColor
actions in the DrawColors
monad where UseBlending
is True
.
(OpenGl 3.3 unfortunately doesn't support having different blending settings for different color targets.)
drawDepth :: forall a os f s d. DepthRenderable d => (s -> (Blending, Image (Format d), DepthOption)) -> FragmentStream (a, FragDepth) -> (a -> DrawColors os s ()) -> Shader os f s () Source
Like draw
, but performs a depth test on each fragment first. The DrawColors
monad is then only run for fragments where the depth test passes.
drawStencil :: forall a os f s st. StencilRenderable st => (s -> (Blending, Image (Format st), StencilOptions)) -> FragmentStream a -> (a -> DrawColors os s ()) -> Shader os f s () Source
Like draw
, but performs a stencil test on each fragment first. The DrawColors
monad is then only run for fragments where the stencil test passes.
drawDepthStencil :: forall a os f s d st. (DepthRenderable d, StencilRenderable st) => (s -> (Blending, Image (Format d), Image (Format st), DepthStencilOption)) -> FragmentStream (a, FragDepth) -> (a -> DrawColors os s ()) -> Shader os f s () Source
Like draw
, but performs a stencil test and a depth test (in that order) on each fragment first. The DrawColors
monad is then only run for fragments where the stencil and depth test passes.
drawColor :: forall c s os. ColorRenderable c => (s -> (Image (Format c), ColorMask c, UseBlending)) -> FragColor c -> DrawColors os s () Source
Draw color values into a color renderable texture image.
data DrawColors os s a Source
A monad in which individual color images can be drawn.
Instances
Monad (DrawColors os s) | |
Functor (DrawColors os s) | |
Applicative (DrawColors os s) |
Texture images
A texture image is a reference to a 2D array of pixels in a texture. Some textures contain one Image
per level of detail while some contain several.
imageEquals :: Image a -> Image b -> Bool Source
Compare two images that doesn't necessarily has same type
getTexture1DArrayImage :: Texture1DArray os f -> Level -> Int -> Render os f' (Image f) Source
getTexture2DArrayImage :: Texture2DArray os f -> Level -> Int -> Render os f' (Image f) Source
getTextureCubeImage :: TextureCube os f -> Level -> CubeSide -> Render os f' (Image f) Source
Clearing the context window
Use these functions to clear the color, depth or stencil values in the context's window
clearContextColor :: forall os c ds. ContextColorFormat c => Color c Float -> Render os (ContextFormat c ds) () Source
Fill the context window's back buffer with a constant color value
clearContextDepth :: DepthRenderable ds => Float -> Render os (ContextFormat c ds) () Source
Fill the context window's back depth buffer with a constant depth value (in the range [0,1])
clearContextStencil :: StencilRenderable ds => Int -> Render os (ContextFormat c ds) () Source
Fill the context window's back stencil buffer with a constant stencil value
clearContextDepthStencil :: Float -> Int -> Render os (ContextFormat c DepthStencil) () Source
Fill the context window's back depth and stencil buffers with a constant depth value (in the range [0,1]) and a constant stencil value
Clearing texture images
Use these functions to clear the color, depth or stencil values in texture images.
clearColorImage :: forall c os f. ColorRenderable c => Image c -> Color c (ColorElement c) -> Render os f () Source
Fill a color image with a constant color value
clearDepthImage :: DepthRenderable d => Image d -> Float -> Render os f () Source
Fill a depth image with a constant depth value (in the range [0,1])
clearStencilImage :: StencilRenderable s => Image s -> Int -> Render os f () Source
Fill a depth image with a constant stencil value
clearDepthStencilImage :: Image DepthStencil -> Float -> Int -> Render os f () Source
Fill a combined depth stencil image with a constant depth value (in the range [0,1]) and a constant stencil value
Color drawing types
data ContextColorOption f Source
Constructors
ContextColorOption Blending (ColorMask f) |
type ColorMask f = Color f Bool Source
True
for each color component that should be written to the target.
type UseBlending = Bool Source
Denotes how each fragment's color value should be blended with the target value.
Constructors
NoBlending | The fragment's color will simply replace the target value. |
BlendRgbAlpha (BlendEquation, BlendEquation) (BlendingFactors, BlendingFactors) ConstantColor | The fragment's color will be blended using an equation and a set of factors for the RGB components, and a separate equation and set of factors for the Alpha component (if present), and a |
LogicOp LogicOp | A logical operation that will be done on the bits of the fragment color and the target color. This kind of blending is only done on colors that has a
integral internal representation (e.g. |
type ConstantColor = V4 Float Source
data BlendingFactors Source
A set of blending factors used for the source (fragment) and the destination (target).
Constructors
BlendingFactors | |
Fields |
data BlendEquation Source
The equation used to combine the source (fragment) and the destination (target) after they have been multiplied with their respective BlendingFactor
s.
Constructors
FuncAdd | |
FuncSubtract | |
FuncReverseSubtract | |
Min | |
Max |
data BlendingFactor Source
A factor that the source (fragment) or the destination (target) will be multiplied with before combined with the other in the BlendEquation
.
A bitwise logical operation that will be used to combine colors that has an integral internal representation.
Constructors
Clear | |
And | |
AndReverse | |
Copy | |
AndInverted | |
Noop | |
Xor | |
Or | |
Nor | |
Equiv | |
Invert | |
OrReverse | |
CopyInverted | |
OrInverted | |
Nand | |
Set |
Depth drawing types
data DepthOption Source
Constructors
DepthOption DepthFunction DepthMask |
type DepthFunction = ComparisonFunction Source
The function used to compare the fragment's depth and the depth buffers depth with. E.g. Less
means "where fragment's depth is less than the buffers current depth".
Stencil drawing types
data StencilOption Source
Constructors
StencilOption | |
data DepthStencilOption Source
Constructors
DepthStencilOption | |
Denotes the operation that will be performed on the target's stencil value
Constructors
OpZero | |
OpKeep | |
OpReplace | |
OpIncr | |
OpIncrWrap | |
OpDecr | |
OpDecrWrap | |
OpInvert |