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

Graphics.LambdaCube.Compositor

Synopsis

Documentation

data PassType Source

Constructors

PT_CLEAR

Clear target to one colour

PT_STENCIL

Set stencil operation

PT_RENDERSCENE

Render the scene or part of it

PT_RENDERQUAD

Render a full screen quad

data InputMode Source

Input mode of a TargetPass

Constructors

IM_NONE

No input

IM_PREVIOUS

Output of previous Composition in chain

Instances

data Texture t => TextureDefinition t Source

Constructors

TextureDefinition 

Fields

tdName :: String
 
tdWidth :: Maybe Int

Nothing means adapt to target width

tdHeight :: Maybe Int

Nothing means adapt to target height

tdWidthFactor :: FloatType

multiple of target width to use (if width = Nothing)

tdHeightFactor :: FloatType

multiple of target height to use (if height = Nothing)

tdFormatList :: [PixelFormat]

more than one means MRT

tdFsaa :: Bool

FSAA enabled; true = determine from main target (if render_scene), false = disable

tdHwGammaWrite :: Bool

Do sRGB gamma correction on write (only 8-bit per channel formats)

tdShared :: Bool

whether to use shared textures for this one

tdTexture :: Maybe t
 

data InputTex Source

Constructors

InputTex 

Fields

itName :: String

Name (local) of the input texture

itMrtIndex :: Int

MRT surface index if applicable

data (Texture t, LinkedGpuProgram lp) => CompositionTechnique t lp Source

Constructors

CompositionTechnique 

Fields

ctTextureDefinitions :: [TextureDefinition t]

Local texture definitions

ctTargetPasses :: [CompositionTargetPass t lp]

Intermediate target passes

ctOutputTarget :: CompositionTargetPass t lp

Output target pass (can be only one)

ctSchemeName :: String

Optional scheme name

data (Texture t, LinkedGpuProgram lp) => CompositionTargetPass t lp Source

Constructors

CompositionTargetPass 

Fields

ctpInputMode :: InputMode

Input name

ctpOutputName :: String

(local) output texture

ctpOutput :: Maybe (TextureDefinition t)
 
ctpPasses :: [CompositionPass t lp]

Passes

ctpOnlyInitial :: Bool

This target pass is only executed initially after the effect has been enabled.

ctpVisibilityMask :: Word32

Visibility mask for this render

ctpLodBias :: FloatType

LOD bias of this render

ctpMaterialScheme :: String

Material scheme name

ctpShadowsEnabled :: Bool

Shadows option

data (Texture t, LinkedGpuProgram lp) => CompositionPass t lp Source

Constructors

CompositionPass 

Fields

cpType :: PassType

Type of composition pass

cpIdentifier :: Word32

Identifier for this pass

cpMaterialName :: String

Material used for rendering

cpMaterial :: Maybe (Material t lp)
 
cpFirstRenderQueue :: Int
first,last
render queue to render this pass (in case of PT_RENDERSCENE)
cpLastRenderQueue :: Int
 
cpClearBuffers :: (Bool, Bool, Bool)

Clear buffers (in case of PT_CLEAR), hint: [colour] [depth] [stencil]

cpClearColour :: ColourValue

Clear colour (in case of PT_CLEAR)

cpClearDepth :: FloatType

Clear depth (in case of PT_CLEAR)

cpClearStencil :: Word32

Clear stencil value (in case of PT_CLEAR)

cpInputs :: IntMap InputTex

Inputs (for material used for rendering the quad)

cpStencilCheck :: Bool

Stencil operation parameters

cpStencilFunc :: CompareFunction
 
cpStencilRefValue :: Word32
 
cpStencilMask :: Word32
 
cpStencilFailOp :: StencilOperation
 
cpStencilDepthFailOp :: StencilOperation
 
cpStencilPassOp :: StencilOperation
 
cpStencilTwoSidedOperation :: Bool
 
cpQuadCornerModified :: Bool

true if quad should not cover whole screen

cpQuadLeft :: FloatType

quad positions in normalised coordinates [-1;1]x[-1;1] (in case of PT_RENDERQUAD)

cpQuadTop :: FloatType
 
cpQuadRight :: FloatType
 
cpQuadBottom :: FloatType
 
cpQuadFarCorners :: Bool
 
cpQuadFarCornersViewSpace :: Bool