Made the edge article

This commit is contained in:
Yann Esposito 2012-05-03 18:09:00 +02:00
parent bb57daf09f
commit 629adbee68
5 changed files with 157 additions and 12 deletions

View file

@ -73,12 +73,18 @@ No easy parallel drawing here.
Here is the function which will render something on the screen:
> drawMandelbrot =
> -- We will print Points (not triangles for example)
> renderPrimitive Points $ do
> mapM_ (\(x,y,c) -> do
> color c
> vertex $ Vertex3 x y 0) allPoints
> mapM_ drawColoredPoint allPoints
> where
> drawColoredPoint (x,y,c) = do
> color c -- set the current color to c
> -- then draw the point at position (x,y,0)
> -- remember we're in 3D
> vertex $ Vertex3 x y 0
This is simple, without the `mapM_` function, it would be equivalent to:
The `mapM_` function is mainly the same as map but inside a monadic context.
More precisely, this can be transformed as a list of actions where the order is important:
~~~
drawMandelbrot =
@ -90,10 +96,9 @@ drawMandelbrot =
vertex $ Vertex3 xN yN 0
~~~
This is all the orders given in the right order.
Mainly it is, set the color, draw the point, set another color, draw another point, etc...
We need some kind of global variable, in fact, this is the proof of a bad design. But this is our first start:
We also need some kind of global variables.
In fact, global variable are a proof of some bad design.
But remember it is our first try:
> width = 320 :: GLfloat
> height = 320 :: GLfloat
@ -125,7 +130,22 @@ Given two coordinates in pixels, it returns some integer value:
> in
> f (complex r i) 0 64
It uses the main mandelbrot function for each complex z.
It uses the main mandelbrot function for each complex c.
The mandelbrot set is the set of complex number c such that the following sequence does not escape to infinity.
Let us define:
<div>
$$ f_c : z \rightarrow z^2 + c $$
</div>
The serie is:
<div>
$$ 0 \rightarrow f_c(0) \rightarrow f_c(f_c(0)) \rightarrow \cdots \rightarrow f^n_c(0) \rightarrow \cdots $$
</div>
Of course, instead of trying to test the real limit, we just make a test after a finite number of occurences.
> f :: Complex -> Complex -> Int -> Int
> f c z 0 = 0
@ -133,10 +153,22 @@ It uses the main mandelbrot function for each complex z.
> then n
> else f c ((z*z)+c) (n-1)
Well, use this file, and see what occurs!
Well, if you download this lhs file, compile it and run it this is the result:
blogimage("hglmandel_v01.png","The mandelbrot set version 1")
But see what occurs, if we make the window bigger:
A first very interresting property of this program is that the computation for all the points is done only once.
The proof is that it might be a bit long before a first image appears, but if you resize the window, it updates instantaneously.
This property is a direct consequence of purity.
If you look closely, you see that `allPoints` is a pure list.
Therefore, calling `allPoints` will always render the same result.
While Haskell doesn't grabage collect `allPoints` the result is reused for free.
We didn't specified this value should be saved for later use.
It is saved for us.
See what occurs if we make the window bigger:
blogimage("hglmandel_v01_too_wide.png","The mandelbrot too wide, black lines and columns")
Wep, we see some black lines.
Why? Simply because we drawed points and not surfaces.

BIN
02_Edges/hglmandel Executable file

Binary file not shown.

113
02_Edges/hglmandel.lhs Normal file
View file

@ -0,0 +1,113 @@
## Only the edges
<div style="display:hidden">
> import Graphics.Rendering.OpenGL
> import Graphics.UI.GLUT
> import Data.IORef
> newtype Complex = C (Float,Float) deriving (Show,Eq)
> instance Num Complex where
> fromInteger n = C (fromIntegral n,0.0)
> C (x,y) * C (z,t) = C (z*x - y*t, y*z + x*t)
> C (x,y) + C (z,t) = C (x+z, y+t)
> abs (C (x,y)) = C (sqrt (x*x + y*y),0.0)
> signum (C (x,y)) = C (signum x , 0.0)
> complex :: Float -> Float -> Complex
> complex x y = C (x,y)
>
> real :: Complex -> Float
> real (C (x,y)) = x
>
> im :: Complex -> Float
> im (C (x,y)) = y
>
> magnitude :: Complex -> Float
> magnitude = real.abs
> main :: IO ()
> main = do
> -- GLUT need to be initialized
> (progname,_) <- getArgsAndInitialize
> -- We will use the double buffered mode (GL constraint)
> initialDisplayMode $= [DoubleBuffered]
> -- We create a window with some title
> createWindow "Mandelbrot Set with Haskell and OpenGL"
> -- Each time we will need to update the display
> -- we will call the function 'display'
> displayCallback $= display
> -- We enter the main loop
> mainLoop
> display = do
> clear [ColorBuffer] -- make the window black
> loadIdentity -- reset any transformation
> preservingMatrix drawMandelbrot
> swapBuffers -- refresh screen
>
> width = 320 :: GLfloat
> height = 320 :: GLfloat
</div>
This time, instead of drawing all points, I'll simply want to draw the edges of the Mandelbrot set.
We change slightly the drawMandelbrot function.
We replace the `Points` by `LineLoop`
> drawMandelbrot =
> -- We will print Points (not triangles for example)
> renderPrimitive LineLoop $ do
> mapM_ drawColoredPoint allPoints
> where
> drawColoredPoint (x,y,c) = do
> color c -- set the current color to c
> -- then draw the point at position (x,y,0)
> -- remember we're in 3D
> vertex $ Vertex3 x y 0
And now, we should change our list of points.
Instead of drawing every point of the visible surface,
we will choose only point on the surface.
> allPoints = positivePoints ++ map (\(x,y,c) -> (x,-y,c)) (reverse positivePoints)
We only need to compute the positive point.
The mandelbrot set is symetric on the abscisse axis.
> positivePoints :: [(GLfloat,GLfloat,Color3 GLfloat)]
> positivePoints = do
> x <- [-width..width]
> let y = findMaxOrdFor (mandel x) 0 height 10 -- log height
> return (x/width,y/height,colorFromValue $ mandel x y)
We make a simple dichotomic search:
> findMaxOrdFor func minval maxval 0 = (minval+maxval)/2
> findMaxOrdFor func minval maxval n =
> if (func medpoint) /= 0
> then findMaxOrdFor func minval medpoint (n-1)
> else findMaxOrdFor func medpoint maxval (n-1)
> where medpoint = (minval+maxval)/2
<div style="display:hidden">
> colorFromValue n =
> let
> t :: Int -> GLfloat
> t i = 0.5 + 0.5*cos( fromIntegral i / 10 )
> in
> Color3 (t n) (t (n+5)) (t (n+10))
> mandel x y =
> let r = 2.0 * x / width
> i = 2.0 * y / height
> in
> f (complex r i) 0 64
> f :: Complex -> Complex -> Int -> Int
> f c z 0 = 0
> f c z n = if (magnitude z > 2 )
> then n
> else f c ((z*z)+c) (n-1)
</div>

View file

@ -61,7 +61,7 @@ enddiv
END
for fic in *.lhs(.N) **/*.lhs(.N); do
for fic in **/*.lhs(.N); do
contains_haskell=$(( $( egrep '^>' $fic | wc -l) > 0 ))
((contains_haskell)) && \
print -- "\n<hr/><a href=\"code/$fic\" class=\"cut\">${fic:h}/<strong>${fic:t}</strong></a>\n"