pioneers/src/Render/Render.hs

392 lines
14 KiB
Haskell
Raw Normal View History

{-# LANGUAGE BangPatterns, InstanceSigs, ExistentialQuantification #-}
module Render.Render where
import qualified Data.ByteString as B
import Foreign.Marshal.Array (withArray)
import Foreign.Storable
import Graphics.Rendering.OpenGL.GL
2014-01-04 23:47:07 +01:00
import Graphics.Rendering.OpenGL.Raw.Core31
import Graphics.Rendering.OpenGL.Raw.ARB.TessellationShader
import Graphics.GLUtil.BufferObjects (offset0)
import qualified Linear as L
import Control.Lens ((^.))
import Control.Monad.RWS.Strict (liftIO)
import qualified Control.Monad.RWS.Strict as RWS (get)
import Data.Distributive (distribute, collect)
-- FFI
import Foreign (Ptr, castPtr, with)
import Foreign.C (CFloat)
import Map.Graphics
import Types
import Render.Misc
import Render.Types
import Graphics.GLUtil.BufferObjects (makeBuffer)
2014-03-24 08:21:30 +01:00
mapVertexShaderFile :: String
mapVertexShaderFile = "shaders/map/vertex.shader"
mapTessControlShaderFile :: String
mapTessControlShaderFile = "shaders/map/tessControl.shader"
mapTessEvalShaderFile :: String
mapTessEvalShaderFile = "shaders/map/tessEval.shader"
mapFragmentShaderFile :: String
mapFragmentShaderFile = "shaders/map/fragment.shader"
uiVertexShaderFile :: String
uiVertexShaderFile = "shaders/ui/vertex.shader"
uiFragmentShaderFile :: String
uiFragmentShaderFile = "shaders/ui/fragment.shader"
initBuffer :: [GLfloat] -> IO BufferObject
initBuffer varray =
let
sizeOfVarray = length varray * sizeOfComponent
sizeOfComponent = sizeOf (head varray)
in do
bufferObject <- genObjectName
bindBuffer ArrayBuffer $= Just bufferObject
withArray varray $ \buffer ->
bufferData ArrayBuffer $= (fromIntegral sizeOfVarray, buffer, StaticDraw)
checkError "initBuffer"
return bufferObject
2014-03-24 08:21:30 +01:00
initMapShader :: IO (
2014-04-15 17:28:38 +02:00
Program -- the GLSL-Program
, AttribLocation -- color
, AttribLocation -- normal
, AttribLocation -- vertex
, UniformLocation -- ProjectionMat
, UniformLocation -- ViewMat
, UniformLocation -- ModelMat
, UniformLocation -- NormalMat
, UniformLocation -- TessLevelInner
, UniformLocation -- TessLevelOuter
, TextureObject -- Texture where to draw into
) -- ^ (the GLSL-Program, color, normal, vertex, ProjectionMat, ViewMat,
-- ModelMat, NormalMat, TessLevelInner, TessLevelOuter,
-- Texture where to draw into)
2014-03-24 08:21:30 +01:00
initMapShader = do
! vertexSource <- B.readFile mapVertexShaderFile
! tessControlSource <- B.readFile mapTessControlShaderFile
! tessEvalSource <- B.readFile mapTessEvalShaderFile
! fragmentSource <- B.readFile mapFragmentShaderFile
vertexShader <- compileShaderSource VertexShader vertexSource
checkError "compile Vertex"
2014-01-21 16:18:48 +01:00
tessControlShader <- compileShaderSource TessControlShader tessControlSource
2014-03-24 08:21:30 +01:00
checkError "compile TessControl"
2014-01-21 16:18:48 +01:00
tessEvalShader <- compileShaderSource TessEvaluationShader tessEvalSource
2014-03-24 08:21:30 +01:00
checkError "compile TessEval"
fragmentShader <- compileShaderSource FragmentShader fragmentSource
checkError "compile Frag"
2014-01-21 16:18:48 +01:00
program <- createProgramUsing [vertexShader, tessControlShader, tessEvalShader, fragmentShader]
checkError "compile Program"
currentProgram $= Just program
2014-01-21 16:18:48 +01:00
projectionMatrixIndex <- get (uniformLocation program "ProjectionMatrix")
checkError "projMat"
2014-01-21 16:18:48 +01:00
viewMatrixIndex <- get (uniformLocation program "ViewMatrix")
2014-01-05 19:09:01 +01:00
checkError "viewMat"
2014-01-21 16:18:48 +01:00
modelMatrixIndex <- get (uniformLocation program "ModelMatrix")
2014-01-04 14:09:42 +01:00
checkError "modelMat"
2014-01-21 16:18:48 +01:00
normalMatrixIndex <- get (uniformLocation program "NormalMatrix")
2014-01-06 21:13:58 +01:00
checkError "normalMat"
2014-01-21 16:44:42 +01:00
tessLevelInner <- get (uniformLocation program "TessLevelInner")
checkError "TessLevelInner"
tessLevelOuter <- get (uniformLocation program "TessLevelOuter")
checkError "TessLevelOuter"
2014-01-21 16:18:48 +01:00
vertexIndex <- get (attribLocation program "Position")
vertexAttribArray vertexIndex $= Enabled
checkError "vertexInd"
2014-01-21 16:18:48 +01:00
normalIndex <- get (attribLocation program "Normal")
2014-01-04 16:55:59 +01:00
vertexAttribArray normalIndex $= Enabled
checkError "normalInd"
2014-01-21 16:18:48 +01:00
colorIndex <- get (attribLocation program "Color")
2014-01-04 14:09:42 +01:00
vertexAttribArray colorIndex $= Enabled
checkError "colorInd"
2014-01-04 16:55:59 +01:00
att <- get (activeAttribs program)
2014-01-04 14:09:42 +01:00
putStrLn $ unlines $ "Attributes: ":map show att
2014-01-04 16:55:59 +01:00
putStrLn $ unlines $ ["Indices: ", show (colorIndex, normalIndex, vertexIndex)]
2014-01-04 14:09:42 +01:00
tex <- genObjectName
checkError "initShader"
return (program, colorIndex, normalIndex, vertexIndex, projectionMatrixIndex, viewMatrixIndex, modelMatrixIndex, normalMatrixIndex, tessLevelInner, tessLevelOuter, tex)
2014-03-24 08:21:30 +01:00
initHud :: IO GLHud
initHud = do
! vertexSource <- B.readFile "shaders/ui/vertex.shader"
! fragmentSource <- B.readFile "shaders/ui/fragment.shader"
2014-03-24 08:21:30 +01:00
vertexShader <- compileShaderSource VertexShader vertexSource
checkError "compile UI-Vertex"
2014-03-24 08:21:30 +01:00
fragmentShader <- compileShaderSource FragmentShader fragmentSource
checkError "compile UI-Fragment"
2014-03-24 08:21:30 +01:00
program <- createProgramUsing [vertexShader, fragmentShader]
checkError "compile Program"
tex <- genObjectName
currentProgram $= Just program
backIndex <- get (uniformLocation program "tex[0]")
texIndex <- get (uniformLocation program "tex[1]")
checkError "ui-tex"
2014-04-15 17:28:38 +02:00
-- simple triangle over the whole screen.
let vertexBufferData = reverse [-1, -1, 1, -1, -1, 1, 1, 1] :: [GLfloat]
vertexIndex <- get (attribLocation program "position")
vertexAttribArray vertexIndex $= Enabled
checkError "vertexInd"
ebo <- makeBuffer ElementArrayBuffer ([0..3] :: [GLuint])
vbo <- makeBuffer ArrayBuffer vertexBufferData
2014-03-24 08:21:30 +01:00
att <- get (activeAttribs program)
putStrLn $ unlines $ "Attributes: ":map show att
putStrLn $ unlines $ ["Indices: ", show (texIndex)]
checkError "initHud"
return GLHud
{ _hudTexture = tex
, _hudTexIndex = texIndex
, _hudBackIndex = backIndex
, _hudVertexIndex = vertexIndex
, _hudVert = 4
, _hudVBO = vbo
, _hudEBO = ebo
, _hudProgram = program
}
2014-03-24 08:21:30 +01:00
initRendering :: IO ()
initRendering = do
2014-04-21 15:55:22 +02:00
clearColor $= Color4 0.6 0.7 0.8 1
2014-01-04 23:47:07 +01:00
depthFunc $= Just Less
glCullFace gl_BACK
checkError "initRendering"
2014-04-22 16:25:29 +02:00
{-renderOverview :: Pioneers ()
renderOverview = do
liftIO $ do
---- RENDER OVERVIEW MAP ------------------------------------------
bindFramebuffer Framebuffer $= (state ^. gl.glFramebuffer)
bindRenderbuffer Renderbuffer $= (state ^. gl.glRenderbuffer)
framebufferRenderbuffer
Framebuffer
DepthAttachment
Renderbuffer
(state ^. gl.glRenderbuffer)
textureBinding Texture2D $= Just (state ^. gl.glMap.mapTexture)
framebufferTexture2D
Framebuffer
(ColorAttachment 0)
Texture2D
(state ^. gl.glMap.mapTexture)
0
-- Render to FrameBufferObject
drawBuffers $= [FBOColorAttachment 0]
checkError "setup Render-Target"
clear [ColorBuffer, DepthBuffer]
checkError "clear buffer"
currentProgram $= Just (state ^. gl.glMap.mapProgram)
checkError "setting up buffer"
--set up projection (= copy from state)
with (distribute frust) $ \ptr ->
glUniformMatrix4fv proj 1 0 (castPtr (ptr :: Ptr (L.M44 CFloat)))
checkError "copy projection"
--set up camera
let ! cam = getCam camPos zDist' xa ya
with (distribute cam) $ \ptr ->
glUniformMatrix4fv vmat 1 0 (castPtr (ptr :: Ptr (L.M44 CFloat)))
checkError "copy cam"
--set up normal--Mat transpose((model*camera)^-1)
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"
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 :: 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
liftIO $ do
---- RENDER MAP IN TEXTURE ------------------------------------------
bindFramebuffer Framebuffer $= (state ^. gl.glFramebuffer)
bindRenderbuffer Renderbuffer $= (state ^. gl.glRenderbuffer)
framebufferRenderbuffer
Framebuffer
DepthAttachment
Renderbuffer
(state ^. gl.glRenderbuffer)
textureBinding Texture2D $= Just (state ^. gl.glMap.mapTexture)
framebufferTexture2D
Framebuffer
(ColorAttachment 0)
Texture2D
(state ^. gl.glMap.mapTexture)
0
-- Render to FrameBufferObject
drawBuffers $= [FBOColorAttachment 0]
checkError "setup Render-Target"
clear [ColorBuffer, DepthBuffer]
checkError "clear buffer"
currentProgram $= Just (state ^. gl.glMap.mapProgram)
checkError "setting up buffer"
--set up projection (= copy from state)
with (distribute frust) $ \ptr ->
glUniformMatrix4fv proj 1 0 (castPtr (ptr :: Ptr (L.M44 CFloat)))
checkError "copy projection"
--set up camera
let ! cam = getCam camPos zDist' xa ya
with (distribute cam) $ \ptr ->
glUniformMatrix4fv vmat 1 0 (castPtr (ptr :: Ptr (L.M44 CFloat)))
checkError "copy cam"
--set up normal--Mat transpose((model*camera)^-1)
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"
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"
-- set sample 1 as target in renderbuffer
{-framebufferRenderbuffer
DrawFramebuffer --write-only
(ColorAttachment 1) --sample 1
Renderbuffer --const
rb --buffer-}
---- COMPOSE RENDERING --------------------------------------------
-- Render to BackBuffer (=Screen)
bindFramebuffer Framebuffer $= defaultFramebufferObject
drawBuffer $= BackBuffers
-- Drawing HUD
clear [ColorBuffer, DepthBuffer]
checkError "clear buffer"
let hud = state ^. gl.glHud
stride = fromIntegral $ sizeOf (undefined::GLfloat) * 2
vad = VertexArrayDescriptor 2 Float stride offset0
currentProgram $= Just (hud ^. hudProgram)
activeTexture $= TextureUnit 0
textureBinding Texture2D $= Just (hud ^. hudTexture)
uniform (hud ^. hudTexIndex) $= Index1 (0::GLint)
activeTexture $= TextureUnit 1
textureBinding Texture2D $= Just (state ^. gl.glMap.mapTexture)
uniform (hud ^. hudBackIndex) $= Index1 (1::GLint)
bindBuffer ArrayBuffer $= Just (hud ^. hudVBO)
vertexAttribPointer (hud ^. hudVertexIndex) $= (ToFloat, vad)
vertexAttribArray (hud ^. hudVertexIndex) $= Enabled
bindBuffer ElementArrayBuffer $= Just (hud ^. hudEBO)
drawElements TriangleStrip 4 UnsignedInt offset0
{-let winRenderer = env ^. renderer
tryWithTexture
(state ^. hudTexture) --maybe tex
(\tex -> renderCopy winRenderer tex Nothing Nothing) --function with "hole"
--Nothing == whole source-tex, whole dest-tex
(return ()) --fail-case-}