Zippers, Random Numbers & Terrain

Hi All, To amuse myself while waiting for test-runs to complete, I was thinking about random terrain generation. I came across a bunch of nice posts by Torben Mogensen, where he describes a neat way of constructing random terrains by recursively subdividing right angled isosceles triangles. It got me thinking - it's all well and good subdividing to give more detail as you zoom in, but what about when you zoom out? This got me thinking that it would be cool to make an infinite terrain generator using a zipper, so you can zoom in/out infinitely, and by implication, infinitely in any direction. One of the key components that seems to be necessary is a random number generator zipper. In Mogensen's scheme, you have a number associated with each point, and when you subdivide, you create a new RNG seed from the numbers at each end of the hypotenuse which you are bisecting. These numbers are used to generate height variation. The trick, is to make the combination order independent (e.g. xor). This is easy for zooming in, but it's not clear how to do this for zooming out. It's probably sufficient to assume a (parameterizable) hashing/mixing scheme, and to simply number the nodes in some deterministic fashion. The subdivision is binary, so we could number the children deterministically. If we use "decimals", from some arbitrary starting point, we can extend in the "fractional" direction when we zoom in, and extend in the "whole number" direction. I'm only just discovering zippers, so my question to the learned members of this forum is: Am I on the right track? Is a scheme like this going to work? cheers, Tom -- Dr Thomas Conway drtomc@gmail.com Silence is the perfectest herald of joy: I were but little happy, if I could say how much.

Thomas Conway wrote:
To amuse myself while waiting for test-runs to complete, I was thinking about random terrain generation. I came across a bunch of nice posts by Torben Mogensen, where he describes a neat way of constructing random terrains by recursively subdividing right angled isosceles triangles. It got me thinking - it's all well and good subdividing to give more detail as you zoom in, but what about when you zoom out?
Can you post a hyperlink for an exact description of the algorithm?
This got me thinking that it would be cool to make an infinite terrain generator using a zipper, so you can zoom in/out infinitely, and by implication, infinitely in any direction.
An infinite random terrain sounds like great fun :) I can't say whether it's possible or whether zippers are needed without knowing the details, though. One problem is probably having a "point of reference", i.e. one needs a point (0,0) with a fixed height 0. In the bounded case, one has a rectangle to subdivide instead. Regards, apfelmus

apfelmus
Thomas Conway wrote:
To amuse myself while waiting for test-runs to complete, I was thinking about random terrain generation. I came across a bunch of nice posts by Torben Mogensen, where he describes a neat way of constructing random terrains by recursively subdividing right angled isosceles triangles. It got me thinking - it's all well and good subdividing to give more detail as you zoom in, but what about when you zoom out?
Can you post a hyperlink for an exact description of the algorithm?
This got me thinking that it would be cool to make an infinite terrain generator using a zipper, so you can zoom in/out infinitely, and by implication, infinitely in any direction.
An infinite random terrain sounds like great fun :) I can't say whether it's possible or whether zippers are needed without knowing the details, though.
One problem is probably having a "point of reference", i.e. one needs a point (0,0) with a fixed height 0. In the bounded case, one has a rectangle to subdivide instead.
Regards, apfelmus
You might want to consider Perlin-Noise: http://wiki.delphigl.com/index.php/Perlin_Noise (good introduction) It uses a chaotic function (ergodic?) that works on integers. In the case of Terrain it uses 2. One for the x and one for y coordinate. It should be infinite for Zooming out. When zooming in one uses interpolation. The drawback(?) is when zooming out is that it becomes more "noisy". When zooming in it becomes less. The advantage is that you dont need a reference point. That means you can render any portion of your infinite terrain without tracing back to the origin. But I fear you would need a reference point if you want to attach other kinds of data (not just the hight) with each point. Of course you could layer another perlin-noise for plants and another for rivers. But in the end all this will get boring pretty soon because its static.

On 7/30/07, Martin Lütke
It uses a chaotic function (ergodic?) that works on integers. In the case of Terrain it uses 2. One for the x and one for y coordinate. It should be infinite for Zooming out. When zooming in one uses interpolation. The drawback(?) is when zooming out is that it becomes more "noisy".
Typically you'd sum different 'octaves' of noise to get a function that's approximately self-similar under scaling, that way it'd be qualitatively similar when zooming in or out. There are many descriptions on the web. Here's one I found: http://local.wasp.uwa.edu.au/~pbourke/texture_colour/perlin/ -- Dan

