[HOpenGL] -O strangeness
Robert Vollmert
rvollmert@gmx.net
Thu, 7 Mar 2002 15:05:13 +0000
--wac7ysb48OaltWcw
Content-Type: text/plain; charset=us-ascii
Content-Disposition: inline
Hello,
I've been experimenting with HOpenGL a little, and have run into
strange behaviour when compiling with -O. In particular, while things
work as expected when compiling normally, if I compile the following
module with -O, drawLine' appears to scale the line by 2, while
drawLine works as before.
module Lines where
import GL
drawLine = do
pushMatrix
beginEnd Lines . sequence_ . map vertex $
[ Vertex2 0 0, Vertex2 0 (1::GLfloat) ]
popMatrix
drawLine' = do
pushMatrix
scale 1 1 (1::GLfloat)
beginEnd Lines . sequence_ . map vertex $
[ Vertex2 0 0, Vertex2 0 (1::GLfloat) ]
popMatrix
This was tested using the attached program. I'm using HOpenGL-1.01
with the recent patch, and a ghc from CVS which is about a week old.
When compiling Lines.hs with -O, I get
/tmp/ghc14725.hc: In function `s8Wy_ret':
/tmp/ghc14725.hc:474: warning: implicit declaration of function `glScalef'
Also, if I actually compile the test program with -O, it doesn't
display anything.
--wac7ysb48OaltWcw
Content-Type: text/plain; charset=us-ascii
Content-Disposition: attachment; filename="Test2.hs"
import GL
import GLU
import GLUT
import System(ExitCode(..), exitWith)
import Lines
display :: DisplayAction
display = do
clear [ ColorBufferBit ]
loadIdentity
color (Color3 1.0 0.0 (0.0::GLfloat))
translate $ Vector3 1 1 (0::GLfloat)
drawLine
translate $ Vector3 1 0 (0::GLfloat)
drawLine'
flush
myInit :: IO ()
myInit = do
clearColor (Color4 0 0 0 0)
matrixMode Projection
loadIdentity
ortho 0 3 0 4 (-1) 1
matrixMode Modelview
keyboard :: KeyboardAction
keyboard '\27' _ = exitWith ExitSuccess
keyboard 'q' _ = exitWith ExitSuccess
main :: IO ()
main = do
GLUT.init Nothing
createWindow "mine test" (return ()) [ GLUT.Single, GLUT.Rgb ]
Nothing
(Just (WindowSize 320 240))
myInit
keyboardFunc (Just keyboard)
displayFunc display
mainLoop
--wac7ysb48OaltWcw--