release v0.2.0
This commit is contained in:
@@ -1,9 +1,9 @@
|
||||
{-# LANGUAGE DisambiguateRecordFields, NamedFieldPuns, OverloadedRecordDot #-}
|
||||
{- |
|
||||
- Module : Game.Internal
|
||||
- Description : 'hidden' functions
|
||||
- Copyright : Andromeda 2025
|
||||
- License : WTFPL
|
||||
- Description : internal functions
|
||||
- Copyright : 2025 Andromeda
|
||||
- License : BSD 3-clause
|
||||
- Maintainer : Matrix @Andromeda:tchncs.de
|
||||
- Stability : Experimental
|
||||
-}
|
||||
@@ -25,10 +25,8 @@ import Game.Internal.LoadShaders
|
||||
import Game.Internal.Types
|
||||
|
||||
import Control.Concurrent (threadDelay)
|
||||
import Control.Lens ((^.), (+~), (&), (%~))
|
||||
import Control.Monad (when)
|
||||
import Data.Fixed (mod')
|
||||
import Data.IORef (atomicModifyIORef', IORef, modifyIORef', newIORef, readIORef, writeIORef)
|
||||
import Data.IORef (IORef, modifyIORef', readIORef)
|
||||
import Data.List (delete)
|
||||
import Foreign.Marshal.Array (withArray)
|
||||
import Foreign.Ptr (nullPtr, plusPtr)
|
||||
@@ -39,20 +37,15 @@ import qualified Graphics.UI.GLFW as GLFW
|
||||
import qualified Graphics.Rendering.OpenGL as GL
|
||||
import Graphics.Rendering.OpenGL as GL (($=))
|
||||
|
||||
import qualified Linear as L
|
||||
import Linear ( V3(..)
|
||||
, _x
|
||||
, _y
|
||||
, _z
|
||||
)
|
||||
import Linear (V3(..))
|
||||
|
||||
--------------------------------------------------------------------------------
|
||||
-- Shader creation and object initialisation
|
||||
--------------------------------------------------------------------------------
|
||||
|
||||
-- | loads models, shaders
|
||||
initResources :: GLFW.Window -> [V3 GL.GLfloat] -> IO ([Object], GL.Program)
|
||||
initResources window array = do
|
||||
initResources :: [V3 GL.GLfloat] -> IO ([Object], GL.Program)
|
||||
initResources array = do
|
||||
-- create objects
|
||||
testObject0 <- createObject (map (+(V3 (-1) (-1) (-1))) array) 3 GL.TriangleStrip
|
||||
testObject1 <- createObject (map (+(V3 (1) (1) (1))) array) 3 GL.TriangleStrip
|
||||
@@ -151,7 +144,7 @@ createObject array numComponents primitiveMode = do
|
||||
GL.bindVertexArrayObject $= Just vao
|
||||
|
||||
-- vbo for vertices
|
||||
createVBO array numComponents $ GL.AttribLocation 0
|
||||
_ <- createVBO array numComponents $ GL.AttribLocation 0
|
||||
|
||||
return
|
||||
(Object
|
||||
@@ -187,9 +180,9 @@ loop window dt update view modelRef = do
|
||||
-- end frame timer, wait the difference between expected and actual
|
||||
Just frameEnd <- GLFW.getTime
|
||||
let
|
||||
dt = double2Float $ frameEnd - frameStart
|
||||
drawTime = double2Float $ frameEnd - frameStart
|
||||
target = 1 / 60 :: Float
|
||||
when (dt < target) $ threadDelay $ floor $ (target - dt) * 1000000
|
||||
when (drawTime < target) $ threadDelay $ floor $ (target - drawTime) * 1000000
|
||||
Just frameEnd' <- GLFW.getTime
|
||||
let
|
||||
dt' = double2Float $ frameEnd' - frameStart
|
||||
@@ -254,9 +247,9 @@ resizeWindow _ _ _ = return ()
|
||||
keyPressed :: Maybe (IORef Model) -> GLFW.KeyCallback
|
||||
keyPressed _ window GLFW.Key'Escape _ GLFW.KeyState'Pressed _ =
|
||||
shutdownWindow window
|
||||
keyPressed (Just modelRef) window key _ GLFW.KeyState'Pressed _ =
|
||||
keyPressed (Just modelRef) _ key _ GLFW.KeyState'Pressed _ =
|
||||
modifyIORef' modelRef $ updateKeyPressed key
|
||||
keyPressed (Just modelRef) window key _ GLFW.KeyState'Released _ =
|
||||
keyPressed (Just modelRef) _ key _ GLFW.KeyState'Released _ =
|
||||
modifyIORef' modelRef $ updateKeyReleased key
|
||||
keyPressed _ _ _ _ _ _ = return ()
|
||||
|
||||
|
||||
Reference in New Issue
Block a user