objects now use their position and scale.
- objects use their position and scale - cube hacky nailed down at camera-pos. - started working on Icons
This commit is contained in:
parent
28e5f47596
commit
24e05db27d
@ -6,7 +6,8 @@ layout(location=2) in vec2 TexCoord;
|
||||
uniform mat4 ProjectionMatrix;
|
||||
uniform mat4 ViewMatrix;
|
||||
uniform mat3 NormalMatrix;
|
||||
uniform vec3 PositionOffset = vec3(5,2,5);
|
||||
uniform vec3 PositionOffset = vec3(5.0,2.0,5.0);
|
||||
uniform vec3 Scale = vec3(1.0,1.0,1.0);
|
||||
uniform float TessLevelInner = 1.0; // controlled by keyboard buttons
|
||||
uniform float TessLevelOuter = 1.0; // controlled by keyboard buttons
|
||||
|
||||
@ -16,6 +17,7 @@ out vec3 vNormal;
|
||||
void main () {
|
||||
vPosition = Position;
|
||||
//gl_Position = vec4(Position,1);
|
||||
gl_Position = ProjectionMatrix * ViewMatrix * vec4(PositionOffset + Position, 1);
|
||||
// component-wise
|
||||
gl_Position = ProjectionMatrix * ViewMatrix * vec4(PositionOffset + (Scale * Position), 1);
|
||||
vNormal = Normal;
|
||||
}
|
||||
|
40
src/Icons/GUIQuad.hs
Normal file
40
src/Icons/GUIQuad.hs
Normal file
@ -0,0 +1,40 @@
|
||||
module Icons.GUIQuad (GUIQuad(..), Icon(..), marshalIcon) where
|
||||
|
||||
import Data.Word (Word8)
|
||||
|
||||
type Coord = (Float, Float)
|
||||
type ZIndex = Float
|
||||
|
||||
data GUIQuad = GUIQuad Coord Coord ZIndex Icon
|
||||
|
||||
data Icon =
|
||||
Woodcutter
|
||||
| Stonemason
|
||||
--
|
||||
| CloseButton
|
||||
| NextButton
|
||||
| PreviousButton
|
||||
|
||||
numIcons :: Int
|
||||
numIcons = 32
|
||||
|
||||
sizeIcon :: Float
|
||||
sizeIcon = 1.0/(fromIntegral numIcons)
|
||||
|
||||
iconToTex :: Icon -> Coord
|
||||
iconToTex i =
|
||||
(x,y)
|
||||
where
|
||||
x = (fromIntegral (num `mod` numIcons)) * sizeIcon
|
||||
y = (fromIntegral (num `div` numIcons)) * sizeIcon
|
||||
num = fromIntegral.marshalIcon $ i
|
||||
|
||||
|
||||
marshalIcon :: Icon -> Word8
|
||||
marshalIcon a = case a of
|
||||
Woodcutter -> 0
|
||||
Stonemason -> 1
|
||||
--
|
||||
CloseButton -> 32
|
||||
NextButton -> 33
|
||||
PreviousButton -> 34
|
@ -9,9 +9,9 @@ import Graphics.Rendering.OpenGL.Raw.Core31
|
||||
import Graphics.Rendering.OpenGL.Raw.ARB.TessellationShader
|
||||
import Graphics.GLUtil.BufferObjects
|
||||
import qualified Linear as L
|
||||
import Control.Lens ((^.))
|
||||
import Control.Lens ((^.),(%~))
|
||||
import Control.Monad.RWS.Strict (liftIO)
|
||||
import qualified Control.Monad.RWS.Strict as RWS (get)
|
||||
import qualified Control.Monad.RWS.Strict as RWS (get,modify)
|
||||
import Control.Concurrent.STM (readTVarIO)
|
||||
import Data.Distributive (distribute, collect)
|
||||
-- FFI
|
||||
@ -166,6 +166,12 @@ initMapShader tessFac (buf, vertDes) = do
|
||||
normalMatrixIndex' <- get (uniformLocation objProgram "NormalMatrix")
|
||||
checkError "normalMat"
|
||||
|
||||
positionOffsetIndex' <- get (uniformLocation objProgram "PositionOffset")
|
||||
checkError "PositionOffset"
|
||||
|
||||
scaleIndex' <- get (uniformLocation objProgram "Scale")
|
||||
checkError "Scale"
|
||||
|
||||
--tessLevelInner' <- get (uniformLocation objProgram "TessLevelInner")
|
||||
--checkError "TessLevelInner"
|
||||
|
||||
@ -180,9 +186,12 @@ initMapShader tessFac (buf, vertDes) = do
|
||||
uni' <- get (activeUniforms objProgram)
|
||||
putStrLn $ unlines $ "Model-Uniforms: ":map show uni'
|
||||
putStrLn $ unlines $ ["Model-Indices: ", show (texIndex', normalIndex', vertexIndex')]
|
||||
|
||||
|
||||
testobj <- parseIQM "models/holzfaellerHaus1.iqm"
|
||||
let objs = [MapObject testobj (L.V3 0 10 0) (MapObjectState ())]
|
||||
cube <- parseIQM "models/box.iqm"
|
||||
let objs = [ MapObject testobj (L.V3 20 3 20) (MapObjectState ())
|
||||
, MapObject cube (L.V3 25 5 25) (MapObjectState ())
|
||||
]
|
||||
|
||||
currentProgram $= Nothing
|
||||
|
||||
@ -200,31 +209,33 @@ initMapShader tessFac (buf, vertDes) = do
|
||||
}
|
||||
|
||||
let smodata = MapObjectShaderData
|
||||
{ shdrMOVertexIndex = vertexIndex'
|
||||
, shdrMOVertexOffsetIndex = vertexOffsetIndex'
|
||||
, shdrMONormalIndex = normalIndex'
|
||||
, shdrMOTexIndex = texIndex'
|
||||
, shdrMOProjMatIndex = projectionMatrixIndex'
|
||||
, shdrMOViewMatIndex = viewMatrixIndex'
|
||||
, shdrMOModelMatIndex = modelMatrixIndex'
|
||||
, shdrMONormalMatIndex = normalMatrixIndex'
|
||||
, shdrMOTessInnerIndex = UniformLocation 0 --tessLevelInner'
|
||||
, shdrMOTessOuterIndex = UniformLocation 0 --tessLevelOuter'
|
||||
{ shdrMOVertexIndex = vertexIndex'
|
||||
, shdrMOVertexOffsetIndex = vertexOffsetIndex'
|
||||
, shdrMONormalIndex = normalIndex'
|
||||
, shdrMOTexIndex = texIndex'
|
||||
, shdrMOProjMatIndex = projectionMatrixIndex'
|
||||
, shdrMOViewMatIndex = viewMatrixIndex'
|
||||
, shdrMOModelMatIndex = modelMatrixIndex'
|
||||
, shdrMONormalMatIndex = normalMatrixIndex'
|
||||
, shdrMOPositionOffsetIndex = positionOffsetIndex'
|
||||
, shdrMOScaleIndex = scaleIndex'
|
||||
, shdrMOTessInnerIndex = UniformLocation 0 --tessLevelInner'
|
||||
, shdrMOTessOuterIndex = UniformLocation 0 --tessLevelOuter'
|
||||
}
|
||||
|
||||
return (GLMapState
|
||||
{ _mapProgram = program
|
||||
, _mapShaderData = sdata
|
||||
, _mapObjectShaderData = smodata
|
||||
{ _mapProgram = program
|
||||
, _mapShaderData = sdata
|
||||
, _mapObjectShaderData = smodata
|
||||
, _stateTessellationFactor = tessFac
|
||||
, _stateMap = buf
|
||||
, _mapVert = vertDes
|
||||
, _overviewTexture = overTex
|
||||
, _mapTextures = textures
|
||||
, _shadowMapTexture = smap
|
||||
, _mapObjects = objs
|
||||
, _objectProgram = objProgram
|
||||
, _shadowMapProgram = shadowProgram
|
||||
, _stateMap = buf
|
||||
, _mapVert = vertDes
|
||||
, _overviewTexture = overTex
|
||||
, _mapTextures = textures
|
||||
, _shadowMapTexture = smap
|
||||
, _mapObjects = objs
|
||||
, _objectProgram = objProgram
|
||||
, _shadowMapProgram = shadowProgram
|
||||
}, tex, dtex)
|
||||
|
||||
initHud :: IO GLHud
|
||||
@ -285,23 +296,31 @@ initRendering = do
|
||||
|
||||
|
||||
-- | renders an IQM-Model at Position with scaling
|
||||
renderIQM :: IQM -> L.V3 CFloat -> L.V3 CFloat -> IO ()
|
||||
renderIQM m p@(L.V3 x y z) s@(L.V3 sx sy sz) = do
|
||||
withVAO (vertexArrayObject m) $ do
|
||||
withVAA [(AttribLocation 0),(AttribLocation 1)] $ do
|
||||
checkError "setting array to enabled"
|
||||
bindBuffer ElementArrayBuffer $= Just (triangleBufferObject m)
|
||||
checkError "bindBuffer"
|
||||
let n = fromIntegral.(*3).num_triangles.header $ m
|
||||
--print $ concat ["drawing ", show n," triangles"]
|
||||
drawElements Triangles n UnsignedInt nullPtr
|
||||
checkError "drawing model"
|
||||
bindBuffer ElementArrayBuffer $= Nothing
|
||||
checkError "unbind buffer"
|
||||
return ()
|
||||
renderIQM :: IQM -> L.V3 CFloat -> L.V3 CFloat -> Pioneers ()
|
||||
renderIQM m (L.V3 x y z) (L.V3 sx sy sz) = do
|
||||
state <- RWS.get
|
||||
let
|
||||
dmo = state ^. gl.glMap.mapObjectShaderData
|
||||
po = shdrMOPositionOffsetIndex dmo
|
||||
so = shdrMOScaleIndex dmo
|
||||
liftIO $ do
|
||||
withVAO (vertexArrayObject m) $ do
|
||||
withVAA [(AttribLocation 0),(AttribLocation 1)] $ do
|
||||
uniform po $= Vertex3 x y z
|
||||
uniform so $= Vertex3 sx sy sz
|
||||
checkError "setting array to enabled"
|
||||
bindBuffer ElementArrayBuffer $= Just (triangleBufferObject m)
|
||||
checkError "bindBuffer"
|
||||
let n = fromIntegral.(*3).num_triangles.header $ m
|
||||
--print $ concat ["drawing ", show n," triangles"]
|
||||
drawElements Triangles n UnsignedInt nullPtr
|
||||
checkError "drawing model"
|
||||
bindBuffer ElementArrayBuffer $= Nothing
|
||||
checkError "unbind buffer"
|
||||
return ()
|
||||
|
||||
renderObject :: MapObject -> IO ()
|
||||
renderObject (MapObject model pos@(L.V3 x y z) _{-state-}) =
|
||||
renderObject :: MapObject -> Pioneers ()
|
||||
renderObject (MapObject model pos _{-state-}) =
|
||||
renderIQM model pos (L.V3 1 1 1)
|
||||
|
||||
drawMap :: Pioneers ()
|
||||
@ -343,6 +362,7 @@ drawMap = do
|
||||
(ColorAttachment 1) --sample 1
|
||||
Renderbuffer --const
|
||||
rb --buffer-}
|
||||
|
||||
mat44ToGPU :: L.M44 CFloat -> UniformLocation -> String -> IO ()
|
||||
mat44ToGPU mat (UniformLocation dest) name = do
|
||||
with (distribute mat) $ \ptr ->
|
||||
@ -386,6 +406,14 @@ render = do
|
||||
(Just a) -> a
|
||||
Nothing -> L.eye3) :: L.M33 CFloat
|
||||
nmap = collect id normal' :: L.M33 CFloat --transpose...
|
||||
camTarget = getCamTarget camPos
|
||||
|
||||
moveTo :: L.V3 CFloat -> MapObject -> MapObject
|
||||
moveTo p (MapObject o _ s) = MapObject o p s
|
||||
|
||||
-- TODO: remove hack for Target
|
||||
RWS.modify $ gl.glMap.mapObjects %~ (\objs ->
|
||||
head objs : [moveTo camTarget $ objs !! 1])
|
||||
|
||||
liftIO $ do
|
||||
|
||||
@ -499,7 +527,8 @@ render = do
|
||||
--set up normal
|
||||
mat33ToGPU nmap nmatmo "mapObjects-nmat"
|
||||
|
||||
mapM_ renderObject (state ^. gl.glMap.mapObjects)
|
||||
mapM_ renderObject (state ^. gl.glMap.mapObjects)
|
||||
liftIO $ do
|
||||
checkError "draw mapobjects"
|
||||
|
||||
---- COMPOSE RENDERING --------------------------------------------
|
||||
@ -531,7 +560,7 @@ render = do
|
||||
|
||||
bindBuffer ElementArrayBuffer $= Just (hud ^. hudEBO)
|
||||
drawElements TriangleStrip 4 UnsignedInt offset0
|
||||
|
||||
|
||||
bindBuffer ArrayBuffer $= Nothing
|
||||
bindBuffer ElementArrayBuffer $= Nothing
|
||||
|
||||
|
@ -24,6 +24,8 @@ class GLCamera a where
|
||||
moveBy :: a -> (Position -> Position) -> PlayMap -> a
|
||||
-- | Moves the Camera-Target to an absoloute position
|
||||
move :: a -> Position -> PlayMap -> a
|
||||
-- | Gets the target point of a camera
|
||||
getCamTarget :: a -> V3 CFloat
|
||||
|
||||
-- | Alias for a camera-position onto the 2d-plane it moves on
|
||||
type Position = (Double, Double)
|
||||
@ -88,6 +90,14 @@ instance GLCamera Camera where
|
||||
(x,z) = f (x', z')
|
||||
y = giveMapHeight map (x,z)
|
||||
move c (x', z') map = moveBy c (\(x,z) -> (x+x',z+z')) map
|
||||
getCamTarget (Flat (x',z') y') =
|
||||
V3 x y z
|
||||
where
|
||||
x = realToFrac x'
|
||||
y = realToFrac y'
|
||||
z = realToFrac z'
|
||||
getCamTarget (Sphere (inc', az') r') =
|
||||
undefined
|
||||
|
||||
-- | converting spherical to cartesian coordinates
|
||||
sphereToCart :: (Floating a) => a -> a -> a -> V3 a
|
||||
|
44
src/Types.hs
44
src/Types.hs
@ -96,18 +96,18 @@ data KeyboardState = KeyboardState
|
||||
|
||||
|
||||
data GLMapState = GLMapState
|
||||
{ _mapShaderData :: !MapShaderData
|
||||
, _mapObjectShaderData :: !MapObjectShaderData
|
||||
{ _mapShaderData :: !MapShaderData
|
||||
, _mapObjectShaderData :: !MapObjectShaderData
|
||||
, _stateTessellationFactor :: !Int
|
||||
, _stateMap :: !GL.BufferObject
|
||||
, _mapVert :: !GL.NumArrayIndices
|
||||
, _mapProgram :: !GL.Program
|
||||
, _overviewTexture :: !TextureObject
|
||||
, _shadowMapTexture :: !TextureObject
|
||||
, _mapTextures :: ![TextureObject] --TODO: Fix size on list?
|
||||
, _objectProgram :: !GL.Program
|
||||
, _mapObjects :: ![MapObject]
|
||||
, _shadowMapProgram :: !GL.Program
|
||||
, _stateMap :: !GL.BufferObject
|
||||
, _mapVert :: !GL.NumArrayIndices
|
||||
, _mapProgram :: !GL.Program
|
||||
, _overviewTexture :: !TextureObject
|
||||
, _shadowMapTexture :: !TextureObject
|
||||
, _mapTextures :: ![TextureObject] --TODO: Fix size on list?
|
||||
, _objectProgram :: !GL.Program
|
||||
, _mapObjects :: ![MapObject]
|
||||
, _shadowMapProgram :: !GL.Program
|
||||
}
|
||||
|
||||
data MapShaderData = MapShaderData
|
||||
@ -123,16 +123,18 @@ data MapShaderData = MapShaderData
|
||||
}
|
||||
|
||||
data MapObjectShaderData = MapObjectShaderData
|
||||
{ shdrMOVertexIndex :: !GL.AttribLocation
|
||||
, shdrMOVertexOffsetIndex :: !GL.UniformLocation
|
||||
, shdrMONormalIndex :: !GL.AttribLocation
|
||||
, shdrMOTexIndex :: !GL.AttribLocation
|
||||
, shdrMOProjMatIndex :: !GL.UniformLocation
|
||||
, shdrMOViewMatIndex :: !GL.UniformLocation
|
||||
, shdrMOModelMatIndex :: !GL.UniformLocation
|
||||
, shdrMONormalMatIndex :: !GL.UniformLocation
|
||||
, shdrMOTessInnerIndex :: !GL.UniformLocation
|
||||
, shdrMOTessOuterIndex :: !GL.UniformLocation
|
||||
{ shdrMOVertexIndex :: !GL.AttribLocation
|
||||
, shdrMOVertexOffsetIndex :: !GL.UniformLocation
|
||||
, shdrMONormalIndex :: !GL.AttribLocation
|
||||
, shdrMOTexIndex :: !GL.AttribLocation
|
||||
, shdrMOProjMatIndex :: !GL.UniformLocation
|
||||
, shdrMOViewMatIndex :: !GL.UniformLocation
|
||||
, shdrMOModelMatIndex :: !GL.UniformLocation
|
||||
, shdrMONormalMatIndex :: !GL.UniformLocation
|
||||
, shdrMOPositionOffsetIndex :: !GL.UniformLocation
|
||||
, shdrMOScaleIndex :: !GL.UniformLocation
|
||||
, shdrMOTessInnerIndex :: !GL.UniformLocation
|
||||
, shdrMOTessOuterIndex :: !GL.UniformLocation
|
||||
}
|
||||
|
||||
|
||||
|
Loading…
Reference in New Issue
Block a user