finished episode14

This commit is contained in:
nek0 2020-05-20 05:54:14 +02:00
parent 3046622519
commit 2db17d3fd6
4 changed files with 46 additions and 18 deletions

View File

@ -1,3 +1,4 @@
{-# LANGUAGE TypeFamilies #-}
module BufferClass where
import qualified Graphics.Rendering.OpenGL as GL
@ -9,19 +10,21 @@ import SDL (($=), get)
-- think of it as some kind of interface in the object oriented context
class Buffer a where
type ObjName a :: *
-- what buffer target does te buffer bind to
target :: a -> GL.BufferTarget
-- what ID does the buffer have
glId :: a -> GL.BufferObject
glId :: a -> ObjName a
-- bind the buffer object and fill it with data
initialize :: a -> IO ()
-- bind the buffer
bind :: a -> IO ()
bind buf = GL.bindBuffer (target buf) $= Just (glId buf)
-- bind buf = GL.bindBuffer (target buf) $= Just (glId buf)
-- unbind the buffer
unbind :: a -> IO ()
unbind buf = GL.bindBuffer (target buf) $= Nothing
-- unbind buf = GL.bindBuffer (target buf) $= Nothing

View File

@ -1,3 +1,4 @@
{-# LANGUAGE TypeFamilies #-}
module IndexBuffer where
import qualified Graphics.Rendering.OpenGL as GL
@ -21,6 +22,8 @@ data IndexBuffer a = IndexBuffer
-- instanciate typeclass from BufferClass and fill in missing implementations
instance Buffer (IndexBuffer a) where
type ObjName (IndexBuffer a) = GL.BufferObject
target _ = GL.ElementArrayBuffer
glId = iBufId
@ -37,6 +40,12 @@ instance Buffer (IndexBuffer a) where
-- release the buffer using the default implementation of the typeclass
unbind buf
-- bind the buffer
bind buf = GL.bindBuffer (target buf) $= Just (glId buf)
-- unbind the buffer
unbind buf = GL.bindBuffer (target buf) $= Nothing
newIndexBuffer ::
(Storable a) => -- we have to be able to get a pointer to provided data
[a] -> -- list of data elements

View File

@ -32,6 +32,7 @@ import System.Random (randomRIO)
-- internal imports
import BufferClass
import VertexArray
import VertexBuffer
import IndexBuffer
@ -88,25 +89,31 @@ main = do
indices = [0, 1, 2, 2, 3, 0] :: [GL.GLuint]
-- construct new VertexBuffer and fill it with data
vao <- newVertexArray
vbo <- newVertexBuffer vertexPositions
-- rebind the vertex buffer
bind vbo
-- enable and specify data layout of the in-memory vertices
GL.vertexAttribPointer (GL.AttribLocation 0) $=
( GL.ToFloat
, GL.VertexArrayDescriptor
-- There are 2 components (Floats) to our attribute
2
-- They are Floats
GL.Float
-- ???
0
-- our attribute is directly at the beginning of each vertex
(plusPtr nullPtr 0)
)
GL.vertexAttribArray (GL.AttribLocation 0) $= GL.Enabled
layout <- newVertexBufferLayout
pushElements layout GL.Float 2
addBuffer vao vbo layout
-- GL.vertexAttribPointer (GL.AttribLocation 0) $=
-- ( GL.ToFloat
-- , GL.VertexArrayDescriptor
-- -- There are 2 components (Floats) to our attribute
-- 2
-- -- They are Floats
-- GL.Float
-- -- ???
-- 0
-- -- our attribute is directly at the beginning of each vertex
-- (plusPtr nullPtr 0)
-- )
-- GL.vertexAttribArray (GL.AttribLocation 0) $= GL.Enabled
-- construct new IndexBuffer and fill it with data
ibo <- newIndexBuffer indices
@ -166,7 +173,7 @@ main = do
GL.clear [GL.ColorBuffer]
-- rebind everything neccessary for draw call
GL.bindVertexArrayObject $= Just vao
bind vao
-- (note the missing bindings to the vertex buffer and the attrib pointer)
bind ibo
GL.currentProgram $= Just sp

View File

@ -1,3 +1,4 @@
{-# LANGUAGE TypeFamilies #-}
module VertexBuffer where
import qualified Graphics.Rendering.OpenGL as GL
@ -20,6 +21,8 @@ data VertexBuffer a = VertexBuffer
-- instanciate typeclass from BufferClass and fill in missing implementations
instance Buffer (VertexBuffer a) where
type ObjName (VertexBuffer a) = GL.BufferObject
target _ = GL.ArrayBuffer
glId = vBufId
@ -36,6 +39,12 @@ instance Buffer (VertexBuffer a) where
-- release the buffer using the default implementation of the typeclass
unbind buf
-- bind the buffer
bind buf = GL.bindBuffer (target buf) $= Just (glId buf)
-- unbind the buffer
unbind buf = GL.bindBuffer (target buf) $= Nothing
newVertexBuffer ::
(Storable a) => -- we have to be able to get a pointer to provided data
[a] -> -- list of data elements