2014-02-23 12:32:20 +00:00
|
|
|
{-# 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-02-23 12:32:20 +00:00
|
|
|
import Graphics.UI.SDL as SDL (Event, Window)
|
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)
|
2014-02-23 12:32:20 +00:00
|
|
|
import Control.Lens
|
2014-02-05 20:06:19 +00:00
|
|
|
|
|
|
|
|
2014-02-23 12:32:20 +00:00
|
|
|
--Static Read-Only-State
|
|
|
|
data Env = Env
|
|
|
|
{ _eventsChan :: TQueue Event
|
|
|
|
, _windowObject :: !Window
|
|
|
|
, _zDistClosest :: !Double
|
|
|
|
, _zDistFarthest :: !Double
|
|
|
|
--, envGLContext :: !GLContext
|
|
|
|
--, envFont :: TTF.TTFFont
|
|
|
|
}
|
|
|
|
|
|
|
|
--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
|
|
|
|
2014-02-23 12:32:20 +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 {
|
2014-02-23 12:32:20 +00:00
|
|
|
_up :: !Bool
|
|
|
|
,_down :: !Bool
|
|
|
|
,_left :: !Bool
|
|
|
|
,_right :: !Bool
|
2014-02-05 20:06:19 +00:00
|
|
|
}
|
|
|
|
|
2014-02-23 12:32:20 +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
|
|
|
|
}
|
|
|
|
|
|
|
|
data GLState = GLState
|
|
|
|
{ _glMap :: !GLMapState
|
2014-02-05 20:06:19 +00:00
|
|
|
}
|
|
|
|
|
|
|
|
data State = State
|
2014-02-23 12:32:20 +00:00
|
|
|
{ _window :: !WindowState
|
|
|
|
, _camera :: !CameraState
|
|
|
|
, _io :: !IOState
|
|
|
|
, _mouse :: !MouseState
|
|
|
|
, _keyboard :: !KeyboardState
|
|
|
|
, _gl :: !GLState
|
|
|
|
, _game :: !GameState
|
2014-02-05 20:06:19 +00:00
|
|
|
}
|
|
|
|
|
2014-03-05 13:42:26 +00:00
|
|
|
$(makeLenses ''State)
|
|
|
|
$(makeLenses ''GLState)
|
|
|
|
$(makeLenses ''GLMapState)
|
|
|
|
$(makeLenses ''KeyboardState)
|
|
|
|
$(makeLenses ''ArrowKeyState)
|
|
|
|
$(makeLenses ''MouseState)
|
|
|
|
$(makeLenses ''GameState)
|
|
|
|
$(makeLenses ''IOState)
|
|
|
|
$(makeLenses ''CameraState)
|
|
|
|
$(makeLenses ''WindowState)
|
|
|
|
$(makeLenses ''Position)
|
|
|
|
$(makeLenses ''Env)
|
|
|
|
|
2014-02-23 12:32:20 +00:00
|
|
|
|
2014-03-05 14:09:05 +00:00
|
|
|
type Pioneers = RWST Env () State IO
|