I tried to haskellize an algorithm which poorly fits into the
functional style: plasma fractal generation. It computes a rectangular
array in a funny order, using previously computed elements, and uses
random numbers all the time.
It works (I didn't check if the result is correct but it's not
important now), but I'm not happy with explicit passing of random
generator and inconsistent methods of composing functions using randoms
I used. It looks ugly for me. It would probably look a bit better if
randoms were unsafely cheated, but I don't accept cheating for such
a simple thing. I tried to make some kind of monad for it but failed,
especially with composing it with Array.
Here it is:
>>>>>>>>
import Array
import Random
import List
plazma :: Int -> Int -> Float -> StdGen -> (Array (Int, Int) Float, StdGen)
plazma width height density gen0 =
(a, gen2)
where
(pixel, gen1) = randomR (0, 1) gen0
(pixels, gen2) = subdivide (0, 0) (width, height) gen1
a = array ((0, 0), (width - 1, height - 1))
(((0, 0), pixel) : pixels [])
subdivide (x1, y1) (x2, y2) gen = let
x = (x1 + x2) `div` 2
y = (y1 + y2) `div` 2
x2' = if x2 == width then 0 else x2
y2' = if y2 == height then 0 else y2
mid (x, y) (x1, y1) (x2, y2) size gen0 = let
(v1, gen1) = randomR (0, 1) gen0
(v2, gen2) = randomR (0, 1) gen1
v = (a!(x1, y1) + a!(x2, y2)) / 2 + density * (v1 - v2)
v' = if v < 0 then 0 else if v >= 1 then 1 else v
in ((((x, y), v'):), gen2)
cl = mid (x1, y) (x1, y1) (x1, y2') (y2 - y1)
uc = mid (x, y1) (x1, y1) (x2', y1) (x2 - x1)
cc g = ((((x, y), s / 4):), g)
where s = a!(x1, y) + a!(x, y1) + a!(x2', y) + a!(x, y2')
dr = subdivide (x, y) (x2, y2)
dl = subdivide (x1, y) (x, y2)
ur = subdivide (x, y1) (x2, y)
ul = subdivide (x1, y1) (x, y)
todo = case (x2 - x1, y2 - y1) of
(1, 1) -> []
(1, _) -> [cl, dr, ur]
(_, 1) -> [uc, dr, dl]
(_, _) -> [cl, uc, cc, dr, dl, ur, ul]
pass a b gen0 = let
(a', gen1) = a gen0
(b', gen2) = b gen1
in (a' . b', gen2)
in foldr pass (\gen -> (id, gen)) todo gen
main :: IO ()
main = do
gen0 <- newStdGen
let
(pl, gen1) = plazma 15 10 1 gen0
in print pl
<<<<<<<<
(Works with ghc. Doesn't work with Hugs because of incompatible Random
module (?).)
It was very nice that array allows specifying dependencies in any
order.
Is it now possible - or worth - to put random numbers in some monad,
so e.g. mid could be rewritten similar to this:
mid (x, y) (x1, y1) (x2, y2) size = do
v1 <- randomR?? (0, 1)
v2 <- randomR?? (0, 1)
let
v = (a!(x1, y1) + a!(x2, y2)) / 2 + density * (v1 - v2)
v' = if v < 0 then 0 else if v >= 1 then 1 else v
in return (((x, y), v'):)
without the need to name each state of random generator?
I needed some trickery (pass) with composing functions cl, uc, cc etc.
because various subsets of them are needed in various cases. Previously
I did them similar to the rest, naming each state of generator, but
it computed randoms unnecessarily in some cases. So it's inconsistent
with the rest.
I want the whole function to appear similar to random, taking generator
and returning (result,generator), or taking generator and returning
result - but don't want to put it in IO monad by using RandomIO,
because getting random numbers can hardly be considered as IO and
everything using it would be forced to be put in IO monad.
Is there - or should be - or how to do it - a monad for random numbers
only, which can be used outside IO? I'm not sure if it would help at
all, because everything is then passed to the array which requires
the values to be able to be computed in arbitrary order (because of
recursive usage of the array inside them). I may not be possible to
begin plazma with something like:
do
pixel <- randomR?? (0, 1)
pixels <- subdivide (0, 0) (width, height)
because subdivide needs a, which again needs pixel and pixels, so I
don't know where to define a and subdivide.
So how to do the whole thing right?
I don't like that in some places I have to name each state of random
generator, that cc has to explicitly pass the generator although it
doesn't use it, and I don't like "foldr pass (\gen -> (id, gen))"
together with the definition of pass (some monadic "sequence" would
look nicer IMHO).
Let's assume that I have two independent monads. Is it possible
to combine functions working in them into one sequential do, with a
result of somewhat combined monad? Maybe it does not make any sense...
Sorry, I'm new to FP.
Is there a generic monad that converts functions of the form
g -> (a, g) into nice monadic syntax which maintains the state of g?
Or maybe which takes split :: g -> (g, g) and functions of the form
g -> a.
Maybe Array is not the right tool to use here?
BTW, am I right that here is the case where using composed functions
instead of ++'ed Strings makes the thing faster?
--
__("< Marcin Kowalczyk * [EMAIL PROTECTED] http://kki.net.pl/qrczak/
\__/ GCS/M d- s+:-- a22 C+++>+++$ UL++>++++$ P+++ L++>++++$ E->++
^^ W++ N+++ o? K? w(---) O? M- V? PS-- PE++ Y? PGP->+ t
QRCZAK 5? X- R tv-- b+>++ DI D- G+ e>++++ h! r--%>++ y-