Ro/Haskell/OpenGL

From HaskellWiki
< Ro/Haskell
Revision as of 23:30, 22 January 2010 by Ha$kell (talk | contribs)
Jump to navigation Jump to search
The printable version is no longer supported and may have rendering errors. Please update your browser bookmarks and please use the default browser print function instead.

Open GL Resources (ro)

. Pentru cei care nu au curajul sa se apuce de OpenGL in Haskell

cat_umbrella.png Descarcati si jucati Raincat http://raincat.bysusanlin.com/

Uitati-va nitel si prin arhiva windows ca sa vedeti din ce se compune o astfel de aplicatie.

Download: Raincat 4 Windows: http://stage.gamecreation.org/raincat/raincat.win32.zip

Download: Raincat 4 Linux: http://stage.gamecreation.org/raincat/raincat.linux.tar.gz

Sursele in Haskell: http://www.gamecreation.org/file_download/18/raincat-source.zip

. Cum sa va pregatiti de lucru

Instalati The Haskell Platform pe Windows. http://hackage.haskell.org/platform/ Sau varianta 2009.2.0.2 direct de aici http://hackage.haskell.org/platform/2009.2.0.2/HaskellPlatform-2009.2.0.2-setup.exe

. Un prim exemplu luati dintre exemplele din RedBook

Ati putea incepe cu torul Torus.hs


{-
   Torus.hs (adapted from torus.c which is (c) Silicon Graphics, Inc.)
   Copyright (c) Sven Panne 2002-2006 <sven.panne@aedion.de>
   This file is part of HOpenGL and distributed under a BSD-style license
   See the file libraries/GLUT/LICENSE

   This program demonstrates the creation of a display list.
-}

import Data.Char ( toLower )
import Data.IORef ( IORef, newIORef )
import System.Exit ( exitWith, ExitCode(ExitSuccess) )
import Graphics.UI.GLUT

data State = State { spinX, spinY :: IORef GLfloat }

makeState :: IO State
makeState = do
   x <- newIORef 0
   y <- newIORef 0
   return $ State { spinX = x, spinY = y }

torus :: Int -> Int -> IO ()
torus numC numT = do
   let stepC = 2 * pi / fromIntegral numC :: GLfloat
       stepT = 2 * pi / fromIntegral numT
   flip mapM_ [ 0 .. numC - 1 ] $ \i ->
      renderPrimitive QuadStrip $
         flip mapM_ [ 0 .. numT ] $ \j ->
            flip mapM_ [ 1, 0 ] $ \k -> do
               let s = (fromIntegral ((i + k) `mod` numC) + 0.5) * stepC
                   t = (fromIntegral (      j `mod` numT)      ) * stepT
                   x = (1 + 0.1 * cos s) * cos t
                   y = (1 + 0.1 * cos s) * sin t
                   z =      0.1 * sin s
               vertex (Vertex3 x y z)

myInit :: IO DisplayList
myInit = do
   theTorus <- defineNewList Compile $
      torus 8 25
   shadeModel $= Flat
   clearColor $= Color4 0 0 0 0
   return theTorus

display :: State -> DisplayList -> DisplayCallback
display state theTorus = do
   clear [ ColorBuffer ]
   loadIdentity
   lookAt (Vertex3 0 0 10) (Vertex3 0 0 0) (Vector3 0 1 0)
   x <- get (spinX state)
   rotate x (Vector3 1 0 0)
   y <- get (spinY state)
   rotate y (Vector3 0 1 0)
   color (Color3 1 1 (1 :: GLfloat))
   callList theTorus
   flush

reshape :: ReshapeCallback
reshape size@(Size w h) = do
   viewport $= (Position 0 0, size)
   matrixMode $= Projection
   loadIdentity
   perspective  30 (fromIntegral w / fromIntegral h) 1 100
   matrixMode $= Modelview 0

incSpin :: IORef GLfloat -> IO ()
incSpin spinRef = do
   let wrap n s = if s > n then s - n else s
   spinRef $~ (wrap 360 . (+ 30))
   postRedisplay Nothing

keyboard :: State -> KeyboardMouseCallback
keyboard state (Char c) Down _ _ = case toLower c of
   'x'   -> incSpin (spinX state)
   'y'   -> incSpin (spinY state)
   'i'   -> do spinX state $= 0; spinY state $= 0; postRedisplay Nothing
   '\27' -> exitWith ExitSuccess
   _     -> return ()
keyboard _ _ _ _ _ = return ()

main :: IO ()
main = do
   (progName, _args) <- getArgsAndInitialize
   initialDisplayMode $= [ SingleBuffered, RGBMode ]
   initialWindowSize $= Size 200 200
   createWindow progName
   state <- makeState
   theTorus <- myInit
   reshapeCallback $= Just reshape
   keyboardMouseCallback $= Just (keyboard state)
   displayCallback $= display state theTorus
   mainLoop

Torus.hs

A fost disponibil la:

http://darcs.haskell.org/packages/GLUT/examples/RedBook/Torus.hs

Compilati-l folosind comanda:

ghc --make Torus.hs -package GLUT -o Torus.exe - pentru a produce Exe-uri sau ghc --make -package GLUT Torus.hs - pentru a produce executabile Linux (am testat cu GHC6 sub Ubuntu Linux 9.10 - Versiunea GNOME)

Alternativ, puteti da click pe fisierul .hs iar la prompterul GHCI puteti scrie main sau main()

Mariti fereastra aplicatiei si "rotiti" torul in jurul diverselor axe cu tastele "x" si "y". Ce alte taste mai puteti folosi...scrie in codul sursa.

