lowgl-0.3.1.1: Basic gl wrapper and reference

Safe HaskellNone
LanguageHaskell2010

Graphics.GL.Low

Contents

Description

Basic low-level GL wrapper and reference.

Synopsis

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. Graphics.GL.Low.EntirePictureUpFront

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

See specific modules for topic-specific docs and example code:

Graphics.GL.Low.VAO
Graphics.GL.Low.BufferObject
Graphics.GL.Low.Shader
Graphics.GL.Low.VertexAttrib
Graphics.GL.Low.Texture
Graphics.GL.Low.Render
Graphics.GL.Low.Color
Graphics.GL.Low.Depth
Graphics.GL.Low.Stencil
Graphics.GL.Low.Blending
Graphics.GL.Low.Framebuffer

VAO

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.

data VAO Source

Handle to a VAO.

Instances

Buffer Objects

newVBO :: Storable a => Vector a -> 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.

newElementArray :: Storable a => Vector a -> 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.

bindVBO :: VBO -> IO () Source

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

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.

updateVBO :: Storable a => Vector a -> Int -> IO () Source

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

updateElementArray :: Storable a => Vector a -> Int -> IO () Source

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

deleteBufferObject :: BufferObject a => a -> IO () Source

Delete a VBO or ElementArray.

data VBO Source

Handle to a VBO.

data ElementArray Source

Handle to an element array buffer object.

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.

Shader Program

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.

data Program Source

Handle to a shader program.

Instances

data ProgramError Source

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

Vertex Attributes

setVertexLayout :: [VertexLayout] -> IO () Source

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

data VertexLayout 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 DataType

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 DataType Source

The size and interpretation of a vertex attribute component.

Constructors

GLFloat

4-byte float

GLByte

signed byte

GLUnsignedByte

unsigned byte

GLShort

2-byte signed integer

GLUnsignedShort

2-byte unsigned integer

GLInt

4-byte signed integer

GLUnsignedInt

4-byte unsigned integer

Textures

newTexture2D :: (Storable a, InternalFormat b) => Vector a -> Dimensions -> IO (Tex2D b) Source

Create a new 2D texture from a blob and its dimensions. Dimensions should be powers of two. The internal format type determines how the data is interpreted.

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

Create a new cube map texture from six blobs and their respective dimensions. 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.

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.

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.

data Tex2D a Source

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

Instances

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.

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.

data Filtering Source

Texture filtering modes.

Constructors

Nearest

No interpolation.

Linear

Linear interpolation.

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.

Rendering

Primitives

setViewport :: Viewport -> IO () Source

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

enableScissorTest :: Viewport -> IO () Source

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

disableScissorTest :: IO () Source

Disable the scissor test.

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.

data Viewport Source

A rectangular section of the window.

Constructors

Viewport 

Instances

data Culling Source

Facet culling modes.

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.

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. Otherwise the depth in the buffer will get updated to the new pixel's depth.

disableDepthTest :: IO () Source

Disable the depth test and depth buffer updates.

clearDepthBuffer :: IO () Source

Clear the depth buffer with the maximum depth value.

Stencil Test

enableStencil :: Stencil -> IO () Source

Enable the stencil test with a set of operating parameters.

disableStencil :: IO () Source

Disable the stencil test and updates to the stencil buffer, if one exists.

clearStencilBuffer :: IO () Source

Clear the stencil buffer with all zeros.

basicStencil :: Stencil Source

In this basic configuration of the stencil, anything rendered will create a silhouette of 1s in the stencil buffer. Attempting to render a second time into the silhouette will have no effect because the stencil test will fail (ref=1 isn't greater than buffer=1).

def { func = Greater
    , ref = 1
    , onBothPass = Replace }

data Stencil Source

Configuration of the stencil test and associated stencil buffer updating.

Instances

Default Stencil

The default state of the stencil, if it were simply enabled, would be to always pass and update nothing in the buffer. It would have no effect on rendering.

data StencilFunc Source

The stencil test passes under what condition.

data StencilOp Source

Modification action for the stencil buffer.

Constructors

Keep

Do nothing.

Zero

Set to zero.

Replace

Write the ref value passed to enableStencil.

Increment 
Decrement 
Invert

Bitwise complement.

IncrementWrap 
DecrementWrap 

Blending

enableBlending :: Blending -> IO () Source

Enable blending with the specified blending parameters.

disableBlending :: IO () Source

Disable alpha blending.

basicBlending :: Blending Source

This blending configuration is suitable for ordinary alpha blending transparency effects.

Blending
  { sFactor   = BlendSourceAlpha
  , dFactor   = BlendOneMinusSourceAlpha
  , blendFunc = FuncAdd }

data Blending Source

Blending parameters.

Instances

Default Blending

The default blending parameters have no effect if enabled. The result will be no blending effect.

Framebuffers

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.

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) 
GLObject (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. This call has the semantics of a dequeue. If an error is returned, then calling getGLError again may return more errors that have "stacked up." When it returns Nothing then there are no more errors to report. An error indicates that a bug in your code caused incorrect ussage of the API or that the implementation has run out of memory.

It has been suggested that using this after every single GL command may adversely affect performance (not to mention be very tedious). Since there is no reasonable way to recover from a GL error, a good idea might be to check this once per frame or even less often, and respond with a core dump.

assertNoGLError :: IO () Source

Throws an exception if getGLError returns non-Nothing.

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 GLObject a => Texture a Source

Textures are GL objects.

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