Difference between revisions of "OpenGLTutorial1"

From HaskellWiki
Jump to navigation Jump to search
m (Reformatted compilation command)
 
(13 intermediate revisions by 4 users not shown)
Line 1: Line 1:
''This tutorial [http://blog.mikael.johanssons.org/archive/2006/09/opengl-programming-in-haskell-a-tutorial-part-1/] was originally written by Mikael Vejdemo Johansson, and was copied here with permission.''
+
''This tutorial [http://blog.mikael.johanssons.org/archive/2006/09/opengl-programming-in-haskell-a-tutorial-part-1/] was originally written by Mikael Vejdemo Johansson, and was copied here with permission. Parts of the tutorial have been modified and extended to keep it up to date.''
   
After having failed following the [http://www.cs.hs-rm.de/~panitz/hopengl/skript.html googled tutorial in HOpenGL programming], I thought I'd write down the steps I actually can get to work in a tutorial-like fashion. It may be a good idea to read this in parallell to the tutorial linked, since Panitz actually brings a lot of good explanations, even though his syntax isn't up to speed with the latest HOpenGL at all points.
+
After having failed following the [http://www.cs.hs-rm.de/~panitz/hopengl/skript.html googled tutorial in HOpenGL programming], I thought I'd write down the steps I actually can get to work in a tutorial-like fashion. It may be a good idea to read this in paralell to the tutorial linked, since Panitz actually brings a lot of good explanations, even though his syntax isn't up to speed with the latest HOpenGL at all points.
   
Note: GHCI interactive shell has problems running these program on some platforms (such as Mac OS X). <strong>Compile these programs with ghc, and run the generated executables.
+
Note: The OpenGL packages are part of the Haskell Platform, so you are ready to go if you have the HP already. Alas, on some platforms GHCi has problems running the following programs, so you might have to compile them with GHC and run the generated executables instead.
</strong>
 
   
 
==Hello World==
 
==Hello World==
First of all, we'll want to load the OpenGL libraries, throw up a window, and generally get to grips with what needs to be done to get a program running at all.
+
A minimal OpenGL program will need to load the OpenGL libraries and open a window. This is all you need to get an OpenGL program running.
  +
This is the skeleton that we'll be building on for the rest of this tutorial:
   
 
<haskell>
 
<haskell>
import Graphics.Rendering.OpenGL
 
 
import Graphics.UI.GLUT
 
import Graphics.UI.GLUT
  +
 
main :: IO ()
 
main = do
 
(progname, _) <- getArgsAndInitialize
 
createWindow "Hello World"
 
displayCallback $= flush
 
mainLoop
 
</haskell>
 
 
This code throws up a window, with a given title, and sets the main display function to do nothing but flush the (empty) graphics buffer. This is the skeleton that we'll be building on to.
 
 
Save it to HelloWorld.hs and compile it by running <hask>ghc -package GLUT HelloWorld.hs -o HelloWorld</hask>.
 
 
You will see a window open, with the title "Hello World", with either a blank canvas, or with some garbage graphics content pulled from somewhere in your system's graphics memory.
 
 
In either case, this program is profoundly worthless.
 
 
At a minimum, let's have our program display a clean blank canvas:
 
 
So we modify our code to the following:
 
 
<haskell>
 
import Graphics.Rendering.OpenGL
 
import Graphics.UI.GLUT
 
 
 
main :: IO ()
 
main :: IO ()
 
main = do
 
main = do
(progname, _) <- getArgsAndInitialize
+
(_progName, _args) <- getArgsAndInitialize
createWindow "Hello World"
+
_window <- createWindow "Hello World"
 
displayCallback $= display
 
displayCallback $= display
 
mainLoop
 
mainLoop
  +
 
display :: IO ()
+
display :: DisplayCallback
 
display = do
 
display = do
clear [ ColorBuffer ]; flush
+
clear [ ColorBuffer ]
  +
flush
  +
</haskell>
   
  +
Save it to HelloWorld.hs and load it into GHCi or compile it with GHC via <code>ghc --make HelloWorld.hs</code>. When you run the program, a new blank window open with the title "Hello World" will open.
</haskell>
 
  +
  +
This code creates a window and sets the main display function.
  +
<hask>getArgsAndInitialize</hask> initializes the OpenGL systems.
  +
<hask>createWindow</hask> opens the window; its argument is the title of the window.
  +
<hask>displayCallback</hask> controls the main display function for the current window.
   
  +
We use <hask>($=)</hask> to set it to our <hask>display</hask> function.
This defines a function "display" that calls a few OpenGL functions: "clear" to clear out the graphics color state (so we get a blank canvas), and "flush" to push our OpenGL commands down to the system graphics for actual display.
 
  +
<hask>mainLoop</hask> is where GLUT takes over, using our <hask>displayCallback</hask> to draw the contents of the window.
   
  +
This defines a function <hask>display</hask> that calls a few OpenGL functions.
We don't call "display" directly. (In fact, we don't call any graphics drawing functions directly). Instead, we set a display callback, and then call mainLoop. In mainLoop, OpenGL akes over, handles all the details of interacting with the OS and refreshing our window, calling our displayCallback to draw graphics.
 
  +
<hask>clear</hask> clears out the graphics color state (so we get a blank canvas).
  +
<hask>flush</hask> pushes our OpenGL commands down to the system graphics for actual display.
   
  +
===<code>displayCallback $= display</code>===
displayCallback is a Data.IORef (mutable state variable), which we set using a call to <hask>($=)</hask>.
 
  +
We don't call <hask>display</hask> directly. In fact, we don't call any graphics drawing functions directly.
  +
Instead we set a display callback, and then call <hask>mainLoop</hask>.
  +
In <hask>mainLoop</hask>, GLUT takes over.
  +
It handles all the details of interacting with the OS, refreshing our window, and calling our <hask>displayCallback</hask> to draw graphics.
   
  +
<hask>displayCallback</hask> is a globally defined StateVar (mutable state variable), which we set using a call to <hask>($=)</hask>.
Save this to the HelloWorld.hs, recompile, and rerun. This program displays an endless series of blank canvases (a solid blank image).
 
  +
In the OpenGL [http://hackage.haskell.org/packages/archive/OpenGL/latest/doc/html/Graphics-Rendering-OpenGL-GL-StateVar.html StateVar] module, there is a HasSetter type class and an StateVar implementation providing functions <hask>($=)</hask> (assignment) and <hask>get</hask> to facilitate interactions with these state variables.
   
  +
IORefs are StateVars, too:
The displayCallback is a globally defined IORef, which can be accessed through a host of functions defined in Data.IORef. In [http://hackage.haskell.org/packages/archive/OpenGL/2.2.2.0/doc/html/Graphics-Rendering-OpenGL-GL-StateVar.html OpenGL StateVar module], there is a HasSetter type class and an IORef implementation providing functions <hask>($=)</hask> (assignment) and <hask>get</hask> to fascilitate interactions with these state variables.
 
   
 
<haskell>
 
<haskell>
height = newIORef 1.0
+
do height <- newIORef 1.0
currentheight <- get height
+
currentHeight <- get height
height $= 1.5
+
height $= 1.5
 
</haskell>
 
</haskell>
   
Line 69: Line 59:
 
So, we have a window, we have a display callback that clears the canvas. Don't we want more out of it? Sure we do. So let's draw some things.
 
So, we have a window, we have a display callback that clears the canvas. Don't we want more out of it? Sure we do. So let's draw some things.
 
<haskell>
 
<haskell>
import Graphics.Rendering.OpenGL
 
 
import Graphics.UI.GLUT
 
import Graphics.UI.GLUT
  +
 
myPoints :: [(GLfloat,GLfloat,GLfloat)]
 
myPoints :: [(GLfloat,GLfloat,GLfloat)]
myPoints = map (\k -> (sin(2*pi*k/12),cos(2*pi*k/12),0.0)) [1..12]
+
myPoints = [ (sin (2*pi*k/12), cos (2*pi*k/12), 0) | k <- [1..12] ]
  +
main = do
 
  +
main :: IO ()
(progname, _) <- getArgsAndInitialize
 
  +
main = do
createWindow "Hello World"
 
  +
(_progName, _args) <- getArgsAndInitialize
  +
_window <- createWindow "Hello World"
 
displayCallback $= display
 
displayCallback $= display
 
mainLoop
 
mainLoop
  +
  +
display :: DisplayCallback
 
display = do
 
display = do
 
clear [ColorBuffer]
 
clear [ColorBuffer]
renderPrimitive Points $ mapM_ (\(x, y, z)->vertex$Vertex3 x y z) myPoints
+
renderPrimitive Points $
  +
mapM_ (\(x, y, z) -> vertex $ Vertex3 x y z) myPoints
 
flush
 
flush
 
</haskell>
 
</haskell>
   
Now, the important thing to notice in this code extract is that last line. It starts a rendering definition, gives the type to be rendered, and then a sequence of function calls, each of which adds a vertex to the rendering canvas. The statement is basically equivalent to something along the lines of
+
Now, the important thing to notice in this code extract is that <hask>renderPrimitive</hask> line. It starts a rendering definition, gives the kind of things to be rendered, and then a sequence of function calls, each of which adds a vertex to the rendering canvas. The statement is basically equivalent to something along the lines of
 
<haskell>
 
<haskell>
 
renderPrimitive Points do
 
renderPrimitive Points do
vertex Vertex3 ...
+
vertex (Vertex3 ...)
vertex Vertex3 ...
+
vertex (Vertex3 ...)
  +
...
 
</haskell>
 
</haskell>
 
for appropriate triples of coordinate values at the appropriate places. This results in the rendition here:
 
for appropriate triples of coordinate values at the appropriate places. This results in the rendition here:
Line 100: Line 96:
   
 
Each three coordinates following each other define a triangle. The last n mod 3 coordinates are ignored.
 
Each three coordinates following each other define a triangle. The last n mod 3 coordinates are ignored.
 
Keyword <code>Triangles</code>
 
   
 
===Triangle strips===
 
===Triangle strips===
 
[[image:OG-Trianglestrip.png]]
 
[[image:OG-Trianglestrip.png]]
   
Triangles are drawn according to a “moving window” of size three, so the two last coordinates in the previous triangle become the two first in the next triangle.
+
When using <code>TriangleStrip</code>, triangles are drawn according to a “moving window” of size three, so the two last coordinates in the previous triangle become the two first in the next triangle.
 
Keyword <code>TriangleStrip</code>
 
   
 
===Triangle fans===
 
===Triangle fans===
 
[[image:OG-Trianglesfan.png]]
 
[[image:OG-Trianglesfan.png]]
   
<code>TriangleFan</code>s have the first given coordinate as a basepoint, and takes each pair of subsequent coordinates to define a triangle together with the first coordinate.
+
When using a <code>TriangleFan</code>, the first given coordinate is used as a base point, and takes each pair of subsequent coordinates to define a triangle together with the first coordinate.
 
Keyword <code>TriangleFan</code>
 
   
 
===Lines===
 
===Lines===
Line 121: Line 111:
   
 
Each pair of coordinates define a line.
 
Each pair of coordinates define a line.
 
Keyword <code>Lines</code>
 
   
 
===Line loops===
 
===Line loops===
Line 128: Line 116:
   
 
With <code>LineLoop</code>, each further coordinate defines a line together with the last coordinate used. Once all coordinates are used up, an additional line is drawn back to the beginning.
 
With <code>LineLoop</code>, each further coordinate defines a line together with the last coordinate used. Once all coordinates are used up, an additional line is drawn back to the beginning.
 
Keyword <code>LineLoop</code>
 
   
 
===Line strips===
 
===Line strips===
 
[[image:OG-Linestrip.png]]
 
[[image:OG-Linestrip.png]]
   
<code>LineStrip</code>s are like <code>LineLoop</code>s, only without the last link added.
+
A <code>LineStrip</code> is like a <code>LineLoop</code>, only without the last link added.
 
Keyword <code>LineStrip</code>
 
   
 
===Quadrangles===
 
===Quadrangles===
Line 142: Line 126:
   
 
For the <code>Quads</code> keyword, each four coordinates given define a quadrangle.
 
For the <code>Quads</code> keyword, each four coordinates given define a quadrangle.
 
Keyword <code>Quads</code>
 
   
 
===Quadrangle strips===
 
===Quadrangle strips===
Line 150: Line 132:
 
And a <code>QuadStrip</code> works as the <code>TriangleStrip</code>, only the window is 4 coordinates wide and steps 2 steps each time, so each new pair of coordinates attaches a new quadrangle to the last edge of the last quadrangle.
 
And a <code>QuadStrip</code> works as the <code>TriangleStrip</code>, only the window is 4 coordinates wide and steps 2 steps each time, so each new pair of coordinates attaches a new quadrangle to the last edge of the last quadrangle.
   
  +
It is easier to understand what is going on when you see how the window is formed. Giving each coordinate a number, the QuadStrip is rendered as follows:
Keyword <code>QuadStrip</code>
 
  +
Coordinates 1, 2 and 4 are rendered as a triangle followed by coordinates 1, 3 and 4.
  +
Next coordinates 3, 4 and 6 are rendered as a triangle followed by coordinates 3, 5 and 6.
  +
  +
Rendering continues for as many coordinates that can be formed by that pattern.
   
 
===Polygon===
 
===Polygon===
Line 157: Line 143:
 
A <code>Polygon</code> is a filled line loop. Simple as that!
 
A <code>Polygon</code> is a filled line loop. Simple as that!
   
  +
===Using colors===
Keyword <code>Polygon</code>
 
 
 
There are more things we can do on our canvas than just spreading out coordinates. Within the command list constructed after a renderPrimitive, we can give several different commands that control what things are supposed to look like, so for instance we could use the following:
 
There are more things we can do on our canvas than just spreading out coordinates. Within the command list constructed after a renderPrimitive, we can give several different commands that control what things are supposed to look like, so for instance we could use the following:
 
<haskell>
 
<haskell>
display = do
+
display = do
  +
let color3f r g b = color $ Color3 r g (b :: GLfloat)
  +
vertex3f x y z = vertex $ Vertex3 x y (z :: GLfloat)
 
clear [ColorBuffer]
 
clear [ColorBuffer]
 
renderPrimitive Quads $ do
 
renderPrimitive Quads $ do
color $ (Color3 (1.0::GLfloat) 0 0)
+
color3f 1 0 0
vertex $ (Vertex3 (0::GLfloat) 0 0)
+
vertex3f 0 0 0
vertex $ (Vertex3 (0::GLfloat) 0.2 0)
+
vertex3f 0 0.2 0
vertex $ (Vertex3 (0.2::GLfloat) 0.2 0)
+
vertex3f 0.2 0.2 0
vertex $ (Vertex3 (0.2::GLfloat) 0 0)
+
vertex3f 0.2 0 0
  +
color $ (Color3 (0::GLfloat) 1 0)
 
vertex $ (Vertex3 (0::GLfloat) 0 0)
+
color3f 0 1 0
vertex $ (Vertex3 (0::GLfloat) (-0.2) 0)
+
vertex3f 0 0 0
vertex $ (Vertex3 (0.2::GLfloat) (-0.2) 0)
+
vertex3f 0 (-0.2) 0
vertex $ (Vertex3 (0.2::GLfloat) 0 0)
+
vertex3f 0.2 (-0.2) 0
color $ (Color3 (0::GLfloat) 0 1)
+
vertex3f 0.2 0 0
  +
vertex $ (Vertex3 (0::GLfloat) 0 0)
 
  +
color3f 0 0 1
vertex $ (Vertex3 (0::GLfloat) (-0.2) 0)
 
  +
vertex3f 0 0 0
vertex $ (Vertex3 ((-0.2)::GLfloat) (-0.2) 0)
 
vertex $ (Vertex3 ((-0.2)::GLfloat) 0 0)
+
vertex3f 0 (-0.2) 0
color $ (Color3 (1::GLfloat) 0 1)
+
vertex3f (-0.2) (-0.2) 0
vertex $ (Vertex3 (0::GLfloat) 0 0)
+
vertex3f (-0.2) 0 0
  +
vertex $ (Vertex3 (0::GLfloat) 0.2 0)
 
  +
color3f 1 0 1
vertex $ (Vertex3 ((-0.2::GLfloat)) 0.2 0)
 
vertex $ (Vertex3 ((-0.2::GLfloat)) 0 0)
+
vertex3f 0 0 0
  +
vertex3f 0 0.2 0
  +
vertex3f (-0.2) 0.2 0
  +
vertex3f (-0.2) 0 0
 
flush
 
flush
 
</haskell>
 
</haskell>
Line 190: Line 180:
 
[[image:OG-Colorsquares.png]]
 
[[image:OG-Colorsquares.png]]
   
where each color command sets the color for the next item drawn, and the vertex commands give vertices for the four squares.
+
where each color command sets the color for the next items drawn, and the vertex commands give vertices for the four squares.
   
 
==Callbacks - how we react to changes==
 
==Callbacks - how we react to changes==
We have already seen one callback in action: <code>displayCallback</code>. The Callbacks are state variables of the HOpenGL system, and are called in order to handle various things that may happen to the place the drawing canvas lives. For a first exercise, go resize the latest window you've used. Go on, do it now.
+
We have already seen one callback in action: <code>displayCallback</code>. The callbacks are state variables of the HOpenGL system, and are called in order to handle various things that may happen to the place the drawing canvas lives. For a first exercise, resize the latest window you've used. Go on, do it now.
   
 
I bet it looked ugly, didn't it?
 
I bet it looked ugly, didn't it?
   
This is because we have no code handling what to do if the window should suddenly change. Handling this is done in a callback, residing in the <code>IORef reshapeCallback</code>. Similarly, repainting is done in <code>displayCallback</code>, keyboard and mouse input is in <code>keyboardMouseCallback</code>, and so on. We can refer to the HOpenGL documentation for [http://hackage.haskell.org/packages/archive/GLUT/latest/doc/html/Graphics-UI-GLUT-Callbacks-Window.html window callbacks] and for [http://hackage.haskell.org/packages/archive/GLUT/latest/doc/html/Graphics-UI-GLUT-Callbacks-Global.html global callbacks]. Window callbacks are things like display, keyboard and mouse, and reshape. Global callbacks deal with timing issues (for those snazzy animations) and the menu interface systems.
+
This is because we have no code handling what to do if the window should suddenly change. Handling this is done in a callback, residing in the <code>reshapeCallback</code>. Similarly, repainting is done in <code>displayCallback</code>, keyboard and mouse input is in <code>keyboardMouseCallback</code>, and so on. We can refer to the HOpenGL documentation for [http://hackage.haskell.org/packages/archive/GLUT/latest/doc/html/Graphics-UI-GLUT-Callbacks-Window.html window callbacks] and for [http://hackage.haskell.org/packages/archive/GLUT/latest/doc/html/Graphics-UI-GLUT-Callbacks-Global.html global callbacks]. Window callbacks are things like display, keyboard and mouse, and reshape. Global callbacks deal with timing issues (for those snazzy animations) and the menu interface systems.
  +
  +
Some callbacks are not necessarily set, so those callback state variables contain a <hask>Maybe</hask>, where <hask>Nothing</hask> means that the corresponding callback is currently not set, i.e. disabled. If there is a callback, it is wrapped in <hask>Just</hask>. We'll add a callback for reshaping the window to our neat code, changing the main function to:
   
In order for a callback to possibly not be defined, most are typed within the <code>Maybe</code> monad, so by setting the state variable to <code>Nothing</code>, a callback can be disabled. Thus, setting callbacks is done using the keyword <code>Just</code>. We'll add a callback for reshaping the window to our neat code, changing the main function to:
 
 
<haskell>
 
<haskell>
main = do
+
main :: IO ()
  +
main = do
(progname, _) <- getArgsAndInitialize
 
  +
(_progName, _args) <- getArgsAndInitialize
createWindow "Hello World"
 
  +
_window <- createWindow "Hello World"
 
displayCallback $= display
 
displayCallback $= display
 
reshapeCallback $= Just reshape
 
reshapeCallback $= Just reshape
 
mainLoop
 
mainLoop
  +
reshape s@(Size w h) = do
 
  +
reshape :: ReshapeCallback
viewport $= (Position 0 0, s)
 
  +
reshape size = do
  +
viewport $= (Position 0 0, size)
 
postRedisplay Nothing
 
postRedisplay Nothing
 
</haskell>
 
</haskell>
Line 215: Line 209:
   
 
==Summary==
 
==Summary==
So, in conclusion, so far we can display a window, post basic callbacks to get the windowhandling to run smoothly, and draw in our window. Next installment of the tutorial will bring you 3d drawing, keyboard and mouse interactions, the incredible power of matrices and the ability to rotate 3d objects for your leisure. Possibly, we'll even look into animations.
+
So, in conclusion, so far we can display a window, post basic callbacks to get the window handling to run smoothly, and draw in our window. Next installment of the tutorial will bring you 3D drawing, keyboard and mouse interactions, the incredible power of matrices and the ability to rotate 3D objects for your leisure. Possibly, we'll even look into animations.
   
 
[[OpenGLTutorial2|Continue with part 2]]
 
[[OpenGLTutorial2|Continue with part 2]]

Latest revision as of 09:22, 20 September 2013

This tutorial [1] was originally written by Mikael Vejdemo Johansson, and was copied here with permission. Parts of the tutorial have been modified and extended to keep it up to date.

After having failed following the googled tutorial in HOpenGL programming, I thought I'd write down the steps I actually can get to work in a tutorial-like fashion. It may be a good idea to read this in paralell to the tutorial linked, since Panitz actually brings a lot of good explanations, even though his syntax isn't up to speed with the latest HOpenGL at all points.

Note: The OpenGL packages are part of the Haskell Platform, so you are ready to go if you have the HP already. Alas, on some platforms GHCi has problems running the following programs, so you might have to compile them with GHC and run the generated executables instead.

Hello World

A minimal OpenGL program will need to load the OpenGL libraries and open a window. This is all you need to get an OpenGL program running. This is the skeleton that we'll be building on for the rest of this tutorial:

import Graphics.UI.GLUT
 
main :: IO ()
main = do
  (_progName, _args) <- getArgsAndInitialize
  _window <- createWindow "Hello World"
  displayCallback $= display
  mainLoop
 
display :: DisplayCallback
display = do
  clear [ ColorBuffer ]
  flush

Save it to HelloWorld.hs and load it into GHCi or compile it with GHC via ghc --make HelloWorld.hs. When you run the program, a new blank window open with the title "Hello World" will open.

This code creates a window and sets the main display function. getArgsAndInitialize initializes the OpenGL systems. createWindow opens the window; its argument is the title of the window. displayCallback controls the main display function for the current window.

We use ($=) to set it to our display function. mainLoop is where GLUT takes over, using our displayCallback to draw the contents of the window.

This defines a function display that calls a few OpenGL functions. clear clears out the graphics color state (so we get a blank canvas). flush pushes our OpenGL commands down to the system graphics for actual display.

displayCallback $= display

We don't call display directly. In fact, we don't call any graphics drawing functions directly. Instead we set a display callback, and then call mainLoop. In mainLoop, GLUT takes over. It handles all the details of interacting with the OS, refreshing our window, and calling our displayCallback to draw graphics.

displayCallback is a globally defined StateVar (mutable state variable), which we set using a call to ($=). In the OpenGL StateVar module, there is a HasSetter type class and an StateVar implementation providing functions ($=) (assignment) and get to facilitate interactions with these state variables.

IORefs are StateVars, too:

do height <- newIORef 1.0
   currentHeight <- get height
   height $= 1.5

Using the drawing canvas

So, we have a window, we have a display callback that clears the canvas. Don't we want more out of it? Sure we do. So let's draw some things.

import Graphics.UI.GLUT

myPoints :: [(GLfloat,GLfloat,GLfloat)]
myPoints = [ (sin (2*pi*k/12), cos (2*pi*k/12), 0) | k <- [1..12] ]

main :: IO ()
main = do
  (_progName, _args) <- getArgsAndInitialize
  _window <- createWindow "Hello World"
  displayCallback $= display
  mainLoop

display :: DisplayCallback
display = do 
  clear [ColorBuffer]
  renderPrimitive Points $
     mapM_ (\(x, y, z) -> vertex $ Vertex3 x y z) myPoints
  flush

Now, the important thing to notice in this code extract is that renderPrimitive line. It starts a rendering definition, gives the kind of things to be rendered, and then a sequence of function calls, each of which adds a vertex to the rendering canvas. The statement is basically equivalent to something along the lines of

renderPrimitive Points do
  vertex (Vertex3 ...)
  vertex (Vertex3 ...)
  ...

for appropriate triples of coordinate values at the appropriate places. This results in the rendition here:

OG-Points.png

We can replace Points with other primitives, leading to the rendering of:

Triangles

OG-Triangles.png

Each three coordinates following each other define a triangle. The last n mod 3 coordinates are ignored.

Triangle strips

OG-Trianglestrip.png

When using TriangleStrip, triangles are drawn according to a “moving window” of size three, so the two last coordinates in the previous triangle become the two first in the next triangle.

Triangle fans

OG-Trianglesfan.png

When using a TriangleFan, the first given coordinate is used as a base point, and takes each pair of subsequent coordinates to define a triangle together with the first coordinate.

Lines

OG-Lines.png

Each pair of coordinates define a line.

Line loops

OG-Lineloop.png

With LineLoop, each further coordinate defines a line together with the last coordinate used. Once all coordinates are used up, an additional line is drawn back to the beginning.

Line strips

OG-Linestrip.png

A LineStrip is like a LineLoop, only without the last link added.

Quadrangles

OG-Quad.png

For the Quads keyword, each four coordinates given define a quadrangle.

Quadrangle strips

OG-Quadstrip.png

And a QuadStrip works as the TriangleStrip, only the window is 4 coordinates wide and steps 2 steps each time, so each new pair of coordinates attaches a new quadrangle to the last edge of the last quadrangle.

It is easier to understand what is going on when you see how the window is formed. Giving each coordinate a number, the QuadStrip is rendered as follows: Coordinates 1, 2 and 4 are rendered as a triangle followed by coordinates 1, 3 and 4. Next coordinates 3, 4 and 6 are rendered as a triangle followed by coordinates 3, 5 and 6.

Rendering continues for as many coordinates that can be formed by that pattern.

Polygon

OG-Polygon.png

A Polygon is a filled line loop. Simple as that!

Using colors

There are more things we can do on our canvas than just spreading out coordinates. Within the command list constructed after a renderPrimitive, we can give several different commands that control what things are supposed to look like, so for instance we could use the following:

display = do
  let color3f r g b = color $ Color3 r g (b :: GLfloat)
      vertex3f x y z = vertex $ Vertex3 x y (z :: GLfloat)
  clear [ColorBuffer]
  renderPrimitive Quads $ do
    color3f 1 0 0
    vertex3f 0 0 0
    vertex3f 0 0.2 0
    vertex3f 0.2 0.2 0
    vertex3f 0.2 0 0

    color3f 0 1 0
    vertex3f 0 0 0
    vertex3f 0 (-0.2) 0
    vertex3f 0.2 (-0.2) 0
    vertex3f 0.2 0 0

    color3f 0 0 1
    vertex3f 0 0 0
    vertex3f 0 (-0.2) 0
    vertex3f (-0.2) (-0.2) 0
    vertex3f (-0.2) 0 0

    color3f 1 0 1
    vertex3f 0 0 0
    vertex3f 0 0.2 0
    vertex3f (-0.2) 0.2 0
    vertex3f (-0.2) 0 0
  flush

in order to produce these four coloured squares:

OG-Colorsquares.png

where each color command sets the color for the next items drawn, and the vertex commands give vertices for the four squares.

Callbacks - how we react to changes

We have already seen one callback in action: displayCallback. The callbacks are state variables of the HOpenGL system, and are called in order to handle various things that may happen to the place the drawing canvas lives. For a first exercise, resize the latest window you've used. Go on, do it now.

I bet it looked ugly, didn't it?

This is because we have no code handling what to do if the window should suddenly change. Handling this is done in a callback, residing in the reshapeCallback. Similarly, repainting is done in displayCallback, keyboard and mouse input is in keyboardMouseCallback, and so on. We can refer to the HOpenGL documentation for window callbacks and for global callbacks. Window callbacks are things like display, keyboard and mouse, and reshape. Global callbacks deal with timing issues (for those snazzy animations) and the menu interface systems.

Some callbacks are not necessarily set, so those callback state variables contain a Maybe, where Nothing means that the corresponding callback is currently not set, i.e. disabled. If there is a callback, it is wrapped in Just. We'll add a callback for reshaping the window to our neat code, changing the main function to:

main :: IO ()
main = do
  (_progName, _args) <- getArgsAndInitialize
  _window <- createWindow "Hello World"
  displayCallback $= display
  reshapeCallback $= Just reshape
  mainLoop

reshape :: ReshapeCallback
reshape size = do
  viewport $= (Position 0 0, size)
  postRedisplay Nothing

Here, the code for the reshape function resizes the viewport so that our drawing area contains the entire new window. After setting the new viewport, it also tells the windowing system that something has happened to the window, and that therefore, the display function should be called.

Summary

So, in conclusion, so far we can display a window, post basic callbacks to get the window handling to run smoothly, and draw in our window. Next installment of the tutorial will bring you 3D drawing, keyboard and mouse interactions, the incredible power of matrices and the ability to rotate 3D objects for your leisure. Possibly, we'll even look into animations.

Continue with part 2