Nu uitati sa copiati: glut32.dll -ul in directorul proiectului. Unde il gasiti ? Nu stiti ? Reveniti la punctul 1.

Nu uitati sa instalati pachetele cu GLUT , GL (fara versiunea 3), FreeGlut etc si tot ce mai e necesar, inclusiv acele pachete cu GL sau GLUT si DRI (Dri = Direct rendering interface, asigura rendering prin suportul hardware). Le gasiti cu programul de instalare de pachete ori cautand: ghc, GL, GLU, GLUT, FreeGlut , DRI. Pentru Raincat v-ar trebui si SDL.

. Urmatoarele ar putea fi

Cube. - fara comentarii

Planet. - folositi tasta y pentru a misca satelitul in jurul planetei. Puteti face din satelit o nava spatiala ca in Star Wars ? Ii mai lipsesc doar aripile.

Teapots. - frumoase si colorate. Va dau o idee cam ce poate face OpenGL.


Haskell-Teapots.png
Teapots.hs rulind sub Ubuntu 9.10 Linux - compilat cu GHC6

Texture3D. - vedeti cum arata, tot color.

Robot - un brat de robot, articulat. Cine face o palma intreaga cu toate cele 5 degete ? E simplu!

dan2@dans2-laptop:~$ ghc --make -package GLUT Cube.hs
[1 of 1] Compiling Main             ( Cube.hs, Cube.o )
Linking Cube ...
dan2@dans2-laptop:~$ ./Cube
dan2@dans2-laptop:~$ ghc --make -package GLUT Planet.hs
[1 of 1] Compiling Main             ( Planet.hs, Planet.o )
Linking Planet ...
dan2@dans2-laptop:~$ ./Planet
dan2@dans2-laptop:~$ ghc --make -package GLUT Teapots.hs
[1 of 1] Compiling Main             ( Teapots.hs, Teapots.o )
Linking Teapots ...
dan2@dans2-laptop:~$ ./Teapots
dan2@dans2-laptop:~$ ghc --make -package GLUT Texture3D.hs
[1 of 1] Compiling Main             ( Texture3D.hs, Texture3D.o )
Linking Texture3D ...
dan2@dans2-laptop:~$ ./Texture3D
dan2@dans2-laptop:~$ ghc --make -package GLUT Robot.hs
[1 of 1] Compiling Main             ( Robot.hs, Robot.o )
Linking Robot ...
dan2@dans2-laptop:~$ ./Robot


.Pregatiti-va sa cititi o carte despre OpenGL

stiind ca el

- este doar un mediu grafic pentru afisare 3D, gestiunea datelor despre obiectele din spatiul 3D ramane programatorului

- trebuie sa-i furnizati - ca unui joc - functii pentru ecran si tastatura si apoi sa activati motorul grafic

- are mai multe moduri de lucru: (Display, Matrix etc. aici mai am de povestit...paragraf in lucru.)

- totdeauna se recomanda sa definiti un corp articulat, de exemplu un brat de robot , intr-un reper de coordonate plasat in punctul de articulatie. Revedeti Robot.hs

- transformarile geometrice - translatii, rotatii - se exprima prin produse de matrice

- matricea identitate este element neutru la inmultire

- obtineti inversa unei succcesiuni de transformari calculand produsul inverselor matricelor transformarilor

- functiile de nivel superior din Haskell rezolva superb nevoia de a aplica transformari pe o intreaga scena alcatuita din obiectel sau pe toate triunghiurile unei suprafete sau pe toate colturile unui obiect din scena... asa ca: map, fold, foldl, foldr si altele sunt numai bune de folosit.

La pagina despre Programare functionala gasiti un celebru articol despre fold-uri.

.Mini Bibliografie On Line

OpenGLTutorial1 http://www.haskell.org/haskellwiki/OpenGLTutorial1

HOpenGL - 3D Graphics with Haskell http://public.beuth-hochschule.de/~panitz/hopengl/skript.html

OpenGL in Haskell http://www.haskell.org/haskellwiki/Opengl

Exemplele din RedBook http://darcs.haskell.org/packages/GLUT/examples/RedBook/

Si ordinea lor in carte http://darcs.haskell.org/packages/GLUT/examples/RedBook/00-README

Alte biblioteci grafice: SDL, WxWidgets http://www.haskell.org/haskellwiki/Cookbook/Graphical_user_interfaces

Beautifull Code. De altfel imaginile generate merita aprecierea de "beautifull". <Download> al acestui volum de grafica in Open GL si Haskell. Link extern, s-ar putea sa nu mai fie disponibila cartea ! Cautati-o si la Biblioteca - vedeti ca s-a mutat la alta pagina sau la pagina Ce merita sa cititi.

. Intrebari despre OpenGL

In ce ordine sa studiem exemplele din RedBook ? R: In ordinea lor din carte pe care o gasiti aici. http://darcs.haskell.org/packages/GLUT/examples/RedBook/00-README (link extern)

. Extra lectures / Lecturi suplimentare

Lumea se ocupa de OpenGL in Haskell intuind potentialul combinatiei. Bloguri, articole, exemple, idei ... cautati printre paginile indexate aici: http://swik.net/Haskell+3D (link extern)

Lista de documentatii despre functii http://hackage.haskell.org/packages/archive/OpenGL/latest/doc/html/

O documentatie in format PDF despre GLUT3.

OpenGL apelat din alte limbaje: Aici din Python. (link ext.)

OpenGL apelat din C: Aici. (link ext.) Descarcati intregul set de exemple din RedBook scrise in C de aici.

Una dintre primele versiuni ale volumului numit apoi RedBook: (extern)

Si editia a 5-a a cartii "OpenGL programming guide". (pe acest site)