|
From: shelarcy <she...@ca...> - 2004-04-07 11:58:25
|
On Sat, 3 Apr 2004 12:29:31 +0200, Daan Leijen <daa...@xs...>
wrote:
> I haven't used it myself as I haven't been able to get HOpenGL
> (the haskell binding to openGL) working yet on my windows machine.
>
> As such, using openGL with wxHaskell is still a bit experimental
> terrain. The best thing you can do is to ask Sean Seefried if you
> can send you his code so that you can see a specific example.
>
> The technology though is pretty straightforward: just create an
> openGL canvas and activate it -- after that, all openGL commands
> are directed to that window, whether you use HOpenGL or other
> openGL code.
I asked him show the simplist example, and I understood how to
work this.
I wrote redbook example, and I checked it out.
Thank you for you and him.
But I don't understand everything yet, so this isn't complete work.
Hide Window Once, then you see work it.
module Main
where
import Data.List ( transpose )
import Graphics.UI.WX
import Graphics.UI.WXCore
import qualified Graphics.Rendering.OpenGL as GL
import Graphics.Rendering.OpenGL
main = start gui
defaultWidth = 500
defaultHeight = 500
gui = do
f <- frame [ text := "Simple OpenGL" ]
glCanvas <- glCanvasCreateEx f 0 (Rect 0 0 defaultWidth defaultHeight)
0 "GLCanvas" [GL_RGBA] nullPalette
let glWidgetLayout = (fill . widget) glCanvas
Graphics.UI.WX.set f [ layout := glWidgetLayout
, on paint := paintGL
]
ctrlPoints :: [[Vertex3 GLfloat]]
ctrlPoints = [
[ Vertex3 (-1.5) (-1.5) 4.0, Vertex3 (-0.5) (-1.5) 2.0,
Vertex3 0.5 (-1.5) (-1.0), Vertex3 1.5 (-1.5) 2.0 ],
[ Vertex3 (-1.5) (-0.5) 1.0, Vertex3 (-0.5) (-0.5) 3.0,
Vertex3 0.5 (-0.5) 0.0, Vertex3 1.5 (-0.5) (-1.0) ],
[ Vertex3 (-1.5) 0.5 4.0, Vertex3 (-0.5) 0.5 0.0,
Vertex3 0.5 0.5 3.0, Vertex3 1.5 0.5 4.0 ],
[ Vertex3 (-1.5) 1.5 (-2.0), Vertex3 (-0.5) 1.5 (-2.0),
Vertex3 0.5 1.5 0.0, Vertex3 1.5 1.5 (-1.0) ]]
initlights :: IO ()
initlights = do
lighting $= Enabled
light (Light 0) $= Enabled
ambient (Light 0) $= Color4 0.2 0.2 0.2 1.0
GL.position (Light 0) $= Vertex4 0 0 2 1
materialDiffuse Front $= Color4 0.6 0.6 0.6 1.0
materialSpecular Front $= Color4 1.0 1.0 1.0 1.0
materialShininess Front $= 50
myInit :: IO ()
myInit = do
clearColor $= Color4 0 0 0 0
depthFunc $= Just Less
m <- newMap2 (0, 1) (0, 1) (transpose ctrlPoints)
map2 $= Just (m :: GLmap2 Vertex3 GLfloat)
autoNormal $= Enabled
mapGrid2 $= ((20, (0, 1)), (20, (0, 1 :: GLfloat)))
initlights -- for lighted version only
display = do
clear [ ColorBuffer, DepthBuffer ]
preservingMatrix $ do
rotate (85 :: GLfloat) (Vector3 1 1 1)
evalMesh2 Fill (0, 20) (0, 20)
flush
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
convWG (Graphics.UI.WX.Size w h) = (GL.Size (convInt32 w) (convInt32 h))
convInt32 = fromInteger . toInteger
paintGL :: DC() -> Graphics.UI.WX.Rect -> IO ()
paintGL dc rect = do
-- write your commands to do OpenGL things here.
myInit
display
reshape $ convWG $ rectSize rect
return ()
--
shelarcy <she...@ca...>
http://page.freett.com/shelarcy/
|