lowgl-0.1.0.0: Basic gl wrapper and reference

Safe HaskellNone
LanguageHaskell2010

Graphics.GL.Low

Contents

Synopsis

In a Nutshell

Overview

OpenGL is a graphics rendering interface. This library exposes a vastly simplified subset of OpenGL that is hopefully still complete enough for many purposes, such as following tutorials, making simple games, and demos. In particular the intention is to concentrate on a subset of OpenGL 3.2 (Core Profile) roughly corresponding to ES 2.0.

A second primary purpose is to document the complex model behind the interface in a way that is more elaborate than tutorials and more concise than the spec. As such, this is an experimental project to aid my own process of understanding OpenGL. It seems that understanding the entire picture up-front is the only way to get started, so this should also serve as a quick reference guide to the core commands and concepts.

This library uses the gl package for raw bindings to OpenGL and the linear package for matrices.

(include link to example programs)

Objects

Objects may be created and destroyed by client code. They include:

Binding Targets

Objects are referenced with integers (called names in GL), so binding targets can be thought of as global variables to put those references. Many operations implicitly read from these globals to determine what the target object of the operation is. They include:

  • Vertex array binding target (for VAO)
  • Buffer binding targets (ARRAY_BUFFER and ELEMENT_ARRAY_BUFFER)
  • Texture binding targets (TEXTURE_2D and TEXTURE_CUBE_MAP)
  • Framebuffer binding target (for FBO)

(not binding targets but similar)

  • Shader program "in use"
  • Texture units
  • Current active texture unit
  • Image attachment points of an FBO

Shader Programs

The role of the second half of a program, the fragment shader, is to compute the color and depth of pixels covered by rasterized primitives (points, lines, and triangles) in the process of rendering. The role of the first half of the program (vertex program) is to arrange the vertices of those primitives somewhere in clip space. Where these vertices and their attributes come from in the first place is determined by the VAO bound to the vertex array binding target. The program may also make use of uniform variables and texture units assigned by client code before rendering (but in a process separate from configuring the VAO). At most one Program can be "in use" at a time.

VAO

The VAO is essential. At least one VAO must be created and bound to the vertex array binding target before rendering, before configuring a program's vertex attributes. Here is why: the VAO stores the association between input variables in the program and a VBO from which to pipe input from. It also stores the format of the VBO data, which is otherwise just a big blob. Finally, the VAO stores the state of the element array binding target used for indexed rendering.

After installing a program with useProgram and binding a source VBO to the array buffer binding target (bindVBO) then the bound VAO can be updated (setVertexAttributeLayout) with new vertex attribute information. After this, the VBO can be rebound to configure a different set of inputs with a different source. Many VAOs can be created and swapped out to pipe vertex data in different ways to different programs (or the same program).

When a VAO is bound it restores the state of the element array binding target. For this reason you can think of that binding target as simply being a function of the VAO itself rather than a separate global state.

Uniforms and Samplers (Textures)

Programs may have uniform variables and "sampler uniforms" as input. Uniforms are accessible from the vertex or fragment shader part of the program but their values are fixed during the course of a rendering command. They can be set and reset with the setUniform family (ex. setUniform1f), which updates a program object with new uniform values. Among other things, updating the uniforms each frame is the main way to animate a scene.

Samplers are textures that the shader can interpolate to get "in between" values. The texture a sampler uses is determined by the contents of the texture unit that that sampler points to. The sampler is a uniform with an integer type. This integer is the texture unit to use. The word texture should not be construed to mean a color image. Shaders can make use of many kinds of multi-dimensional data that happen to be available through the samplers.

Texture Objects and Texture Units

Before a shader can use a texture it must be assigned to a texture unit. First set the active texture unit to the desired unit number (setActiveTextureUnit) then bind the texture object to one of the two texture binding targets, depending on what kind of texture it is (2D or cubemap). Binding a texture has the side effect of assigning it to the active texture unit.

Custom Framebuffers

It is possible (and important to many techniques) to utilize an off-screen render target. To do this create an FBO (newFBO), bind it to the framebuffer binding target (bindFramebuffer) and attach a color image object (texture or renderbuffer object). If necessary a depth image or combination depth-stencil image can be attached as well. If no color image is attached then the FBO is incomplete and rendering will be an error. After rendering to an FBO any textures that were attached can be used for a second pass by assigning them to a texture unit. Watch out for feedback loops accidentally sampling a texture that is also being rendered to at the same time!

