Merge branch 'tessallation' into iqm
This commit is contained in:
commit
4d31866256
@ -304,6 +304,7 @@ adjustWindow = do
|
||||
|
||||
let hudtexid = state ^. gl.glHud.hudTexture
|
||||
maptexid = state ^. gl.glMap.renderedMapTexture
|
||||
smaptexid = state ^. gl.glMap.shadowMapTexture
|
||||
allocaBytes (fbWidth*fbHeight*4) $ \ptr -> do
|
||||
--default to ugly pink to see if
|
||||
--somethings go wrong.
|
||||
@ -320,6 +321,13 @@ adjustWindow = do
|
||||
textureFilter Texture2D GL.$= ((Linear', Nothing), Linear')
|
||||
texImage2D Texture2D GL.NoProxy 0 RGBA8 (GL.TextureSize2D fbCWidth fbCHeight) 0
|
||||
(GL.PixelData GL.RGBA GL.UnsignedByte ptr)
|
||||
allocaBytes (2048*2048) $ \ptr -> do
|
||||
let smapdata = genColorData (2048*2048) [0]
|
||||
pokeArray ptr smapdata
|
||||
textureBinding Texture2D GL.$= Just smaptexid
|
||||
textureFilter Texture2D GL.$= ((Nearest,Nothing), Nearest)
|
||||
texImage2D Texture2D GL.NoProxy 0 GL.DepthComponent16 (GL.TextureSize2D 2048 2048) 0
|
||||
(GL.PixelData GL.DepthComponent GL.UnsignedByte ptr)
|
||||
checkError "setting up HUD-Tex"
|
||||
return renderBuffer
|
||||
modify $ gl.glRenderbuffer .~ rb
|
||||
|
@ -72,9 +72,9 @@ mnh2D (a,b) (c,d) = abs (a-c) + abs (b-d)
|
||||
heightToTerrain :: MapType -> YCoord -> TileType
|
||||
heightToTerrain GrassIslandMap y
|
||||
| y < 0.1 = Ocean
|
||||
| y < 1 = Beach
|
||||
| y < 5 = Grass
|
||||
| y < 10 = Hill
|
||||
| y < 0.2 = Beach
|
||||
| y < 1 = Grass
|
||||
| y < 3 = Hill
|
||||
| otherwise = Mountain
|
||||
heightToTerrain _ _ = undefined
|
||||
|
||||
@ -87,16 +87,16 @@ river = undefined
|
||||
|
||||
mnt :: IO [PlayMap -> PlayMap]
|
||||
mnt = do g <- newStdGen
|
||||
let seeds = take 10 $ randoms g
|
||||
return $ map (gaussMountain) seeds
|
||||
let seeds = take 50 $ randoms g
|
||||
return $ map gaussMountain seeds
|
||||
|
||||
gaussMountain :: Int -> PlayMap -> PlayMap
|
||||
gaussMountain seed mp = aplByPlace (liftUp c) (\(_,_) -> True) mp
|
||||
where
|
||||
g = mkStdGen seed
|
||||
c = let ((a,b), (x,y)) = bounds mp in (head (randomRs (a,x) g), (head (randomRs (b,y) g)))
|
||||
amp = head $ randomRs (5.0, 20.0) g
|
||||
sig = head $ randomRs (5.0, 25.0) g
|
||||
amp = head $ randomRs (2.0, 5.0) g
|
||||
sig = head $ randomRs (1.0, 5.0) g
|
||||
fi = fromIntegral
|
||||
htt = heightToTerrain
|
||||
|
||||
|
@ -1,4 +1,3 @@
|
||||
{-# LANGUAGE ForeignFunctionInterface #-}
|
||||
module Render.Misc where
|
||||
|
||||
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 (-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
|
||||
lookAt :: V3 CFloat -> V3 CFloat -> V3 CFloat -> M44 CFloat
|
||||
lookAt eye center up' =
|
||||
@ -128,5 +137,9 @@ tryWithTexture t f fail' =
|
||||
genColorData :: Int -- ^ Amount
|
||||
-> [Int8] -- ^ [r,g,b,a], [r,g,b] - whatever should be repeatet.
|
||||
-> [Int8]
|
||||
genColorData n c = take ((length c)*n) (cycle c)
|
||||
genColorData n c = take (length c*n) (cycle c)
|
||||
|
||||
-- from GLUtil
|
||||
-- |Allocate and fill a 'BufferObject' from a list of 'Storable's.
|
||||
makeBuffer :: Storable a => BufferTarget -> [a] -> IO BufferObject
|
||||
makeBuffer target elems = makeBufferLen target (length elems) elems
|
||||
|
@ -7,7 +7,7 @@ import Foreign.Storable
|
||||
import Graphics.Rendering.OpenGL.GL
|
||||
import Graphics.Rendering.OpenGL.Raw.Core31
|
||||
import Graphics.Rendering.OpenGL.Raw.ARB.TessellationShader
|
||||
import Graphics.GLUtil.BufferObjects (offset0)
|
||||
import Graphics.GLUtil.BufferObjects
|
||||
import qualified Linear as L
|
||||
import Control.Lens ((^.))
|
||||
import Control.Monad.RWS.Strict (liftIO)
|
||||
@ -33,6 +33,8 @@ mapTessEvalShaderFile :: String
|
||||
mapTessEvalShaderFile = "shaders/map/tessEval.shader"
|
||||
mapFragmentShaderFile :: String
|
||||
mapFragmentShaderFile = "shaders/map/fragment.shader"
|
||||
mapFragmentShaderShadowMapFile :: String
|
||||
mapFragmentShaderShadowMapFile = "shaders/map/fragmentShadow.shader"
|
||||
|
||||
objectVertexShaderFile :: String
|
||||
objectVertexShaderFile = "shaders/mapobjects/vertex.shader"
|
||||
@ -66,6 +68,7 @@ initMapShader tessFac (buf, vertDes) = do
|
||||
! tessControlSource <- B.readFile mapTessControlShaderFile
|
||||
! tessEvalSource <- B.readFile mapTessEvalShaderFile
|
||||
! fragmentSource <- B.readFile mapFragmentShaderFile
|
||||
! fragmentShadowSource <- B.readFile mapFragmentShaderShadowMapFile
|
||||
vertexShader <- compileShaderSource VertexShader vertexSource
|
||||
checkError "compile Vertex"
|
||||
tessControlShader <- compileShaderSource TessControlShader tessControlSource
|
||||
@ -74,7 +77,10 @@ initMapShader tessFac (buf, vertDes) = do
|
||||
checkError "compile TessEval"
|
||||
fragmentShader <- compileShaderSource FragmentShader fragmentSource
|
||||
checkError "compile Frag"
|
||||
fragmentShadowShader <- compileShaderSource FragmentShader fragmentShadowSource
|
||||
checkError "compile Frag"
|
||||
program <- createProgramUsing [vertexShader, tessControlShader, tessEvalShader, fragmentShader]
|
||||
shadowProgram <- createProgramUsing [vertexShader, tessControlShader, tessEvalShader, fragmentShadowShader]
|
||||
checkError "compile Program"
|
||||
|
||||
currentProgram $= Just program
|
||||
@ -120,6 +126,8 @@ initMapShader tessFac (buf, vertDes) = do
|
||||
|
||||
texts <- genObjectNames 6
|
||||
|
||||
smap <- genObjectName
|
||||
|
||||
testobj <- parseIQM "sample.iqm"
|
||||
|
||||
let
|
||||
@ -137,25 +145,31 @@ initMapShader tessFac (buf, vertDes) = do
|
||||
currentProgram $= Just objProgram
|
||||
|
||||
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
|
||||
{ _mapProgram = program
|
||||
, _shdrColorIndex = colorIndex
|
||||
, _shdrNormalIndex = normalIndex
|
||||
, _shdrVertexIndex = vertexIndex
|
||||
, _shdrProjMatIndex = projectionMatrixIndex
|
||||
, _shdrViewMatIndex = viewMatrixIndex
|
||||
, _shdrModelMatIndex = modelMatrixIndex
|
||||
, _shdrNormalMatIndex = normalMatrixIndex
|
||||
, _shdrTessInnerIndex = tessLevelInner
|
||||
, _shdrTessOuterIndex = tessLevelOuter
|
||||
, _mapShaderData = sdata
|
||||
, _renderedMapTexture = tex
|
||||
, _stateTessellationFactor = tessFac
|
||||
, _stateMap = buf
|
||||
, _mapVert = vertDes
|
||||
, _overviewTexture = overTex
|
||||
, _mapTextures = texts
|
||||
, _shadowMapTexture = smap
|
||||
, _mapObjects = objs
|
||||
, _objectProgram = objProgram
|
||||
, _shadowMapProgram = shadowProgram
|
||||
}
|
||||
|
||||
initHud :: IO GLHud
|
||||
@ -190,7 +204,7 @@ initHud = do
|
||||
att <- get (activeAttribs program)
|
||||
|
||||
putStrLn $ unlines $ "Attributes: ":map show att
|
||||
putStrLn $ unlines $ ["Indices: ", show (texIndex)]
|
||||
putStrLn $ unlines $ ["Indices: ", show texIndex]
|
||||
|
||||
checkError "initHud"
|
||||
return GLHud
|
||||
@ -299,38 +313,125 @@ renderObject :: MapObject -> IO ()
|
||||
renderObject (MapObject model pos@(L.V3 x y z) _{-state-}) =
|
||||
renderIQM model pos (L.V3 1 1 1)
|
||||
|
||||
drawMap :: Pioneers ()
|
||||
drawMap = do
|
||||
state <- RWS.get
|
||||
let
|
||||
d = state ^. gl.glMap.mapShaderData
|
||||
vi = shdrVertexIndex d
|
||||
ni = shdrNormalIndex d
|
||||
ci = shdrColorIndex d
|
||||
numVert = state ^. gl.glMap.mapVert
|
||||
map' = state ^. gl.glMap.stateMap
|
||||
tessFac = state ^. gl.glMap.stateTessellationFactor
|
||||
(UniformLocation tli) = shdrTessInnerIndex d
|
||||
(UniformLocation tlo) = shdrTessOuterIndex d
|
||||
liftIO $ do
|
||||
glUniform1f tli (fromIntegral tessFac)
|
||||
glUniform1f tlo (fromIntegral tessFac)
|
||||
|
||||
bindBuffer ArrayBuffer $= Just map'
|
||||
vertexAttribPointer ci $= fgColorIndex
|
||||
vertexAttribArray ci $= Enabled
|
||||
vertexAttribPointer ni $= fgNormalIndex
|
||||
vertexAttribArray ni $= Enabled
|
||||
vertexAttribPointer vi $= fgVertexIndex
|
||||
vertexAttribArray vi $= Enabled
|
||||
checkError "beforeDraw"
|
||||
|
||||
glPatchParameteri gl_PATCH_VERTICES 3
|
||||
|
||||
cullFace $= Just Front
|
||||
|
||||
glDrawArrays gl_PATCHES 0 (fromIntegral numVert)
|
||||
|
||||
checkError "draw map"
|
||||
|
||||
---- RENDER MAPOBJECTS --------------------------------------------
|
||||
|
||||
currentProgram $= Just (state ^. gl.glMap.objectProgram)
|
||||
|
||||
mapM_ renderObject (state ^. gl.glMap.mapObjects)
|
||||
|
||||
-- set sample 1 as target in renderbuffer
|
||||
{-framebufferRenderbuffer
|
||||
DrawFramebuffer --write-only
|
||||
(ColorAttachment 1) --sample 1
|
||||
Renderbuffer --const
|
||||
rb --buffer-}
|
||||
|
||||
render :: Pioneers ()
|
||||
render = do
|
||||
state <- RWS.get
|
||||
let xa = state ^. camera.xAngle
|
||||
ya = state ^. camera.yAngle
|
||||
(UniformLocation proj) = state ^. gl.glMap.shdrProjMatIndex
|
||||
(UniformLocation nmat) = state ^. gl.glMap.shdrNormalMatIndex
|
||||
(UniformLocation vmat) = state ^. gl.glMap.shdrViewMatIndex
|
||||
(UniformLocation tli) = state ^. gl.glMap.shdrTessInnerIndex
|
||||
(UniformLocation tlo) = state ^. gl.glMap.shdrTessOuterIndex
|
||||
vi = state ^. gl.glMap.shdrVertexIndex
|
||||
ni = state ^. gl.glMap.shdrNormalIndex
|
||||
ci = state ^. gl.glMap.shdrColorIndex
|
||||
numVert = state ^. gl.glMap.mapVert
|
||||
map' = state ^. gl.glMap.stateMap
|
||||
frust = state ^. camera.Types.frustum
|
||||
camPos = state ^. camera.camObject
|
||||
zDist' = state ^. camera.zDist
|
||||
tessFac = state ^. gl.glMap.stateTessellationFactor
|
||||
d = state ^. gl.glMap.mapShaderData
|
||||
(UniformLocation proj) = shdrProjMatIndex d
|
||||
(UniformLocation nmat) = shdrNormalMatIndex d
|
||||
(UniformLocation vmat) = shdrViewMatIndex d
|
||||
liftIO $ do
|
||||
---- RENDER MAP IN TEXTURE ------------------------------------------
|
||||
|
||||
bindFramebuffer Framebuffer $= (state ^. gl.glFramebuffer)
|
||||
bindRenderbuffer Renderbuffer $= (state ^. gl.glRenderbuffer)
|
||||
{-bindRenderbuffer Renderbuffer $= (state ^. gl.glRenderbuffer)
|
||||
framebufferRenderbuffer
|
||||
Framebuffer
|
||||
DepthAttachment
|
||||
Renderbuffer
|
||||
(state ^. gl.glRenderbuffer)
|
||||
textureBinding Texture2D $= Just (state ^. gl.glMap.renderedMapTexture)
|
||||
(state ^. gl.glRenderbuffer)-}
|
||||
|
||||
-- SHADOWMAP
|
||||
textureBinding Texture2D $= Just (state ^. gl.glMap.shadowMapTexture)
|
||||
framebufferTexture2D
|
||||
Framebuffer
|
||||
DepthAttachment
|
||||
Texture2D
|
||||
(state ^. gl.glMap.shadowMapTexture)
|
||||
0
|
||||
|
||||
drawBuffer $= NoBuffers --color-buffer is not needed but must(?) be set up
|
||||
checkError "setup Render-Target"
|
||||
|
||||
clear [DepthBuffer]
|
||||
checkError "clearing shadowmap-buffer"
|
||||
|
||||
--TODO: simplified program for shadows?
|
||||
currentProgram $= Just (state ^. gl.glMap.mapProgram)
|
||||
checkError "setting up shadowmap-program"
|
||||
|
||||
--set up projection (= copy from state)
|
||||
--TODO: Fix width/depth
|
||||
with (distribute (createFrustumOrtho 20 20 0 100)) $ \ptr ->
|
||||
glUniformMatrix4fv proj 1 0 (castPtr (ptr :: Ptr (L.M44 CFloat)))
|
||||
checkError "copy shadowmap-projection"
|
||||
|
||||
--set up camera
|
||||
--TODO: Fix magic constants... and camPos
|
||||
let ! cam = getCam camPos 1 0.7 0
|
||||
with (distribute cam) $ \ptr ->
|
||||
glUniformMatrix4fv vmat 1 0 (castPtr (ptr :: Ptr (L.M44 CFloat)))
|
||||
checkError "copy shadowmap-cam"
|
||||
|
||||
--set up normal--Mat transpose((model*camera)^-1)
|
||||
--needed?
|
||||
let normal' = (case L.inv33 (fmap (^. L._xyz) cam ^. L._xyz) of
|
||||
(Just a) -> a
|
||||
Nothing -> L.eye3) :: L.M33 CFloat
|
||||
nmap = collect id normal' :: L.M33 CFloat --transpose...
|
||||
|
||||
with (distribute nmap) $ \ptr ->
|
||||
glUniformMatrix3fv nmat 1 0 (castPtr (ptr :: Ptr (L.M33 CFloat)))
|
||||
|
||||
checkError "nmat"
|
||||
drawMap
|
||||
liftIO $ do
|
||||
checkError "draw ShadowMap"
|
||||
|
||||
-- COLORMAP
|
||||
textureBinding Texture2D $= Just (state ^. gl.glMap.renderedMapTexture)
|
||||
framebufferTexture2D
|
||||
Framebuffer
|
||||
(ColorAttachment 0)
|
||||
@ -371,38 +472,8 @@ render = do
|
||||
|
||||
checkError "nmat"
|
||||
|
||||
glUniform1f tli (fromIntegral tessFac)
|
||||
glUniform1f tlo (fromIntegral tessFac)
|
||||
|
||||
bindBuffer ArrayBuffer $= Just map'
|
||||
vertexAttribPointer ci $= fgColorIndex
|
||||
vertexAttribArray ci $= Enabled
|
||||
vertexAttribPointer ni $= fgNormalIndex
|
||||
vertexAttribArray ni $= Enabled
|
||||
vertexAttribPointer vi $= fgVertexIndex
|
||||
vertexAttribArray vi $= Enabled
|
||||
checkError "beforeDraw"
|
||||
|
||||
glPatchParameteri gl_PATCH_VERTICES 3
|
||||
|
||||
cullFace $= Just Front
|
||||
|
||||
glDrawArrays gl_PATCHES 0 (fromIntegral numVert)
|
||||
|
||||
checkError "draw map"
|
||||
|
||||
---- RENDER MAPOBJECTS --------------------------------------------
|
||||
|
||||
currentProgram $= Just (state ^. gl.glMap.objectProgram)
|
||||
|
||||
mapM_ renderObject (state ^. gl.glMap.mapObjects)
|
||||
|
||||
-- set sample 1 as target in renderbuffer
|
||||
{-framebufferRenderbuffer
|
||||
DrawFramebuffer --write-only
|
||||
(ColorAttachment 1) --sample 1
|
||||
Renderbuffer --const
|
||||
rb --buffer-}
|
||||
drawMap --draw map -> put to another function for readability
|
||||
liftIO $ do
|
||||
|
||||
---- COMPOSE RENDERING --------------------------------------------
|
||||
-- Render to BackBuffer (=Screen)
|
||||
|
24
src/Types.hs
24
src/Types.hs
@ -101,24 +101,30 @@ data KeyboardState = KeyboardState
|
||||
|
||||
|
||||
data GLMapState = GLMapState
|
||||
{ _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
|
||||
{ _mapShaderData :: !MapShaderData
|
||||
, _stateTessellationFactor :: !Int
|
||||
, _stateMap :: !GL.BufferObject
|
||||
, _mapVert :: !GL.NumArrayIndices
|
||||
, _mapProgram :: !GL.Program
|
||||
, _renderedMapTexture :: !TextureObject --TODO: Probably move to UI?
|
||||
, _overviewTexture :: !TextureObject
|
||||
, _shadowMapTexture :: !TextureObject
|
||||
, _mapTextures :: ![TextureObject] --TODO: Fix size on list?
|
||||
, _objectProgram :: !GL.Program
|
||||
, _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
|
||||
|
Loading…
Reference in New Issue
Block a user