moved GLMapState: _renderedMapTexture to State: _mapTexture
This commit is contained in:
		@@ -14,7 +14,7 @@ import           Control.Lens                         ((^.), (.~), (%~))
 | 
			
		||||
-- data consistency/conversion
 | 
			
		||||
import           Control.Concurrent                   (threadDelay)
 | 
			
		||||
import           Control.Concurrent.STM               (TQueue, newTQueueIO, atomically)
 | 
			
		||||
import           Control.Concurrent.STM.TVar          (newTVarIO, writeTVar, readTVar)
 | 
			
		||||
import           Control.Concurrent.STM.TVar          (newTVarIO, writeTVar, readTVar, readTVarIO)
 | 
			
		||||
 | 
			
		||||
import           Control.Monad.RWS.Strict             (ask, evalRWST, get, liftIO, modify)
 | 
			
		||||
import           Data.Functor                         ((<$>))
 | 
			
		||||
@@ -89,7 +89,8 @@ main = do
 | 
			
		||||
        initRendering
 | 
			
		||||
        --generate map vertices
 | 
			
		||||
        curMap <- exportedMap
 | 
			
		||||
        glMap' <- initMapShader 4 =<< getMapBufferObject curMap
 | 
			
		||||
        (glMap', tex) <- initMapShader 4 =<< getMapBufferObject curMap
 | 
			
		||||
        tex' <- newTVarIO tex
 | 
			
		||||
        eventQueue <- newTQueueIO :: IO (TQueue SDL.Event)
 | 
			
		||||
        now <- getCurrentTime
 | 
			
		||||
        --font <- TTF.openFont "fonts/ttf-04B_03B_/04B_03B_.TTF" 10
 | 
			
		||||
@@ -140,6 +141,7 @@ main = do
 | 
			
		||||
                        , _tessClockTime       = now
 | 
			
		||||
                        }
 | 
			
		||||
              , _camera              = cam'
 | 
			
		||||
              , _mapTexture          = tex'
 | 
			
		||||
              , _camStack            = camStack'
 | 
			
		||||
              , _mouse               = MouseState
 | 
			
		||||
                        { _isDragging          = False
 | 
			
		||||
@@ -325,8 +327,8 @@ adjustWindow = do
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
                   let hudtexid = state ^. gl.glHud.hudTexture
 | 
			
		||||
                       maptexid = state ^. gl.glMap.renderedMapTexture
 | 
			
		||||
                       smaptexid = state ^. gl.glMap.shadowMapTexture
 | 
			
		||||
                   maptexid <- liftIO $ readTVarIO (state ^. mapTexture)
 | 
			
		||||
                   allocaBytes (fbWidth*fbHeight*4) $ \ptr -> do
 | 
			
		||||
                                                               --default to ugly pink to see if
 | 
			
		||||
                                                               --somethings go wrong.
 | 
			
		||||
 
 | 
			
		||||
@@ -62,7 +62,7 @@ initBuffer varray =
 | 
			
		||||
initMapShader ::
 | 
			
		||||
                Int                                -- ^ initial Tessallation-Factor
 | 
			
		||||
                -> (BufferObject,NumArrayIndices)  -- ^ Buffer with Data and DataDescriptor
 | 
			
		||||
                -> IO GLMapState
 | 
			
		||||
                -> IO (GLMapState, TextureObject)
 | 
			
		||||
initMapShader tessFac (buf, vertDes) = do
 | 
			
		||||
   ! vertexSource <- B.readFile mapVertexShaderFile
 | 
			
		||||
   ! tessControlSource <- B.readFile mapTessControlShaderFile
 | 
			
		||||
@@ -131,7 +131,7 @@ initMapShader tessFac (buf, vertDes) = do
 | 
			
		||||
   testobj <- parseIQM "models/box.iqm"
 | 
			
		||||
 | 
			
		||||
   let
 | 
			
		||||
	objs = [MapObject testobj (L.V3 0 10 0) (MapObjectState ())]
 | 
			
		||||
    objs = [MapObject testobj (L.V3 0 10 0) (MapObjectState ())]
 | 
			
		||||
 | 
			
		||||
   currentProgram $= Nothing
 | 
			
		||||
 | 
			
		||||
@@ -210,11 +210,10 @@ initMapShader tessFac (buf, vertDes) = do
 | 
			
		||||
            , shdrMOTessOuterIndex = UniformLocation 0 --tessLevelOuter'
 | 
			
		||||
            }
 | 
			
		||||
 | 
			
		||||
   return GLMapState
 | 
			
		||||
   return (GLMapState
 | 
			
		||||
        { _mapProgram         = program
 | 
			
		||||
        , _mapShaderData      = sdata
 | 
			
		||||
        , _mapObjectShaderData = smodata
 | 
			
		||||
        , _renderedMapTexture = tex
 | 
			
		||||
        , _stateTessellationFactor = tessFac
 | 
			
		||||
        , _stateMap           = buf
 | 
			
		||||
        , _mapVert            = vertDes
 | 
			
		||||
@@ -224,7 +223,7 @@ initMapShader tessFac (buf, vertDes) = do
 | 
			
		||||
        , _mapObjects         = objs
 | 
			
		||||
        , _objectProgram      = objProgram
 | 
			
		||||
        , _shadowMapProgram   = shadowProgram
 | 
			
		||||
        }
 | 
			
		||||
        }, tex)
 | 
			
		||||
 | 
			
		||||