A renderbuffer object is a minor character to be used when you do not expect to use the results of rendering but need an image anyway. For example you may need a depth buffer to do depth testing, or you may want to ignore the (required for rendering to work at all) color buffer.

Images and Image Formats

FBOs have attachment points for images. A texture serves as an image and a renderbuffer object serves as an image. Images have an "internal format" which describes the size and interpretation of pixel components. There are seven internal formats, five of which are color image formats such as grayscale and RGB. The other two are the depth buffer format and the combination depth-stencil format. RBOs (newRBO) and empty textures (newEmptyTexture2D, newEmptyCubeMap) can be created with any of these formats.

(The above is a gross simplification of OpenGL's image formats. I should probably revise, because it may greatly improve performance to use some of the 16-bit color formats rather than 32.)

Depth Testing, Stencil Testing, Scissor Testing, Facet Culling

The depth buffer and stencil buffers, if present in the current framebuffer, can be used to avoid rendering to points of the screen by testing against the value stored at those points. For example if commanded to show a triangle in a region of the framebuffer with a depth greater than current depth buffer values, then the triangle may not be rendered to the color buffer or anywhere else (depending on settings). There are many global settings to switch on and off these tests and the ability to modify the buffers involved. The stencil test in particular is highly configurable. The scissor test is the simplest: when activated nothing outside the scissor box (in screen space) will be rendered. The only other configuration is to set that scissor box (setScissorBox). Polygons facing toward or away from the viewer can be dropped (or culled) from rendering with enableCulling.

Coordinate Systems

  • Screen space is simply the 2D coordinate system of your window. The viewport transformation (see setViewport) determines where in the window the mapping of the NDS cube (see below) will appear.
  • NDS, normalized device coordinates, or sometimes viewport space is a cube 2x2x2 centered at the origin the inside of which is your final scene, before it is mapped to the screen via the viewport setting (see setViewport). If an orthographic projection was used to put the scene in clip space then clip space and NDS are the same.
  • Clip space is the destination of vertices transformed by the vertex program. Objects here are mapped to NDS using the perspective division technique to account for the case that the vertex shader used a perspective matrix.
  • Model space is the name for positions of raw vertices as present in the VBOs. The vertex program will want to somehow move these vertexes into clip space, representing generally the position and direction the user is viewing the scene from.

Rendering Points, Lines, and Triangles

The draw family (ex. drawTriangles) of commands commissions the rendering of a certain number of vertices worth of primitives. The current program will get input from the current VAO, the current texture units, and execute on all the potentially affected pixels in the current framebuffer. Vertexes are consumed in the order they appear in their respective source VBOs. If the VAO is missing, the program is missing, or the current framebuffer has no color attachment, then rendering will not work.

The drawIndexed family (ex. drawIndexedTriangles) of commands carries out the same effects as the non-indexed rendering commands but traverses vertices in an order determined by the sequence of indexes packed in the ElementArray currently bound to the element array binding target. This mainly allows a huge reuse of vertex data in the case that the object being rendered forms a closed mesh.

VAO

data VAO Source

A VAO stores vertex attribute layouts and the VBO source of vertices for those attributes. It also stores the state of the element array binding target. The vertex array binding target admits one VAO at a time.

Instances

newVAO :: IO VAO Source

Create a new VAO. The only thing you can do with a VAO is bind it to the vertex array binding target.

bindVAO :: VAO -> IO () Source

Assign the VAO to the vertex array binding target. The VAO already bound will be replaced, if any.

deleteVAO :: VAO -> IO () Source

Delete a VAO.

Buffer Objects

VBO

data VBO Source

A VBO is a buffer object which has vertex data. Shader programs use VBOs as input to their vertex attributes according to the configuration of the bound VAO.

Instances

data UsageHint Source

Usage hint for allocation of buffer object storage.

Constructors

StaticDraw

Data will seldomly change.

DynamicDraw

Data will change.

StreamDraw

Data will change very often.

Instances

newVBO :: Vector Word8 -> UsageHint -> IO VBO Source

Create a buffer object from a blob of bytes. The usage argument hints at how often you will modify the data.

bindVBO :: VBO -> IO () Source

Bind a VBO to the array buffer binding target. The buffer object bound there will be replaced, if any.

updateVBO :: Vector Word8 -> Int -> IO () Source

Modify the data in the currently bound VBO starting from the specified index in bytes.

deleteVBO :: VBO -> IO () Source

Delete a VBO.

Element Array

data ElementArray Source

A buffer object which has a packed sequence of vertex indices. Indexed rendering uses the ElementArray bound to the element array binding target.

Instances

data IndexFormat Source

How indices are packed in an ElementArray buffer object.

Constructors

UByteIndices

Each index is one unsigned byte.

UShortIndices

Each index is a two byte unsigned int.

UIntIndices

Each index is a four byte unsigned int.

Instances

newElementArray :: Vector Word8 -> UsageHint -> IO ElementArray Source

Create a new ElementArray buffer object from the blob of packed indices. The usage argument hints at how often you plan to modify the data.

bindElementArray :: ElementArray -> IO () Source

Assign an ElementArray to the element array binding target. It will replace the ElementArray already bound there, if any. Note that the state of the element array binding target is a function of the current VAO.

updateElementArray :: Vector Word8 -> Int -> IO () Source

Modify contents in the currently bound ElementArray starting at the specified index in bytes.

deleteElementArray :: ElementArray -> IO () Source

Delete an ElementArray

Shader Program

data Program Source

A Program object is the combination of a compiled vertex shader and fragment shader. Programs have three kinds of inputs: vertex attributes, uniforms, and samplers. Programs have two outputs: fragment color and fragment depth. At most one program can be "in use" at a time. Same idea as binding targets it's just not called that.

Instances

data ProgramError Source

The error message emitted by the driver when shader compilation or linkage fails.

newProgram Source

Arguments

:: String

vertex shader source code

-> String

fragment shader source code

-> IO Program 

Compile the code for a vertex shader and a fragment shader, then link them into a new program. If the compiler or linker fails it will throw a ProgramError.

newProgramSafe :: String -> String -> IO (Either ProgramError Program) Source

Same as newProgram but does not throw exceptions.

useProgram :: Program -> IO () Source

Install a program into the rendering pipeline. Replaces the program already in use, if any.

deleteProgram :: Program -> IO () Source

Delete a program.

Vertex Attributes

type VertexAttributeLayout = [LayoutElement] Source

The layout of interleaved vertex attribute data.

data LayoutElement Source

The name of a vertex input to a program combined with the component format and number of components for that attribute in the vertex data. Alternatively the size of an unused section of the data in bytes.

Constructors

Attrib String Int ComponentFormat

Name, component count and component format of a vertex attribute.

Unused Int

Size in bytes of an unused section of the vertex data.

Instances

data ComponentFormat Source

The size and interpretation of a vertex attribute component. Normalized components will be mapped to floats in the range [0, 1].

Constructors

VFloat

4-byte float

VByte 
VUByte 
VByteNormalized 
VUByteNormalized 
VShort

2-byte signed integer

VUShort

2-byte unsigned integer

VShortNormalized 
VUShortNormalized 
VInt

4-byte signed integer

VUInt

4-byte unsigned integer

VIntNormalized 
VUIntNormalized 

setVertexAttributeLayout :: Program -> VertexAttributeLayout -> IO () Source

This configures the currently bound VAO. It calls glVertexAttribPointer and glEnableVertexAttribArray.

Uniform Variables

Set uniform variables for the current program. To set an array of uniforms pass a list of more than one value.

Float Uniforms

These call glUniformNfv.

Int Uniforms

These call glUniformNiv.

Matrix Uniforms

These call glUniformMatrixNfv.

Textures

data Tex2D a Source

A 2D texture. A program can sample a texture if it has been bound to the appropriate texture unit.

Instances

Show (Tex2D a) 
Texture (Tex2D a) 

data CubeMap a Source

A cubemap texture is just six 2D textures. A program can sample a cubemap texture if it has been bound to the appropriate texture unit.

Instances

data Dimensions Source

The size of an image in pixels, parameterized by an image format type.

Constructors

Dimensions 

Fields

imageWidth :: Int
 
imageHeight :: Int
 

Instances

data Cube a Source

Six values, one on each side.

Constructors

Cube 

Fields

cubeRight :: a
 
cubeLeft :: a
 
cubeTop :: a
 
cubeBottom :: a
 
cubeFront :: a
 
cubeBack :: a
 

type Side = forall a. Cube a -> a Source

A type to pick one of the sides of a cube. See the accessors of the type Cube.

newTexture2D :: InternalFormat a => Vector Word8 -> Dimensions -> IO (Tex2D a) Source

Create a new 2D texture from a blob and its image format. Dimensions should be powers of two.

newCubeMap :: InternalFormat a => Cube (Vector Word8, Dimensions) -> IO (CubeMap a) Source

Create a new cube map texture from six blobs and their respective formats. Dimensions should be powers of two.

newEmptyTexture2D :: InternalFormat a => Int -> Int -> IO (Tex2D a) Source

Create an empty texture with the specified dimensions and format.

newEmptyCubeMap :: InternalFormat a => Int -> Int -> IO (CubeMap a) Source

Create a cubemap texture where each of the six sides has the specified dimensions and format.

deleteTexture :: Texture a => a -> IO () Source

Delete a texture.

setActiveTextureUnit :: Enum a => a -> IO () Source

Set the active texture unit. The default is zero.

bindTexture2D :: Tex2D a -> IO () Source

Bind a 2D texture to the 2D texture binding target and the currently active texture unit.

bindTextureCubeMap :: CubeMap a -> IO () Source

Bind a cubemap texture to the cubemap texture binding target and the currently active texture unit.

data Filtering Source

Texture filtering modes.

Constructors

Nearest

No interpolation.

Linear

Linear interpolation.

Instances

setTex2DFiltering :: Filtering -> IO () Source

Set the filtering for the 2D texture currently bound to the 2D texture binding target.

setCubeMapFiltering :: Filtering -> IO () Source

Set the filtering for the cubemap texture currently bound to the cubemap texture binding target.

data Wrapping Source

Texture wrapping modes.

Constructors

Repeat

Tile the texture past the boundary.

MirroredRepeat

Tile the texture but mirror every other tile.

ClampToEdge

Use the edge color for anything past the boundary.

Instances

setTex2DWrapping :: Wrapping -> IO () Source

Set the wrapping mode for the 2D texture currently bound to the 2D texture binding target.

setCubeMapWrapping :: Wrapping -> IO () Source

Set the wrapping mode for the cubemap texture currently bound to the cubemap texture binding target. Because no blending occurs between cube faces you probably want ClampToEdge.

Rendering

Primitives

Draw primitives to the framebuffer currently bound to the framebuffer binding target. Each primitive drawing command takes the number of vertices in the VBOs to render. The vertices are traversed in order.

Primitives by Index

Draw primitives as above, but use the order of vertices defined in the ElementArray currently bound to the element array buffer binding target.

Color Buffer

enableColorWriting :: IO () Source

Allow rendering commands to modify the color buffer of the current framebuffer.

disableColorWriting :: IO () Source

Disable rendering to color buffer.

clearColorBuffer :: (Float, Float, Float) -> IO () Source

Clear the color buffer of the current framebuffer with the specified color. Has no effect if writing to the color buffer is disabled.

Depth Test

enableDepthTest :: IO () Source

Enable the depth test. Attempting to render pixels with a depth value greater than the depth buffer at those pixels will have no effect.

disableDepthTest :: IO () Source

Disable the depth test. Rendering will not be affected by the depth. Use this to render graphics even if they are behind something.

clearDepthBuffer :: IO () Source

Clear the depth buffer with the maximum depth value.

enableDepthWriting :: IO () Source

Enable writing depth values to the depth buffer of the current framebuffer. It is enabled by default.

disableDepthWriting :: IO () Source

Disable writing to the depth buffer.

Stencil Test

enableStencilTest :: IO () Source

Enable the stencil test. Any pixels rendered to the screen where the stencil buffer is 1 will not be rendered. This disables writing to the stencil buffer.

disableStencilTest :: IO () Source

Disable the stencil test.

clearStencilBuffer :: IO () Source

Clear the stencil buffer with all zeros.

enableStencilWriting :: IO () Source

Allow rendering to modify the stencil buffer. Any pixels rendered to the screen will set the stencil buffer to 1 at that location.

disableStencilWriting :: IO () Source

Disable rendering to the stencil buffer.

Scissor Test

setScissorBox :: Viewport -> IO () Source

Set the scissor box. Graphics outside this box will not be rendered as long as the scissor test is enabled.

enableScissorTest :: IO () Source

Enable the scissor test. Graphics outside the scissor box will not be rendered.

disableScissorTest :: IO () Source

Disable the scissor test.

Facet Culling

data Culling Source

Facet culling modes.

Instances

enableCulling :: Culling -> IO () Source

Enable facet culling. The argument specifies whether front faces, back faces, or both will be omitted from rendering. If both front and back faces are culled you can still render points and lines.

disableCulling :: IO () Source

Disable facet culling. Front and back faces will now be rendered.

Blending

When blending is enabled, colors written to the color buffer will be blended with the color already there using a formula. The three options for the formula are (setBlendEquation):

  • Xs + Yd (FuncAdd, the default)
  • Xs - Yd (FuncSub)
  • Yd - Xs (FuncReverseSubtract)

where X and Y are source and destination color components respetively. The factors s and d are blending factors which can be configured (setBlendFactors) and should depend on the alpha channel to get a correct transparency effect. The typical choice is

setBlendFactors BlendSourceAlpha BlendOneMinusSourceAlpha

When using blending the order of rendering matters. The farther away primitives should be rendered first to get transparent materials to look right. This means a depth test is unhelpful when using this technique. Also blending many layers of transparent primitives can significantly degrade performance. For these reasons transparency effects may be better accomplished with an off-screen rendering pass followed by a suitable shader.

data BlendEquation Source

Blending functions for alpha blending.

Constructors

FuncAdd

the default

FuncSubtract 
FuncReverseSubtract 

enableBlending :: IO () Source

Enable alpha blending.

disableBlending :: IO () Source

Disable alpha blending.

setBlendFactors :: BlendFactor -> BlendFactor -> IO () Source

Set the computation for source and destination blending factors.

setBlendEquation :: BlendEquation -> IO () Source

Set the overall blending function.

Viewport

data Viewport Source

A rectangular section of the window.

Constructors

Viewport 

Instances

setViewport :: Viewport -> IO () Source

Set the viewport. The default viewport simply covers the entire window.

Framebuffers

data DefaultFramebuffer Source

The default framebuffer. Bind this to render to the screen as usual. Use the Default instance method def to construct it.

data FBO Source

A framebuffer object is an alternative rendering destination. Once an FBO is bound to framebuffer binding target, it is possible to attach images (textures or RBOs) for color, depth, or stencil rendering.

Instances

bindFramebuffer :: Framebuffer a => a -> IO () Source

Binds an FBO or the default framebuffer to the framebuffer binding target. Replaces the framebuffer already bound there.

newFBO :: IO FBO Source

Create a new framebuffer object. Before the framebuffer can be used for rendering it must have a color image attachment.

attachTex2D :: Attachable a => Tex2D a -> IO () Source

Attach a 2D texture to the FBO currently bound to the framebuffer binding target.

attachCubeMap :: Attachable a => CubeMap a -> Side -> IO () Source

Attach one of the sides of a cubemap texture to the FBO currently bound to the framebuffer binding target.

attachRBO :: Attachable a => RBO a -> IO () Source

Attach an RBO to the FBO currently bound to the framebuffer binding target.

deleteFBO :: FBO -> IO () Source

Delete an FBO.

Renderbuffers

data RBO a Source

An RBO is a kind of image object used for rendering. The only thing you can do with an RBO is attach it to an FBO.

Instances

Show (RBO a) 

newRBO :: InternalFormat a => Int -> Int -> IO (RBO a) Source

Create a new renderbuffer with the specified dimensions.

deleteRBO :: RBO a -> IO () Source

Delete an RBO.

Errors

data GLError Source

Detectable errors.

Constructors

InvalidEnum

Enum argument out of range.

InvalidValue

Integer argument out of range.

InvalidOperation

Operation illegal in current state.

InvalidFramebufferOperation

Framebuffer is not complete.

OutOfMemory 

getGLError :: IO (Maybe GLError) Source

Check for a GL Error.

Image Formats

data Alpha Source

1-byte alpha channel only.

data Luminance Source

1-byte grayscale pixel format.

data LuminanceAlpha Source

2-byte luminance and alpha channel format.

data RGB Source

3-byte true color pixel format.

data RGBA Source

4-byte true color plus alpha channel format.

data Depth24 Source

24-bit depth format.

Classes

class Framebuffer a where Source

Framebuffers can be bound to the framebuffer binding target. There is a default framebuffer and the client may create an arbitrary number of new framebuffer objects.

Methods

framebufferName :: Num b => a -> b Source

class Texture a where Source

Textures have an internal numeric name.

Methods

textureName :: Num b => a -> b Source

Instances

class InternalFormat a => Attachable a where Source

The allowed attachment point for images with an internal format.

Methods

attachPoint :: (Eq b, Num b) => proxy a -> b Source