lambdacube-engine-0.2.4: 3D rendering engine written entirely in Haskell

Safe HaskellSafe-Infered

Graphics.LambdaCube.RenderSystem

Documentation

data TexCoordCalcMethod Source

Constructors

TEXCALC_NONE

No calculated texture coordinates

TEXCALC_ENVIRONMENT_MAP

Environment map based on vertex normals

TEXCALC_ENVIRONMENT_MAP_PLANAR

Environment map based on vertex positions

TEXCALC_ENVIRONMENT_MAP_REFLECTION

Environment map based on vertex positions

TEXCALC_ENVIRONMENT_MAP_NORMAL

Environment map based on vertex positions

TEXCALC_PROJECTIVE_TEXTURE

Projective texture

data StencilOperation Source

Constructors

SOP_KEEP

Leave the stencil buffer unchanged

SOP_ZERO

Set the stencil value to zero

SOP_REPLACE

Set the stencil value to the reference value

SOP_INCREMENT

Increase the stencil value by 1, clamping at the maximum value

SOP_DECREMENT

Decrease the stencil value by 1, clamping at 0

SOP_INCREMENT_WRAP

Increase the stencil value by 1, wrapping back to 0 when incrementing the maximum value

SOP_DECREMENT_WRAP

Decrease the stencil value by 1, wrapping when decrementing 0

SOP_INVERT

Invert the bits of the stencil buffer

Instances

class (HardwareVertexBuffer vb, HardwareIndexBuffer ib, HardwareOcclusionQuery q, Texture t, GpuProgram p, LinkedGpuProgram lp) => RenderSystem rs vb ib q t p lp | rs -> vb ib q t p lp whereSource

Methods

prepareRender :: rs -> IO ()Source

finishRender :: rs -> IO ()Source

createVertexBuffer :: rs -> Int -> Int -> Usage -> Bool -> IO vbSource

createIndexBuffer :: rs -> IndexType -> Int -> Usage -> Bool -> IO ibSource

createTexture :: rs -> String -> TextureType -> Int -> Int -> Int -> TextureMipmap -> PixelFormat -> TextureUsage -> Bool -> Int -> String -> Maybe [Image] -> IO tSource

withFrameBuffer :: rs -> Int -> Int -> Int -> Int -> (Ptr Word8 -> IO ()) -> IO ()Source

dirtyHackCopyTexImage :: rs -> t -> Int -> Int -> Int -> Int -> IO ()Source

createGpuProgram :: rs -> GpuProgramType -> String -> IO (Either p String)Source

createLinkedGpuProgram :: rs -> [p] -> IO (Either lp String)Source

getNameSource

Arguments

:: rs 
-> String

Returns the name of the rendering system.

createOcclusionQuerySource

Arguments

:: rs 
-> IO q

Create an object for performing hardware occlusion queries.

setAmbientLightSource

Arguments

:: rs 
-> Float 
-> Float 
-> Float 
-> IO ()

Sets the colour & strength of the ambient (global directionless) light in the world.

setShadingTypeSource

Arguments

:: rs 
-> ShadeOptions 
-> IO ()

Sets the type of light shading required (default = Gouraud).

setLightingEnabled :: rs -> Bool -> IO ()Source

setWBufferEnabled :: rs -> Bool -> IO ()Source

setWaitForVerticalBlank :: rs -> Bool -> IO ()Source

useLights :: rs -> [(Proj4, Light)] -> IO ()Source

setWorldMatrixSource

Arguments

:: rs 
-> Proj4 
-> IO ()

Sets the world transform matrix.

setViewMatrixSource

Arguments

:: rs 
-> Proj4 
-> IO ()

Sets the view transform matrix

setProjectionMatrixSource

Arguments

:: rs 
-> Mat4 
-> IO ()

Sets the projection transform matrix

setSurfaceParams :: rs -> ColourValue -> ColourValue -> ColourValue -> ColourValue -> FloatType -> TrackVertexColourType -> IO ()Source

setPointSpritesEnabled :: rs -> Bool -> IO ()Source

