Hello Triangle

Learn OpenGL - Hello Triangle

Here's where we learn to draw a single triangle. This is actually the hardest step, because you have to learn about all the shaders and stuff, and at the same time you have to learn all the FFI stuff to make those things interact with Haskell properly.

Imports

Now that we're passing data through the FFI ourselves, we need to use the Foreign module.

import Foreign -- includes many sub-modules

Most importantly to us, Foreign includes

  • Foreign.Ptr, which lets us manipulate pointers to data of various kinds.
  • Foreign.Storable, which lets us "peek" (read) and "poke" (write) pointers of Storable types (including the OpenGL types) to get at the data pointed to.
  • Foreign.Marshal, which again is a collection of sub-modules, but what we want is:
    • Foreign.Marshal.Alloc is what actually gets us the Ptrs that we'll be writing data into before we send it off to OGL.
    • Foreign.Marshal.Array is similar, but for "array" pointers, which are just normal pointers but you can store many values contiguously.

That might seem like a whole lot, but each module is dedicated to one specific thing, so it's pretty easy to use once you get used to it.

There's one other handy utility that we'll be wanting: converting a Haskell String (including String literals in our source files) into a C compatible value. Thankfully, there's also a module for that, it's just not imported into Foreign by default.

import Foreign.C.String (newCAStringLen)

The function we'll be using there has a kinda funky name. It's one of several related variants. This one turns a Haskell String into an ANSI C String (the type that OpenGL is expecting) and it gives us back the length at the same time.

Vertex Input

If we go to the Graphics.GL.Types module we can see that the GLfloat type is just an alias for Haskell's normal Float type, but we'll still call things by the OpenGL name because that helps us talk to other OpenGL people a little better. We'll turn our [GLfloat] into something we can pass to OpenGL using newArray.

let verticies = [
        -0.5, -0.5, 0.0, -- first vertex
        0.5, -0.5, 0.0, -- second vertex
        0.0,  0.5, 0.0 -- third vertex
        ] :: [GLfloat]
let verticesSize = fromIntegral $ sizeOf (0.0 :: GLfloat) * (length verticies)
verticesP <- newArray verticies

Next we're gonna call glGenBuffers to make a single buffer ID. Unlike in C, where you generally declare the variable and then take its address to get a pointer, in Haskell we declare that we want a pointer to some place and then after that we read and write to that location. The malloc action is thankfully polymorphic, so Haskell figures out the type of the pointer for us. If we were building a larger program we'd probably want to use alloca instead, but for now we're fine. We'll cover that and other helper abstractions at the end of the lesson once our triangle is working.

vboP <- malloc
glGenBuffers 1 vboP
vbo <- peek vboP

And then once that's set up we use glBindBuffer to make it our active buffer, and then glBufferData to send it the data.

glBindBuffer GL_ARRAY_BUFFER vbo
glBufferData GL_ARRAY_BUFFER verticesSize (castPtr verticesP) GL_STATIC_DRAW

Vertex Shader

For the vertex shader, we need the desired source code as a String to start. We can either have it be a string literal inside our program (and it would be compiled into the final binary that way) or we could load it from disk. It's a little better when you don't have to worry about extra resource files, so for now we'll use a string literal.

Even then, there's a few options. The first is to use backslash notation.

vertexShaderSource = "#version 330 core\n\
    \layout (location = 0) in vec3 position;\
    \void main()\
    \{\
    \    gl_Position = vec4(position.x, position.y, position.z, 1.0);\
    \}"

That's pretty ugly, and note that we specifically need to add the \n at the end of the version line ourselves, since that must be on its own line, and the backslash notation concatenates the substrings directly.

Our next option is to just use unlines on a list of lines.

vertexShaderSource = unlines ["#version 330 core",
    "layout (location = 0) in vec3 position;",
    "void main()",
    "{",
    "    gl_Position = vec4(position.x, position.y, position.z, 1.0);",
    "}"]

