
Patrick Scheibe wrote:
/* remove back faces */ glDisable(GL_CULL_FACE); glEnable(GL_DEPTH_TEST); [...] In the HOpenGL Package (not the hOpenGL that comes with ghc!!) exists the command
enable DepthTest
I do not find a command like this in the ghc-opengl source. Is there one?
[ I cut-n-paste a bit from a previous mail on this list... :-) ] This is one of the design principles of the new API: Instead of separately setting a "cheap" aspect of the OpenGL state (here: the depth comparison function) and enabling/disabling the associated functionality (here: the depth test), a single state variable (here: depthFunc) of a Maybe type is used. So e.g. disabling the depth test is simply done by depthFunc $= Nothing or querying its state by df <- get depthFunc case df of Nothing -> ... -- the depth test is disabled Just func -> ... -- the depth test is enabled and func is used as the -- comparison function Therefore, what you are looking for is: depthFunc $= Just Less
Does it matter in what order I give the lightcommands? Or isn't it important when I give the "light (...) $= Enable" command at first.
No, this should not matter.
I attach my source and a pick of the output. [...]
I don't have wxHaskell installed currently, so I've quickly ported your example to GLUT (see attachment) with a few small changes: * Now culling is disabled and the depth function is enabled. * A reshape callback has been added and the projection matrix is set there. * A simple keyboard callback for exit has been added. * clearColor is set only once. Strangely enough, things work for me, see the attached picture. Does this GLUT program work on your platform? Does a 1:1 C GLUT program work? Cheers, S. module Main where import System.Exit import Graphics.Rendering.OpenGL.GL as GL import Graphics.Rendering.OpenGL.GLU as GLU import Graphics.UI.GLUT as GLUT glDisplay :: DisplayCallback glDisplay = do clear [ColorBuffer,DepthBuffer] GL.color (Color4 0.8 0.5 0.0 (1.0:: GLfloat)) preservingMatrix $ do rotate 5 (Vector3 0.0 1.0 (0.0::GLfloat)) GLUT.renderObject Solid (Sphere' 0.1 20 20) GL.color (Color4 0.0 0.1 0.8 (1.0:: GLfloat)) rotate 10 (Vector3 1.0 0.0 (0.0::GLfloat)) translate (Vector3 0.5 0.0 (-0.1::GLfloat)) GLUT.renderObject Solid (Cube 0.5) flush glInit :: IO () glInit = do clearColor $= (Color4 0.0 0.0 0.0 (1.0:: GLfloat)) cullFace $= Nothing depthFunc $= Just Less dither $= Enabled shadeModel $= Smooth hint PerspectiveCorrection $= Fastest hint PolygonSmooth $= Fastest GL.position (Light 0) $= (Vertex4 (-51.0) 51.0 (-2.0) 0.0) diffuse (Light 0) $= Color4 0.6 0.6 0.6 1.0 GL.position (Light 1) $= (Vertex4 51.0 51.0 (-2.0) 0.0) diffuse (Light 1) $= Color4 0.4 0.4 1.0 1.0 light (Light 0) $= Enabled light (Light 1) $= Enabled lighting $= Enabled colorMaterial $= Just (FrontAndBack, AmbientAndDiffuse) reshape :: ReshapeCallback reshape size@(Size w h) = do viewport $= (Position 0 0, size) matrixMode $= Projection loadIdentity GLU.perspective 60.0 1 1 20 GLU.lookAt (Vertex3 0.0 0.0 (-2)) (Vertex3 0.0 0.0 0.0) (Vector3 0.0 1.0 0.0) matrixMode $= Modelview 0 keyboard :: KeyboardMouseCallback keyboard (Char '\27') Down _ _ = exitWith ExitSuccess keyboard _ _ _ _ = return () main :: IO () main = do (progName, _args) <- getArgsAndInitialize initialWindowSize $= Size 500 500 initialDisplayMode $= [ SingleBuffered, RGBMode, WithDepthBuffer ] createWindow progName glInit displayCallback $= glDisplay keyboardMouseCallback $= Just keyboard mainLoop