0

I wrote a little program which has to display the mandelbrot set, in haskell, using Gtk2Hs.

thought there is no compilation error, nothing is displayed in the canvas (the component in which the points are colored)...

could you help me to debug this logical error?

my code:

module Main where

import           Control.Monad            (when)
import           Graphics.Rendering.Cairo as C
import           Graphics.UI.Gtk
import           Graphics.UI.Gtk.Builder  ()


main :: IO()
main = do
    _ <- initGUI
    builder <- builderNew
    builderAddFromFile builder "09-mandelbrot.ui"

    window   <- builderGetObject builder castToWindow "Figure de Mandelbrot"
    canvas <- builderGetObject builder castToDrawingArea "drawingarea1"
    _ <- onExpose canvas $ const (updateCanvas canvas)

    widgetShowAll window
    mainGUI


updateCanvas :: DrawingArea -> IO Bool
updateCanvas canvas = do
  win <- widgetGetDrawWindow canvas
  (width, height) <- widgetGetSize canvas
  _ <- mapM_ (affiche win)  (points (fromIntegral width) (fromIntegral height))

  return True

k :: Int
k=100

mandelbrot :: Double -> Double -> Bool
mandelbrot a b =
  let
    mandelrec :: Double -> Double -> Int -> Bool
    mandelrec x y i
      | (x * x + y * y > 4) = False
      | (i==k) && (x * x + y * y <= 4) = True
      | otherwise = mandelrec x' y' (i+1)
            where x' = x * x - y * y + a
                  y' = 2 * x * y + b
  in mandelrec 0 0 0

affiche2 :: DrawWindow -> Double -> Double -> IO()
affiche2 win a b = do
  renderWithDrawable win $ setSourceRGB 0 1 0
  renderWithDrawable win $ setLineWidth 1
  renderWithDrawable win $ C.rectangle a b 1 1 
  renderWithDrawable win stroke


affiche :: DrawWindow -> ((Double,Double), (Double,Double)) -> IO ()
affiche win ((a0,a), (b0,b)) = when (mandelbrot a b) $ postGUIAsync (affiche2 win a0 b0)

colonnes :: Double -> [(Double, Double)]
colonnes w = [ (t,t/w*4-2) | t<-[0..(w-1)] ]

lignes :: Double -> [(Double, Double)]
lignes h = [ (t,t/h*4-2) | t<-[0..(h-1)] ]

points :: Double -> Double -> [((Double, Double), (Double, Double))]
points w h = [ (colonne,ligne)| colonne <- colonnes w,ligne <- lignes h]

