pioneers/src/Types.hs

143 lines
4.5 KiB
Haskell
Raw Normal View History

{-# LANGUAGE TemplateHaskell #-}
2014-02-05 20:06:19 +00:00
module Types where
import Control.Concurrent.STM (TQueue)
import qualified Graphics.Rendering.OpenGL.GL as GL
2014-03-24 22:26:02 +00:00
import Graphics.UI.SDL as SDL (Event, Window, Texture, Renderer)
2014-02-05 20:06:19 +00:00
import Foreign.C (CFloat)
import Data.Time (UTCTime)
import Linear.Matrix (M44)
import Control.Monad.RWS.Strict (RWST)
import Control.Lens
import Graphics.Rendering.OpenGL.GL.Texturing.Objects (TextureObject)
2014-02-05 20:06:19 +00:00
--Static Read-Only-State
data Env = Env
{ _eventsChan :: TQueue Event
, _windowObject :: !Window
, _zDistClosest :: !Double
, _zDistFarthest :: !Double
--, envGLContext :: !GLContext
--, envFont :: TTF.TTFFont
2014-04-04 09:18:42 +00:00
-- , _renderer :: !Renderer
}
--Mutable State
data Position = Position
{ __x :: !Double
, __y :: !Double
}
data WindowState = WindowState
{ _width :: !Int
, _height :: !Int
, _shouldClose :: !Bool
}
data CameraState = CameraState
{ _xAngle :: !Double
, _yAngle :: !Double
, _zDist :: !Double
, _frustum :: !(M44 CFloat)
, _camPosition :: !Position --TODO: Get rid of cam-prefix
}
data IOState = IOState
{ _clock :: !UTCTime
}
data GameState = GameState
{
}
2014-02-05 20:06:19 +00:00
data MouseState = MouseState
{ _isDown :: !Bool
, _isDragging :: !Bool
, _dragStartX :: !Double
, _dragStartY :: !Double
, _dragStartXAngle :: !Double
, _dragStartYAngle :: !Double
, _mousePosition :: !Position --TODO: Get rid of mouse-prefix
}
2014-02-05 20:06:19 +00:00
data ArrowKeyState = ArrowKeyState {
_up :: !Bool
,_down :: !Bool
,_left :: !Bool
,_right :: !Bool
2014-02-05 20:06:19 +00:00
}
data KeyboardState = KeyboardState
{ _arrowsPressed :: !ArrowKeyState
}
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
, _stateTessellationFactor :: !Int
, _stateMap :: !GL.BufferObject
, _mapVert :: !GL.NumArrayIndices
2014-03-24 07:21:30 +00:00
, _mapProgram :: !GL.Program
, _mapTexture :: !TextureObject
}
data GLHud = GLHud
{ _hudTexture :: !TextureObject -- ^ HUD-Texture itself
, _hudTexIndex :: !GL.UniformLocation -- ^ Position of Overlay-Texture in Shader
, _hudBackIndex :: !GL.UniformLocation -- ^ Position of Background-Texture in Shader
, _hudVertexIndex :: !GL.AttribLocation -- ^ Position of Vertices in Shader
, _hudVert :: !GL.NumArrayIndices -- ^ Number of Vertices to draw
, _hudVBO :: !GL.BufferObject -- ^ Vertex-Buffer-Object
, _hudEBO :: !GL.BufferObject -- ^ Element-Buffer-Object
, _hudProgram :: !GL.Program -- ^ Program for rendering HUD
}
data GLState = GLState
{ _glMap :: !GLMapState
, _glHud :: !GLHud
, _glRenderbuffer :: !GL.RenderbufferObject
, _glFramebuffer :: !GL.FramebufferObject
2014-02-05 20:06:19 +00:00
}
2014-03-24 07:21:30 +00:00
data UIState = UIState
2014-04-05 21:09:57 +00:00
{ _uiHasChanged :: !Bool
2014-03-24 07:21:30 +00:00
}
2014-02-05 20:06:19 +00:00
data State = State
{ _window :: !WindowState
, _camera :: !CameraState
, _io :: !IOState
, _mouse :: !MouseState
, _keyboard :: !KeyboardState
, _gl :: !GLState
, _game :: !GameState
2014-03-24 07:21:30 +00:00
, _ui :: !UIState
2014-02-05 20:06:19 +00:00
}
2014-03-05 13:42:26 +00:00
$(makeLenses ''State)
$(makeLenses ''GLState)
$(makeLenses ''GLMapState)
$(makeLenses ''GLHud)
2014-03-05 13:42:26 +00:00
$(makeLenses ''KeyboardState)
$(makeLenses ''ArrowKeyState)
$(makeLenses ''MouseState)
$(makeLenses ''GameState)
$(makeLenses ''IOState)
$(makeLenses ''CameraState)
$(makeLenses ''WindowState)
$(makeLenses ''Position)
$(makeLenses ''Env)
2014-03-24 07:21:30 +00:00
$(makeLenses ''UIState)
2014-03-05 13:42:26 +00:00
type Pioneers = RWST Env () State IO