|
From: Patrick S. <mai...@st...> - 2005-01-11 00:35:03
|
Hi,
A friend of mine helped me solving the problem.
It was really confusing. I just added any printouts in the display function of
opengl and found out that wxhaskell called this display func. But why should
it be called and even though nothing appeared in the frame.
We figured out that it is probably the best way to have a look at the GTK
opengl sample. So we changed some lines in the source relating to the c++
sample code.
I won't have time to find some more out but here is the modified sample that
runs on our machines.. (mainly for Mike who wants the news)
It shows just a white square on a black background. Compilation with
ghc -package wx -package OpenGL foobar.hs
Cheers
Patrick
module Main
where
import Graphics.Rendering.OpenGL
import qualified Graphics.UI.WX as WX
import qualified Graphics.Rendering.OpenGL as GL
main = start gui
convWG (WX.Size w h) = (GL.Size (convInt32 w) (convInt32 h))
convInt32 = fromInteger . toInteger
gui = do
f <- frame [ text := "Simple OpenGL" ]
glCanvas <- glCanvasCreateEx f 0 (Rect 0 0 200 200)
0 "GLCanvas" [GL_RGBA] nullPalette
initme glCanvas
let glWidgetLayout = (fill . widget) glCanvas
WX.set f [ on paintRaw := paintGL glCanvas
, layout := glWidgetLayout
]
paintGL :: GLCanvas a -> DC() -> WX.Rect -> [WX.Rect] -> IO ()
paintGL canvas dc rect _ = do
reshape $ convWG $ rectSize rect
display canvas
return ()
initme :: GLCanvas a -> IO ()
initme canvas = do
glCanvasSetCurrent canvas
display canvas = do
clear [ ColorBuffer]
preservingMatrix $ do
stdQuad
putStrLn "Display"
flush
glCanvasSwapBuffers canvas
reshape size@(GL.Size w h) = do
viewport $= (Position 0 0, size)
matrixMode $= Projection
loadIdentity
let wf = fromIntegral w
hf = fromIntegral h
if w <= h
then ortho (-4.0) 4.0 (-4.0*hf/wf) (4.0*hf/wf) (-4.0) 4.0
else ortho (-4.0*wf/hf) (4.0*wf/hf) (-4.0) 4.0 (-4.0) 4.0
matrixMode $= Modelview 0
loadIdentity
vertex3f :: Vertex3 GLfloat -> IO ()
vertex3f = vertex :: Vertex3 GLfloat -> IO ()
stdQuad :: IO ()
stdQuad = do
renderPrimitive Polygon $ mapM_ vertex3f [
Vertex3 0 0 0,
Vertex3 0 1 0,
Vertex3 1 1 0,
Vertex3 1 0 0
]
On Tuesday 04 January 2005 19:58, Mike Gunter wrote:
> Too bad. Do let me know if you figure this out.
>
> thanks,
> mike
>
> Patrick Scheibe <mai...@st...> writes:
> > Hi,
> >
> > I try to run the GLCanvas sample from the source of wxHaskell and the
> > only thing I get is a blank screen. Mike said I should try to recompile
> > all stuff (wxGTK and wxHaskell) with the --with-opengl option.
> > But this was what I did in the first time. The opengl sample in the wxGTK
> > source (penguin and so on) runs perfectly.
> > I can compile wxHaskell with opengl without any error.
> > But the sample shows just the blank screen.
> >
> > I figured out that it doesn't matter when I don't give the -package
> > OpenGL option to ghc. The sample compiles without error and runs in the
> > same way. Does wxHaskell add the Gl libs itself?
> >
> > Has anybody a compiled wxhaskell where this sample runs and can he help
> > me by showing his configuration of ghc, gtk, wxgkt, glib, wxhaskell, ...
> > I have a running SuSe distribution.
> >
> > Cheers
> > Patrick
> >
> > On Monday 03 January 2005 19:50, Mike Gunter wrote:
> >> I was seeing the same behavior. Responding to my question, Sean
> >> Seefried pointed out that both wxWidgets and wxHaskell must be built
> >> with OpenGL support (by passing --with-opengl to their configure
> >> scripts). I haven't had time to determine if that's the issue for me.
> >> Perhaps it is for you? (If you do figure out why you're seeing the
> >> behavior you are, please let me know ...)
> >>
> >> mike
|