main() is not interesting, it works, I am sure. update_canvas grab some values (width, height, win) and call the side-effect function, affiche, providing it the values in "points" (points contains the good values, namely the coordinates of the points between [-2..2] for the 2 axes. mandelbrot is good, since I succeeded in drawing the mandelbrot set (yet all points were drawed together). I think if there is a problem, it could come from affiche or affiche2, but I'm new to Gtk programming.

thank you.

EDIT

Well, it works with your change, but why? and I have another question : if I raise the parameter k (say to 1000), the set is displayed only 17 seconds after having launched the program, and it is displayed very quickly; but that's not what I would like : I want the points be drawed as soon as they are computed. DO you know what change I must do?

EDIT 2

here is a code which - works : it displays the image in <10s - doesn't use any UI or GLADE file - draws points after all are computed

module Main where

import           Control.Monad            (when)
import           Graphics.Rendering.Cairo as C
import           Graphics.UI.Gtk
import           Graphics.UI.Gtk.Builder  ()


main :: IO()
main = do
    _ <- initGUI

    window <- windowNew
    windowSetPosition window WinPosCenter
    windowSetDefaultSize window 500 350
    set window [windowTitle := "Ensemble de Mandelbrot"]
    on window objectDestroy mainQuit

    canvas <- drawingAreaNew
    canvas `on` sizeRequest $ return (Requisition 450 300)
    window `containerAdd` canvas

    _ <- onExpose canvas $ const (updateCanvas canvas)

    widgetShowAll window
    mainGUI


updateCanvas :: DrawingArea -> IO Bool
updateCanvas canvas = do
  win <- widgetGetDrawWindow canvas
  (width, height) <- widgetGetSize canvas
  _ <- mapM_ (affiche win)  (points (fromIntegral width) (fromIntegral height))

  return True

k :: Int
k=100 -- 100 : after launching, u must wait less than 10s

mandelbrot :: Double -> Double -> Bool
mandelbrot a b =
  let
    mandelrec :: Double -> Double -> Int -> Bool
    mandelrec x y i
      | (x * x + y * y > 4) = False
      | (i==k) && (x * x + y * y <= 4) = True
      | otherwise = mandelrec x' y' (i+1)
            where x' = x * x - y * y + a
                  y' = 2 * x * y + b
  in mandelrec 0 0 0

affiche2 :: DrawWindow -> Double -> Double -> IO()
affiche2 win a b = renderWithDrawable win $ do
    setSourceRGB 0 0 0
    setLineWidth 1
    C.rectangle a b 1 1 
    stroke


affiche :: DrawWindow -> ((Double,Double), (Double,Double)) -> IO ()
affiche win ((a0,a), (b0,b)) = when (mandelbrot a b) $ postGUIAsync (affiche2 win a0 b0)

colonnes :: Double -> [(Double, Double)]
colonnes w = [ (t,t/w*4-2) | t<-[0..(w-1)] ]

lignes :: Double -> [(Double, Double)]
lignes h = [ (t,t/h*4-2) | t<-[0..(h-1)] ]

points :: Double -> Double -> [((Double, Double), (Double, Double))]
points w h = [ (colonne,ligne)| colonne <- colonnes w,ligne <- lignes h]

olivier

lolveley
  • 1,659
  • 2
  • 18
  • 34
  • It would be helpful for us if you got rid of the ui file – that doesn't really seem necessary here. Without it, we could just quickly test the program. – leftaroundabout Apr 04 '16 at 12:31
  • I think `renderWithDrawable` creates a new context for cairo and the commands after it should be in the same context to see something (it makes no sense to do a `stroke` in a new context when there was nothing drawn before in this new context). – MichaelO Apr 04 '16 at 12:57
  • @leftaroundabout ok, I will make it and provide you with it as soon I will be at home – lolveley Apr 04 '16 at 13:25
  • @leftaroundabout ok, it's done – lolveley Apr 04 '16 at 15:10
  • @leftaroundabout here is a tutorial that could help you if all the tools are not installed : http://rizwanbulbul.blogspot.fr/2010/06/installing-leksah-gtk-gtk2hs-and-glade.html – lolveley Apr 04 '16 at 15:43
  • ...and here's an other, which is better I think : https://pamiz.wordpress.com/2012/12/11/packages-needed-to-install-gtk2hs-on-ubuntu/ – lolveley Apr 04 '16 at 15:46
  • So... what part of the question remains? — You needn't add information on how to install packages, just try to keep your posts short, focused and your own code self-contained (like the second example is, now; very good). – leftaroundabout Apr 04 '16 at 15:55
  • @leftaroundabout I would like my program to display the points progressively : now they are all displayed together after having been computed. For this particular example, this not seems to be important, but for some other programs which need more time to be computed, it could become of high importance. – lolveley Apr 04 '16 at 16:02
  • Ok, so basically [your other question](http://stackoverflow.com/questions/36378409/haskell-gtk-how-to-draw-points-as-soon-as-they-are-computed). – leftaroundabout Apr 04 '16 at 16:20
  • We could continue with the other question, as we have to select only one, and the title of the other one fits best to the remaining problem! – lolveley Apr 04 '16 at 17:02

1 Answers1

2

While i haven't worked with Gtk2Hs, i guess the problem is in affiche2. Try changing it to this:

affiche2 win a b = do
  renderWithDrawable win $ do
    setSourceRGB 0 1 0
    setLineWidth 1
    C.rectangle a b 1 1 
    stroke
arrowd
  • 33,231
  • 8
  • 79
  • 110