Julias from Pc type polynomial solutions for n=2 the Mandelbulb
- To: mathgroup at smc.vnet.net
- Subject: [mg105805] Julias from Pc type polynomial solutions for n=2 the Mandelbulb
- From: Roger Bagula <rlbagula at sbcglobal.net>
- Date: Sun, 20 Dec 2009 06:52:25 -0500 (EST)
- Reply-to: rlbagulatftn at yahoo.com
In investigating the claims that the Mandelbulb n forms are "true" 3d Mandelbrots I did some 2d projections of Pc polynomial solutions of cycle 2 and cycle 3 using programs programmed in Mathematica by Paul Nylander. ( I'm posting this with his specific permission). The cycle two Julia points are:(pc in Nylander's notation) {-1,0,0} http://www.facebook.com/photo.php?pid=4182775&id=787071498 {1/2,0,Sqrt[3]/2} {1/2,0,-Sqrt[3]/2} The Douady's rabbit cycle 3 is: pc = {-0.122561, 0.744862, 0} http://www.flickr.com/photos/fractalmusic/4196769055/ This last one was found by trying the Douady values in the Julia program. not by calculation. My conclusion is that they ( Mandlbulbs) are Mandelbrot like but scaled to near a unit sphere instead of the complex plane bigger values. I've also verified that the Siegel disk from 2d works in the 3d projection Julia:( figure 7 The Beauty of Fractals) pc = {-0.39054, -0.58679, 0}; A rescaled n=2 Mandelbulb would be: {x,y,z}'={(x^2 - y^2 - z^2) /(1 - z^2), 2 x y, -2 *(x^2 + y^2)^(3/2)* z/(1 - z^2) Daniel White and Paul Nylander seem to have been the principle investigators but there also seems to be a cast of thousands. They are all very good at 3d rendering but somewhat sketchy about Mandelbrot set theory and how to actually "prove" their claims? I call this the great taffy pulling contest of modern fractals... ("Taffy" is the nick name the 3d renders that Terry Gintz has been doing for the last 10 years have gotten: no disrespect meant:a discription of what the surfaces look like.) I also did a toral inverse transform on the Mandelbulb algorithm and it appeared as you would expect. They certainly have the endorsement of most of the fractal community encluding Terry Gintz. Respectfully, Roger L. Bagula 11759 Waterhill Road, Lakeside,Ca 92040-2905,tel: 619-5610814 : http://www.google.com/profiles/Roger.Bagula alternative email: roger.bagula at gmail.com Mathematica: Pc polynomials for mandelbulb n=2: Clear[g, gg, a, p, q, r, x, y, z, x0, y0, z0] (*definition of a 3d Mandelbrot Mandelbulb algorithm*) p[x_, y_, z_] = (x^2 - y^2)(1 - z^2/(x^2 + y^2)) + x0; q[x_, y_, z_] = 2*x*y(1 - z^2/(x^2 + y^2)) + y0; r[x_, y_, z_] = -2*z*Sqrt[x^2 + y^2] + z0; g[x_, y_, z_] = {p[x, y, z], q[x, y, z], r[x, y, z]}; (*definition of recursive 3d polynomials*) gg[0] := {x0, y0, z0} gg[1] := g[x0, y0, z0] gg[n_] := gg[n] = g[gg[n - 1][[1]], gg[n - 1][[2]], gg[n - 1][[3]]] a = Table[Table[FullSimplify[gg[n][[i]]] == 0, {i, 1, 3}], {n, 0, 3}]; (*First level solution :*) NSolve[a[[1]], {x0, y0, z0}] {{x0 -> 0, y0 -> 0, z0 -> 0}} (*Second level solution :*) NSolve[a[[2]], {x0, y0, z0}] NSolve[a[[3]], {x0, y0, z0}] Mathematica: Paul Nylander's Julia program:( try n=50 for a fast render) http://www.facebook.com/photo.php?pid=4182775&id=787071498 n = 300; norm[x_] := x.x; pc = {-1, 0, 0}; BagulaSquare[{x_, y_, z_}] := Module[{rxy2 = x^2 + y^2, rxz2 = x^2 + z^2, a}, a = 1 - z^2/rxy2; If[rxz2 == 0, {0, 0, 0}, {a(x^2 - y^2), 2 a x y, -2 Sqrt[rxy2] z}]]; gradient = {{0., {0, 0, 0.5}}, {0.1, {0, 0, 1}}, {0.4, {0, 1, 1}}, { 0.6, {1, 1, 0}}, {0.9, {1, 0, 0}}, {1, {0.5, 0, 0}}}; Gradient2[x_, grad_] := Module[{i = 1, n = Length[grad]}, While[i â?¤ n && gradã??i, 1ã?? < x, i++]; RGBColor @@ If[1 < i â?¤ n, Module[{x1 = gradã??i - 1, 1ã??, x2 = gradã??i, 1ã??}, ((x2 - x) gradã??i - 1, 2ã?? + ( x - x1)gradã??i, 2ã??)/(x2 - x1)], gradã??Min[i, n], 2ã??]]; Julia3D[p0_] := Module[{p = p0, i = 0}, While[i < 24 && norm[p] < 4, p = BagulaSquare[p] + pc; i++]; i]; image = Table[z = 1.25; While[z â?¥ -0.1 && Julia3D[{x, y, z}] < 24, z -= 3.5/n]; z, {y, -1.75, 1.75, 3.5/ n}, {x, -1.75, 1.75, 3.5/n}]; ListDensityPlot[image, Mesh -> False, Frame -> False, PlotRange -> {-0.1, 1.25}, ColorFunction -> (Gradient2[#, gradient] &), ImageSize -> 1000]; gr = ListPlot3D[image, Mesh -> False, AspectRatio -> Automatic, Boxed -> False, Axes -> False, ViewPoint -> {-0.884, -1.543, 2.879}];