aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorYann Herklotz <git@yannherklotz.com>2020-12-28 03:51:03 +0000
committerYann Herklotz <git@yannherklotz.com>2020-12-28 03:51:19 +0000
commit0d52335b21587c21774cdf2090c27aa204a7903d (patch)
tree12c4e79788cec627f92a0fdda7022a7df19076d3
parentdf9d7726541c0e3dcb65bb0294a528fe9732d350 (diff)
downloadVivant-0d52335b21587c21774cdf2090c27aa204a7903d.tar.gz
Vivant-0d52335b21587c21774cdf2090c27aa204a7903d.zip
Add proper VAO and VBO
-rw-r--r--shaders/triangle.frag6
-rw-r--r--shaders/triangle.vert6
-rw-r--r--src/Vivant.hs132
-rw-r--r--src/Vivant/Shader.hs15
4 files changed, 123 insertions, 36 deletions
diff --git a/shaders/triangle.frag b/shaders/triangle.frag
index 244d850..2d290fd 100644
--- a/shaders/triangle.frag
+++ b/shaders/triangle.frag
@@ -1,7 +1,9 @@
-#version 120
+#version 150
uniform vec4 ourColour;
+out vec4 fragColor;
+
void main() {
- gl_FragColor = ourColour.yyzw;
+ fragColor = ourColour;
}
diff --git a/shaders/triangle.vert b/shaders/triangle.vert
index 45f6c13..cc5441d 100644
--- a/shaders/triangle.vert
+++ b/shaders/triangle.vert
@@ -1,5 +1,7 @@
-attribute vec2 coord2d;
+#version 150
+
+in vec2 position;
void main(void) {
- gl_Position = vec4(coord2d, 0.0, 1.0);
+ gl_Position = vec4(position, 0.0, 1.0);
}
diff --git a/src/Vivant.hs b/src/Vivant.hs
index e786228..fa356ad 100644
--- a/src/Vivant.hs
+++ b/src/Vivant.hs
@@ -16,23 +16,67 @@ module Main where
import Control.Monad
import Foreign.C.Types
+import Foreign.Ptr
+import Foreign.Storable (sizeOf)
import SDL.Vect
-import qualified Data.ByteString as BS
-import qualified Data.Vector.Storable as V
-import System.Exit (exitFailure)
-import System.IO
-
+import System.Exit (exitFailure)
+import System.IO
import SDL (($=))
-import qualified SDL
import SDL.Time (ticks)
+import SDL.Raw.Video as SDL (glSetAttribute)
+import SDL.Raw.Enum as SDL
+import Data.Word (Word32)
+import Linear
+
import qualified Graphics.Rendering.OpenGL as GL
+import qualified Data.ByteString as BS
+import qualified Data.Vector.Storable as V
+import qualified SDL
import Paths_vivant (getDataDir)
-import Vivant.Shader (initShaders)
+import Vivant.Shader (createProgram)
screenWidth, screenHeight :: CInt
(screenWidth, screenHeight) = (640, 480)
+data Camera = Camera
+ { cameraPos :: V3 Float
+ , cameraUp :: V3 Float
+ , cameraFront :: V3 Float
+ , cameraSpeed :: Float
+ , cameraPitch :: Float
+ , cameraYaw :: Float
+ } deriving (Show)
+
+initialCamera :: Camera
+initialCamera = Camera
+ { cameraPos = V3 0 0 3
+ , cameraUp = V3 0 1 0
+ , cameraFront = V3 0 0 (-1)
+ , cameraSpeed = 0.05
+ , cameraPitch = 0
+ , cameraYaw = (-90)
+ }
+
+data Game = Game
+ { gameProgram :: Maybe (GL.Program)
+ , gameVao :: Maybe (GL.VertexArrayObject)
+ , gameModelP :: Ptr (M44 Float)
+ , gameViewP :: Ptr (M44 Float)
+ , gameProjectionP :: Ptr (M44 Float)
+ , gameCamera :: Camera
+ } deriving (Show)
+
+initialGameState :: Game
+initialGameState = Game
+ { gameProgram = Nothing
+ , gameVao = Nothing
+ , gameModelP = nullPtr
+ , gameViewP = nullPtr
+ , gameProjectionP = nullPtr
+ , gameCamera = initialCamera
+ }
+
main :: IO ()
main = do
SDL.initialize [SDL.InitVideo]
@@ -46,17 +90,27 @@ main = do
"SDL / OpenGL Example"
SDL.defaultWindow {SDL.windowInitialSize = V2 screenWidth screenHeight,
SDL.windowGraphicsContext = SDL.OpenGLContext SDL.defaultOpenGL}
+
+ SDL.glSetAttribute SDL_GL_CONTEXT_PROFILE_MASK SDL_GL_CONTEXT_PROFILE_CORE
+ SDL.glSetAttribute SDL_GL_CONTEXT_MAJOR_VERSION 3
+ SDL.glSetAttribute SDL_GL_CONTEXT_MINOR_VERSION 2
+
+ SDL.glSetAttribute SDL_GL_DOUBLEBUFFER 1
+ SDL.glSetAttribute SDL_GL_DEPTH_SIZE 24
+
SDL.showWindow window
_ <- SDL.glCreateContext window
- (prog, attrib) <- initShaders
+
+ GL.viewport $= (GL.Position 0 0, GL.Size (fromIntegral screenWidth) (fromIntegral screenHeight))
+
+ game <- initResources
let loop = do
events <- SDL.pollEvents
let quit = elem SDL.QuitEvent $ map SDL.eventPayload events
- GL.clear [GL.ColorBuffer]
- draw prog attrib
+ draw game
SDL.glSwapWindow window
unless quit loop
@@ -66,29 +120,57 @@ main = do
SDL.destroyWindow window
SDL.quit
-draw :: GL.Program -> GL.AttribLocation -> IO ()
-draw program attrib = do
+setVertexAttribute :: GL.Program -> String -> Int -> Int -> Int -> IO ()
+setVertexAttribute program name vertices stride offset = do
+ let floatSize = sizeOf (1.0 :: Float)
+ attrib <- GL.get $ GL.attribLocation program name
+ GL.vertexAttribPointer attrib $= (GL.ToFloat, GL.VertexArrayDescriptor 2 GL.Float
+ (fromIntegral $ stride * floatSize)
+ (plusPtr nullPtr (offset * floatSize)))
+ GL.vertexAttribArray attrib $= GL.Enabled
+
+initResources :: IO Game
+initResources = do
+ vao <- GL.genObjectName
+ GL.bindVertexArrayObject $= Just vao
+
+ vbo <- GL.genObjectName
+ GL.bindBuffer GL.ArrayBuffer $= Just vbo
+ V.unsafeWith vertices $ \ptr ->
+ GL.bufferData GL.ArrayBuffer $= (vectorSize vertices, castPtr ptr, GL.StaticDraw)
+
+ prog <- createProgram
+
+ setVertexAttribute prog "position" 2 0 0
+
+ return $ initialGameState { gameProgram = Just prog, gameVao = Just vao }
+
+draw :: Game -> IO ()
+draw game@(Game {gameProgram = Just p, gameVao = Just v}) = do
GL.clearColor $= GL.Color4 1 1 1 1
- GL.clear [GL.ColorBuffer]
- GL.viewport $= (GL.Position 0 0, GL.Size (fromIntegral screenWidth) (fromIntegral screenHeight))
+ GL.clear [GL.ColorBuffer, GL.DepthBuffer]
- GL.currentProgram $= Just program
+ GL.currentProgram $= gameProgram game
+ GL.bindVertexArrayObject $= gameVao game
- ourColorLoc <- GL.uniformLocation program "ourColour"
+ ourColorLoc <- GL.uniformLocation p "ourColour"
tick <- ticks
GL.uniform ourColorLoc $= (GL.Vector4 (1::Float) (sin (fromIntegral tick / 500) / 2 + 0.5) 1 1)
- GL.vertexAttribArray attrib $= GL.Enabled
- V.unsafeWith vertices $ \ptr ->
- GL.vertexAttribPointer attrib $=
- (GL.ToFloat, GL.VertexArrayDescriptor 2 GL.Float 0 ptr)
- GL.drawArrays GL.Triangles 0 3 -- 3 is the number of vertices
- GL.vertexAttribArray attrib $= GL.Disabled
+ GL.drawArrays GL.Triangles 0 6
+
+ GL.bindVertexArrayObject $= Nothing
+ return ()
+
+vectorSize array = fromIntegral $ V.length array * sizeOf (1.0 :: Float)
vertices :: V.Vector Float
-vertices = V.fromList [ 0.0, 0.8
- , -0.8, -0.8
- , 0.8, -0.8
+vertices = V.fromList [ 0.5, -0.5
+ , -0.5, -0.5
+ , 0.5, 0.5
+ , -0.5, 0.5
+ , -0.5, -0.5
+ , 0.5, 0.5
]
texCoords :: V.Vector Float
diff --git a/src/Vivant/Shader.hs b/src/Vivant/Shader.hs
index 503d1b7..dfd5d41 100644
--- a/src/Vivant/Shader.hs
+++ b/src/Vivant/Shader.hs
@@ -1,4 +1,4 @@
-module Vivant.Shader (initShaders) where
+module Vivant.Shader (createProgram) where
import SDL (($=))
import qualified Graphics.Rendering.OpenGL as GL
@@ -8,8 +8,8 @@ import System.IO (stderr, hPutStrLn)
import Control.Monad (unless)
import Paths_vivant (getDataDir)
-initShaders :: IO (GL.Program, GL.AttribLocation)
-initShaders = do
+createProgram :: IO GL.Program
+createProgram = do
datadir <- getDataDir
-- compile vertex shader
vs <- GL.createShader GL.VertexShader
@@ -18,7 +18,8 @@ initShaders = do
GL.compileShader vs
vsOK <- GL.get $ GL.compileStatus vs
unless vsOK $ do
- hPutStrLn stderr "Error in vertex shader\n"
+ log <- GL.shaderInfoLog vs
+ hPutStrLn stderr ("Error in vertex shader\n" <> log)
exitFailure
-- Do it again for the fragment shader
@@ -28,13 +29,13 @@ initShaders = do
GL.compileShader fs
fsOK <- GL.get $ GL.compileStatus fs
unless fsOK $ do
- hPutStrLn stderr "Error in fragment shader\n"
+ log <- GL.shaderInfoLog fs
+ hPutStrLn stderr ("Error in fragment shader\n" <> log)
exitFailure
program <- GL.createProgram
GL.attachShader program vs
GL.attachShader program fs
- GL.attribLocation program "coord2d" $= GL.AttribLocation 0
GL.linkProgram program
linkOK <- GL.get $ GL.linkStatus program
GL.validateProgram program
@@ -46,4 +47,4 @@ initShaders = do
exitFailure
GL.currentProgram $= Just program
- return (program, GL.AttribLocation 0)
+ return program