cameraaaaaaa -.-

This commit is contained in:
Nicole Dresselhaus 2014-01-04 23:47:07 +01:00
parent 6cc9177082
commit df9b37429c
3 changed files with 50 additions and 26 deletions

View File

@ -16,6 +16,7 @@ import Foreign (Ptr, castPtr, nullPtr, sizeOf, with)
import Foreign.C (CFloat) import Foreign.C (CFloat)
import Linear as L import Linear as L
import Linear ((!*!)) import Linear ((!*!))
import qualified Debug.Trace as T (trace)
import qualified Graphics.Rendering.OpenGL.GL as GL import qualified Graphics.Rendering.OpenGL.GL as GL
import qualified Graphics.Rendering.OpenGL.Raw as GL import qualified Graphics.Rendering.OpenGL.Raw as GL
@ -23,7 +24,7 @@ import qualified Graphics.UI.GLFW as GLFW
import qualified Data.Vector.Storable as V import qualified Data.Vector.Storable as V
import Map.Map import Map.Map
import Render.Render (initShader) import Render.Render (initShader, initRendering)
import Render.Misc (up, lookAtUniformMatrix4fv, createFrustum, checkError, lookAt) import Render.Misc (up, lookAtUniformMatrix4fv, createFrustum, checkError, lookAt)
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
@ -113,6 +114,7 @@ main = do
(fbWidth, fbHeight) <- GLFW.getFramebufferSize win (fbWidth, fbHeight) <- GLFW.getFramebufferSize win
initRendering
--generate map vertices --generate map vertices
(mapBuffer, vert) <- getMapBufferObject (mapBuffer, vert) <- getMapBufferObject
(ci, ni, vi, pi, mi) <- initShader (ci, ni, vi, pi, mi) <- initShader
@ -244,14 +246,14 @@ run = do
(x, y) <- liftIO $ GLFW.getCursorPos win (x, y) <- liftIO $ GLFW.getCursorPos win
let myrot = (x - sodx) / 2 let myrot = (x - sodx) / 2
mxrot = (y - sody) / 2 mxrot = (y - sody) / 2
newXAngle = if newXAngle' > pi then pi else newXAngle = if newXAngle' > 2*pi then 2*pi else
if newXAngle' < 0 then 0 else if newXAngle' < -2*pi then -2*pi else
newXAngle' newXAngle'
newXAngle' = sodxa - mxrot/100 newXAngle' = sodxa + mxrot/100
newYAngle = if newYAngle' > 2*pi then newYAngle'-2*pi else newYAngle = if newYAngle' > 2*pi then newYAngle'-2*pi else
if newYAngle' < 0 then newYAngle'+2*pi else if newYAngle' < 0 then newYAngle'+2*pi else
newYAngle' newYAngle'
newYAngle' = sodya - myrot/100 newYAngle' = sodya + myrot/100
put $ state put $ state
{ stateXAngle = newXAngle { stateXAngle = newXAngle
, stateYAngle = newYAngle , stateYAngle = newYAngle
@ -412,20 +414,35 @@ draw = do
f = 1000 f = 1000
n = 1 n = 1
let perspective = V4 (V4 s 0 0 0) let perspective = V4 (V4 (2*s) 0 0 0)
(V4 0 s 0 0) (V4 0 (2*s) 0 0)
(V4 0 0 (-((f+n)/(f-n))) (-((2*f*n)/(f-n)))) (V4 0 0 (-((f+n)/(f-n))) (-((2*f*n)/(f-n))))
(V4 0 0 (-1) 0) (V4 0 0 (-1) 0)
!*!
V4 (V4 1 0 0 0)
(V4 0 0 1 0)
(V4 0 1 0 0)
(V4 0 0 0 1)
with (distribute $ perspective) $ \ptr -> with (distribute $ perspective) $ \ptr ->
GL.glUniformMatrix4fv proj 1 0 (castPtr (ptr :: Ptr (M44 CFloat))) GL.glUniformMatrix4fv proj 1 0 (castPtr (ptr :: Ptr (M44 CFloat)))
{-let cam = out !*! roty !*! rotx !*! center
out = V4 (V4 1 0 0 0)
(V4 0 1 0 0)
(V4 0 0 1 (-10))
(V4 0 0 0 1)
rotx = V4 (V4 1 0 0 0)
(V4 0 (cos xa) (-sin xa) 0)
(V4 0 (sin xa) (cos xa) 0)
(V4 0 0 0 1)
roty = V4 (V4 (cos ya) 0 (-sin ya) 0)
(V4 0 1 0 0)
(V4 (sin ya) 0 (cos ya) 0)
(V4 0 0 0 1)
center = V4 (V4 1 0 0 (-x))
(V4 1 1 0 0 )
(V4 0 0 1 (-z))
(V4 0 0 0 1 )
(x,z) = (5,5)-}
--V.unsafeWith perspective $ \ptr -> GL.glUniformMatrix4fv proj 1 0 ptr --V.unsafeWith perspective $ \ptr -> GL.glUniformMatrix4fv proj 1 0 ptr
let cam = lookAt (V3 5 0 5) (crot' !* cdist') up let cam = lookAt (cpos ^+^ at') at' up
--cdist !*! crot !*! camat --cdist !*! crot !*! camat
cpos = -10 *^ normalize (V3 (sin ya) ((cos ya) * (sin xa)) ((cos ya) * (cos xa)))
camat = (eye4 & translation .~ V3 (-0.5) (0) (-0.5)) :: M44 CFloat camat = (eye4 & translation .~ V3 (-0.5) (0) (-0.5)) :: M44 CFloat
cdist = (eye4 & translation .~ V3 (0) (0) (-10)) :: M44 CFloat cdist = (eye4 & translation .~ V3 (0) (0) (-10)) :: M44 CFloat
crot = (m33_to_m44 $ crot = (m33_to_m44 $
@ -433,17 +450,20 @@ draw = do
axisAngle (V3 1 0 0) (xa::CFloat)) axisAngle (V3 1 0 0) (xa::CFloat))
!*! !*!
(fromQuaternion $ (fromQuaternion $
axisAngle (V3 0 1 0) (ya::CFloat)) axisAngle (V3 0 1 0) ((ya::CFloat) - pi/2))
) :: M44 CFloat ) :: M44 CFloat
at' = V3 5 0 5
cdist' = V3 (0) (0) (-10) cdist' = V3 (0) (0) (-10)
crot' = ( crot' = (
(fromQuaternion $ (fromQuaternion $
axisAngle (V3 1 0 0) (xa::CFloat)) axisAngle (V3 0 1 0) (ya::CFloat))
!*! !*!
(fromQuaternion $ (fromQuaternion $
axisAngle (V3 0 1 0) (ya::CFloat)) axisAngle (V3 1 0 0) (xa::CFloat))
) :: M33 CFloat ) :: M33 CFloat
--V.unsafeWith model $ \ptr -> GL.glUniformMatrix4fv mmat 1 0 ptr --V.unsafeWith model $ \ptr -> GL.glUniformMatrix4fv mmat 1 0 ptr -}
putStrLn $ unwords $ "Cam direction:":map show [cpos]
putStrLn $ unwords $ "Cam at:":map show [cpos ^+^ at']
with (distribute $ cam) $ \ptr -> with (distribute $ cam) $ \ptr ->
GL.glUniformMatrix4fv mmat 1 0 (castPtr (ptr :: Ptr (M44 CFloat))) GL.glUniformMatrix4fv mmat 1 0 (castPtr (ptr :: Ptr (M44 CFloat)))
GL.bindBuffer GL.ArrayBuffer GL.$= Just map' GL.bindBuffer GL.ArrayBuffer GL.$= Just map'

View File

@ -128,12 +128,13 @@ infixl 5 ><
_ >< _ = error "non-conformat matrix-multiplication" _ >< _ = error "non-conformat matrix-multiplication"
-- from vmath.h
lookAt :: V3 CFloat -> V3 CFloat -> V3 CFloat -> M44 CFloat lookAt :: V3 CFloat -> V3 CFloat -> V3 CFloat -> M44 CFloat
lookAt at eye@(V3 ex ey ez) up = lookAt eye@(V3 ex ey ez) center up =
V4 V4
(V4 xx yx zx 0) (V4 xx yx (-zx) 0)
(V4 xy yy zy 0) (V4 xy yy (-zy) 0)
(V4 xz yz zz 0) (V4 xz yz (-zz) 0)
(V4 0 0 0 1) (V4 0 0 0 1)
!*! !*!
V4 V4
@ -142,9 +143,9 @@ lookAt at eye@(V3 ex ey ez) up =
(V4 0 0 1 (-ez)) (V4 0 0 1 (-ez))
(V4 0 0 0 1) (V4 0 0 0 1)
where where
z@(V3 zx zy zz) = normalize (eye ^-^ at) z@(V3 zx zy zz) = normalize (center ^-^ eye)
x@(V3 xx xy xz) = normalize (cross up z) x@(V3 xx xy xz) = cross z (normalize up)
y@(V3 yx yy yz) = cross z x y@(V3 yx yy yz) = cross x z
-- generates 4x4-Projection-Matrix -- generates 4x4-Projection-Matrix
lookAt_ :: (Double, Double, Double) -> (Double, Double, Double) -> (Double, Double, Double) -> [GLfloat] lookAt_ :: (Double, Double, Double) -> (Double, Double, Double) -> (Double, Double, Double) -> [GLfloat]

View File

@ -7,12 +7,13 @@ import Foreign.Storable (sizeOf)
import Graphics.Rendering.OpenGL.GL.BufferObjects import Graphics.Rendering.OpenGL.GL.BufferObjects
import Graphics.Rendering.OpenGL.GL.Framebuffer (clearColor) import Graphics.Rendering.OpenGL.GL.Framebuffer (clearColor)
import Graphics.Rendering.OpenGL.GL.ObjectName import Graphics.Rendering.OpenGL.GL.ObjectName
import Graphics.Rendering.OpenGL.GL.PerFragment
import Graphics.Rendering.OpenGL.GL.Shaders import Graphics.Rendering.OpenGL.GL.Shaders
import Graphics.Rendering.OpenGL.GL.StateVar import Graphics.Rendering.OpenGL.GL.StateVar
import Graphics.Rendering.OpenGL.GL.VertexArrays (Capability (..), import Graphics.Rendering.OpenGL.GL.VertexArrays (Capability (..),
vertexAttribArray) vertexAttribArray)
import Graphics.Rendering.OpenGL.GL.VertexSpec import Graphics.Rendering.OpenGL.GL.VertexSpec
import Graphics.Rendering.OpenGL.Raw.Core31.Types (GLfloat) import Graphics.Rendering.OpenGL.Raw.Core31
import Render.Misc import Render.Misc
vertexShaderFile :: String vertexShaderFile :: String
@ -75,4 +76,6 @@ initShader = do
initRendering :: IO () initRendering :: IO ()
initRendering = do initRendering = do
clearColor $= Color4 0 0 0 0 clearColor $= Color4 0 0 0 0
depthFunc $= Just Less
glCullFace gl_BACK
checkError "initRendering" checkError "initRendering"