On Monday 30 July 2007 09:51:48 apfelmus wrote:
Thomas Conway wrote:
To amuse myself while waiting for test-runs to complete, I was thinking about random terrain generation. I came across a bunch of nice posts by Torben Mogensen, where he describes a neat way of constructing random terrains by recursively subdividing right angled isosceles triangles. It got me thinking - it's all well and good subdividing to give more detail as you zoom in, but what about when you zoom out?
Can you post a hyperlink for an exact description of the algorithm?
Maybe this: http://www.geocities.com/Area51/6902/t_torben.html
This got me thinking that it would be cool to make an infinite terrain generator using a zipper, so you can zoom in/out infinitely, and by implication, infinitely in any direction.
An infinite random terrain sounds like great fun :) I can't say whether it's possible or whether zippers are needed without knowing the details, though.
I wrote a real-time infinite-detail random planet renderer along similar lines in C++ many years ago. Thomas' description makes it sound ROAM based (isosceles triangles) but mine subdivided and perturbed an icosahedron into roughly-equilateral triangles. This is a good task for a functional programming language. It is based upon graph theory and you must consider splitting and joining triangles to keep the subdivision suitably accurate in the region currently in view. The perturbations and split/join metric can be made up and tinkered with. For a real time implementation, you maintain a priority queue of splits and joins, doing a few each frame. All in all, a very fun project. -- Dr Jon D Harrop, Flying Frog Consultancy Ltd. OCaml for Scientists http://www.ffconsultancy.com/products/ocaml_for_scientists/?e

Thomas Conway wrote:
This got me thinking that it would be cool to make an infinite terrain generator using a zipper, so you can zoom in/out infinitely, and by implication, infinitely in any direction.
After some pondering, I think it's indeed possible and the zipper is the right tool for the job. I'll present the idea for constructing a one-dimensional "fractal terrain" but it generalizes to higher dimensions. First, consider the task to construct a 1D fractal height function defined on a bounded interval like [0,1]. type Pos = Double type Height = Double terrain :: Interval -> Pos -> Height We construct the terrain by dividing the interval in half and adjust the height of the midpoint randomly relative to the mean of the other heights. data Interval = I (Pos,Pos) (Height,Height) StdGen terrain :: Interval -> Pos -> Height terrain i x | x `in` left = terrain left x | x `in` right = terrain right x where (left, right) = bisect i in :: Pos -> Interval -> Bool in x (I (a,b) _ _) = a <= x && x <= b bisect :: Interval -> (Interval, Interval) bisect (I (a,b) (ha,hb) g) = (I (a,m) (ha,h) ga, I (m,b) (h,hb) gb) where m = (a+b)/2 h = (ha+hb)/2 + d * (a-b) * scale (d,g') = randomR (0,1) g (ga,gb) = split g' The factor scale controls the roughness of the terrain. True enough, the function terrain never returns but that shouldn't be an issue to the mathematician ;) Of course, we have to stop as soon as the interval length is smaller than some given resolution epsilon (i.e. the width of a pixel). Splitting the random number generator is not necessarily a good idea, but I don't care right now. For zoom-in, we want to specify different epsilons and get the same random values each time. So, we memoize the steps to produce the height function in an infinite tree data Terrain = Branch Terrain (Height,Height) Terrain terrain :: Interval -> Terrain terrain i = Branch (terrain left) h (terrain right) where (left, right) = bisect i I _ h _ = i The actual rendering can be obtained from the infinite Terrain, I'll omit it for simplicity. For finite zoom-out, we use a zipper type Zipper = (Context, Terrain) type Context = [Either Terrain Terrain] zoomInLeft, zoomInRight :: Zipper -> Zipper zoomInLeft (xs, Branch l h r) = (Left r:xs, l) zoomInRight (xs, Branch l h r) = (Right l:xs, r) zoomOut :: Zipper -> Zipper zoomOut (x:xs, t) = case x of Left r -> (xs, Branch t (t `joinHeights` r) r) Right l -> (xs, Branch l (l `joinHeights` t) t) where joinHeights (Branch _ (ha,_) _) (Branch _ (_,hb) _) = (ha,hb) zoomOut ([], _) = error "You fell out of the picture!" Mnemonics: Left means that we descended into the left half, Right that we descended into the right half of the interval. The final step is to allow infinite zoom-out. How to do that? Well, assume that we generate the landscape on the interval [0,1] and zoom out. The reverse of this would be to create the landscape on the interval [-1,1] and then zoom into the right half [0,1]. In other words, we view [0,1] as the right half of the bigger interval [-1,1]. This in turn can be viewed as the left half of the even bigger interval [-1,3]. In order to grow both interval bounds to infinity, we alternate between viewing it as left half and as right half. In other words, the insight is that *we're inside an infinite context*! Thus, generating an infinite terrain is like generating a finite one except that we need to generate the infinite context as well: terrainInfinite :: Interval -> Zipper terrainInfinite i = (right i, terrain i) where right (I (m,b) (h,hb) g) = Right (terrain l) : left i where l = fst $ bisect i i = I (a,b) (ha,hb) g' a = m - (b -m) ha = hb - (hb-h) + d * (a-b) * scale (d,g') = randomR (0,1) g left (I (a,m) (ha,h) g) = Left (terrain r) : right i where r = snd $ bisect i i = I (a,b) (ha,hb) g' b = m + (m-a ) hb = h + (h-ha) + d * (a-b) * scale (d,g') = randomR (0,1) g Here, left starts by extending a given interval to the right and right starts by extending it to the left. It would be nice to run the random generator backwards, the generator transitions in terrainInfinite are surely wrong, i.e. too deterministic. Also, the scale of the random height adjustment d is probably wrong. But those things are exercises for the attentive reader ;) That concludes the infinite terrain generation for one dimension. For higher dimension, one just needs to use 2D objects instead of intervals to split into two or more pieces. For instance, one can divide equilateral triangles into 4 smaller ones. In fact, it doesn't matter whether the starting triangle is equilateral or not when using the midpoints of the three sides to split it into four smaller triangles. Regards, apfelmus