Another option is to use a package called raw-strings-qq, which gives us a QuasiQuoter called r. What it does is that we can write [r|, and then anything we want, and then |] at the end, and then the stuff in between turns into a string literal, newlines and all that included. To use it we need to import the module, and have the {-# LANGUAGE QuasiQuotes #-} pragma at the top of our file, then we just write

vertexShaderSource :: String
vertexShaderSource = [r|#version 330 core
    layout (location = 0) in vec3 position;
    void main()
    {
        gl_Position = vec4(position.x, position.y, position.z, 1.0);
    }
    |]

The version using the QuasiQuotes takes a little extra effort to set up, but it makes for the easiest editing once you get going. The only real downside is that your editor probably won't know how to look inside a quasiquoter, so the section inside doesn't have the normal "string literal" highlight color you might have set.

Compiling A Shader

Now that our shader is safely in a String, we have to compile it so the GPU can use it. Because there are so many kinds of GPU and so many driver versions for that GPU, it's simplest to just compile the shader source every single time you load up the program. It's a drop in the bucket compared to the time it takes to load other large resources, so it's not a big deal. Note that you can attempt to use a cached version of a shader, but even the OpenGL Wiki will tell you that the cached version is entirely unreliable, so we won't be covering that.

First we need a vertex shader ID (glCreateShader), then we associate some source with it (glShaderSource), and compile it (glCompileShader). We have to check the result with glGetShaderiv, and if ther eis an error we use glGetShaderInfoLog to grab the bytes and then convert it around so we can print it out.

vertexShader <- glCreateShader GL_VERTEX_SHADER
(sourceP,len) <- newCAStringLen vertexShaderSource
linesPtrsPtr <- newArray [sourceP]
lengthsPtr <- newArray [fromIntegral len]
glShaderSource vertexShader 1 linesPtrsPtr lengthsPtr
glCompileShader vertexShader
vertexSuccessP <- malloc
glGetShaderiv vertexShader GL_COMPILE_STATUS vertexSuccessP
vertexSuccess <- peek vertexSuccessP
when (vertexSuccess == GL_FALSE) $ do
    putStrLn "Vertex Shader Compile Error:"
    let infoLength = 512
    resultP <- malloc
    infoLog <- mallocArray (fromIntegral infoLength)
    glGetShaderInfoLog vertexShader (fromIntegral infoLength) resultP infoLog
    result <- fromIntegral <$> peek resultP
    logBytes <- peekArray result infoLog
    putStrLn (map (toEnum.fromEnum) logBytes)

Wow. That is a lot of junk. Lots of little parts we might mess up if we have to do this over and over. This is a top canidate for wrapping it up into a helper function, so we'll come back to this too.

Fragment Shader

Now we do that whole thing we just did a second time and replace a few names.

vertexShader <- glCreateShader GL_VERTEX_SHADER
(sourceP,len) <- newCAStringLen vertexShaderSource
linesPtrsPtr <- newArray [sourceP]
lengthsPtr <- newArray [fromIntegral len]
glShaderSource vertexShader 1 linesPtrsPtr lengthsPtr
glCompileShader vertexShader
vertexSuccessP <- malloc
glGetShaderiv vertexShader GL_COMPILE_STATUS vertexSuccessP
vertexSuccess <- peek vertexSuccessP
when (vertexSuccess == GL_FALSE) $ do
    putStrLn "Fragment Shader Compile Error:"
    let infoLength = 512
    resultP <- malloc
    infoLog <- mallocArray (fromIntegral infoLength)
    glGetShaderInfoLog vertexShader (fromIntegral infoLength) resultP infoLog
    result <- fromIntegral <$> peek resultP
    logBytes <- peekArray result infoLog
    putStrLn (map (toEnum.fromEnum) logBytes)

Yes, we just shadowed a bunch of bindings that had memory associated with them. Yes, this is essentially a memory leak. However, we'll fix it up in a moment, so for now we'll just use what works.

Shader Program

Linking our two shaders together follows a similar pattern. glCreateProgram, glAttachShader for each shader part, glLinkProgram to compile it together. Use glGetProgramiv to check for success. Print the error, if any. As in the C++ version, we can use glDeleteShader to delete the shaders once we're done making the whole program. We must also set the program to be used of course, with glUseProgram.

shaderProgram <- glCreateProgram
glAttachShader shaderProgram vertexShader
glAttachShader shaderProgram fragmentShader
glLinkProgram shaderProgram
linkingSuccessP <- malloc
glGetProgramiv shaderProgram GL_LINK_STATUS linkingSuccessP
linkingSuccess <- peek linkingSuccessP
when (linkingSuccess == GL_FALSE) $ do
    putStrLn "Program Linking Error:"
    let infoLength = 512
    resultP <- malloc
    infoLog <- mallocArray (fromIntegral infoLength)
    glGetProgramInfoLog shaderProgram (fromIntegral infoLength) resultP infoLog
    result <- fromIntegral <$> peek resultP
    logBytes <- peekArray result infoLog
    putStrLn (map (toEnum.fromEnum) logBytes)

glDeleteShader vertexShader
glDeleteShader fragmentShader

glUseProgram shaderProgram

Linking Vertex Attributes

Now we're ready to "define an array of generic vertex attribute data" (glVertexAttribPointer) and then "enable a generic vertex attribute array" (glEnableVertexAttributeArray), as the official docs put it.

let threeFloats = fromIntegral $ sizeOf (0.0::GLfloat) * 3
glVertexAttribPointer 0 3 GL_FLOAT GL_FALSE threeFloats nullPtr
glEnableVertexAttribArray 0

Vertex Array Object

We're almost ready, but we just need to get a Vertex Array Object setup (glGenVertexArrays, glBindVertexArray). We move the vertex buffer object and the vertex attribute pointer code to the "inside" of the vertex array object use.

vaoP <- malloc
glGenVertexArrays 1 vaoP
vao <- peek vaoP
glBindVertexArray vao
glBindBuffer GL_ARRAY_BUFFER vbo
glBufferData GL_ARRAY_BUFFER verticesSize (castPtr verticesP) GL_STATIC_DRAW
let threeFloats = fromIntegral $ sizeOf (0.0::GLfloat) * 3
glVertexAttribPointer 0 3 GL_FLOAT GL_FALSE threeFloats nullPtr
glEnableVertexAttribArray 0
glBindVertexArray 0

A Triangle!

Now that we've got everything in line, the main loop just needs us to bind the VAO, call glDrawArrays, and then unbind the VAO.

glBindVertexArray vao
glDrawArrays GL_TRIANGLES 0 3
glBindVertexArray 0

Code So Far

Now that we're able to draw the triangle we wanted, we can run hello-triangle1.hs and see a triangle on the screen.

But, we're not done yet!

Element Buffer Objects

Adding more verticies is pretty easy, we just add more to our list, and then we update our glDrawArrays call. The rest resizes itself.

-- new verticies
let verticies = [
        -- First triangle
        0.5,  0.5, 0.0,  -- Top Right
        0.5, -0.5, 0.0,  -- Bottom Right
        -0.5,  0.5, 0.0, -- Top Left 
        -- Second triangle
        0.5, -0.5, 0.0,  -- Bottom Right
        -0.5, -0.5, 0.0, -- Bottom Left
        -0.5,  0.5, 0.0  -- Top Left
        ] :: [GLfloat]
-- in the main loop
glDrawArrays GL_TRIANGLES 0 6

But this is about vertex savings! So the element buffer object stuff is pretty easy to do now that we know how to marshal the data. First we setup the vertex and index data:

-- setup our verticies
let verticies = [
        0.5,  0.5, 0.0,  -- Top Right
        0.5, -0.5, 0.0,  -- Bottom Right
        -0.5, -0.5, 0.0, -- Bottom Left
        -0.5,  0.5, 0.0  -- Top Left
        ] :: [GLfloat]
let verticesSize = fromIntegral $ sizeOf (0.0 :: GLfloat) * (length verticies)
verticesP <- newArray verticies

-- setup the indexes
let indices = [  -- Note that we start from 0!
        0, 1, 3, -- First Triangle
        1, 2, 3  -- Second Triangle
        ] :: [GLuint]
let indicesSize = fromIntegral $ sizeOf (0 :: GLuint) * (length indices)
indicesP <- newArray indices

Then after we have our Vertex Array Object and Vertex Buffer Object, we setup an Element Buffer Object

-- setup an element buffer object and send it data
eboP <- malloc
glGenBuffers 1 eboP
ebo <- peek eboP
glBindBuffer GL_ELEMENT_ARRAY_BUFFER ebo
glBufferData GL_ELEMENT_ARRAY_BUFFER indicesSize (castPtr indicesP) GL_STATIC_DRAW

And then the drawing process we use glDrawElements instead.

glBindVertexArray vao
glDrawElements GL_TRIANGLES 6 GL_UNSIGNED_INT nullPtr
glBindVertexArray 0

And we're back to having a rectangle, but with 30% off on verticies used.

Wireframe Mode

Don't miss that little green box that talks about wire frame mode! By using glPolygonMode we can change the default draw of filling in the triangles to draw just the triangle lines instead.

glPolygonMode GL_FRONT_AND_BACK GL_LINE

Helper Abstractions

The same as we utilized bracket to make GLFW setup and tear down a little less error prone, there's a few key things we can do to make things less error prone in this lesson as well. First of all, we want that shader loading process cut down a lot. The primary input is a single String with the shader's source, and then it either works or we have some error message. All the stuff with allocating pointers and all that can be done without the caller having to know about it, and we can use the "with" variants of the allocating operations so that the cleanup is done automatically for us as well.

The only downside is that the function will be a little longer when we write it all out like that with error handling and such. But, since we only have to write it once, it's worth it. Since this will be both somewhat long and also very fiddly, we'll comment each step of the process as well.

-- | Given a shader type and a shader source, it gives you (Right id) of the
-- successfully compiled shader, or (Left err) with the error message. In the
-- error case, the shader id is deleted before the function returns to avoid
-- accidentally leaking shader objects.
loadShader :: GLenum -> String -> IO (Either String GLuint)
loadShader shaderType source = do
    -- new shader object
    shaderID <- glCreateShader shaderType
    -- assign the source to the shader object
    withCAStringLen source $ \(strP, strLen) ->
        withArray [strP] $ \linesPtrsPtr ->
            withArray [fromIntegral strLen] $ \lengthsPtr ->
                glShaderSource shaderID 1 linesPtrsPtr lengthsPtr
    -- compile and check success
    glCompileShader shaderID
    success <- alloca $ \successP -> do
        glGetShaderiv shaderID GL_COMPILE_STATUS successP
        peek successP
    if success == GL_TRUE
        -- success: we're done
        then return (Right shaderID)
        -- failure: we get the log, delete the shader, and return the log.
        else do
            -- how many bytes the info log should be (including the '\0')
            logLen <- alloca $ \logLenP -> do
                glGetShaderiv shaderID GL_INFO_LOG_LENGTH logLenP
                peek logLenP
            -- space for the info log
            logBytes <- allocaBytes (fromIntegral logLen) $ \logP -> do
                -- space for the log reading result
                alloca $ \resultP -> do
                    -- Try to obtain the log bytes
                    glGetShaderInfoLog shaderID logLen resultP logP
                    -- this is how many bytes we actually got
                    result <- fromIntegral <$> peek resultP
                    peekArray result logP
            -- delete the shader object and return the log
            glDeleteShader shaderID
            let prefix = case shaderType of
                    GL_VERTEX_SHADER -> "Vertex"
                    GL_GEOMETRY_SHADER -> "Geometry"
                    GL_FRAGMENT_SHADER -> "Fragment"
                    _ -> "Unknown Type"
            return $ Left $
                prefix ++ " Shader Error:" ++
                    (map (toEnum.fromEnum) logBytes)

In later versions of OpenGL there are additional shader types available, so at the bottom we make our code a little more flexible compatible by allowing for additional inputs without crashing.

Using this is pretty simple

-- vertex shader compile and load
eErrId <- loadShader GL_VERTEX_SHADER vertexShaderSource
vertexShader <- case eErrId of
    Left s -> putStrLn s >> return 0
    Right i -> return i

-- fragment shader compile and load
eErrId <- loadShader GL_FRAGMENT_SHADER fragmentShaderSource
fragmentShader <- case eErrId of
    Left s -> putStrLn s >> return 0
    Right i -> return i

Now we want a way to link two shaders and have the same error message deal going on. It's almost an identical function, but with slightly different names.

-- | Given a vertex shader object and a fragment shader object, this will link
-- them into a new program, giving you (Right id). If there's a linking error
-- the error log is retrieved, the program deleted, and (Left err) is returned.
linkProgram :: GLuint -> GLuint -> IO (Either String GLuint)
linkProgram vertexID fragmentID = do
    programID <- glCreateProgram
    glAttachShader programID vertexID
    glAttachShader programID fragmentID
    glLinkProgram programID
    success <- alloca $ \successP -> do
        glGetProgramiv programID GL_LINK_STATUS successP
        peek successP
    if success == GL_TRUE
        -- success: we're done
        then return (Right programID)
        -- failure: we get the log, delete the shader, and return the log.
        else do
            -- how many bytes the info log should be (including the '\0')
            logLen <- alloca $ \logLenP -> do
                glGetProgramiv programID GL_INFO_LOG_LENGTH logLenP
                peek logLenP
            -- space for the info log
            logBytes <- allocaBytes (fromIntegral logLen) $ \logP -> do
                -- space for the log reading result
                alloca $ \resultP -> do
                    -- Try to obtain the log bytes
                    glGetProgramInfoLog programID logLen resultP logP
                    -- this is how many bytes we actually got
                    result <- fromIntegral <$> peek resultP
                    peekArray result logP
            -- delete the program object and return the log
            glDeleteProgram programID
            return $ Left $ "Program Link Error: " ++
                (map (toEnum.fromEnum) logBytes)

And we can combine our steps fairly easily, but with care to make sure we always delete any created shader IDs before we return.

-- | Given the source for the vertex shader and the fragment shader, compiles
-- both and links them into a single program. If all of that is successful, the
-- intermediate shaders are deleted before the final value is returned.
programFromSources :: String -> String -> IO (Either String GLuint)
programFromSources vertexSource fragmentSource = do
    eitherVertShader <- loadShader GL_VERTEX_SHADER vertexSource
    case eitherVertShader of
        Left e -> return $ Left e
        Right vertShader -> do
            eitherFragShader <- loadShader GL_FRAGMENT_SHADER fragmentSource
            case eitherFragShader of
                Left e -> do
                    glDeleteShader vertShader
                    return $ Left e
                Right fragShader -> do
                    eitherProgram <- linkProgram vertShader fragShader
                    glDeleteShader vertShader
                    glDeleteShader fragShader
                    return $ eitherProgram

Final Code

To see all of this put together check out hello-triangle2.hs

results matching ""

    No results matching ""