initHud :: IO GLHud
 | 
			
		||||
initHud = do
 | 
			
		||||
@@ -295,7 +294,7 @@ renderIQM m p@(L.V3 x y z) s@(L.V3 sx sy sz) = do
 | 
			
		||||
 | 
			
		||||
renderObject :: MapObject -> IO ()
 | 
			
		||||
renderObject (MapObject model pos@(L.V3 x y z) _{-state-}) =
 | 
			
		||||
	renderIQM model pos (L.V3 1 1 1)
 | 
			
		||||
    renderIQM model pos (L.V3 1 1 1)
 | 
			
		||||
 | 
			
		||||
drawMap :: Pioneers ()
 | 
			
		||||
drawMap = do
 | 
			
		||||
@@ -444,12 +443,13 @@ render = do
 | 
			
		||||
 | 
			
		||||
        ---- RENDER MAP IN TEXTURE <<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
 | 
			
		||||
        -- COLORMAP
 | 
			
		||||
        textureBinding Texture2D $= Just (state ^. gl.glMap.renderedMapTexture)
 | 
			
		||||
        tex <- liftIO $ readTVarIO (state ^. mapTexture)
 | 
			
		||||
        textureBinding Texture2D $= Just tex
 | 
			
		||||
        framebufferTexture2D
 | 
			
		||||
                Framebuffer
 | 
			
		||||
                (ColorAttachment 0)
 | 
			
		||||
                Texture2D
 | 
			
		||||
                (state ^. gl.glMap.renderedMapTexture)
 | 
			
		||||
                tex
 | 
			
		||||
                0
 | 
			
		||||
 | 
			
		||||
        -- Render to FrameBufferObject
 | 
			
		||||
@@ -501,7 +501,8 @@ render = do
 | 
			
		||||
        uniform (hud ^. hudTexIndex) $= Index1 (0::GLint)
 | 
			
		||||
 | 
			
		||||
        activeTexture  $= TextureUnit 1
 | 
			
		||||
        textureBinding Texture2D $= Just (state ^. gl.glMap.renderedMapTexture)
 | 
			
		||||
        tex <- liftIO $ readTVarIO (state ^. mapTexture)
 | 
			
		||||
        textureBinding Texture2D $= Just tex
 | 
			
		||||
        uniform (hud ^. hudBackIndex) $= Index1 (1::GLint)
 | 
			
		||||
 | 
			
		||||
        bindBuffer ArrayBuffer $= Just (hud ^. hudVBO)
 | 
			
		||||
 
 | 
			
		||||
@@ -11,7 +11,7 @@ import Linear.Matrix (M44)
 | 
			
		||||
import Linear (V3)
 | 
			
		||||
import Control.Monad.RWS.Strict (RWST, liftIO, get)
 | 
			
		||||
import Control.Monad.Writer.Strict
 | 
			
		||||
import Control.Monad (when)
 | 
			
		||||
--import Control.Monad (when)
 | 
			
		||||
import Control.Lens
 | 
			
		||||
import Graphics.Rendering.OpenGL.GL.Texturing.Objects (TextureObject)
 | 
			
		||||
import Render.Types
 | 
			
		||||
@@ -111,7 +111,6 @@ data GLMapState = GLMapState
 | 
			
		||||
    , _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?
 | 
			
		||||
@@ -174,8 +173,8 @@ data GLState = GLState
 | 
			
		||||
 | 
			
		||||
data UIState = UIState
 | 
			
		||||
    { _uiHasChanged        :: !Bool
 | 
			
		||||
    , _uiMap               :: !(Map.HashMap UIId (GUIWidget Pioneers))
 | 
			
		||||
    , _uiObserverEvents    :: !(Map.HashMap EventKey [EventHandler Pioneers])
 | 
			
		||||
    , _uiMap               :: Map.HashMap UIId (GUIWidget Pioneers)
 | 
			
		||||
    , _uiObserverEvents    :: Map.HashMap EventKey [EventHandler Pioneers]
 | 
			
		||||
    , _uiRoots             :: !([UIId])
 | 
			
		||||
    , _uiButtonState       :: !UIButtonState
 | 
			
		||||
    }
 | 
			
		||||
@@ -183,6 +182,7 @@ data UIState = UIState
 | 
			
		||||
data State = State
 | 
			
		||||
    { _window              :: !WindowState
 | 
			
		||||
    , _camera              :: TVar CameraState
 | 
			
		||||
    , _mapTexture          :: TVar TextureObject
 | 
			
		||||
    , _camStack            :: TVar (Map.HashMap UIId (CameraState, TextureObject))
 | 
			
		||||
    , _io                  :: !IOState
 | 
			
		||||
    , _mouse               :: !MouseState
 | 
			
		||||
 
 | 
			
		||||
		Reference in New Issue
	
	Block a user