On 8/2/07, apfelmus
That concludes the infinite terrain generation for one dimension. For higher dimension, one just needs to use 2D objects instead of intervals to split into two or more pieces. For instance, one can divide equilateral triangles into 4 smaller ones. In fact, it doesn't matter whether the starting triangle is equilateral or not when using the midpoints of the three sides to split it into four smaller triangles.
Nice. The issue of the RNG running backwards was what made me realize that rather than using StdGen in the nodes, if you simply number them (Hmmm - the nodes are countably infinite :-)), you can then [e.g.] use a cryptographic hash or similar to turn them into random numbers. You can seed the hash to generate different terrains. You may be interested that in some of the code I wrote for the right angle isosceles triangle case, I got into precision problems. It turns out that all the vertices lie on positions with coordinates that are precisely sums of 2^-k (e.g. 0.5, 0.125, 0.625), yet each time you subdivide, the scaling factor on the side length is sqrt 2/2. The resultant rounding meant that instead of getting 0.5, I got 0.5000000003, or some such. After pondering on this for a while, I realized instead of representing the scale of the triangle as a Double, I could use (Either Double Double), with Left x representing the scale x, and Right x representing the scale x * sqrt 2 / 2. That way, all the rounding problems can be made to go away. Well, not all of them - after all Double has limited digits of mantissa, but down to quite small scales, the arithmetic will be precise. Actually, you could use (Either Rational Rational), except that performance would be [even more] atrocious. cheers, T. -- Dr Thomas Conway drtomc@gmail.com Silence is the perfectest herald of joy: I were but little happy, if I could say how much.

