Difference between revisions of "GLFW"

From HaskellWiki
Jump to navigation Jump to search
m
(→‎More examples and external links: Added links to more examples)
 
(17 intermediate revisions by 6 users not shown)
Line 1: Line 1:
 
[[Category:Libraries]]
 
[[Category:Libraries]]
  +
[[Category:Graphics]]
  +
  +
Note: There are two GLFW hackage packages {{HackagePackage|id=GLFW}} and {{HackagePackage|id=GLFW-b}}. This article is about GLFW (except for bottom paragraph).
   
 
== About ==
 
== About ==
   
This is a Haskell module for [http://glfw.sourceforge.net GLFW OpenGL framework]. It provides an alternative to GLUT for OpenGL based Haskell programs.
+
This is a Haskell module for [http://www.glfw.org/ GLFW OpenGL framework]. It provides an alternative to GLUT for OpenGL based Haskell programs.
   
 
== Status ==
 
== Status ==
   
The library is being used by the [http://www.haskell.org/soe Haskell School of Expression (SOE)] code to render Graphics in a cross-platform manner. It currently interfaces with GLFW version 2.6, works on Windows, Linux (i386) and Mac OS X (both intel and ppc).
+
The library is being used by the [http://www.cs.yale.edu/homes/hudak/SOE/ Haskell School of Expression (SOE)] code to render Graphics in a cross-platform manner. It currently interfaces with GLFW version 2.7.2, works on Windows, Linux (i386) and Mac OS X.
   
GLFW itself is well documented (see [http://glfw.sourceforge.net GLFW website]), and the Haskell module API is documented via Haddock.
+
GLFW itself is well documented (see [http://www.glfw.org/ GLFW website]), and the Haskell module API is documented via Haddock.
   
 
Not all functions are fully tested, and there are still a
 
Not all functions are fully tested, and there are still a
Line 26: Line 29:
 
the SOE package for sample usage.
 
the SOE package for sample usage.
   
GLFW doesn't work well with GHC threads, forkIO or threadDelay.
+
GLFW may not work well with GHC threads, forkIO or threadDelay.
 
So avoid them if you can.
 
So avoid them if you can.
   
 
== Download ==
 
== Download ==
   
Current version is [http://hackage.haskell.org/cgi-bin/hackage-scripts/package/GLFW-0.3 GLFW-0.3]. It's a repackage to work with Cabal 1.2 or later. It now compiles GLFW C source code as part of the building process, please report to the package maintainer if you have build problems.
+
Current version is [http://hackage.haskell.org/cgi-bin/hackage-scripts/package/GLFW GLFW-0.5.0.0]. It works with Cabal 1.10 or later. It compiles GLFW C source code as part of the building process, please report to the package maintainer if you have build problems.
  +
  +
== More information ==
  +
* [http://hackage.haskell.org/packages/archive/GLFW/0.5.0.1/doc/html/Graphics-UI-GLFW.html The Haddock documentation]
  +
* [http://www.glfw.org/ The GLFW site]
   
 
== Sample Program ==
 
== Sample Program ==
Line 41: Line 48:
 
import Graphics.UI.GLFW as GLFW
 
import Graphics.UI.GLFW as GLFW
 
import Graphics.Rendering.OpenGL (($=))
 
import Graphics.Rendering.OpenGL (($=))
import Control.Concurrent
+
import Data.IORef
  +
import Control.Monad
  +
import System.Environment (getArgs, getProgName)
 
</haskell>
 
</haskell>
   
Line 50: Line 59:
 
</haskell>
 
</haskell>
   
The main program is mostly book-keeping such as initializing OpenGL and GLFW, create window, setup viewport, etc.
+
The main program is mostly book-keeping such as initializing OpenGL and GLFW, creating window, setting up viewport, etc.
   
 
<haskell>
 
<haskell>
 
main = do
 
main = do
  +
-- invoke either active or passive drawing loop depending on command line argument
  +
args <- getArgs
  +
prog <- getProgName
  +
case args of
  +
["active"] -> putStrLn "Running in active mode" >> main' active
  +
["passive"] -> putStrLn "Running in passive mode" >> main' passive
  +
_ -> putStrLn $ "USAGE: " ++ prog ++ " [active|passive]"
  +
  +
main' run = do
 
GLFW.initialize
 
GLFW.initialize
 
-- open window
 
-- open window
 
GLFW.openWindow (GL.Size 400 400) [GLFW.DisplayAlphaBits 8] GLFW.Window
 
GLFW.openWindow (GL.Size 400 400) [GLFW.DisplayAlphaBits 8] GLFW.Window
 
GLFW.windowTitle $= "GLFW Demo"
 
GLFW.windowTitle $= "GLFW Demo"
GL.shadeModel $= GL.Smooth
+
GL.shadeModel $= GL.Smooth
 
-- enable antialiasing
 
-- enable antialiasing
 
GL.lineSmooth $= GL.Enabled
 
GL.lineSmooth $= GL.Enabled
GL.blend $= GL.Enabled
+
GL.blend $= GL.Enabled
GL.blendFunc $= (GL.SrcAlpha, GL.OneMinusSrcAlpha)
+
GL.blendFunc $= (GL.SrcAlpha, GL.OneMinusSrcAlpha)
GL.lineWidth $= 1.5
+
GL.lineWidth $= 1.5
 
-- set the color to clear background
 
-- set the color to clear background
 
GL.clearColor $= Color4 0 0 0 0
 
GL.clearColor $= Color4 0 0 0 0
  +
 
-- set 2D orthogonal view inside windowSizeCallback because
 
-- set 2D orthogonal view inside windowSizeCallback because
 
-- any change to the Window size should result in different
 
-- any change to the Window size should result in different
 
-- OpenGL Viewport.
 
-- OpenGL Viewport.
GLFW.windowSizeCallback $= (\ size@(GL.Size w h) -> do
+
GLFW.windowSizeCallback $= \ size@(GL.Size w h) ->
  +
do
GL.viewport $= (GL.Position 0 0, size)
 
GL.matrixMode $= GL.Projection
+
GL.viewport $= (GL.Position 0 0, size)
GL.loadIdentity
+
GL.matrixMode $= GL.Projection
  +
GL.loadIdentity
GL.ortho2D 0 (realToFrac w) (realToFrac h) 0)
+
GL.ortho2D 0 (realToFrac w) (realToFrac h) 0
-- keep all line strokes as a list of points in a MVar
+
-- keep all line strokes as a list of points in an IORef
lines <- newMVar []
+
lines <- newIORef []
-- invoke the active drawing loop
+
-- run the main loop
active lines
+
run lines
 
-- finish up
 
-- finish up
 
GLFW.closeWindow
 
GLFW.closeWindow
Line 89: Line 109:
 
active lines = loop waitForPress
 
active lines = loop waitForPress
 
where
 
where
  +
 
loop action = do
 
loop action = do
 
-- draw the entire screen
 
-- draw the entire screen
Line 96: Line 117:
 
-- check whether ESC is pressed for termination
 
-- check whether ESC is pressed for termination
 
p <- GLFW.getKey GLFW.ESC
 
p <- GLFW.getKey GLFW.ESC
case p of
+
unless (p == GLFW.Press) $
GLFW.Press -> return ()
+
do
_ -> do
 
 
-- perform action
 
-- perform action
 
Action action' <- action
 
Action action' <- action
 
-- sleep for 1ms to yield CPU to other applications
 
-- sleep for 1ms to yield CPU to other applications
 
GLFW.sleep 0.001
 
GLFW.sleep 0.001
  +
-- loop with next action
 
loop action'
+
-- only continue when the window is not closed
  +
windowOpen <- getParam Opened
  +
unless (not windowOpen) $
 
loop action' -- loop with next action
   
 
waitForPress = do
 
waitForPress = do
Line 114: Line 137:
 
-- to lines and switch to waitForRelease action.
 
-- to lines and switch to waitForRelease action.
 
(GL.Position x y) <- GL.get GLFW.mousePos
 
(GL.Position x y) <- GL.get GLFW.mousePos
modifyMVar_ lines (return . ((x,y):) . ((x,y):))
+
modifyIORef lines (((x,y):) . ((x,y):))
 
return (Action waitForRelease)
 
return (Action waitForRelease)
  +
 
 
waitForRelease = do
 
waitForRelease = do
 
-- keep track of mouse movement while waiting for button
 
-- keep track of mouse movement while waiting for button
Line 122: Line 145:
 
(GL.Position x y) <- GL.get GLFW.mousePos
 
(GL.Position x y) <- GL.get GLFW.mousePos
 
-- update the line with new ending position
 
-- update the line with new ending position
modifyMVar_ lines (return . ((x,y):) . tail)
+
modifyIORef lines (((x,y):) . tail)
 
b <- GLFW.getMouseButton GLFW.ButtonLeft
 
b <- GLFW.getMouseButton GLFW.ButtonLeft
 
case b of
 
case b of
Line 141: Line 164:
 
-- disable auto polling in swapBuffers
 
-- disable auto polling in swapBuffers
 
GLFW.disableSpecial GLFW.AutoPollEvent
 
GLFW.disableSpecial GLFW.AutoPollEvent
  +
 
-- keep track of whether ESC has been pressed
 
-- keep track of whether ESC has been pressed
quit <- newMVar False
+
quit <- newIORef False
  +
 
-- keep track of whether screen needs to be redrawn
 
-- keep track of whether screen needs to be redrawn
dirty <- newMVar True
+
dirty <- newIORef True
  +
 
-- mark screen dirty in refresh callback which is often called
 
-- mark screen dirty in refresh callback which is often called
 
-- when screen or part of screen comes into visibility.
 
-- when screen or part of screen comes into visibility.
GLFW.windowRefreshCallback $= (modifyMVar_ dirty (\_ -> return False))
+
GLFW.windowRefreshCallback $= writeIORef dirty True
  +
 
-- use key callback to track whether ESC is pressed
 
-- use key callback to track whether ESC is pressed
GLFW.keyCallback $= (\k s ->
+
GLFW.keyCallback $= \k s ->
if fromEnum k == fromEnum GLFW.ESC && s == GLFW.Press
+
when (fromEnum k == fromEnum GLFW.ESC && s == GLFW.Press) $
then modifyMVar_ quit (\_ -> return True)
+
writeIORef quit True
else return ())
+
  +
-- Terminate the program if the window is closed
  +
GLFW.windowCloseCallback $= (writeIORef quit True >> return True)
  +
 
-- by default start with waitForPress
 
-- by default start with waitForPress
 
waitForPress dirty
 
waitForPress dirty
 
loop dirty quit
 
loop dirty quit
 
where
 
where
  +
 
loop dirty quit = do
 
loop dirty quit = do
 
GLFW.waitEvents
 
GLFW.waitEvents
 
-- redraw screen if dirty
 
-- redraw screen if dirty
d <- readMVar dirty
+
d <- readIORef dirty
  +
if d then (render lines >> GLFW.swapBuffers) else return ()
 
modifyMVar_ dirty (\_ -> False)
+
when d $
 
render lines >> GLFW.swapBuffers
  +
  +
writeIORef dirty False
 
-- check if we need to quit the loop
 
-- check if we need to quit the loop
q <- readMVar quit
+
q <- readIORef quit
if q then return () else loop dirty quit
+
unless q $
  +
loop dirty quit
waitForPress dirty = do
 
  +
GLFW.mousePosCallback $= (\_ -> return ())
 
 
waitForPress dirty =
GLFW.mouseButtonCallback $= (\b s ->
 
  +
do
if b == GLFW.ButtonLeft && s == GLFW.Press
 
then do
+
GLFW.mousePosCallback $= \_ -> return ()
  +
 
GLFW.mouseButtonCallback $= \b s ->
 
when (b == GLFW.ButtonLeft && s == GLFW.Press) $
 
do
 
-- when left mouse button is pressed, add the point
 
-- when left mouse button is pressed, add the point
 
-- to lines and switch to waitForRelease action.
 
-- to lines and switch to waitForRelease action.
 
(GL.Position x y) <- GL.get GLFW.mousePos
 
(GL.Position x y) <- GL.get GLFW.mousePos
modifyMVar_ lines (return . ((x,y):) . ((x,y):))
+
modifyIORef lines (((x,y):) . ((x,y):))
 
waitForRelease dirty
 
waitForRelease dirty
  +
else return ())
 
waitForRelease dirty = do
+
waitForRelease dirty =
  +
do
GLFW.mousePosCallback $= (\ (Position x y) -> do
 
 
GLFW.mousePosCallback $= \(Position x y) ->
  +
do
 
-- update the line with new ending position
 
-- update the line with new ending position
modifyMVar_ lines (return . ((x,y):) . tail)
+
modifyIORef lines (((x,y):) . tail)
 
-- mark screen dirty
 
-- mark screen dirty
modifyMVar_ dirty (\_ -> return True))
+
writeIORef dirty True
  +
GLFW.mouseButtonCallback $= (\b s ->
+
GLFW.mouseButtonCallback $= \b s ->
 
-- when left mouse button is released, switch back to
 
-- when left mouse button is released, switch back to
 
-- waitForPress action.
 
-- waitForPress action.
if b == GLFW.ButtonLeft && s == GLFW.Release
+
when (b == GLFW.ButtonLeft && s == GLFW.Release) $
then waitForPress dirty
+
waitForPress dirty
else return ())
 
 
</haskell>
 
</haskell>
   
Just replace <hask>active</hask> with <hask>passive</hask> in the <hask>main</hask> program to run the second approach.
+
Just replace <hask>active</hask> with <hask>passive</hask> in the <hask>main</hask> function to run the second approach.
   
 
The rest of the program goes below.
 
The rest of the program goes below.
Line 197: Line 237:
 
<haskell>
 
<haskell>
 
render lines = do
 
render lines = do
l <- readMVar lines
+
l <- readIORef lines
GL.clear [GL.ColorBuffer, GL.StencilBuffer]
+
GL.clear [GL.ColorBuffer]
 
GL.color $ color3 1 0 0
 
GL.color $ color3 1 0 0
GL.renderPrimitive GL.Lines $ foldr (>>) (return ()) (map
+
GL.renderPrimitive GL.Lines $ mapM_
(\ (x, y) -> GL.vertex (vertex3 (fromIntegral x) (fromIntegral y) 0)) l)
+
(\ (x, y) -> GL.vertex (vertex3 (fromIntegral x) (fromIntegral y) 0)) l
  +
   
vertex3 :: Float -> Float -> Float -> GL.Vertex3 Float
+
vertex3 :: GLfloat -> GLfloat -> GLfloat -> GL.Vertex3 GLfloat
 
vertex3 = GL.Vertex3
 
vertex3 = GL.Vertex3
  +
   
color3 :: Float -> Float -> Float -> GL.Color3 Float
+
color3 :: GLfloat -> GLfloat -> GLfloat -> GL.Color3 GLfloat
 
color3 = GL.Color3
 
color3 = GL.Color3
 
</haskell>
 
</haskell>
  +
  +
  +
== More examples and external links ==
  +
  +
A number of famous [http://nehe.gamedev.net/ NeHe OpenGL tutorials] have been translated into Haskell using [http://hackage.haskell.org/package/GLFW-b GLFW-b] (instead of GLFW) and made available in the [http://hackage.haskell.org/package/nehe-tuts nehe-tuts package] by Jason Dagit. Code as well as executables are available via the package page.
  +
  +
More examples:
  +
* [https://github.com/ScrambledEggsOnToast/tetris-hs tetris-hs]
  +
* [http://packdeps.haskellers.com/reverse/GLFW Reverse dependencies of the package GLFW]
  +
* [http://packdeps.haskellers.com/reverse/GLFW-b Reverse dependencies of the package GLFW-b]

Latest revision as of 21:44, 2 October 2014


Note: There are two GLFW hackage packages GLFW and GLFW-b. This article is about GLFW (except for bottom paragraph).

About

This is a Haskell module for GLFW OpenGL framework. It provides an alternative to GLUT for OpenGL based Haskell programs.

Status

The library is being used by the Haskell School of Expression (SOE) code to render Graphics in a cross-platform manner. It currently interfaces with GLFW version 2.7.2, works on Windows, Linux (i386) and Mac OS X.

GLFW itself is well documented (see GLFW website), and the Haskell module API is documented via Haddock.

Not all functions are fully tested, and there are still a few GLFW C functions missing from the Haskell module, namely the image loading functions. They are excluded because image handling is a separate issue, and low level buffer manipulation would obscure their use further. Texture loading from TGA format is supported both from file and from memory (via a string buffer)..

The Haskell module also provides basic text rendering while GLFW doesn't. It comes from a free 8x16 font which is made into a TGA texture, stored as a Haskell string in the file GLFW.hs. Text rendering is only possible with Alpha enabled. Again, see SOE.hs from the SOE package for sample usage.

GLFW may not work well with GHC threads, forkIO or threadDelay. So avoid them if you can.

Download

Current version is GLFW-0.5.0.0. It works with Cabal 1.10 or later. It compiles GLFW C source code as part of the building process, please report to the package maintainer if you have build problems.

More information

Sample Program

To demonstrate the usage of GLFW for OpenGL based Haskell applications, here is a sample program that allows user to draw lines by holding the left mouse button and move the mouse.

import Graphics.Rendering.OpenGL as GL
import Graphics.UI.GLFW as GLFW
import Graphics.Rendering.OpenGL (($=))
import Data.IORef
import Control.Monad
import System.Environment (getArgs, getProgName)

Because the program needs to process user input, i.e., mouse button and movements, we'll use a continuation like structure for this purpose. The Action type represents an IO operation that returns the next Action to continue execution.

data Action = Action (IO Action)

The main program is mostly book-keeping such as initializing OpenGL and GLFW, creating window, setting up viewport, etc.

main = do
  -- invoke either active or passive drawing loop depending on command line argument
  args <- getArgs
  prog <- getProgName
  case args of
    ["active"]  -> putStrLn "Running in active mode" >> main' active
    ["passive"] -> putStrLn "Running in passive mode" >> main' passive
    _ -> putStrLn $ "USAGE: " ++ prog ++ " [active|passive]"

main' run = do
  GLFW.initialize
  -- open window
  GLFW.openWindow (GL.Size 400 400) [GLFW.DisplayAlphaBits 8] GLFW.Window
  GLFW.windowTitle $= "GLFW Demo"
  GL.shadeModel    $= GL.Smooth
  -- enable antialiasing
  GL.lineSmooth $= GL.Enabled
  GL.blend      $= GL.Enabled
  GL.blendFunc  $= (GL.SrcAlpha, GL.OneMinusSrcAlpha)
  GL.lineWidth  $= 1.5
  -- set the color to clear background
  GL.clearColor $= Color4 0 0 0 0

  -- set 2D orthogonal view inside windowSizeCallback because
  -- any change to the Window size should result in different
  -- OpenGL Viewport.
  GLFW.windowSizeCallback $= \ size@(GL.Size w h) ->
    do
      GL.viewport   $= (GL.Position 0 0, size)
      GL.matrixMode $= GL.Projection
      GL.loadIdentity
      GL.ortho2D 0 (realToFrac w) (realToFrac h) 0
  -- keep all line strokes as a list of points in an IORef
  lines <- newIORef []
  -- run the main loop
  run lines
  -- finish up
  GLFW.closeWindow
  GLFW.terminate

There are usually two ways to structure the main loop of GLFW programs. One is by actively polling events before processing them. The screen buffer is usually redrawn every time before swapBuffers is called. This is the simplest main loop often seen in game applications, and may waste CPU cycles even when there is no visual update. Note that swapBuffers by default calls pollEvents implicitly, so there is no need to do a separate poll.

-- we start with waitForPress action
active lines = loop waitForPress
  where 
 
    loop action = do
      -- draw the entire screen
      render lines
      -- swap buffer
      GLFW.swapBuffers
      -- check whether ESC is pressed for termination
      p <- GLFW.getKey GLFW.ESC
      unless (p == GLFW.Press) $
        do
            -- perform action
            Action action' <- action
            -- sleep for 1ms to yield CPU to other applications
            GLFW.sleep 0.001

            -- only continue when the window is not closed
            windowOpen <- getParam Opened
            unless (not windowOpen) $
              loop action' -- loop with next action

    waitForPress = do
      b <- GLFW.getMouseButton GLFW.ButtonLeft
      case b of
        GLFW.Release -> return (Action waitForPress)
        GLFW.Press   -> do
          -- when left mouse button is pressed, add the point
          -- to lines and switch to waitForRelease action.
          (GL.Position x y) <- GL.get GLFW.mousePos 
          modifyIORef lines (((x,y):) . ((x,y):))
          return (Action waitForRelease)
 
    waitForRelease = do
        -- keep track of mouse movement while waiting for button 
        -- release
        (GL.Position x y) <- GL.get GLFW.mousePos
        -- update the line with new ending position
        modifyIORef lines (((x,y):) . tail)
        b <- GLFW.getMouseButton GLFW.ButtonLeft
        case b of
          -- when button is released, switch back back to 
          -- waitForPress action
          GLFW.Release -> return (Action waitForPress)
          GLFW.Press   -> return (Action waitForRelease)

Another way to structure the main loop is to register event callbacks and use waitEvents. This way we don't have to put the program to sleep every 1ms because it'll not be using any CPU cycle when there is no event to handle.

One reminder in this approach is that swapBuffers must be handled with care, because it by default invokes pollEvents, which in turn invokes all callback functions. So if swapBuffers is used inside a callback, it'll create infinite loop and hang the program. To avoid it, we should disable the AutoPollEvent behavior using disableSpecial.

Another optimization we can do is to use a dirty marker to remember whether the screen really needs to be redrawn. This'll not only save CPU cycles but also speed up event processing to avoid piling up events in the event queue. Similar tricks can be done to optimize the active polling approach.

passive lines = do
  -- disable auto polling in swapBuffers
  GLFW.disableSpecial GLFW.AutoPollEvent

  -- keep track of whether ESC has been pressed
  quit <- newIORef False

  -- keep track of whether screen needs to be redrawn
  dirty <- newIORef True

  -- mark screen dirty in refresh callback which is often called
  -- when screen or part of screen comes into visibility.
  GLFW.windowRefreshCallback $= writeIORef dirty True

  -- use key callback to track whether ESC is pressed
  GLFW.keyCallback $= \k s -> 
     when (fromEnum k == fromEnum GLFW.ESC && s == GLFW.Press) $ 
        writeIORef quit True
     
  -- Terminate the program if the window is closed
  GLFW.windowCloseCallback $= (writeIORef quit True >> return True)

  -- by default start with waitForPress
  waitForPress dirty
  loop dirty quit
  where
 
    loop dirty quit = do
        GLFW.waitEvents
        -- redraw screen if dirty
        d <- readIORef dirty

        when d $ 
          render lines >> GLFW.swapBuffers

        writeIORef dirty False
        -- check if we need to quit the loop
        q <- readIORef quit
        unless q $
          loop dirty quit
 
    waitForPress dirty =
      do
        GLFW.mousePosCallback    $= \_ -> return ()

        GLFW.mouseButtonCallback $= \b s -> 
            when (b == GLFW.ButtonLeft && s == GLFW.Press) $
              do
                -- when left mouse button is pressed, add the point
                -- to lines and switch to waitForRelease action.
                (GL.Position x y) <- GL.get GLFW.mousePos
                modifyIORef lines (((x,y):) . ((x,y):))
                waitForRelease dirty
 
    waitForRelease dirty = 
      do 
        GLFW.mousePosCallback $= \(Position x y) ->
          do
            -- update the line with new ending position
            modifyIORef lines (((x,y):) . tail)
            -- mark screen dirty
            writeIORef dirty True

        GLFW.mouseButtonCallback $= \b s ->
            -- when left mouse button is released, switch back to
            -- waitForPress action.
            when (b == GLFW.ButtonLeft && s == GLFW.Release) $
              waitForPress dirty

Just replace active with passive in the main function to run the second approach.

The rest of the program goes below.

render lines = do
  l <- readIORef lines
  GL.clear [GL.ColorBuffer]
  GL.color $ color3 1 0 0
  GL.renderPrimitive GL.Lines $ mapM_
      (\ (x, y) -> GL.vertex (vertex3 (fromIntegral x) (fromIntegral y) 0)) l
 

vertex3 :: GLfloat -> GLfloat -> GLfloat -> GL.Vertex3 GLfloat
vertex3 = GL.Vertex3
 

color3 :: GLfloat -> GLfloat -> GLfloat -> GL.Color3 GLfloat
color3 = GL.Color3


More examples and external links

A number of famous NeHe OpenGL tutorials have been translated into Haskell using GLFW-b (instead of GLFW) and made available in the nehe-tuts package by Jason Dagit. Code as well as executables are available via the package page.

More examples: