finished episode13
This commit is contained in:
parent
9830e5d3ed
commit
3046622519
4 changed files with 156 additions and 35 deletions
27
src/BufferClass.hs
Normal file
27
src/BufferClass.hs
Normal file
|
@ -0,0 +1,27 @@
|
|||
module BufferClass where
|
||||
|
||||
import qualified Graphics.Rendering.OpenGL as GL
|
||||
|
||||
import SDL (($=), get)
|
||||
|
||||
-- this aims to be a typeclass for all used buffer objects throughout the
|
||||
-- tutorial.
|
||||
-- think of it as some kind of interface in the object oriented context
|
||||
class Buffer a where
|
||||
|
||||
-- what buffer target does te buffer bind to
|
||||
target :: a -> GL.BufferTarget
|
||||
|
||||
-- what ID does the buffer have
|
||||
glId :: a -> GL.BufferObject
|
||||
|
||||
-- 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)
|
||||
|
||||
-- unbind the buffer
|
||||
unbind :: a -> IO ()
|
||||
unbind buf = GL.bindBuffer (target buf) $= Nothing
|
58
src/IndexBuffer.hs
Normal file
58
src/IndexBuffer.hs
Normal file
|
@ -0,0 +1,58 @@
|
|||
module IndexBuffer where
|
||||
|
||||
import qualified Graphics.Rendering.OpenGL as GL
|
||||
|
||||
import SDL (($=), get)
|
||||
|
||||
import Foreign
|
||||
|
||||
-- internal imports
|
||||
|
||||
import BufferClass
|
||||
|
||||
-- layout of the IndexBuffer data object
|
||||
data IndexBuffer a = IndexBuffer
|
||||
{ iBufId :: GL.BufferObject -- buffer id
|
||||
, iBufSize :: GL.GLsizeiptr -- size of data
|
||||
, iBufData :: Ptr a -- pointer to data
|
||||
, iBufCount :: GL.GLuint -- number of data elements
|
||||
}
|
||||
|
||||
-- instanciate typeclass from BufferClass and fill in missing implementations
|
||||
instance Buffer (IndexBuffer a) where
|
||||
|
||||
target _ = GL.ElementArrayBuffer
|
||||
|
||||
glId = iBufId
|
||||
|
||||
initialize buf = do
|
||||
-- bind the buffer using the default iplementation of the typeclass
|
||||
bind buf
|
||||
-- fill in the data
|
||||
GL.bufferData (target buf) $=
|
||||
( iBufSize buf
|
||||
, iBufData buf
|
||||
, GL.StaticDraw
|
||||
)
|
||||
-- release the buffer using the default implementation of the typeclass
|
||||
unbind buf
|
||||
|
||||
newIndexBuffer ::
|
||||
(Storable a) => -- we have to be able to get a pointer to provided data
|
||||
[a] -> -- list of data elements
|
||||
IO (IndexBuffer a) -- newly built IndexBuffer data object
|
||||
newIndexBuffer list = do
|
||||
-- create the buffer object in applicative style
|
||||
buf <- IndexBuffer
|
||||
-- generate the ID
|
||||
<$> GL.genObjectName
|
||||
-- compute buffer size
|
||||
<*> pure (fromIntegral (length list * sizeOf (head list)))
|
||||
-- make pointer out of list
|
||||
<*> newArray list
|
||||
-- get count
|
||||
<*> pure (fromIntegral $ length list)
|
||||
-- fill the data in to the buffer
|
||||
initialize buf
|
||||
-- return the data object
|
||||
return buf
|
51
src/Main.hs
51
src/Main.hs
|
@ -29,6 +29,12 @@ import qualified Data.List as L
|
|||
|
||||
import System.Random (randomRIO)
|
||||
|
||||
-- internal imports
|
||||
|
||||
import BufferClass
|
||||
import VertexBuffer
|
||||
import IndexBuffer
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
|
||||
|
@ -81,22 +87,11 @@ main = do
|
|||
-- create draw order indices
|
||||
indices = [0, 1, 2, 2, 3, 0] :: [GL.GLuint]
|
||||
|
||||
-- create and bind buffer for vertices
|
||||
buf <- GL.genObjectName
|
||||
GL.bindBuffer GL.ArrayBuffer $= Just buf
|
||||
-- construct new VertexBuffer and fill it with data
|
||||
vbo <- newVertexBuffer vertexPositions
|
||||
|
||||
-- put vertices into the buffer
|
||||
-- turn the list into a pointer
|
||||
withArray vertexPositions $ \ptr ->
|
||||
-- Feed the data to the buffer
|
||||
GL.bufferData GL.ArrayBuffer $=
|
||||
-- how much bytes of memory we are going to write (as an Int32)
|
||||
( fromIntegral $ length vertexPositions * sizeOf (undefined :: GL.GLfloat)
|
||||
-- The pointer to the data
|
||||
, ptr
|
||||
-- The data's usage
|
||||
, GL.StaticDraw
|
||||
)
|
||||
-- rebind the vertex buffer
|
||||
bind vbo
|
||||
|
||||
-- enable and specify data layout of the in-memory vertices
|
||||
GL.vertexAttribPointer (GL.AttribLocation 0) $=
|
||||
|
@ -113,22 +108,8 @@ main = do
|
|||
)
|
||||
GL.vertexAttribArray (GL.AttribLocation 0) $= GL.Enabled
|
||||
|
||||
-- create and bind buffer index buffer
|
||||
ibo <- GL.genObjectName
|
||||
GL.bindBuffer GL.ElementArrayBuffer $= Just ibo
|
||||
|
||||
-- put indices into index buffer
|
||||
-- turn the list into a pointer
|
||||
withArray indices $ \ptr -> do
|
||||
-- Feed the data to the buffer
|
||||
GL.bufferData GL.ElementArrayBuffer $=
|
||||
-- how much bytes of memory we are going to write (as an Int32)
|
||||
( fromIntegral $ length indices * sizeOf (undefined :: GL.GLuint)
|
||||
-- The pointer to the data
|
||||
, ptr
|
||||
-- The data's usage
|
||||
, GL.StaticDraw
|
||||
)
|
||||
-- construct new IndexBuffer and fill it with data
|
||||
ibo <- newIndexBuffer indices
|
||||
|
||||
-- -- SHADERS
|
||||
|
||||
|
@ -158,8 +139,8 @@ main = do
|
|||
-- -- UNBINDING ALL BUFFERS AND VERTEX ARRAYS
|
||||
|
||||
GL.bindVertexArrayObject $= Nothing
|
||||
GL.bindBuffer GL.ArrayBuffer $= Nothing
|
||||
GL.bindBuffer GL.ElementArrayBuffer $= Nothing
|
||||
unbind vbo
|
||||
unbind ibo
|
||||
GL.currentProgram $= Nothing
|
||||
|
||||
-- -- LOOPING
|
||||
|
@ -187,7 +168,7 @@ main = do
|
|||
-- rebind everything neccessary for draw call
|
||||
GL.bindVertexArrayObject $= Just vao
|
||||
-- (note the missing bindings to the vertex buffer and the attrib pointer)
|
||||
GL.bindBuffer GL.ElementArrayBuffer $= Just ibo
|
||||
bind ibo
|
||||
GL.currentProgram $= Just sp
|
||||
|
||||
-- throw away previous errors
|
||||
|
@ -291,7 +272,7 @@ compileShaderSource type_ source = do
|
|||
|
||||
if ok
|
||||
then
|
||||
putStrLn (show type_ ++ ": compilation successfull!")
|
||||
putStrLn (show type_ ++ ": compilation successful!")
|
||||
else do
|
||||
info <- get (GL.shaderInfoLog shaderObject)
|
||||
putStrLn (show type_ ++ ": compilation failed!\nInfo log says:")
|
||||
|
|
55
src/VertexBuffer.hs
Normal file
55
src/VertexBuffer.hs
Normal file
|
@ -0,0 +1,55 @@
|
|||
module VertexBuffer where
|
||||
|
||||
import qualified Graphics.Rendering.OpenGL as GL
|
||||
|
||||
import SDL (($=), get)
|
||||
|
||||
import Foreign
|
||||
|
||||
-- internal imports
|
||||
|
||||
import BufferClass
|
||||
|
||||
-- layout of the VertexBuffer data object
|
||||
data VertexBuffer a = VertexBuffer
|
||||
{ vBufId :: GL.BufferObject -- buffer id
|
||||
, vBufSize :: GL.GLsizeiptr -- size of data
|
||||
, vBufData :: Ptr a -- pointer to data
|
||||
}
|
||||
|
||||
-- instanciate typeclass from BufferClass and fill in missing implementations
|
||||
instance Buffer (VertexBuffer a) where
|
||||
|
||||
target _ = GL.ArrayBuffer
|
||||
|
||||
glId = vBufId
|
||||
|
||||
initialize buf = do
|
||||
-- bind the buffer using the default iplementation of the typeclass
|
||||
bind buf
|
||||
-- fill in the data
|
||||
GL.bufferData (target buf) $=
|
||||
( vBufSize buf
|
||||
, vBufData buf
|
||||
, GL.StaticDraw
|
||||
)
|
||||
-- release the buffer using the default implementation of the typeclass
|
||||
unbind buf
|
||||
|
||||
newVertexBuffer ::
|
||||
(Storable a) => -- we have to be able to get a pointer to provided data
|
||||
[a] -> -- list of data elements
|
||||
IO (VertexBuffer a) -- newly built VertexBuffer data object
|
||||
newVertexBuffer list = do
|
||||
-- create the buffer object in applicative style
|
||||
buf <- VertexBuffer
|
||||
-- generate the ID
|
||||
<$> GL.genObjectName
|
||||
-- compute buffer size
|
||||
<*> pure (fromIntegral $ length list * sizeOf (head list))
|
||||
-- make pointer out of list
|
||||
<*> newArray list
|
||||
-- fill the data in to the buffer
|
||||
initialize buf
|
||||
-- return the data object
|
||||
return buf
|
Loading…
Reference in a new issue