Thomas Conway
On 8/2/07, apfelmus
wrote: That concludes the infinite terrain generation for one dimension. For higher dimension, one just needs to use 2D objects instead of intervals to split into two or more pieces. For instance, one can divide equilateral triangles into 4 smaller ones. In fact, it doesn't matter whether the starting triangle is equilateral or not when using the midpoints of the three sides to split it into four smaller triangles. Nice.
Nice indeed! The infinite binary tree of the terrain intervals reminds me of the hyperbolic plane, of course, and its use in arbitrary-precision real arithmetic (cue a real mathematician).
The issue of the RNG running backwards was what made me realize that rather than using StdGen in the nodes, if you simply number them (Hmmm - the nodes are countably infinite :-)), you can then [e.g.] use a cryptographic hash or similar to turn them into random numbers. You can seed the hash to generate different terrains.
Isn't the whole point of a good RNG that running it forwards and backwards should be statistically the same?
You may be interested that in some of the code I wrote for the right angle isosceles triangle case, I got into precision problems. [...] After pondering on this for a while, I realized instead of representing the scale of the triangle as a Double, I could use (Either Double Double), with Left x representing the scale x, and Right x representing the scale x * sqrt 2 / 2. That way, all the rounding problems can be made to go away. Well, not all of them - after all Double has limited digits of mantissa, but down to quite small scales, the arithmetic will be precise. Actually, you could use (Either Rational Rational), except that performance would be [even more] atrocious.
What about a possibly infinite list of binary digits in base sqrt(2)? Surely the beauty would overshadow any performance problems. (: -- Edit this signature at http://www.digitas.harvard.edu/cgi-bin/ken/sig "Elegance is optional." -- Richard A. O'Keefe

Thomas Conway wrote:
On 8/2/07, apfelmus
wrote: That concludes the infinite terrain generation for one dimension. For higher dimension, one just needs to use 2D objects instead of intervals to split into two or more pieces. For instance, one can divide equilateral triangles into 4 smaller ones. In fact, it doesn't matter whether the starting triangle is equilateral or not when using the midpoints of the three sides to split it into four smaller triangles.
Nice. The issue of the RNG running backwards was what made me realize that rather than using StdGen in the nodes, if you simply number them (Hmmm - the nodes are countably infinite :-)), you can then [e.g.] use a cryptographic hash or similar to turn them into random numbers. You can seed the hash to generate different terrains.
Yes. The number of a node in the tree should be (related to) the path from the top to the tree in binary representation. I.e. if node = zoomInLeft . zoomInLeft . zoomInRight $ top then, number node = 112 in binary with digits 1 and 2 In contrast, breadth first numbering is a bad idea, since that would mean numbering lots of nodes that aren't required when zooming in. It's probably easiest to first create an infinite tree filled with random numbers type Tree a = Branch (Tree a) a (Tree a) type Random = Double mkRandom :: Seed -> Tree Random and then convert that to a landscape afterwards terrain :: Tree Random -> Tree (Height, Height) Yet another option is available if you only use the zipper-operations to navigate in the tree, i.e. data TreeRandom -- abstract and a zipper zoomInLeft, zoomInRight, zoomOut :: TreeRandom -> TreeRandom top :: TreeRandom -> Random In that case, you can represent it by type TreeRandom = (StdGen, Zipper (Maybe Random)) Everytime you visit a node that has not been visited yet (=> Nothing), it gets a new random number from the generator. When it's already been visited (=> Just r), well then the random number associated to it won't change. The resulting zipper may only be used in a single-threaded fashion, however.
You may be interested that in some of the code I wrote for the right angle isosceles triangle case, I got into precision problems. It turns out that all the vertices lie on positions with coordinates that are precisely sums of 2^-k (e.g. 0.5, 0.125, 0.625), yet each time you subdivide, the scaling factor on the side length is sqrt 2/2. The resultant rounding meant that instead of getting 0.5, I got 0.5000000003, or some such.
After pondering on this for a while, I realized instead of representing the scale of the triangle as a Double, I could use (Either Double Double), with Left x representing the scale x, and Right x representing the scale x * sqrt 2 / 2. That way, all the rounding problems can be made to go away.
Cool :) Of course, the representation with Either requires the knowledge that a scale factor cannot contain both Double-multiples of 1 and Double-multiples of sqrt 2 at the same time. While this is clearly the case, you can avoid thinking about it by operating in the field Q[sqrt 2]: data QSqrt2 = !Double :+ !Double deriving (Eq,Read,Show) instance Nume QSqrt2 where (a :+ b) + (c :+ d) = (a+c) :+ (b+d) (a :+ b) * (c :+ d) = (a*c + 2*b*d) :+ (a*d + b*c) negate (a :+ b) = negate a :+ negate b abs (a :+ b) = (a + sqrt 2 * b) :+ 0 fromInteger n = fromInteger n :+ 0 sqrt2 = 0 :+ 1 Regards, apfelmus
participants (6)
-
apfelmus
-
Chung-chieh Shan
-
Dan Piponi
-
Jon Harrop
-
Martin Lütke
-
Thomas Conway