caramia-0.7.2.2: High-level OpenGL bindings

Safe HaskellNone
LanguageHaskell2010

Graphics.Caramia.Render

Contents

Description

Rendering things.

Synopsis

The drawing functions

draw :: (MonadIO m, MonadMask m) => DrawCommand -> DrawParams -> m () Source

Draws according to a DrawCommand.

There is a very large overhead in doing a single draw call. You probably want to use runDraws and drawR instead.

runDraws Source

Arguments

:: (MonadIO m, MonadMask m) 
=> DrawParams

Initial drawing parameters. These can be changed in the Draw command stream.

-> DrawT m a

Draw command stream.

-> m a 

Runs a drawing specification.

You can think of this as running many draw commands with similar draw command specifications. This call is an optimization to draw which has a high overhead by itself.

Another way to think of this is a place where the functional, "no hidden state" design of the Caramia API is relaxed inside the Draw stream.

Draw command stream

data DrawT m a Source

Instances

MonadTrans DrawT Source 
MonadRWS r w s m => MonadRWS r w s (DrawT m) Source 
MonadState s m => MonadState s (DrawT m) Source 
MonadReader r m => MonadReader r (DrawT m) Source 
MonadError e m => MonadError e (DrawT m) Source 
MonadWriter w m => MonadWriter w (DrawT m) Source 
Monad m => Monad (DrawT m) Source 
Functor m => Functor (DrawT m) Source 
Monad m => Applicative (DrawT m) Source 
MonadIO m => MonadIO (DrawT m) Source

Using liftIO is safe inside a DrawT stream. It is possible to run nested DrawT streams this way as well.

MonadCont m => MonadCont (DrawT m) Source 

drawR :: (MonadIO m, MonadMask m) => DrawCommand -> DrawT m () Source

Same as draw but in a Draw command stream.

setBlending :: MonadIO m => BlendSpec -> DrawT m () Source

Changes the current blending mode.

setFragmentPassTests :: MonadIO m => FragmentPassTests -> DrawT m () Source

Sets the new fragment pass tests.

setPipeline :: MonadIO m => Pipeline -> DrawT m () Source

Changes the pipeline in a Draw command stream.

setPolygonOffset :: MonadIO m => Float -> Float -> DrawT m () Source

Sets polygon offset.

setPrimitiveRestart :: MonadIO m => Maybe Word32 -> DrawT m () Source

Sets new primitive restart mode.

setTargetFramebuffer :: MonadIO m => Framebuffer -> DrawT m () Source

Sets the current framebuffer.

setTextureBindings :: MonadIO m => IntMap Texture -> DrawT m () Source

Sets new texture bindings.

Hoisting

hoistDrawT :: Monad n => (forall a. m a -> n a) -> DrawT m a -> DrawT n a Source

Use to hoist the base monad in a DrawT.

Specifying what to draw

data DrawCommand Source

Contains a specification of what to draw.

It is recommended to use drawCommand instead of this constructor.

Constructors

DrawCommand 

Fields

primitiveType :: Primitive
 
primitivesVAO :: VAO

This is the VAO from which attributes are retrieved in the shader pipeline.

numIndices :: Int

How many indices to render?

numInstances :: Int

How many instances to render.

sourceData :: SourceData

How to select the attribute data from primitivesVAO.

drawCommand :: DrawCommand Source

Returns a default draw command.

Several fields are undefined so you must set them. These are

numInstances is set to 1. In future (minor) versions if we add any new fields those fields will have a sane default value.

data DrawParams Source

Contains drawing parameters.

You can use defaultDrawParams to obtain default draw parameters.

Constructors

DrawParams 

Fields

pipeline :: Pipeline

Which shader pipeline to use.

fragmentPassTests :: !FragmentPassTests

What kind of fragment pass tests to use.

blending :: BlendSpec

Which blending to use.

targetFramebuffer :: Framebuffer

Where do you want to render?

bindTextures :: IntMap Texture

Which textures do you want to bind? The keys in this integer map are TextureUnits and tell which texture units you want to bind given textures.

polygonOffset :: !(Float, Float)

Modify the depth values that are being written.

(factor, units) .

By default this is (0, 0) (that is, do nothing). See glPolygonOffset for the meaning of these values.

primitiveRestart :: !(Maybe Word32)

Use primitive restart?

https://www.opengl.org/wiki/Vertex_Rendering#Primitive_Restart

Is this is Nothing (the default) then primitive restart will not be used.

defaultDrawParams :: DrawParams Source

Default drawing parameters.

pipeline is not set (that is, it's undefined). You must set it.

No textures are bound.

Blending mode is premultiplied alpha.

No primitive restart is used.

targetFramebuffer is the screen framebuffer.

data SourceData Source

Values of this type tell how to select attribute data from primitivesVAO.

Future minor versions will not add any new fields or remove any fields from these values. Instead, new constructors are introduced.

Constructors

Primitives

Simply start from some index and continue from there, 0, 1, 2, etc.

OpenGL equivalent is glDrawArrays() or glDrawArraysInstanced() .

Fields

firstIndex :: Int
 
PrimitivesWithIndices

Use an index buffer.

OpenGL equivalent is glDrawElements() or glDrawElementsInstanced() . Index buffer contains indices that point to offsets in the vertex arrays.

class IndexTypeable a where Source

Methods

toIndexType Source

Arguments

:: a

Used to pass the type, not evaluated.

-> IndexType 

Turns a Haskell type to IndexType.

Fragment pass tests

data FragmentPassTests Source

Specifies the tests that are run on a fragment to decide if it should be seen.

Constructors

FragmentPassTests 

Fields

depthTest :: !(Maybe ComparisonFunc)

Which depth test to use, if any?

writeDepth :: Bool

If depth test is specified, should we also update the depth buffer with new depth values? The depth buffer will not be written if depthTest is not specified regardless of the value in this field.

stencilTest :: !(Maybe ComparisonFunc)

Which stencil test to use, if any?

stencilReference :: !Word32
 
stencilMask :: !Word32
 
failStencilOp :: !StencilOp

What to do with the stencil buffer if stencil test fails.

depthFailStencilOp :: !StencilOp

What to do with the stencil buffer if stencil test passes but depth testing fails).

depthPassStencilOp :: !StencilOp

What to do with the stencil buffer if stencil and depth test passes, or if depth buffer is not present or depth test is disabled.

cullFace :: !Culling

What kind of face culling should we do.

defaultFragmentPassTests :: FragmentPassTests Source

Returns the default fragment pass tests.

Neither depth or stencil test is enabled. writeDepth is set to true but that value is only used if you specify with depth test to use.

All stencil operations are set to Keep.

Culling is set to Back.

data ComparisonFunc Source

A comparison function. Incoming value is compared with this function to the existing value.

This can be used with depth and stencil tests.

See glDepthFunc from OpenGL specification or man pages for more detailed explanation.

data StencilOp Source

Stencil buffer operations.

See glStencilOp for explanations of each constructor.

Constructors

Keep 
Zero 
Replace

This one replaces the old value in the stencil buffer with the given reference value and ANDs the result with mask.

Increment 
IncrementAndWrap 
Decrease 
DecreaseAndWrap 
Invert 

data Culling Source

Constructors

Back 
Front 
FrontAndBack

This stops the drawing of any faces but points and lines (or other non-facey like primitives) are drawn.

NoCulling