seperated shaders
- shadowmap now uses own shader - not used only defined - changed a bit in tyes. needs refinement - new indices need to be read out and used. refs #495 @3h
This commit is contained in:
parent
8bd8db922e
commit
dd12f7b136
@ -1,4 +1,3 @@
|
|||||||
{-# LANGUAGE ForeignFunctionInterface #-}
|
|
||||||
module Render.Misc where
|
module Render.Misc where
|
||||||
|
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
@ -75,6 +74,16 @@ createFrustum fov n' f' rat =
|
|||||||
(V4 0 0 (-((f+n)/(f-n))) (-((2*f*n)/(f-n))))
|
(V4 0 0 (-((f+n)/(f-n))) (-((2*f*n)/(f-n))))
|
||||||
(V4 0 0 (-1) 0)
|
(V4 0 0 (-1) 0)
|
||||||
|
|
||||||
|
-- | Creates an orthogonal frustum with given width, height, near and far-plane
|
||||||
|
createFrustumOrtho :: Float -> Float -> Float -> Float -> M44 CFloat
|
||||||
|
createFrustumOrtho w' h' n' f' =
|
||||||
|
let [w,h,n,f] = map realToFrac [w',h',n',f']
|
||||||
|
in
|
||||||
|
V4 (V4 (0.5/w) 0 0 0)
|
||||||
|
(V4 0 (0.5/h) 0 0)
|
||||||
|
(V4 0 0 (-2/(f-n)) ((-f+n)/(f-n)))
|
||||||
|
(V4 0 0 0 1)
|
||||||
|
|
||||||
-- from vmath.h
|
-- from vmath.h
|
||||||
lookAt :: V3 CFloat -> V3 CFloat -> V3 CFloat -> M44 CFloat
|
lookAt :: V3 CFloat -> V3 CFloat -> V3 CFloat -> M44 CFloat
|
||||||
lookAt eye center up' =
|
lookAt eye center up' =
|
||||||
@ -128,5 +137,5 @@ tryWithTexture t f fail' =
|
|||||||
genColorData :: Int -- ^ Amount
|
genColorData :: Int -- ^ Amount
|
||||||
-> [Int8] -- ^ [r,g,b,a], [r,g,b] - whatever should be repeatet.
|
-> [Int8] -- ^ [r,g,b,a], [r,g,b] - whatever should be repeatet.
|
||||||
-> [Int8]
|
-> [Int8]
|
||||||
genColorData n c = take ((length c)*n) (cycle c)
|
genColorData n c = take (length c*n) (cycle c)
|
||||||
|
|
||||||
|
@ -33,6 +33,8 @@ mapTessEvalShaderFile :: String
|
|||||||
mapTessEvalShaderFile = "shaders/map/tessEval.shader"
|
mapTessEvalShaderFile = "shaders/map/tessEval.shader"
|
||||||
mapFragmentShaderFile :: String
|
mapFragmentShaderFile :: String
|
||||||
mapFragmentShaderFile = "shaders/map/fragment.shader"
|
mapFragmentShaderFile = "shaders/map/fragment.shader"
|
||||||
|
mapFragmentShaderShadowMapFile :: String
|
||||||
|
mapFragmentShaderShadowMapFile = "shaders/map/fragmentShadow.shader"
|
||||||
|
|
||||||
objectVertexShaderFile :: String
|
objectVertexShaderFile :: String
|
||||||
objectVertexShaderFile = "shaders/mapobjects/vertex.shader"
|
objectVertexShaderFile = "shaders/mapobjects/vertex.shader"
|
||||||
@ -66,6 +68,7 @@ initMapShader tessFac (buf, vertDes) = do
|
|||||||
! tessControlSource <- B.readFile mapTessControlShaderFile
|
! tessControlSource <- B.readFile mapTessControlShaderFile
|
||||||
! tessEvalSource <- B.readFile mapTessEvalShaderFile
|
! tessEvalSource <- B.readFile mapTessEvalShaderFile
|
||||||
! fragmentSource <- B.readFile mapFragmentShaderFile
|
! fragmentSource <- B.readFile mapFragmentShaderFile
|
||||||
|
! fragmentShadowSource <- B.readFile mapFragmentShaderShadowMapFile
|
||||||
vertexShader <- compileShaderSource VertexShader vertexSource
|
vertexShader <- compileShaderSource VertexShader vertexSource
|
||||||
checkError "compile Vertex"
|
checkError "compile Vertex"
|
||||||
tessControlShader <- compileShaderSource TessControlShader tessControlSource
|
tessControlShader <- compileShaderSource TessControlShader tessControlSource
|
||||||
@ -74,7 +77,10 @@ initMapShader tessFac (buf, vertDes) = do
|
|||||||
checkError "compile TessEval"
|
checkError "compile TessEval"
|
||||||
fragmentShader <- compileShaderSource FragmentShader fragmentSource
|
fragmentShader <- compileShaderSource FragmentShader fragmentSource
|
||||||
checkError "compile Frag"
|
checkError "compile Frag"
|
||||||
|
fragmentShadowShader <- compileShaderSource FragmentShader fragmentShadowSource
|
||||||
|
checkError "compile Frag"
|
||||||
program <- createProgramUsing [vertexShader, tessControlShader, tessEvalShader, fragmentShader]
|
program <- createProgramUsing [vertexShader, tessControlShader, tessEvalShader, fragmentShader]
|
||||||
|
shadowProgram <- createProgramUsing [vertexShader, tessControlShader, tessEvalShader, fragmentShadowShader]
|
||||||
checkError "compile Program"
|
checkError "compile Program"
|
||||||
|
|
||||||
currentProgram $= Just program
|
currentProgram $= Just program
|
||||||
@ -139,17 +145,21 @@ initMapShader tessFac (buf, vertDes) = do
|
|||||||
currentProgram $= Just objProgram
|
currentProgram $= Just objProgram
|
||||||
|
|
||||||
checkError "initShader"
|
checkError "initShader"
|
||||||
|
let sdata = MapShaderData
|
||||||
|
{ shdrVertexIndex = vertexIndex
|
||||||
|
, shdrColorIndex = colorIndex
|
||||||
|
, shdrNormalIndex = normalIndex
|
||||||
|
, shdrProjMatIndex = projectionMatrixIndex
|
||||||
|
, shdrViewMatIndex = viewMatrixIndex
|
||||||
|
, shdrModelMatIndex = modelMatrixIndex
|
||||||
|
, shdrNormalMatIndex = normalMatrixIndex
|
||||||
|
, shdrTessInnerIndex = tessLevelInner
|
||||||
|
, shdrTessOuterIndex = tessLevelOuter
|
||||||
|
}
|
||||||
|
|
||||||
return GLMapState
|
return GLMapState
|
||||||
{ _mapProgram = program
|
{ _mapProgram = program
|
||||||
, _shdrColorIndex = colorIndex
|
, _mapShaderData = sdata
|
||||||
, _shdrNormalIndex = normalIndex
|
|
||||||
, _shdrVertexIndex = vertexIndex
|
|
||||||
, _shdrProjMatIndex = projectionMatrixIndex
|
|
||||||
, _shdrViewMatIndex = viewMatrixIndex
|
|
||||||
, _shdrModelMatIndex = modelMatrixIndex
|
|
||||||
, _shdrNormalMatIndex = normalMatrixIndex
|
|
||||||
, _shdrTessInnerIndex = tessLevelInner
|
|
||||||
, _shdrTessOuterIndex = tessLevelOuter
|
|
||||||
, _renderedMapTexture = tex
|
, _renderedMapTexture = tex
|
||||||
, _stateTessellationFactor = tessFac
|
, _stateTessellationFactor = tessFac
|
||||||
, _stateMap = buf
|
, _stateMap = buf
|
||||||
@ -159,6 +169,7 @@ initMapShader tessFac (buf, vertDes) = do
|
|||||||
, _shadowMapTexture = smap
|
, _shadowMapTexture = smap
|
||||||
, _mapObjects = objs
|
, _mapObjects = objs
|
||||||
, _objectProgram = objProgram
|
, _objectProgram = objProgram
|
||||||
|
, _shadowMapProgram = shadowProgram
|
||||||
}
|
}
|
||||||
|
|
||||||
initHud :: IO GLHud
|
initHud :: IO GLHud
|
||||||
@ -306,14 +317,15 @@ drawMap :: Pioneers ()
|
|||||||
drawMap = do
|
drawMap = do
|
||||||
state <- RWS.get
|
state <- RWS.get
|
||||||
let
|
let
|
||||||
vi = state ^. gl.glMap.shdrVertexIndex
|
d = state ^. gl.glMap.mapShaderData
|
||||||
ni = state ^. gl.glMap.shdrNormalIndex
|
vi = shdrVertexIndex d
|
||||||
ci = state ^. gl.glMap.shdrColorIndex
|
ni = shdrNormalIndex d
|
||||||
|
ci = shdrColorIndex d
|
||||||
numVert = state ^. gl.glMap.mapVert
|
numVert = state ^. gl.glMap.mapVert
|
||||||
map' = state ^. gl.glMap.stateMap
|
map' = state ^. gl.glMap.stateMap
|
||||||
tessFac = state ^. gl.glMap.stateTessellationFactor
|
tessFac = state ^. gl.glMap.stateTessellationFactor
|
||||||
(UniformLocation tli) = state ^. gl.glMap.shdrTessInnerIndex
|
(UniformLocation tli) = shdrTessInnerIndex d
|
||||||
(UniformLocation tlo) = state ^. gl.glMap.shdrTessOuterIndex
|
(UniformLocation tlo) = shdrTessOuterIndex d
|
||||||
liftIO $ do
|
liftIO $ do
|
||||||
glUniform1f tli (fromIntegral tessFac)
|
glUniform1f tli (fromIntegral tessFac)
|
||||||
glUniform1f tlo (fromIntegral tessFac)
|
glUniform1f tlo (fromIntegral tessFac)
|
||||||
@ -356,9 +368,10 @@ render = do
|
|||||||
frust = state ^. camera.Types.frustum
|
frust = state ^. camera.Types.frustum
|
||||||
camPos = state ^. camera.camObject
|
camPos = state ^. camera.camObject
|
||||||
zDist' = state ^. camera.zDist
|
zDist' = state ^. camera.zDist
|
||||||
(UniformLocation proj) = state ^. gl.glMap.shdrProjMatIndex
|
d = state ^. gl.glMap.mapShaderData
|
||||||
(UniformLocation nmat) = state ^. gl.glMap.shdrNormalMatIndex
|
(UniformLocation proj) = shdrProjMatIndex d
|
||||||
(UniformLocation vmat) = state ^. gl.glMap.shdrViewMatIndex
|
(UniformLocation nmat) = shdrNormalMatIndex d
|
||||||
|
(UniformLocation vmat) = shdrViewMatIndex d
|
||||||
liftIO $ do
|
liftIO $ do
|
||||||
---- RENDER MAP IN TEXTURE ------------------------------------------
|
---- RENDER MAP IN TEXTURE ------------------------------------------
|
||||||
|
|
||||||
@ -391,7 +404,7 @@ render = do
|
|||||||
|
|
||||||
--set up projection (= copy from state)
|
--set up projection (= copy from state)
|
||||||
--TODO: Fix
|
--TODO: Fix
|
||||||
with (distribute frust) $ \ptr ->
|
with (distribute (createFrustumOrtho 20 20 0 100)) $ \ptr ->
|
||||||
glUniformMatrix4fv proj 1 0 (castPtr (ptr :: Ptr (L.M44 CFloat)))
|
glUniformMatrix4fv proj 1 0 (castPtr (ptr :: Ptr (L.M44 CFloat)))
|
||||||
checkError "copy shadowmap-projection"
|
checkError "copy shadowmap-projection"
|
||||||
|
|
||||||
|
23
src/Types.hs
23
src/Types.hs
@ -101,15 +101,7 @@ data KeyboardState = KeyboardState
|
|||||||
|
|
||||||
|
|
||||||
data GLMapState = GLMapState
|
data GLMapState = GLMapState
|
||||||
{ _shdrVertexIndex :: !GL.AttribLocation
|
{ _mapShaderData :: !MapShaderData
|
||||||
, _shdrColorIndex :: !GL.AttribLocation
|
|
||||||
, _shdrNormalIndex :: !GL.AttribLocation
|
|
||||||
, _shdrProjMatIndex :: !GL.UniformLocation
|
|
||||||
, _shdrViewMatIndex :: !GL.UniformLocation
|
|
||||||
, _shdrModelMatIndex :: !GL.UniformLocation
|
|
||||||
, _shdrNormalMatIndex :: !GL.UniformLocation
|
|
||||||
, _shdrTessInnerIndex :: !GL.UniformLocation
|
|
||||||
, _shdrTessOuterIndex :: !GL.UniformLocation
|
|
||||||
, _stateTessellationFactor :: !Int
|
, _stateTessellationFactor :: !Int
|
||||||
, _stateMap :: !GL.BufferObject
|
, _stateMap :: !GL.BufferObject
|
||||||
, _mapVert :: !GL.NumArrayIndices
|
, _mapVert :: !GL.NumArrayIndices
|
||||||
@ -120,6 +112,19 @@ data GLMapState = GLMapState
|
|||||||
, _mapTextures :: ![TextureObject] --TODO: Fix size on list?
|
, _mapTextures :: ![TextureObject] --TODO: Fix size on list?
|
||||||
, _objectProgram :: !GL.Program
|
, _objectProgram :: !GL.Program
|
||||||
, _mapObjects :: ![MapObject]
|
, _mapObjects :: ![MapObject]
|
||||||
|
, _shadowMapProgram :: !GL.Program
|
||||||
|
}
|
||||||
|
|
||||||
|
data MapShaderData = MapShaderData
|
||||||
|
{ shdrVertexIndex :: !GL.AttribLocation
|
||||||
|
, shdrColorIndex :: !GL.AttribLocation
|
||||||
|
, shdrNormalIndex :: !GL.AttribLocation
|
||||||
|
, shdrProjMatIndex :: !GL.UniformLocation
|
||||||
|
, shdrViewMatIndex :: !GL.UniformLocation
|
||||||
|
, shdrModelMatIndex :: !GL.UniformLocation
|
||||||
|
, shdrNormalMatIndex :: !GL.UniformLocation
|
||||||
|
, shdrTessInnerIndex :: !GL.UniformLocation
|
||||||
|
, shdrTessOuterIndex :: !GL.UniformLocation
|
||||||
}
|
}
|
||||||
|
|
||||||
data MapObject = MapObject !IQM !MapCoordinates !MapObjectState
|
data MapObject = MapObject !IQM !MapCoordinates !MapObjectState
|
||||||
|
Loading…
Reference in New Issue
Block a user