ombra-0.1.0.0: Render engine.

Safe HaskellNone
LanguageHaskell2010

Graphics.Rendering.Ombra.Generic

Contents

Synopsis

Objects

data Object gs is where Source #

A geometry associated with some uniforms.

Constructors

(:~>) :: Global g -> Object gs is -> Object (g ': gs) is infixr 2 

class MemberGlobal g gs where Source #

Minimal complete definition

(~~>)

Methods

(~~>) :: Uniform S g => (Draw (CPU S g) -> Global g) -> Object gs is -> Object gs is infixr 2 Source #

Modify the global of an Object.

Instances

((~) Bool ((==) * g g1) False, MemberGlobal g gs) => MemberGlobal g ((:) * g1 gs) Source # 

Methods

(~~>) :: Uniform (S * *) g => (Draw (CPU (S * *) g) -> Global g) -> Object ((* ': g1) gs) is -> Object ((* ': g1) gs) is Source #

MemberGlobal g ((:) * g gs) Source # 

Methods

(~~>) :: Uniform (S * *) g => (Draw (CPU (S * *) g) -> Global g) -> Object ((* ': g) gs) is -> Object ((* ': g) gs) is Source #

class RemoveGlobal g gs gs' where Source #

Minimal complete definition

(*~>)

Methods

(*~>) :: (a -> g) -> Object gs is -> Object gs' is infixr 2 Source #

Remove a global from an Object.

Instances

RemoveGlobal g ((:) * g gs) gs Source # 

Methods

(*~>) :: (a -> g) -> Object ((* ': g) gs) is -> Object gs is Source #

((~) Bool ((==) * g g1) False, RemoveGlobal g gs gs') => RemoveGlobal g ((:) * g1 gs) ((:) * g1 gs') Source # 

Methods

(*~>) :: (a -> g) -> Object ((* ': g1) gs) is -> Object ((* ': g1) gs') is Source #

nothing :: Object '[] '[] Source #

An empty object.

geom :: Geometry i -> Object '[] i Source #

An object with a specified Geometry.

modifyGeometry :: Empty is ~ False => (Geometry is -> Geometry is') -> Object gs is -> Object gs is' Source #

Modify the geometry of an Object.

Groups

data Group gs is Source #

A group of Objects.

group :: (Set is, Set gs) => [Object is gs] -> Group is gs Source #

Create a Group from a list of Objects.

(~~) :: (EqualJoin gs gs' (Text "globals"), EqualJoin is is' (Text "inputs")) => Group gs is -> Group gs' is' -> Group (Union gs gs') (Union is is') Source #

Join two groups.

unsafeJoin :: Group gs is -> Group gs' is' -> Group (Union gs gs') (Union is is') Source #

Join two groups, even if they don't provide the same variables.

emptyGroup :: Group is gs Source #

An empty group.

globalGroup :: Global g -> Group gs is -> Group (g ': gs) is Source #

Set a global uniform for a Group.

depthTest :: Bool -> Group gs is -> Group gs is Source #

Enable/disable the depth test for a Group.

Blending

blend :: Mode -> Group gs is -> Group gs is Source #

Set the blending mode for a Group of objects.

noBlend :: Group gs is -> Group gs is Source #

Disable blending for a Group.

transparency :: Mode Source #

Standard transparency (default).

additive :: Mode Source #

Additive blend mode.

Stencil test

Layers

data Layer Source #

A Group associated with a program.

layer :: (Subset progAttr grpAttr, Subset progUni grpUni) => Program progUni progAttr -> Group grpUni grpAttr -> Layer Source #

Associate a group with a program.

combineLayers :: [Layer] -> Layer Source #

Combine some layers.

Sublayers

subLayer Source #

Arguments

:: Int

Texture width.

-> Int

Texture height.

-> Layer

Layer to draw on a Texture.

-> (Texture -> [Layer])

Layers using the texture.

-> Layer 

Use a Layer as a Texture on another.

subLayer w h l = subRenderLayer . renderColor w h l

depthSubLayer Source #

Arguments

:: Int

Texture width.

-> Int

Texture height.

-> Layer

Layer to draw on a depth Texture.

-> (Texture -> [Layer])

Layers using the texture.

-> Layer 

Use a Layer as a depth Texture on another.

depthSubLayer w h l = subRenderLayer . renderDepth w h l

subRenderLayer :: RenderLayer [Layer] -> Layer Source #

Generalized version of subLayer and depthSubLayer.

Render layers

data RenderLayer a Source #

Represents a Layer drawn on a Texture.

renderColor Source #

Arguments

:: Int

Texture width.

-> Int

Texture height.

-> Layer

Layer to draw on a Texture.

-> (Texture -> a)

Function using the texture.

-> RenderLayer a 

Render a Layer in a Texture.

renderDepth Source #

Arguments

:: Int

Texture width.

-> Int

Texture height.

-> Layer

Layer to draw on a depth Texture.

-> (Texture -> a)

Function using the texture.

-> RenderLayer a 

Render a Layer in a depth Texture

renderColorDepth Source #

Arguments

:: Int

Texture width.

-> Int

Texture height.

-> Layer

Layer to draw on a Texture

-> (Texture -> Texture -> a)

Color, depth.

-> RenderLayer a 

Combination of renderColor and renderDepth.

renderColorInspect Source #

Arguments

:: Int

Texture width.

-> Int

Texture height.

-> Layer

Layer to draw on a Texture.

-> Int

First pixel to read X

-> Int

First pixel to read Y

-> Int

Width of the rectangle to read

-> Int

Height of the rectangle to read

-> (Texture -> [Color] -> a)

Function using the texture.

-> RenderLayer a 

Render a Layer in a Texture, reading the content of the texture.

renderDepthInspect Source #

Arguments

:: Int

Texture width.

-> Int

Texture height.

-> Layer

Layer to draw on a depth Texture.

-> Int

First pixel to read X

-> Int

First pixel to read Y

-> Int

Width of the rectangle to read

-> Int

Height of the rectangle to read

-> (Texture -> [Word8] -> a)

Layers using the texture.

-> RenderLayer a 

Render a Layer in a depth Texture, reading the content of the texture. Not supported on WebGL.

renderColorDepthInspect Source #

Arguments

:: Int

Texture width.

-> Int

Texture height.

-> Layer

Layer to draw on a Texture

-> Int

First pixel to read X

-> Int

First pixel to read Y

-> Int

Width of the rectangle to read

-> Int

Height of the rectangle to read

-> (Texture -> Texture -> [Color] -> [Word8] -> a)

Layers using the texture.

-> RenderLayer a 

Combination of renderColorInspect and renderDepthInspect. Not supported on WebGL.

renderBuffers Source #

Arguments

:: Int

Textures width.

-> Int

Textures height.

-> Int

Number of colors.

-> Layer

Layer to draw.

-> ([Texture] -> a)

Function using the texture.

-> RenderLayer a 

Render a Layer with multiple floating point colors (use Fragment2, Fragment3, etc.) in some Textures.

Shaders

data Program gs is Source #

A vertex shader associated with a compatible fragment shader.

Instances

Eq (Program gs is) Source # 

Methods

(==) :: Program gs is -> Program gs is -> Bool #

(/=) :: Program gs is -> Program gs is -> Bool #

Hashable (Program gs is) Source # 

Methods

hashWithSalt :: Int -> Program gs is -> Int #

hash :: Program gs is -> Int #

program :: (ValidVertex vgs vis vos, Valid fgs vos '[], Compatible pgs vgs fgs) => VertexShader vgs vis vos -> FragmentShader fgs vos -> Program pgs vis Source #

Create a Program from the shaders.

data Global g Source #

The value of a GPU uniform.

(-=) :: (ShaderVar g, Uniform S g) => (a -> g) -> CPU S g -> Global g infixr 4 Source #

Create a Global from a pure value. The first argument is ignored, it just provides the type (you can use the constructor of the GPU type). You can use this to set the value of a shader uniform.

globalTexture :: (Uniform S g, CPU S g ~ ActiveTexture, ShaderVar g, GLES) => (a -> g) -> Texture -> Global g Source #

Create a Global of CPU type ActiveTexture using a Texture.

globalTexSize :: (ShaderVar g, Uniform S g, GLES) => (a -> g) -> Texture -> ((Int, Int) -> CPU S g) -> Global g Source #

Create a Global using the size of a Texture.

globalFramebufferSize :: (ShaderVar g, Uniform S g) => (a -> g) -> (Vec2 -> CPU S g) -> Global g Source #

Create a Global using the size of the framebuffer.

Geometries

data Geometry is Source #

A set of attributes and indices.

Instances

Eq (Geometry is) Source # 

Methods

(==) :: Geometry is -> Geometry is -> Bool #

(/=) :: Geometry is -> Geometry is -> Bool #

Hashable (Geometry is) Source # 

Methods

hashWithSalt :: Int -> Geometry is -> Int #

hash :: Geometry is -> Int #

data AttrList is where Source #

A heterogeneous list of attributes.

Constructors

AttrListNil :: AttrList '[] 
AttrListCons :: (Hashable (CPU S i), Attribute S i) => (a -> i) -> [CPU S i] -> AttrList is -> AttrList (i ': is) 

Instances

Hashable (AttrList is) Source # 

Methods

hashWithSalt :: Int -> AttrList is -> Int #

hash :: AttrList is -> Int #

mkGeometry :: GLES => AttrList is -> [Word16] -> Geometry is Source #

Create a custom Geometry.

extend Source #

Arguments

:: (Attribute S i, Hashable (CPU S i), ShaderType i, GLES) 
=> (a -> i)

Attribute constructor (or any other function with that type).

-> [CPU S i]

List of values

-> Geometry is 
-> Geometry (i ': is) 

Add an attribute to a geometry.

remove Source #

Arguments

:: (RemoveAttr i is is', GLES) 
=> (a -> i)

Attribute constructor (or any other function with that type).

-> Geometry is 
-> Geometry is' 

Remove an attribute from a geometry.

Textures

data Texture Source #

A texture.

Instances

mkTexture Source #

Arguments

:: GLES 
=> Int

Width.

-> Int

Height.

-> [Color]

List of pixels

-> Texture 

Creates a Texture from a list of pixels.

Colors

data Color Source #

An RGBA 32-bit color.

Constructors

Color !Word8 !Word8 !Word8 !Word8 

Instances

colorTex :: GLES => Color -> Texture Source #

Generate a 1x1 texture.

class (Integral GLEnum, Integral GLUInt, Integral GLInt, Integral GLSize, Bits GLEnum, Num GLEnum, Num GLUInt, Num GLInt, Num GLPtrDiff, Num GLSize, Eq GLEnum, Eq GLUInt, Eq GLInt, Eq GLPtrDiff, Eq GLSize, Eq Texture) => GLES Source #

Backend API.

Minimal complete definition

true, false, nullGLPtr, toGLString, noBuffer, noTexture, noVAO, noUInt8Array, encodeMat2, encodeMat3, encodeMat4, encodeFloats, encodeInts, encodeVec2s, encodeVec3s, encodeVec4s, encodeIVec2s, encodeIVec3s, encodeIVec4s, encodeUShorts, encodeUInt8s, newByteArray, fromFloat32Array, fromInt32Array, fromUInt8Array, fromUInt16Array, decodeBytes, glActiveTexture, glAttachShader, glBindAttribLocation, glBindBuffer, glBindFramebuffer, glBindRenderbuffer, glBindTexture, glBindVertexArray, glBlendColor, glBlendEquation, glBlendEquationSeparate, glBlendFunc, glBlendFuncSeparate, glBufferData, glBufferSubData, glCheckFramebufferStatus, glClear, glClearColor, glClearDepth, glClearStencil, glColorMask, glCompileShader, glCompressedTexImage2D, glCompressedTexSubImage2D, glCopyTexImage2D, glCopyTexSubImage2D, glCreateBuffer, glCreateFramebuffer, glCreateProgram, glCreateRenderbuffer, glCreateShader, glCreateTexture, glCreateVertexArray, glCullFace, glDeleteBuffer, glDeleteFramebuffer, glDeleteProgram, glDeleteRenderbuffer, glDeleteShader, glDeleteTexture, glDeleteVertexArray, glDepthFunc, glDepthMask, glDepthRange, glDetachShader, glDisable, glDisableVertexAttribArray, glDrawArrays, glDrawBuffers, glDrawElements, glEnable, glEnableVertexAttribArray, glFinish, glFlush, glFramebufferRenderbuffer, glFramebufferTexture2D, glFrontFace, glGenerateMipmap, glGetAttribLocation, glGetError, glGetProgramInfoLog, glGetShaderInfoLog, glGetShaderSource, glGetUniformLocation, glHint, glIsBuffer, glIsEnabled, glIsFramebuffer, glIsProgram, glIsRenderbuffer, glIsShader, glIsTexture, glIsVertexArray, glLineWidth, glLinkProgram, glPixelStorei, glPolygonOffset, glReadPixels, glRenderbufferStorage, glSampleCoverage, glScissor, glShaderSource, glStencilFunc, glStencilFuncSeparate, glStencilMask, glStencilMaskSeparate, glStencilOp, glStencilOpSeparate, glTexImage2D, glTexParameterf, glTexParameteri, glTexSubImage2D, glUniform1f, glUniform1fv, glUniform1i, glUniform1iv, glUniform2f, glUniform2fv, glUniform2i, glUniform2iv, glUniform3f, glUniform3fv, glUniform3i, glUniform3iv, glUniform4f, glUniform4fv, glUniform4i, glUniform4iv, glUniformMatrix2fv, glUniformMatrix3fv, glUniformMatrix4fv, glUseProgram, glValidateProgram, glVertexAttrib1f, glVertexAttrib1fv, glVertexAttrib2f, glVertexAttrib2fv, glVertexAttrib3f, glVertexAttrib3fv, glVertexAttrib4f, glVertexAttrib4fv, glVertexAttribPointer, glViewport, gl_DEPTH_BUFFER_BIT, gl_STENCIL_BUFFER_BIT, gl_COLOR_BUFFER_BIT, gl_POINTS, gl_LINES, gl_LINE_LOOP, gl_LINE_STRIP, gl_TRIANGLES, gl_TRIANGLE_STRIP, gl_TRIANGLE_FAN, gl_ZERO, gl_ONE, gl_SRC_COLOR, gl_ONE_MINUS_SRC_COLOR, gl_SRC_ALPHA, gl_ONE_MINUS_SRC_ALPHA, gl_DST_ALPHA, gl_ONE_MINUS_DST_ALPHA, gl_DST_COLOR, gl_ONE_MINUS_DST_COLOR, gl_SRC_ALPHA_SATURATE, gl_FUNC_ADD, gl_BLEND_EQUATION, gl_BLEND_EQUATION_RGB, gl_BLEND_EQUATION_ALPHA, gl_FUNC_SUBTRACT, gl_FUNC_REVERSE_SUBTRACT, gl_BLEND_DST_RGB, gl_BLEND_SRC_RGB, gl_BLEND_DST_ALPHA, gl_BLEND_SRC_ALPHA, gl_CONSTANT_COLOR, gl_ONE_MINUS_CONSTANT_COLOR, gl_CONSTANT_ALPHA, gl_ONE_MINUS_CONSTANT_ALPHA, gl_BLEND_COLOR, gl_ARRAY_BUFFER, gl_ELEMENT_ARRAY_BUFFER, gl_ARRAY_BUFFER_BINDING, gl_ELEMENT_ARRAY_BUFFER_BINDING, gl_STREAM_DRAW, gl_STATIC_DRAW, gl_DYNAMIC_DRAW, gl_BUFFER_SIZE, gl_BUFFER_USAGE, gl_CURRENT_VERTEX_ATTRIB, gl_FRONT, gl_BACK, gl_FRONT_AND_BACK, gl_CULL_FACE, gl_BLEND, gl_DITHER, gl_STENCIL_TEST, gl_DEPTH_TEST, gl_SCISSOR_TEST, gl_POLYGON_OFFSET_FILL, gl_SAMPLE_ALPHA_TO_COVERAGE, gl_SAMPLE_COVERAGE, gl_NO_ERROR, gl_INVALID_ENUM, gl_INVALID_VALUE, gl_INVALID_OPERATION, gl_OUT_OF_MEMORY, gl_CW, gl_CCW, gl_LINE_WIDTH, gl_ALIASED_POINT_SIZE_RANGE, gl_ALIASED_LINE_WIDTH_RANGE, gl_CULL_FACE_MODE, gl_FRONT_FACE, gl_DEPTH_RANGE, gl_DEPTH_WRITEMASK, gl_DEPTH_CLEAR_VALUE, gl_DEPTH_FUNC, gl_STENCIL_CLEAR_VALUE, gl_STENCIL_FUNC, gl_STENCIL_FAIL, gl_STENCIL_PASS_DEPTH_FAIL, gl_STENCIL_PASS_DEPTH_PASS, gl_STENCIL_REF, gl_STENCIL_VALUE_MASK, gl_STENCIL_WRITEMASK, gl_STENCIL_BACK_FUNC, gl_STENCIL_BACK_FAIL, gl_STENCIL_BACK_PASS_DEPTH_FAIL, gl_STENCIL_BACK_PASS_DEPTH_PASS, gl_STENCIL_BACK_REF, gl_STENCIL_BACK_VALUE_MASK, gl_STENCIL_BACK_WRITEMASK, gl_VIEWPORT, gl_SCISSOR_BOX, gl_COLOR_CLEAR_VALUE, gl_COLOR_WRITEMASK, gl_UNPACK_ALIGNMENT, gl_PACK_ALIGNMENT, gl_MAX_TEXTURE_SIZE, gl_MAX_VIEWPORT_DIMS, gl_SUBPIXEL_BITS, gl_RED_BITS, gl_GREEN_BITS, gl_BLUE_BITS, gl_ALPHA_BITS, gl_DEPTH_BITS, gl_STENCIL_BITS, gl_POLYGON_OFFSET_UNITS, gl_POLYGON_OFFSET_FACTOR, gl_TEXTURE_BINDING_2D, gl_SAMPLE_BUFFERS, gl_SAMPLES, gl_SAMPLE_COVERAGE_VALUE, gl_SAMPLE_COVERAGE_INVERT, gl_COMPRESSED_TEXTURE_FORMATS, gl_DONT_CARE, gl_FASTEST, gl_NICEST, gl_GENERATE_MIPMAP_HINT, gl_BYTE, gl_UNSIGNED_BYTE, gl_SHORT, gl_UNSIGNED_SHORT, gl_INT, gl_UNSIGNED_INT, gl_FLOAT, gl_DEPTH_COMPONENT, gl_ALPHA, gl_RGB, gl_RGBA, gl_RGBA32F, gl_LUMINANCE, gl_LUMINANCE_ALPHA, gl_UNSIGNED_SHORT_4_4_4_4, gl_UNSIGNED_SHORT_5_5_5_1, gl_UNSIGNED_SHORT_5_6_5, gl_FRAGMENT_SHADER, gl_VERTEX_SHADER, gl_MAX_VERTEX_ATTRIBS, gl_MAX_VERTEX_UNIFORM_VECTORS, gl_MAX_VARYING_VECTORS, gl_MAX_COMBINED_TEXTURE_IMAGE_UNITS, gl_MAX_VERTEX_TEXTURE_IMAGE_UNITS, gl_MAX_TEXTURE_IMAGE_UNITS, gl_MAX_FRAGMENT_UNIFORM_VECTORS, gl_SHADER_TYPE, gl_DELETE_STATUS, gl_LINK_STATUS, gl_VALIDATE_STATUS, gl_ATTACHED_SHADERS, gl_ACTIVE_UNIFORMS, gl_ACTIVE_ATTRIBUTES, gl_SHADING_LANGUAGE_VERSION, gl_CURRENT_PROGRAM, gl_NEVER, gl_LESS, gl_EQUAL, gl_LEQUAL, gl_GREATER, gl_NOTEQUAL, gl_GEQUAL, gl_ALWAYS, gl_KEEP, gl_REPLACE, gl_INCR, gl_DECR, gl_INVERT, gl_INCR_WRAP, gl_DECR_WRAP, gl_VENDOR, gl_RENDERER, gl_VERSION, gl_NEAREST, gl_LINEAR, gl_NEAREST_MIPMAP_NEAREST, gl_LINEAR_MIPMAP_NEAREST, gl_NEAREST_MIPMAP_LINEAR, gl_LINEAR_MIPMAP_LINEAR, gl_TEXTURE_MAG_FILTER, gl_TEXTURE_MIN_FILTER, gl_TEXTURE_WRAP_S, gl_TEXTURE_WRAP_T, gl_TEXTURE_2D, gl_TEXTURE, gl_TEXTURE_CUBE_MAP, gl_TEXTURE_BINDING_CUBE_MAP, gl_TEXTURE_CUBE_MAP_POSITIVE_X, gl_TEXTURE_CUBE_MAP_NEGATIVE_X, gl_TEXTURE_CUBE_MAP_POSITIVE_Y, gl_TEXTURE_CUBE_MAP_NEGATIVE_Y, gl_TEXTURE_CUBE_MAP_POSITIVE_Z, gl_TEXTURE_CUBE_MAP_NEGATIVE_Z, gl_MAX_CUBE_MAP_TEXTURE_SIZE, gl_TEXTURE0, gl_TEXTURE1, gl_TEXTURE2, gl_TEXTURE3, gl_TEXTURE4, gl_TEXTURE5, gl_TEXTURE6, gl_TEXTURE7, gl_TEXTURE8, gl_TEXTURE9, gl_TEXTURE10, gl_TEXTURE11, gl_TEXTURE12, gl_TEXTURE13, gl_TEXTURE14, gl_TEXTURE15, gl_TEXTURE16, gl_TEXTURE17, gl_TEXTURE18, gl_TEXTURE19, gl_TEXTURE20, gl_TEXTURE21, gl_TEXTURE22, gl_TEXTURE23, gl_TEXTURE24, gl_TEXTURE25, gl_TEXTURE26, gl_TEXTURE27, gl_TEXTURE28, gl_TEXTURE29, gl_TEXTURE30, gl_TEXTURE31, gl_ACTIVE_TEXTURE, gl_REPEAT, gl_CLAMP_TO_EDGE, gl_MIRRORED_REPEAT, gl_FLOAT_VEC2, gl_FLOAT_VEC3, gl_FLOAT_VEC4, gl_INT_VEC2, gl_INT_VEC3, gl_INT_VEC4, gl_BOOL, gl_BOOL_VEC2, gl_BOOL_VEC3, gl_BOOL_VEC4, gl_FLOAT_MAT2, gl_FLOAT_MAT3, gl_FLOAT_MAT4, gl_SAMPLER_2D, gl_SAMPLER_CUBE, gl_VERTEX_ATTRIB_ARRAY_ENABLED, gl_VERTEX_ATTRIB_ARRAY_SIZE, gl_VERTEX_ATTRIB_ARRAY_STRIDE, gl_VERTEX_ATTRIB_ARRAY_TYPE, gl_VERTEX_ATTRIB_ARRAY_NORMALIZED, gl_VERTEX_ATTRIB_ARRAY_POINTER, gl_VERTEX_ATTRIB_ARRAY_BUFFER_BINDING, gl_COMPILE_STATUS, gl_LOW_FLOAT, gl_MEDIUM_FLOAT, gl_HIGH_FLOAT, gl_LOW_INT, gl_MEDIUM_INT, gl_HIGH_INT, gl_FRAMEBUFFER, gl_RENDERBUFFER, gl_RGBA4, gl_RGB5_A1, gl_RGB565, gl_DEPTH_COMPONENT16, gl_STENCIL_INDEX8, gl_RENDERBUFFER_WIDTH, gl_RENDERBUFFER_HEIGHT, gl_RENDERBUFFER_INTERNAL_FORMAT, gl_RENDERBUFFER_RED_SIZE, gl_RENDERBUFFER_GREEN_SIZE, gl_RENDERBUFFER_BLUE_SIZE, gl_RENDERBUFFER_ALPHA_SIZE, gl_RENDERBUFFER_DEPTH_SIZE, gl_RENDERBUFFER_STENCIL_SIZE, gl_FRAMEBUFFER_ATTACHMENT_OBJECT_TYPE, gl_FRAMEBUFFER_ATTACHMENT_OBJECT_NAME, gl_FRAMEBUFFER_ATTACHMENT_TEXTURE_LEVEL, gl_FRAMEBUFFER_ATTACHMENT_TEXTURE_CUBE_MAP_FACE, gl_MAX_DRAW_BUFFERS, gl_DRAW_BUFFER0, gl_DRAW_BUFFER1, gl_DRAW_BUFFER2, gl_DRAW_BUFFER3, gl_DRAW_BUFFER4, gl_DRAW_BUFFER5, gl_DRAW_BUFFER6, gl_DRAW_BUFFER7, gl_DRAW_BUFFER8, gl_DRAW_BUFFER9, gl_DRAW_BUFFER10, gl_DRAW_BUFFER11, gl_DRAW_BUFFER12, gl_DRAW_BUFFER13, gl_DRAW_BUFFER14, gl_DRAW_BUFFER15, gl_MAX_COLOR_ATTACHMENTS, gl_COLOR_ATTACHMENT0, gl_COLOR_ATTACHMENT1, gl_COLOR_ATTACHMENT2, gl_COLOR_ATTACHMENT3, gl_COLOR_ATTACHMENT4, gl_COLOR_ATTACHMENT5, gl_COLOR_ATTACHMENT6, gl_COLOR_ATTACHMENT7, gl_COLOR_ATTACHMENT8, gl_COLOR_ATTACHMENT9, gl_COLOR_ATTACHMENT10, gl_COLOR_ATTACHMENT11, gl_COLOR_ATTACHMENT12, gl_COLOR_ATTACHMENT13, gl_COLOR_ATTACHMENT14, gl_COLOR_ATTACHMENT15, gl_DEPTH_ATTACHMENT, gl_STENCIL_ATTACHMENT, gl_NONE, gl_FRAMEBUFFER_COMPLETE, gl_FRAMEBUFFER_INCOMPLETE_ATTACHMENT, gl_FRAMEBUFFER_INCOMPLETE_MISSING_ATTACHMENT, gl_FRAMEBUFFER_INCOMPLETE_DIMENSIONS, gl_FRAMEBUFFER_UNSUPPORTED, gl_FRAMEBUFFER_BINDING, gl_RENDERBUFFER_BINDING, gl_MAX_RENDERBUFFER_SIZE, gl_INVALID_FRAMEBUFFER_OPERATION