{- Vivant: Haskell OpenGL game. Copyright (C) 2020 Yann Herklotz This program is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. -} module Main where import Control.Monad import Foreign.C.Types import Foreign.Ptr import Foreign.Storable (sizeOf) import SDL.Vect import System.Exit (exitFailure) import System.IO import 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 (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] SDL.HintRenderScaleQuality $= SDL.ScaleLinear do renderQuality <- SDL.get SDL.HintRenderScaleQuality when (renderQuality /= SDL.ScaleLinear) $ putStrLn "Warning: Linear texture filtering not enabled!" window <- SDL.createWindow "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 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 draw game SDL.glSwapWindow window unless quit loop loop SDL.destroyWindow window SDL.quit 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.DepthBuffer] GL.currentProgram $= gameProgram game GL.bindVertexArrayObject $= gameVao game ourColorLoc <- GL.uniformLocation p "ourColour" tick <- ticks GL.uniform ourColorLoc $= (GL.Vector4 (1::Float) (sin (fromIntegral tick / 500) / 2 + 0.5) 1 1) 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.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 texCoords = V.fromList [ 0, 0 , 1, 0 , 0.5, 1 ]