| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Graphics.OpenGLES.Framebuffer
Contents
- clear :: [RenderConfig] -> BufferMask -> GL ()
- clearColor :: Float -> Float -> Float -> Float -> GL ()
- clearDepth :: Float -> GL ()
- clearStencil :: Int32 -> GL ()
- data BufferMask
- colorBuffer :: BufferMask
- depthBuffer :: BufferMask
- stencilBuffer :: BufferMask
- colorMask :: Bool -> Bool -> Bool -> Bool -> GL ()
- depthMask :: Bool -> GL ()
- stencilMask :: Word32 -> GL ()
- stencilMaskSep :: CullFace -> Word32 -> GL ()
- glRenderbuffer :: forall a b. InternalFormat a b => Int32 -> GL (V2 Int32) -> GL (Renderbuffer b)
- unsafeRenderbuffer :: Int32 -> GL (V2 Int32) -> GLenum -> GL (Renderbuffer a)
- glFramebuffer :: [CR] -> DepthStencil -> GL Framebuffer
- data CR = forall a c . (Attachable a c, ColorRenderable c) => CR (a c)
- class Attachable a b
- data DepthStencil
- colorOnly :: DepthStencil
- depthImage :: (Attachable a d, DepthRenderable d) => a d -> DepthStencil
- stencilImage :: (Attachable a s, StencilRenderable s) => a s -> DepthStencil
- depthStencil :: (Attachable a r, DepthRenderable r, StencilRenderable r) => a r -> DepthStencil
- bindFb :: Framebuffer -> GL ()
- withFb :: Framebuffer -> GL a -> GL a
- defaultFramebuffer :: Framebuffer
- viewport :: V4 Int32 -> GL ()
- getViewport :: GL (V4 Int32)
- withViewport :: V4 Int32 -> GL a -> GL a
- depthRange :: V2 Float -> GL ()
- getDepthRange :: GL (V2 Float)
- withDepthRange :: V2 Float -> GL a -> GL a
Whole Framebuffer Operations
Clearing the Buffers
clear :: [RenderConfig] -> BufferMask -> GL () Source
Clear the bound Framebuffer.
clear [] colorBuffer clear [bindFb framebuffer] (colorBuffer+depthBuffer)
clearDepth :: Float -> GL () Source
Specify clear depth
clearStencil :: Int32 -> GL () Source
Specify clear stencil
data BufferMask Source
Instances
Fine Control of Buffer Updates
stencilMask :: Word32 -> GL () Source
Stencil mask
stencilMaskSep :: CullFace -> Word32 -> GL () Source
Stencil mask by face
Renderbuffer
Arguments
| :: InternalFormat a b | |
| => Int32 | sample count (0 to disable multisampling) | 
| -> GL (V2 Int32) | renderbuffer dimentions getter | 
| -> GL (Renderbuffer b) | 
New Renderbuffer with specified sample count and dimentions.
Arguments
| :: Int32 | sample count (0 to disable multisampling) | 
| -> GL (V2 Int32) | renderbuffer dimentions getter | 
| -> GLenum | internal format enum | 
| -> GL (Renderbuffer a) | 
glRenderbuffer with explicit internal format.
Framebuffer
glFramebuffer :: [CR] -> DepthStencil -> GL Framebuffer Source
New Framebuffer from specified ColorRenderables and DepthStencil
Color renderable wrapper.
Constructors
| forall a c . (Attachable a c, ColorRenderable c) => CR (a c) | 
class Attachable a b Source
Minimal complete definition
data DepthStencil Source
Depth and Stencil renderable wrapper.
depthImage :: (Attachable a d, DepthRenderable d) => a d -> DepthStencil Source
stencilImage :: (Attachable a s, StencilRenderable s) => a s -> DepthStencil Source
depthStencil :: (Attachable a r, DepthRenderable r, StencilRenderable r) => a r -> DepthStencil Source
Framebuffer Settings
bindFb :: Framebuffer -> GL () Source
Bind the Framebuffer.
withFb :: Framebuffer -> GL a -> GL a Source
Cliping current framebuffer. Note that origin is left-bottom.
depthRange :: V2 Float -> GL () Source