module Graphics.LambdaCube.Pass where

import Graphics.LambdaCube.BlendMode
import Graphics.LambdaCube.Common
import Graphics.LambdaCube.GpuProgram
import Graphics.LambdaCube.GpuProgramUsage
import Graphics.LambdaCube.Light
import Graphics.LambdaCube.Texture
import Graphics.LambdaCube.TextureUnitState
import Graphics.LambdaCube.Types

-- | Categorisation of passes for the purpose of additive lighting
data IlluminationStage
    = IS_AMBIENT    -- ^ Part of the rendering which occurs without any kind of direct lighting
    | IS_PER_LIGHT  -- ^ Part of the rendering which occurs per light
    | IS_DECAL      -- ^ Post-lighting rendering
    | IS_UNKNOWN    -- ^ Not determined
    deriving (Eq,Ord)

data (Texture t, LinkedGpuProgram lp) => Pass t lp
    = Pass
    { psName                     :: String                      -- ^ optional name for the pass

    -- Colour properties, only applicable in fixed-function passes
    , psAmbient                  :: ColourValue
    , psDiffuse                  :: ColourValue
    , psSpecular                 :: ColourValue
    , psEmissive                 :: ColourValue
    , psShininess                :: FloatType
    , psTracking                 :: TrackVertexColourType

    -- Blending factors
    , psSourceBlendFactor        :: SceneBlendFactor
    , psDestBlendFactor          :: SceneBlendFactor
    , psSourceBlendFactorAlpha   :: SceneBlendFactor
    , psDestBlendFactorAlpha     :: SceneBlendFactor

    , psSeparateBlend            :: Bool                        -- ^ Used to determine if separate alpha blending should be used for color and alpha channels

    -- Blending operations
    , psBlendOperation           :: SceneBlendOperation
    , psAlphaBlendOperation      :: SceneBlendOperation
    , psSeparateBlendOperation   :: Bool                        -- ^ Determines if we should use separate blending operations for color and alpha channels

    -- Depth buffer settings
    , psDepthCheck               :: Bool
    , psDepthWrite               :: Bool
    , psDepthFunc                :: CompareFunction
    , psDepthBiasConstant        :: FloatType
    , psDepthBiasSlopeScale      :: FloatType
    , psDepthBiasPerIteration    :: FloatType

    -- Colour buffer settings
    , psColourWrite              :: Bool

    -- Alpha reject settings
    , psAlphaRejectFunc          :: CompareFunction
    , psAlphaRejectVal           :: Int
    , psAlphaToCoverageEnabled   :: Bool

    , psTransparentSorting       :: Bool                        -- ^ Transparent depth sorting
    , psTransparentSortingForced :: Bool                        -- ^ Transparent depth sorting forced

    -- Culling mode
    , psCullMode                 :: CullingMode
    , psManualCullMode           :: ManualCullingMode

    , psLightingEnabled          :: Bool                        -- ^ Lighting enabled?
    , psMaxSimultaneousLights    :: Int                         -- ^ Max simultaneous lights
    , psStartLight               :: Int                         -- ^ Starting light index
    , psLightsPerIteration       :: Maybe Int                   -- ^ Run this pass once per light? Iterate per how many lights?
    , psOnlyLightType            :: Maybe LightTypes            -- ^ Should it only be run for a certain light type?

    , psShadeOptions             :: ShadeOptions                -- ^ Shading options
    , psPolygonMode	             :: PolygonMode                 -- ^ Polygon mode

    -- Normalisation
    , psNormaliseNormals         :: Bool
    , psPolygonModeOverrideable  :: Bool

    -- Fog
    , psFogOverride              :: Bool
    , psFogMode                  :: FogMode
    , psFogColour                :: ColourValue
    , psFogStart                 :: FloatType
    , psFogEnd                   :: FloatType
    , psFogDensity               :: FloatType

    , psTextureUnitStates        :: [TextureUnitState t]

    , psVertexProgramUsage       :: Maybe GpuProgramUsage   -- ^ Vertex program details
    , psFragmentProgramUsage     :: Maybe GpuProgramUsage   -- ^ Fragment program details
    , psGeometryProgramUsage     :: Maybe GpuProgramUsage   -- ^ Geometry program details
    , psLinkedGpuProgram         :: Maybe lp

    , psPassIterationCount       :: Int                         -- ^ number of pass iterations to perform

    , psPointSize                :: FloatType                   -- ^ point size, applies when not using per-vertex point size
    , psPointMinSize             :: FloatType
    , psPointMaxSize             :: FloatType
    , psPointSpritesEnabled      :: Bool
    , psPointAttenuationEnabled  :: Bool
    , psPointAttenuationCoeffs   :: FloatType3                  -- ^ constant, linear, quadratic coeffs

    , psLightScissoring          :: Bool                        -- ^ Scissoring for the light?
    , psLightClipPlanes          :: Bool                        -- ^ User clip planes for light?
    , psIlluminationStage        :: IlluminationStage           -- ^ Illumination stage?
    }
    deriving (Eq,Ord)