pioneers/src/Main.hs

354 lines
15 KiB
Haskell
Raw Normal View History

{-# LANGUAGE BangPatterns, DoAndIfThenElse #-}
module Main where
import Graphics.Rendering.OpenGL.GL.Texturing.Specification (texImage2D,TextureTarget2D(Texture2D))
import Graphics.Rendering.OpenGL.GL.PixelRectangles.ColorTable (PixelInternalFormat(..))
import Graphics.Rendering.OpenGL.GL.Texturing.Objects (textureBinding)
import Graphics.Rendering.OpenGL.GL.Texturing.Parameters (TextureFilter(..),textureFilter)
2014-01-20 23:18:07 +01:00
-- Monad-foo and higher functional stuff
import Control.Monad (unless, when, join)
import Control.Arrow ((***))
-- data consistency/conversion
import Control.Concurrent (threadDelay)
import Control.Concurrent.STM (TQueue,
newTQueueIO)
import Control.Monad.RWS.Strict (ask, evalRWST, get, liftIO, modify)
2014-04-15 08:59:53 +02:00
import Data.Functor ((<$>))
import Data.Monoid (mappend)
-- FFI
import Foreign.Marshal.Array (pokeArray)
import Foreign.Marshal.Alloc (allocaBytes)
-- Math
2014-03-05 14:42:26 +01:00
import Control.Lens ((^.), (.~), (%~))
-- GUI
2014-03-05 14:42:26 +01:00
import Graphics.UI.SDL as SDL
-- Render
import qualified Graphics.Rendering.OpenGL.GL as GL
import Graphics.Rendering.OpenGL.Raw.Core31
import Data.Time (getCurrentTime, diffUTCTime)
-- Our modules
2014-04-21 19:46:24 +02:00
import Render.Misc (checkError, createFrustum, curb,
2014-04-05 23:09:57 +02:00
genColorData)
import Render.Render (initRendering,
initMapShader,
initHud, render)
2014-04-21 19:46:24 +02:00
import Render.Types
import UI.Callbacks
import Map.Graphics
import Types
import Importer.IQM.Parser
2014-04-25 21:21:19 +02:00
--import Data.Attoparsec.Char8 (parseTest)
--import qualified Data.ByteString as B
-- import qualified Debug.Trace as D (trace)
--------------------------------------------------------------------------------
2014-04-25 21:21:19 +02:00
testParser :: String -> IO ()
testParser a = putStrLn . show =<< parseIQM a
{-do
f <- B.readFile a
putStrLn "reading in:"
putStrLn $ show f
putStrLn "parsed:"
parseTest parseIQM f-}
--------------------------------------------------------------------------------
2013-12-22 23:29:11 +01:00
main :: IO ()
main =
SDL.withInit [InitVideo, InitAudio, InitEvents, InitTimer] $ --also: InitNoParachute -> faster, without parachute!
2014-04-09 17:45:13 +02:00
SDL.withWindow "Pioneers" (SDL.Position 100 100) (Size 1024 600) [WindowOpengl -- we want openGL
2014-03-26 18:48:59 +01:00
,WindowShown -- window should be visible
,WindowResizable -- and resizable
2014-03-26 18:48:59 +01:00
,WindowInputFocus -- focused (=> active)
,WindowMouseFocus -- Mouse into it
--,WindowInputGrabbed-- never let go of input (KB/Mouse)
] $ \window' -> do
withOpenGL window' $ do
--Create Renderbuffer & Framebuffer
-- We will render to this buffer to copy the result into textures
renderBuffer <- GL.genObjectName
frameBuffer <- GL.genObjectName
GL.bindFramebuffer GL.Framebuffer GL.$= frameBuffer
GL.bindRenderbuffer GL.Renderbuffer GL.$= renderBuffer
(Size fbWidth fbHeight) <- glGetDrawableSize window'
initRendering
--generate map vertices
glMap' <- initMapShader 4 =<< getMapBufferObject
print window'
eventQueue <- newTQueueIO :: IO (TQueue Event)
putStrLn "foo"
now <- getCurrentTime
putStrLn "foo"
--font <- TTF.openFont "fonts/ttf-04B_03B_/04B_03B_.TTF" 10
--TTF.setFontStyle font TTFNormal
--TTF.setFontHinting font TTFHNormal
glHud' <- initHud
let zDistClosest' = 1
zDistFarthest' = zDistClosest' + 50
--TODO: Move near/far/fov to state for runtime-changability & central storage
fov = 90 --field of view
near = 1 --near plane
far = 500 --far plane
ratio = fromIntegral fbWidth / fromIntegral fbHeight
frust = createFrustum fov near far ratio
(guiMap, guiRoots) = createGUI
2014-01-20 23:18:07 +01:00
aks = ArrowKeyState {
_up = False
, _down = False
, _left = False
, _right = False
2014-01-20 23:18:07 +01:00
}
env = Env
{ _eventsChan = eventQueue
, _windowObject = window'
, _zDistClosest = zDistClosest'
, _zDistFarthest = zDistFarthest'
}
state = State
{ _window = WindowState
{ _width = fbWidth
, _height = fbHeight
, _shouldClose = False
}
, _camera = CameraState
{ _xAngle = pi/6
, _yAngle = pi/2
, _zDist = 10
, _frustum = frust
2014-04-21 19:46:24 +02:00
, _camObject = createFlatCam 25 25
}
, _io = IOState
{ _clock = now
, _tessClockFactor = 0
}
, _mouse = MouseState
{ _isDown = False
, _isDragging = False
, _dragStartX = 0
, _dragStartY = 0
, _dragStartXAngle = 0
, _dragStartYAngle = 0
2014-03-05 14:42:26 +01:00
, _mousePosition = Types.Position
{ Types.__x = 5
, Types.__y = 5
}
}
, _keyboard = KeyboardState
{ _arrowsPressed = aks
}
, _gl = GLState
{ _glMap = glMap'
, _glHud = glHud'
, _glRenderbuffer = renderBuffer
, _glFramebuffer = frameBuffer
}
, _game = GameState
{
}
2014-03-24 08:21:30 +01:00
, _ui = UIState
2014-04-05 23:09:57 +02:00
{ _uiHasChanged = True
, _uiMap = guiMap
, _uiRoots = guiRoots
2014-03-24 08:21:30 +01:00
}
}
putStrLn "init done."
2014-04-15 08:59:53 +02:00
uncurry mappend <$> evalRWST (adjustWindow >> run) env state
putStrLn "shutdown complete."
2014-04-04 11:18:42 +02:00
--SDL.glDeleteContext mainGlContext
--SDL.destroyRenderer renderer
--destroyWindow window
-- Main game loop
run :: Pioneers ()
run = do
2014-03-05 14:42:26 +01:00
env <- ask
-- draw Scene
draw
2014-03-05 14:42:26 +01:00
liftIO $ glSwapWindow (env ^. windowObject)
-- getEvents & process
processEvents
-- update State
state <- get
-- change in camera-angle
2014-03-05 14:42:26 +01:00
when (state ^. mouse.isDragging) $ do
let sodx = state ^. mouse.dragStartX
sody = state ^. mouse.dragStartY
sodxa = state ^. mouse.dragStartXAngle
sodya = state ^. mouse.dragStartYAngle
x' = state ^. mouse.mousePosition._x
y' = state ^. mouse.mousePosition._y
2014-03-05 14:42:26 +01:00
myrot = (x' - sodx) / 2
mxrot = (y' - sody) / 2
newXAngle = curb (pi/12) (0.45*pi) newXAngle'
newXAngle' = sodxa + mxrot/100
newYAngle
| newYAngle' > pi = newYAngle' - 2 * pi
| newYAngle' < (-pi) = newYAngle' + 2 * pi
| otherwise = newYAngle'
newYAngle' = sodya + myrot/100
2014-03-05 14:42:26 +01:00
modify $ ((camera.xAngle) .~ newXAngle)
. ((camera.yAngle) .~ newYAngle)
-- get cursor-keys - if pressed
--TODO: Add sin/cos from stateYAngle
(kxrot, kyrot) <- fmap (join (***) fromIntegral) getArrowMovement
let
2014-03-05 14:42:26 +01:00
multc = cos $ state ^. camera.yAngle
mults = sin $ state ^. camera.yAngle
modx x' = x' - 0.2 * kxrot * multc
- 0.2 * kyrot * mults
mody y' = y' + 0.2 * kxrot * mults
2014-03-05 14:42:26 +01:00
- 0.2 * kyrot * multc
2014-04-21 19:46:24 +02:00
modify $ camera.camObject %~ (\c -> moveBy c (\(x,y) -> (modx x,mody y)))
2014-03-05 14:42:26 +01:00
{-
--modify the state with all that happened in mt time.
mt <- liftIO GLFW.getTime
modify $ \s -> s
{
}
-}
2014-03-05 14:42:26 +01:00
2014-05-05 08:11:33 +02:00
(mt,tc,sleepAmount) <- liftIO $ do
let double = fromRational.toRational :: (Real a) => a -> Double
targetFramerate = 40.0
targetFrametime = 1.0/targetFramerate
targetFrametimeμs = targetFrametime * 1000000.0
now <- getCurrentTime
let diff = diffUTCTime now (state ^. io.clock) -- get time-diffs
title = unwords ["Pioneers @ ",show ((round . double $ 1.0/diff)::Int),"fps"]
2014-03-05 14:42:26 +01:00
setWindowTitle (env ^. windowObject) title
2014-05-05 08:11:33 +02:00
let sleepAmount = floor ((targetFrametime - double diff)*1000000) :: Int -- get time until next frame in microseconds
clockFactor = (state ^. io.tessClockFactor)
2014-05-05 08:11:33 +02:00
tessChange
| (clockFactor > (2*targetFrametimeμs)) && (state ^. gl.glMap.stateTessellationFactor < 5) = ((+)1 :: Int -> Int)
2014-05-05 08:11:33 +02:00
-- > factor < 5 & 10% of frame idle -> increase graphics
| sleepAmount < 0 && (state ^. gl.glMap.stateTessellationFactor > 1) = (flip (-) 1 :: Int -> Int)
-- frame used up completely -> decrease
| otherwise = ((+)0 :: Int -> Int) -- 0ms > x > 10% -> keep settings
when (sleepAmount > 0) $ threadDelay sleepAmount
return (now,tessChange,sleepAmount)
-- set state with new clock-time
2014-05-05 08:11:33 +02:00
modify $ (io.clock .~ mt)
. (gl.glMap.stateTessellationFactor %~ tc)
. (io.tessClockFactor %~ (((+) (fromIntegral sleepAmount)).((*) 0.99)))
-- liftIO $ putStrLn $ concat $ ["TessFactor at: ",show (state ^. gl.glMap.stateTessellationFactor), " - slept for ",show sleepAmount, "μs."]
shouldClose' <- return $ state ^. window.shouldClose
unless shouldClose' run
draw :: Pioneers ()
draw = do
state <- get
when (state ^. ui . uiHasChanged) prepareGUI
render
2014-01-20 23:18:07 +01:00
getArrowMovement :: Pioneers (Int, Int)
getArrowMovement = do
state <- get
aks <- return $ state ^. (keyboard.arrowsPressed)
let
2014-01-20 23:18:07 +01:00
horz = left' + right'
vert = up'+down'
2014-03-05 14:42:26 +01:00
left' = if aks ^. left then -1 else 0
right' = if aks ^. right then 1 else 0
up' = if aks ^. up then -1 else 0
down' = if aks ^. down then 1 else 0
2014-01-20 23:18:07 +01:00
return (horz,vert)
adjustWindow :: Pioneers ()
adjustWindow = do
state <- get
2014-03-05 14:42:26 +01:00
let fbWidth = state ^. window.width
fbHeight = state ^. window.height
fov = 90 --field of view
near = 1 --near plane
far = 100 --far plane
ratio = fromIntegral fbWidth / fromIntegral fbHeight
frust = createFrustum fov near far ratio
liftIO $ glViewport 0 0 (fromIntegral fbWidth) (fromIntegral fbHeight)
2014-03-05 14:42:26 +01:00
modify $ camera.frustum .~ frust
rb <- liftIO $ do
-- bind ints to CInt for lateron.
let fbCWidth = (fromInteger.toInteger) fbWidth
fbCHeight = (fromInteger.toInteger) fbHeight
-- free old renderbuffer & create new (reuse is NOT advised!)
GL.deleteObjectName (state ^. gl.glRenderbuffer)
renderBuffer <- GL.genObjectName
GL.bindRenderbuffer GL.Renderbuffer GL.$= renderBuffer
GL.renderbufferStorage
GL.Renderbuffer -- use the only available renderbuffer
-- - must be this constant.
GL.DepthComponent' -- 32-bit float-rgba-color
(GL.RenderbufferSize fbCWidth fbCHeight) -- size of buffer
let hudtexid = state ^. gl.glHud.hudTexture
maptexid = state ^. gl.glMap.renderedMapTexture
allocaBytes (fbWidth*fbHeight*4) $ \ptr -> do
2014-04-05 22:02:48 +02:00
--default to ugly pink to see if
--somethings go wrong.
2014-04-05 23:09:57 +02:00
let imData = genColorData (fbWidth*fbHeight) [255,0,255,0]
--putStrLn $ show imData
pokeArray ptr imData
-- HUD
textureBinding Texture2D GL.$= Just hudtexid
textureFilter Texture2D GL.$= ((Linear', Nothing), Linear')
texImage2D Texture2D GL.NoProxy 0 RGBA8 (GL.TextureSize2D fbCWidth fbCHeight) 0
(GL.PixelData GL.RGBA GL.UnsignedByte ptr)
-- MAP
textureBinding Texture2D GL.$= Just maptexid
textureFilter Texture2D GL.$= ((Linear', Nothing), Linear')
texImage2D Texture2D GL.NoProxy 0 RGBA8 (GL.TextureSize2D fbCWidth fbCHeight) 0
(GL.PixelData GL.RGBA GL.UnsignedByte ptr)
checkError "setting up HUD-Tex"
return renderBuffer
modify $ gl.glRenderbuffer .~ rb
2014-04-05 23:09:57 +02:00
modify $ ui.uiHasChanged .~ True
processEvents :: Pioneers ()
processEvents = do
me <- liftIO pollEvent
case me of
Just e -> do
processEvent e
processEvents
Nothing -> return ()
processEvent :: Event -> Pioneers ()
processEvent e = do
eventCallback e
-- env <- ask
case SDL.eventData e of
SDL.Window _ winEvent -> -- windowID event
case winEvent of
SDL.Closing ->
2014-03-05 14:42:26 +01:00
modify $ window.shouldClose .~ True
SDL.Resized {windowResizedTo=size} -> do
modify $ (window . width .~ SDL.sizeWidth size)
. (window . height .~ SDL.sizeHeight size)
adjustWindow
SDL.SizeChanged ->
adjustWindow
_ -> return ()
_ -> return ()