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 [EMAIL PROTECTED]'
c:/ghc/ghc-6.2/libHSGLUT.a(Window__61.o)(.text+0x33):ghc14736.hc: undefined refe
rence to [EMAIL PROTECTED]'
c:/ghc/ghc-6.2/libHSGLUT.a(Window__53.o)(.text+0x85):ghc14736.hc: undefined refe
rence to [EMAIL PROTECTED]'
Manually adding -lglut -lglut32 does not help. Libraries libglut32.a and libglut.a are there, they contain needed symbols but with '_' prepended, like [EMAIL PROTECTED]
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.
-- Gracjan
_______________________________________________ Glasgow-haskell-users mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/glasgow-haskell-users