setPointParameters :: rs -> FloatType -> Bool -> FloatType -> FloatType -> FloatType -> FloatType -> FloatType -> IO ()Source

setActiveTextureUnit :: rs -> Int -> IO ()Source

setTexture :: rs -> Maybe t -> IO ()Source

setVertexTexture :: rs -> Maybe t -> IO ()Source

setTextureCoordCalculation :: rs -> TexCoordCalcMethod -> IO ()Source

setTextureBlendMode :: rs -> LayerBlendModeEx -> LayerBlendModeEx -> IO ()Source

setTextureUnitFiltering :: rs -> TextureType -> FilterOptions -> FilterOptions -> FilterOptions -> IO ()Source

setTextureLayerAnisotropy :: rs -> TextureType -> Int -> IO ()Source

setTextureAddressingMode :: rs -> TextureType -> UVWAddressingMode -> IO ()Source

setTextureBorderColour :: rs -> TextureType -> ColourValue -> IO ()Source

setTextureMipmapBias :: rs -> FloatType -> IO ()Source

setTextureMatrix :: rs -> Proj4 -> IO ()Source

setSceneBlending :: rs -> SceneBlendFactor -> SceneBlendFactor -> SceneBlendOperation -> IO ()Source

setSeparateSceneBlending :: rs -> SceneBlendFactor -> SceneBlendFactor -> SceneBlendFactor -> SceneBlendFactor -> SceneBlendOperation -> SceneBlendOperation -> IO ()Source

setAlphaRejectSettings :: rs -> CompareFunction -> Int -> Bool -> IO ()Source

setViewport :: rs -> Int -> Int -> Int -> Int -> IO ()Source

setCullingMode :: rs -> CullingMode -> IO ()Source

setDepthBufferParams :: rs -> Bool -> Bool -> CompareFunction -> IO ()Source

setDepthBufferCheckEnabled :: rs -> Bool -> IO ()Source

setDepthBufferWriteEnabled :: rs -> Bool -> IO ()Source

setDepthBufferFunction :: rs -> CompareFunction -> IO ()Source

setColourBufferWriteEnabled :: rs -> Bool -> Bool -> Bool -> Bool -> IO ()Source

setDepthBias :: rs -> FloatType -> FloatType -> IO ()Source

setFog :: rs -> FogMode -> ColourValue -> FloatType -> FloatType -> FloatType -> IO ()Source

setPolygonMode :: rs -> PolygonMode -> IO ()Source

setStencilCheckEnabled :: rs -> Bool -> IO ()Source

setStencilBufferParams :: rs -> CompareFunction -> Word32 -> Word32 -> StencilOperation -> StencilOperation -> StencilOperation -> Bool -> IO ()Source

setNormaliseNormals :: rs -> Bool -> IO ()Source

render :: rs -> RenderOperation vb ib -> IO ()Source

bindGeometry :: rs -> RenderOperation vb ib -> [TextureUnitState t] -> IO ()Source

unbindGeometry :: rs -> RenderOperation vb ib -> IO ()Source

getCapabilities :: rs -> RenderSystemCapabilitiesSource

bindLinkedGpuProgram :: rs -> lp -> IO ()Source

unbindLinkedGpuProgram :: rs -> IO ()Source

setScissorTest :: rs -> Bool -> Int -> Int -> Int -> Int -> IO ()Source

clearFrameBuffer :: rs -> FrameBufferType -> ColourValue -> FloatType -> Word16 -> IO ()Source

getHorizontalTexelOffset :: rs -> IO FloatTypeSource

getVerticalTexelOffset :: rs -> IO FloatTypeSource

getMinimumDepthInputValue :: rs -> FloatTypeSource

getMaximumDepthInputValue :: rs -> FloatTypeSource

class (HardwareVertexBuffer vb, HardwareIndexBuffer ib, Texture t, LinkedGpuProgram lp) => Renderable r vb ib t lp | r -> vb ib t lp whereSource

Methods

prepare :: Proj4 -> r -> [RenderEntity vb ib t lp]Source

Instances

setPass :: RenderSystem rs vb ib q t p lp => FloatType -> rs -> Pass t lp -> IO ()Source