typograffiti-0.2.0.1: Just let me draw nice text already
Safe HaskellSafe-Inferred
LanguageHaskell2010

Typograffiti.GL

Synopsis

Documentation

allocAndActivateTex :: (MonadIO m, MonadFail m) => GLenum -> m GLuint Source #

Allocates a new active texture (image data) in the GPU.

clearErrors :: MonadIO m => String -> m () Source #

Report any exceptions encounted by OpenGL.

newBoundVAO :: (MonadIO m, MonadFail m) => m GLuint Source #

Allocates a new, bound Vertex Array Object.

withVAO :: MonadIO m => (GLuint -> IO b) -> m b Source #

Runs the given callback giving a new temporarily-bound Vertex Array Object, catching any errors.

newBuffer :: MonadIO m => m GLuint Source #

Allocates a new buffer on the GPU.

withBuffers :: MonadIO m => Int -> ([GLuint] -> m b) -> m b Source #

bufferGeometry Source #

Arguments

:: (Foldable f, Unbox (f Float), Storable (f Float), Finite f, KnownNat (Size f), MonadIO m) 
=> GLuint

The attribute location.

-> GLuint

The buffer identifier.

-> Vector (f Float)

The geometry to buffer.

-> m () 

Buffer some geometry into an attribute. The type variable f should be V0, V1, V2, V3 or V4.

convertVec :: (Unbox (f Float), Foldable f) => Vector (f Float) -> Vector GLfloat Source #

Converts an unboxed vector to a storable vector suitable for storing in a GPU buffer.

withBoundTextures :: MonadIO m => [GLuint] -> m a -> m a Source #

Binds the given textures to GL_TEXTURE0, GL_TEXTURE1, ... in ascending order of the texture unit, runs the IO action and then unbinds the textures.

drawVAO Source #

Arguments

:: MonadIO m 
=> GLuint

The program

-> GLuint

The vao

-> GLenum

The draw mode

-> GLsizei

The number of vertices to draw

-> m () 

Render the given slice of the given Vertex-Array Object with the given program in the given mode, with exception handling.

compileOGLShader Source #

Arguments

:: MonadIO m 
=> ByteString

The shader source

-> GLenum

The shader type (vertex, frag, etc)

-> m (Either String GLuint)

Either an error message or the generated shader handle.

Compiles GLSL code to GPU opcodes, or returns an error message.

compileOGLProgram :: MonadIO m => [(String, Integer)] -> [GLuint] -> m (Either String GLuint) Source #

getUniformLocation :: MonadIO m => GLuint -> String -> m GLint Source #

Lookup ID for a named uniform GLSL variable.

class UniformValue a where Source #

Data that can be uploaded to GLSL uniform variables.

Methods

updateUniform Source #

Arguments

:: MonadIO m 
=> GLuint

The program

-> GLint

The uniform location

-> a

The value.

-> m () 

Upload a value to a GLSL uniform variable.

Instances

Instances details
UniformValue Bool Source # 
Instance details

Defined in Typograffiti.GL

Methods

updateUniform :: MonadIO m => GLuint -> GLint -> Bool -> m () Source #

UniformValue Double Source # 
Instance details

Defined in Typograffiti.GL

Methods

updateUniform :: MonadIO m => GLuint -> GLint -> Double -> m () Source #

UniformValue Float Source # 
Instance details

Defined in Typograffiti.GL

Methods

updateUniform :: MonadIO m => GLuint -> GLint -> Float -> m () Source #

UniformValue Int Source # 
Instance details

Defined in Typograffiti.GL

Methods

updateUniform :: MonadIO m => GLuint -> GLint -> Int -> m () Source #

UniformValue (M44 Float) Source # 
Instance details

Defined in Typograffiti.GL

Methods

updateUniform :: MonadIO m => GLuint -> GLint -> M44 Float -> m () Source #

UniformValue (V2 Float) Source # 
Instance details

Defined in Typograffiti.GL

Methods

updateUniform :: MonadIO m => GLuint -> GLint -> V2 Float -> m () Source #

UniformValue (V2 Int) Source # 
Instance details

Defined in Typograffiti.GL

Methods

updateUniform :: MonadIO m => GLuint -> GLint -> V2 Int -> m () Source #

UniformValue (V3 Float) Source # 
Instance details

Defined in Typograffiti.GL

Methods

updateUniform :: MonadIO m => GLuint -> GLint -> V3 Float -> m () Source #

UniformValue (V4 Float) Source # 
Instance details

Defined in Typograffiti.GL

Methods

updateUniform :: MonadIO m => GLuint -> GLint -> V4 Float -> m () Source #

UniformValue (Int, Int) Source # 
Instance details

Defined in Typograffiti.GL

Methods

updateUniform :: MonadIO m => GLuint -> GLint -> (Int, Int) -> m () Source #

clearUniformUpdateError :: (MonadIO m, Show a) => GLuint -> GLint -> a -> m () Source #

Report exceptions setting GLSL uniform variables.

mat4Translate :: Num a => V3 a -> M44 a Source #

Constructs a matrix that shifts a vector horizontally or vertically.

mat4Rotate :: (Num a, Epsilon a, Floating a) => a -> V3 a -> M44 a Source #

Constructs a matrix that rotates a vector.

mat4Scale :: Num a => V3 a -> M44 a Source #

Constructs a matrix that resizes a vector.

mat4SkewXbyY :: Num a => a -> M44 a Source #

orthoProjection Source #

Arguments

:: Integral a 
=> V2 a

The window width and height

-> M44 Float 

Constructs a matrix that converts screen coordinates to range 1,-1; with perspective.

boundingBox :: (Unbox a, Real a, Fractional a) => Vector (V2 a) -> (V2 a, V2 a) Source #

Computes the boundingbox for an array of points.