[HOpenGL] Re: Open GL, GLUT
Sven Panne
Sven.Panne at aedion.de
Fri Jun 11 11:32:36 EDT 2004
[ redirected to hopengl mailing list ]
Gracjan Polak wrote:
>
> Hi all,
>
> I'd like to make some use of OpenGL with Haskell (under Win2000).
> Here is some code:
>
>
> module Main where
> import Graphics.Rendering.OpenGL.GL
> import Graphics.Rendering.OpenGL.GLU
> import Graphics.UI.GLUT
>
> main = do
> ver <- get gluVersion
> putStrLn ver
>
> getArgsAndInitialize
> fullScreen
> wnd <- createWindow "Hello World"
>
> vertex (Vertex2 (100::GLint) 100)
> return ()
>
> Compilation (linking) fails with:
>
> $ ghc --make openglapp.hs -o openglapp.exe
> Chasing modules from: openglapp.hs
> Compiling Main ( openglapp.hs, openglapp.o )
> Linking ...
> c:/ghc/ghc-6.2/libHSGLUT.a(Initialization__158.o)(.text+0x123):ghc16024.hc:
> unde
> fined reference to `glutInit at 8'
> c:/ghc/ghc-6.2/libHSGLUT.a(Window__61.o)(.text+0x33):ghc14736.hc:
> undefined refe
> rence to `glutFullScreen at 0'
> c:/ghc/ghc-6.2/libHSGLUT.a(Window__53.o)(.text+0x85):ghc14736.hc:
> undefined refe
> rence to `glutCreateWindow at 4'
>
> Manually adding -lglut -lglut32 does not help. Libraries libglut32.a and
> libglut.a are there, they contain needed symbols but with '_' prepended,
> like _glutInit at 8.
>
> Functions from GL and GLU link perfectly. They do even work correctly
> when run. Only GLUT ones do not :(
>
> Has anybody compiled anything for GL recently? Google pointed me only to
> some old, not relevant any more, material.
>
> Am I missing something obvious here?
>
> GHC 6.2, installer for Window taken from www.haskell.org, Win2000
> Professional.
It compiles fine with GHC 6.2.1 on my Win2k box, you might want to update your
GHC installation. There have been quite a few bug fixes, so it might be worth it
even when you are not using OpenGL/GLUT. Does it work with 6.2 when you add -O?
Just curious...
Apart from that, there are a few things you should change in your code:
* GL/GLU state can only be accessed after you have a rendering context, i.e.
after createWindow
* fullScreen only works when you have a current window, i.e. after createWindow
* Rendering should only be done in the display callback
* The vertex call should probably be within a renderPrimitive.
Perhaps Sven Panitz' tutorial might help a bit:
http://www.tfh-berlin.de/~panitz/hopengl/
A more up-to-date version of the tutorial is available from the fptools CVS repository,
but building it requires some unusual tools, BTW.
Cheers,
S.
More information about the HOpenGL
mailing list