GPipe-1.1.4: A functional graphics API for programmable GPUsSource codeContentsIndex
Graphics.GPipe.FrameBuffer
Contents
The data type
Displaying framebuffers
Creation
Data retrieval
Paint operations
Description
FrameBuffers are 2D images in which fragments from FragmentStreams are painted. A FrameBuffer may contain any combination of a color buffer, a depth buffer and a stencil buffer. FrameBuffers may be shown in windows, saved to memory or converted to textures. FrameBuffers have no size, but takes the size of the window when shown, or are given a size when saved to memory or converted to a texture.
Synopsis
data FrameBuffer c d s
newWindow :: String -> Vec2 Int -> Vec2 Int -> IO (FrameBuffer c d s) -> (Window -> IO ()) -> IO ()
newFrameBufferColor :: ColorFormat f => Color f Float -> FrameBuffer f () ()
newFrameBufferColorDepth :: ColorFormat f => Color f Float -> Depth -> FrameBuffer f DepthFormat ()
newFrameBufferColorStencil :: ColorFormat f => Color f Float -> Stencil -> FrameBuffer f () StencilFormat
newFrameBufferColorDepthStencil :: ColorFormat f => Color f Float -> Depth -> Stencil -> FrameBuffer f DepthFormat StencilFormat
newFrameBufferDepth :: Depth -> FrameBuffer () DepthFormat ()
newFrameBufferStencil :: Stencil -> FrameBuffer () () StencilFormat
newFrameBufferDepthStencil :: Depth -> Stencil -> FrameBuffer () DepthFormat StencilFormat
getFrameBufferColor :: forall c d s a. GPUFormat c => CPUFormat c -> Vec2 Int -> FrameBuffer c d s -> Ptr a -> IO ()
getFrameBufferDepth :: CPUFormat DepthFormat -> Vec2 Int -> FrameBuffer c DepthFormat s -> Ptr a -> IO ()
getFrameBufferStencil :: CPUFormat StencilFormat -> Vec2 Int -> FrameBuffer c d StencilFormat -> Ptr a -> IO ()
getFrameBufferCPUFormatByteSize :: StorableCPUFormat f => f -> Vec2 Int -> Int
paintColor :: ColorFormat c => Blending -> ColorMask c -> FragmentStream (Color c (Fragment Float)) -> FrameBuffer c d s -> FrameBuffer c d s
paintDepth :: DepthFunction -> DepthMask -> FragmentStream FragmentDepth -> FrameBuffer c DepthFormat s -> FrameBuffer c DepthFormat s
paintColorDepth :: ColorFormat c => DepthFunction -> DepthMask -> Blending -> ColorMask c -> FragmentStream (Color c (Fragment Float), FragmentDepth) -> FrameBuffer c DepthFormat s -> FrameBuffer c DepthFormat s
paintStencil :: StencilTests -> StencilOps -> StencilOps -> FragmentStream (Fragment a) -> FrameBuffer c d StencilFormat -> FrameBuffer c d StencilFormat
paintDepthStencil :: StencilTests -> StencilOps -> DepthFunction -> DepthMask -> StencilOps -> StencilOps -> FragmentStream FragmentDepth -> FrameBuffer c DepthFormat StencilFormat -> FrameBuffer c DepthFormat StencilFormat
paintColorStencil :: ColorFormat c => StencilTests -> StencilOps -> StencilOps -> Blending -> ColorMask c -> FragmentStream (Color c (Fragment Float)) -> FrameBuffer c d StencilFormat -> FrameBuffer c d StencilFormat
paintColorDepthStencil :: ColorFormat c => StencilTests -> StencilOps -> DepthFunction -> DepthMask -> StencilOps -> StencilOps -> Blending -> ColorMask c -> FragmentStream (Color c (Fragment Float), FragmentDepth) -> FrameBuffer c DepthFormat StencilFormat -> FrameBuffer c DepthFormat StencilFormat
paintRastDepth :: DepthFunction -> DepthMask -> FragmentStream (Fragment a) -> FrameBuffer c DepthFormat s -> FrameBuffer c DepthFormat s
paintColorRastDepth :: ColorFormat c => DepthFunction -> DepthMask -> Blending -> ColorMask c -> FragmentStream (Color c (Fragment Float)) -> FrameBuffer c DepthFormat s -> FrameBuffer c DepthFormat s
paintRastDepthStencil :: StencilTests -> StencilOps -> DepthFunction -> DepthMask -> StencilOps -> StencilOps -> FragmentStream (Fragment a) -> FrameBuffer c DepthFormat StencilFormat -> FrameBuffer c DepthFormat StencilFormat
paintColorRastDepthStencil :: ColorFormat c => StencilTests -> StencilOps -> DepthFunction -> DepthMask -> StencilOps -> StencilOps -> Blending -> ColorMask c -> FragmentStream (Color c (Fragment Float)) -> FrameBuffer c DepthFormat StencilFormat -> FrameBuffer c DepthFormat StencilFormat
type ColorMask f = Color f Bool
data Blending
= NoBlending
| Blend (BlendEquation, BlendEquation) ((BlendingFactor, BlendingFactor), (BlendingFactor, BlendingFactor)) (Color RGBAFormat Float)
| BlendLogicOp LogicOp
BlendEquation (FuncAdd, FuncSubtract, FuncReverseSubtract, Min, Max, LogicOp)
BlendingFactor (Zero, One, SrcColor, OneMinusSrcColor, DstColor, OneMinusDstColor, SrcAlpha, OneMinusSrcAlpha, DstAlpha, OneMinusDstAlpha, ConstantColor, OneMinusConstantColor, ConstantAlpha, OneMinusConstantAlpha, SrcAlphaSaturate)
LogicOp (Clear, And, AndReverse, Copy, AndInverted, Noop, Xor, Or, Nor, Equiv, Invert, OrReverse, CopyInverted, OrInverted, Nand, Set)
ComparisonFunction (Never, Less, Equal, Lequal, Greater, Notequal, Gequal, Always)
type DepthFunction = ComparisonFunction
type DepthMask = Bool
data StencilOps = StencilOps {
frontStencilOp :: StencilOp
backStencilOp :: StencilOp
}
StencilOp (OpZero, OpKeep, OpReplace, OpIncr, OpIncrWrap, OpDecr, OpDecrWrap, OpInvert)
data StencilTest = StencilTest {
stencilComparision :: ComparisonFunction
stencilReference :: Int32
stencilMask :: Word32
}
data StencilTests = StencilTests StencilTest StencilTest
type FragmentDepth = Fragment Float
The data type
data FrameBuffer c d s Source
A polymorphic frame buffer. It is parameterized on the type of color buffer, depth buffer and stencil buffer. Any instances of ColorFormat can be used for color buffer, or '()' to denote no color buffer. For depth and stencil buffers, DepthFormat and StencilFormat marks the existance of buffer, while '()' marks the inexistance.
Displaying framebuffers
newWindowSource
::
=> StringThe window title
-> Vec2 IntThe window position
-> Vec2 IntThe window size
-> IO (FrameBuffer c d s)This IO action will be run every time the window needs to be redrawn, and the resulting FrameBuffer will be drawn in the window.
-> Window -> IO ()Extra optional initialization of the window. The provided Window should not be used outside this function.
-> IO ()
Cretes and shows a new GPipe window. Use the last parameter to add extra GLUT callbacks to the window. Note that you can't register your own displayCallback and reshapeCallback.
Creation
These functions create new FrameBuffers with initial color, depth values and/or stencil values.
newFrameBufferColor :: ColorFormat f => Color f Float -> FrameBuffer f () ()Source
newFrameBufferColorDepth :: ColorFormat f => Color f Float -> Depth -> FrameBuffer f DepthFormat ()Source
newFrameBufferColorStencil :: ColorFormat f => Color f Float -> Stencil -> FrameBuffer f () StencilFormatSource
newFrameBufferColorDepthStencil :: ColorFormat f => Color f Float -> Depth -> Stencil -> FrameBuffer f DepthFormat StencilFormatSource
newFrameBufferDepth :: Depth -> FrameBuffer () DepthFormat ()Source
newFrameBufferStencil :: Stencil -> FrameBuffer () () StencilFormatSource
newFrameBufferDepthStencil :: Depth -> Stencil -> FrameBuffer () DepthFormat StencilFormatSource
Data retrieval
These functions provides the means for saving a FrameBuffer to main memory without the need to show it in a window.
getFrameBufferColorSource
:: forall c d s a . GPUFormat c
=> CPUFormat cThe format to store data to
-> Vec2 IntThe size to give the frame buffer
-> FrameBuffer c d sA frame buffer with a color buffer
-> Ptr aA pointer to the memory where the data will be saved
-> IO ()
Saves a FrameBuffers color buffer to main memory.
getFrameBufferDepthSource
::
=> CPUFormat DepthFormatThe format to store data to
-> Vec2 IntThe size to give the frame buffer
-> FrameBuffer c DepthFormat sA frame buffer with a depth buffer
-> Ptr aA pointer to the memory where the data will be saved
-> IO ()
Saves a FrameBuffers depth buffer to main memory.
getFrameBufferStencilSource
::
=> CPUFormat StencilFormatThe format to store data to
-> Vec2 IntThe size to give the frame buffer
-> FrameBuffer c d StencilFormatA frame buffer with a stencil buffer
-> Ptr aA pointer to the memory where the data will be saved
-> IO ()
Saves a FrameBuffers stencil buffer to main memory.
getFrameBufferCPUFormatByteSizeSource
:: StorableCPUFormat f
=> fThe format to store data to
-> Vec2 IntThe size to give the frame buffer
-> IntThe size in bytes of the data
Returns the byte size needed to store a certain format and size of a framebuffer. Use this to allocate memory before using getFrameBufferColor, getFrameBufferDepth or getFrameBufferStencil.
Paint operations

These functions paint FragmentStreams on FrameBuffers. A lot of different functions are provided for different types of FrameBuffers and FragmentStreams, all which takes more or less state values. The preffered way of using those is to curry them into the specific functions you need in your GPipe program, e.g.

paintSolid = paintColorRastDepth Lequal True NoBlending (RGB (vec True))

The RastDepth-functions uses the rasterized depth for the fragments.

Functions with two StencilOps arguments use them in this order: First if stencil test fail, second if stencil test pass. Functions with three StencilOps arguments use them in this order: First if stencil test fail, second if depth test fail, third if depth test pass.

paintColor :: ColorFormat c => Blending -> ColorMask c -> FragmentStream (Color c (Fragment Float)) -> FrameBuffer c d s -> FrameBuffer c d sSource
paintDepth :: DepthFunction -> DepthMask -> FragmentStream FragmentDepth -> FrameBuffer c DepthFormat s -> FrameBuffer c DepthFormat sSource
paintColorDepth :: ColorFormat c => DepthFunction -> DepthMask -> Blending -> ColorMask c -> FragmentStream (Color c (Fragment Float), FragmentDepth) -> FrameBuffer c DepthFormat s -> FrameBuffer c DepthFormat sSource
paintStencil :: StencilTests -> StencilOps -> StencilOps -> FragmentStream (Fragment a) -> FrameBuffer c d StencilFormat -> FrameBuffer c d StencilFormatSource
paintDepthStencil :: StencilTests -> StencilOps -> DepthFunction -> DepthMask -> StencilOps -> StencilOps -> FragmentStream FragmentDepth -> FrameBuffer c DepthFormat StencilFormat -> FrameBuffer c DepthFormat StencilFormatSource
paintColorStencil :: ColorFormat c => StencilTests -> StencilOps -> StencilOps -> Blending -> ColorMask c -> FragmentStream (Color c (Fragment Float)) -> FrameBuffer c d StencilFormat -> FrameBuffer c d StencilFormatSource
paintColorDepthStencil :: ColorFormat c => StencilTests -> StencilOps -> DepthFunction -> DepthMask -> StencilOps -> StencilOps -> Blending -> ColorMask c -> FragmentStream (Color c (Fragment Float), FragmentDepth) -> FrameBuffer c DepthFormat StencilFormat -> FrameBuffer c DepthFormat StencilFormatSource
paintRastDepth :: DepthFunction -> DepthMask -> FragmentStream (Fragment a) -> FrameBuffer c DepthFormat s -> FrameBuffer c DepthFormat sSource
paintColorRastDepth :: ColorFormat c => DepthFunction -> DepthMask -> Blending -> ColorMask c -> FragmentStream (Color c (Fragment Float)) -> FrameBuffer c DepthFormat s -> FrameBuffer c DepthFormat sSource
paintRastDepthStencil :: StencilTests -> StencilOps -> DepthFunction -> DepthMask -> StencilOps -> StencilOps -> FragmentStream (Fragment a) -> FrameBuffer c DepthFormat StencilFormat -> FrameBuffer c DepthFormat StencilFormatSource
paintColorRastDepthStencil :: ColorFormat c => StencilTests -> StencilOps -> DepthFunction -> DepthMask -> StencilOps -> StencilOps -> Blending -> ColorMask c -> FragmentStream (Color c (Fragment Float)) -> FrameBuffer c DepthFormat StencilFormat -> FrameBuffer c DepthFormat StencilFormatSource
type ColorMask f = Color f BoolSource
True for each color component that should be written to the FrameBuffer.
data Blending Source
Sets how the painted colors are blended with the FrameBuffers previous value.
Constructors
NoBlendingThe painted fragment completely overwrites the previous value.
Blend (BlendEquation, BlendEquation) ((BlendingFactor, BlendingFactor), (BlendingFactor, BlendingFactor)) (Color RGBAFormat Float)Use blending equations to combine the fragment with the previous value. The first BlendEquation and BlendingFactors is used for front faced triangles and other primitives, and the second for back faced triangles.
BlendLogicOp LogicOpUse a LogicOp to combine the fragment with the previous value.
show/hide Instances
BlendEquation (FuncAdd, FuncSubtract, FuncReverseSubtract, Min, Max, LogicOp)
BlendingFactor (Zero, One, SrcColor, OneMinusSrcColor, DstColor, OneMinusDstColor, SrcAlpha, OneMinusSrcAlpha, DstAlpha, OneMinusDstAlpha, ConstantColor, OneMinusConstantColor, ConstantAlpha, OneMinusConstantAlpha, SrcAlphaSaturate)
LogicOp (Clear, And, AndReverse, Copy, AndInverted, Noop, Xor, Or, Nor, Equiv, Invert, OrReverse, CopyInverted, OrInverted, Nand, Set)
ComparisonFunction (Never, Less, Equal, Lequal, Greater, Notequal, Gequal, Always)
type DepthFunction = ComparisonFunctionSource
The function used to compare the fragment's depth and the depth buffers depth with.
type DepthMask = BoolSource
True if the depth component should be written to the FrameBuffer.
data StencilOps Source
Sets the operations that should be performed on the FrameBuffers stencil value
Constructors
StencilOps
frontStencilOp :: StencilOpUsed for front faced triangles and other primitives.
backStencilOp :: StencilOpUsed for back faced triangles.
show/hide Instances
StencilOp (OpZero, OpKeep, OpReplace, OpIncr, OpIncrWrap, OpDecr, OpDecrWrap, OpInvert)
data StencilTest Source
Sets a test that should be performed on the stencil value.
Constructors
StencilTest
stencilComparision :: ComparisonFunctionThe function used to compare the stencilReference and the stencil buffers value with.
stencilReference :: Int32The value to compare with the stencil buffer's value.
stencilMask :: Word32A bit mask with ones in each position that should be compared and written to the stencil buffer.
show/hide Instances
data StencilTests Source
Sets the tests that should be performed on the stencil value, first for front facing triangles and other primitives, then for back facing triangles.
Constructors
StencilTests StencilTest StencilTest
show/hide Instances
type FragmentDepth = Fragment FloatSource
Produced by Haddock version 2.4.2