Logo by Trifox - Contribute your own Logo!

END OF AN ERA, FRACTALFORUMS.COM IS CONTINUED ON FRACTALFORUMS.ORG

it was a great time but no longer maintainable by c.Kleinhuis contact him for any data retrieval,
thanks and see you perhaps in 10 years again

this forum will stay online for reference
News: Visit us on facebook
 
*
Welcome, Guest. Please login or register. March 28, 2024, 04:51:35 PM


Login with username, password and session length


The All New FractalForums is now in Public Beta Testing! Visit FractalForums.org and check it out!


Pages: [1]   Go Down
  Print  
Share this topic on DiggShare this topic on FacebookShare this topic on GoogleShare this topic on RedditShare this topic on StumbleUponShare this topic on Twitter
Author Topic: inflector-gadget : inflection mapping of complex quadratic polynomials  (Read 7836 times)
0 Members and 1 Guest are viewing this topic.
claude
Fractal Bachius
*
Posts: 563



WWW
« on: February 11, 2017, 05:14:06 PM »

Download:
https://mathr.co.uk/mandelbrot/inflector-gadget-0.1.tar.bz2 source code ( https://mathr.co.uk/mandelbrot/inflector-gadget-0.1.tar.bz2.sig signature)
https://mathr.co.uk/mandelbrot/inflector-gadget-0.1-win.zip Windows binaries ( https://mathr.co.uk/mandelbrot/inflector-gadget-0.1.tar.bz2.sig signature)

README.md:
Quote
inflector-gadget
================

Inflection mapping gadget for complex quadratic polynomials.


Keyboard Controls
-----------------

ESC, Q
: quit
HOME
: reset view
UP
: zoom in (faster with SHIFT)
DOWN
: zoom out (faster with SHIFT)
J
: Julia mode
M
: Mandelbrot mode
0
: reset inflections
-
: undo add inflection point
=
: redo add inflection point
H
: show help in terminal


Mouse Controls
--------------

WHEEL
: zoom about mouse cursor position
LEFT
: add inflection point at cursor position
RIGHT
: undo add inflection point
MIDDLE
: recenter window about mouse cursor position


Legal
-----

inflector-gadget 0.1 (GPL) 2017-02-11 Claude Heiland-Allen <claude@mathr.co.uk>

inflector-gadget is free software: you can redistribute it and/or modify
it under the terms of the GNU General Public License as published by
the Free Software Foundation, either version 3 of the License, or
(at your option) any later version.

inflector-gadget is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
GNU General Public License for more details.

You should have received a copy of the GNU General Public License
along with inflector-gadget.  If not, see <http://www.gnu.org/licenses/>.

About:
http://www.fractalforums.com/images-showcase-%28rate-my-fractal%29/inflection-mappings
http://www.fractalforums.com/images-showcase-%28rate-my-fractal%29/12-inflection-points

Image:
Logged
PieMan597
Conqueror
*******
Posts: 122



WWW
« Reply #1 on: February 11, 2017, 05:18:08 PM »

Thanks for the great program!
Logged
jwm-art
Iterator
*
Posts: 171



WWW
« Reply #2 on: February 11, 2017, 06:42:46 PM »

The Unix Makefile has wrong options to pkg-config for the LINK_FLAGS variable. It should be --libs instead of --cflags.
Logged
jwm-art
Iterator
*
Posts: 171



WWW
« Reply #3 on: February 11, 2017, 07:01:14 PM »

and thanks, will find this really useful for getting to grips with zooming/morphing :-)
Logged
claude
Fractal Bachius
*
Posts: 563



WWW
« Reply #4 on: February 12, 2017, 05:07:57 PM »

The Unix Makefile has wrong options to pkg-config for the LINK_FLAGS variable. It should be --libs instead of --cflags.

Thanks, fixed in 0.1.1 (the only change):
https://mathr.co.uk/mandelbrot/inflector-gadget-0.1.1.tar.bz2
https://mathr.co.uk/mandelbrot/inflector-gadget-0.1.1.tar.bz2.sig
Logged
hgjf2
Fractal Phenom
******
Posts: 456


« Reply #5 on: February 18, 2017, 04:49:05 PM »

Cool Julia fractal system. Those fractals iterations type you can find on PAULBOURKE.NET/FRACTALS at chapter "Mauldin Gasket", and INCENDIA can generating so models.
 A peacock A Star
Logged
Kalles Fraktaler
Fractal Senior
******
Posts: 1458



kallesfraktaler
WWW
« Reply #6 on: February 19, 2017, 02:51:28 PM »

claude, have you tried to make this work with calculations from a reference different from <0,0> (the thing we call perturbation...wink )?
I had a quick try but it doesn't work for me...
Logged

Want to create DEEP Mandelbrot fractals 100 times faster than the commercial programs, for FREE? One hour or one minute? Three months or one day? Try Kalles Fraktaler http://www.chillheimer.de/kallesfraktaler
http://www.facebook.com/kallesfraktaler
Dinkydau
Fractal Senior
******
Posts: 1616



WWW
« Reply #7 on: February 20, 2017, 04:12:34 PM »

Cool program. It's fascinating to look at the ghosts of julia morphings so deep they will probably remain unreachable forever. The clicking makes it very easy to use compared to ultra fractal, but I run into precision problems very easily:


This happens when a very precise inflection point is selected by zooming in a lot.

3 layers of trees:
« Last Edit: February 20, 2017, 04:26:27 PM by Dinkydau » Logged

claude
Fractal Bachius
*
Posts: 563



WWW
« Reply #8 on: March 21, 2017, 02:37:11 PM »

I run into precision problems very easily

Thanks.  Indeed with 24 bit float you can't do much.  Another example:



But! You can use the derivative of the inflections (before Julia iterations) to calculate the required precision needed smiley  Something like

Code:
max(16, ceil(16 - log2(abs(derivative))))

Using this precision (different for each pixel) gives a clean image:



Here's a full working Haskell program using the 'rounded' package for MPFR bindings:

Code:
{-

Simple inflection mapping with dynamic precision.  First compute the inflections
with low constant precision, then use the computed derivative to decide how much
precision to use for each pixel in the final render.

Usage:

    ghc -O2 Main.hs
    ./Main > output.pgm

Runtime is about 5m30s on one core of a 3GHz amd64 desktop running Debian.

-}

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}

module Main (main) where

-- MPFR binding, not on Hackage yet, get it from either of these:
-- https://code.mathr.co.uk/rounded/shortlog/refs/heads/claude5
-- https://github.com/ekmett/rounded/pull/27
import Numeric.Rounded

import Data.Complex (Complex((:+)), magnitude)
import Data.List (foldl')
import Data.Monoid ((<>))
import Data.Proxy (Proxy)
import Data.Word (Word8)

import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as BSC

-- arbitrary precision types (p bits of precision)

type R (p :: k) = Rounded 'TowardNearest p
type C (p :: k) = Complex (R p)

-- dual numbers for automatic differentiation

data AD p = AD !(C p) !(C p)
  deriving (Eq, Read, Show)

instance Precision p => Num (AD p) where
  negate (AD a b) = AD (negate a) (negate b)
  AD a b + AD c d = AD (a + c) (b + d)
  AD a b - AD c d = AD (a - c) (b - d)
  AD a b * AD c d = AD (a * c) (a * d + b * c)
  fromInteger = constant . fromInteger

constant :: Precision p => C p -> AD p
constant p = AD p 0

variable :: Precision p => C p -> C p -> AD p
variable d p = AD p d

getVariable :: Precision p => AD p -> C p
getVariable (AD x _) = x

getDerivative :: Precision p => AD p -> C p
getDerivative (AD _ y) = y

-- inflection mapping

inflect :: Precision p => C p -> AD p -> AD p
inflect p c =
  let f = constant p
      d = c - f
  in  d * d + f

inflects :: Precision p => [C p] -> AD p -> AD p
inflects ps z = foldl' (flip inflect) z ps

-- estimate required precision from derivative

precisionRequired :: Precision p => AD p -> Int
precisionRequired (AD _ d) = max 16 . ceiling $ 16 - logBase 2 (magnitude d)

-- generate a grid of coordinates

grid :: Precision p => Int -> Int -> C p -> R p -> [[C p]]
grid w h c r =
    [ [ c + d * (x i :+ y j) | i <- take w [0..] ] | j <- take h [0..] ]
  where
    d = 2 * r :+ 0
    aspect = fromInt w / fromInt h
    x i = ((fromInt i + 0.5) / fromInt w - 0.5) * aspect
    y j = (fromInt h - fromInt j + 0.5) / fromInt h - 0.5

clamp :: Ord a => a -> a -> a -> a
clamp mi ma = min ma . max mi

-- simple greyscale colouring

grey :: Double -> Word8
grey = fromIntegral . clamp 0 (255 :: Int) . floor . (255 *) . tanh . clamp 0 8

-- distance estimator

de :: Precision p => AD p -> Double
de (AD z' dz')
  | isInfinite mdz || isNaN mdz || isInfinite mz || isNaN mz = 1e10
  | otherwise = 2 * mz * log mz / mdz
  where
    z = fmap toDouble z'
    dz = fmap toDouble dz'
    mz = magnitude z
    mdz = magnitude dz

-- Julia iteration loop

calculate :: Precision p => AD p -> AD p -> AD p
calculate c
    = head . (++ [AD 0 0])
    . dropWhile ((< escapeRadius) . magnitude . getVariable)
    . take maxIters
    . iterate (z -> z * z + c)

-- calculate and colour a point

render :: Precision p => [C p] -> AD p -> Proxy p -> Word8
render ps z0 _proxy = grey . de . calculate c . inflects ps $ z0
  where
    c = constant . fmap precRound . last $ ps

-- compute a pixel

pixel :: Precision p => [C p] -> C p -> Word8
pixel ps z0 = reifyPrecision prec render'
  where
    -- compute precision at base precision of input
    -- prec = 24 -- uncomment this and comment the next line to see the effect
    prec = precisionRequired . inflects ps . variable delta0 $ z0
    delta0 = fmap precRound delta
    -- round to computed necessary precision for rendering
    render' :: forall p . Precision p => Proxy p -> Word8
    render' = render ps' (variable delta' z0')
      where
        z0' = fmap precRound z0
        delta' = fmap precRound delta
        ps' = map (fmap precRound) ps

-- pixel size
delta :: C 24
delta = radius * 2 / fromInt height :+ 0

main' :: [C 24] -> BS.ByteString
main' ps
  =  BSC.pack ("P5
" ++ show width ++ " " ++ show height ++ "
255
")
  <> BS.pack (concatMap (map (pixel ps)) (grid width height (head ps) radius))

main :: IO ()
main = BS.putStr (main' example)

-- image parameters

width :: Int
width = 1280

height :: Int
height = 702

-- iteration parameters

escapeRadius :: Precision p => R p
escapeRadius = 65536

maxIters :: Int
maxIters = 1000

-- view size

radius :: R 24
radius = 1.1

-- example inflections

example :: [C 24]
example =
  [   0.29166666  :+ 1.20277774
  ,   0.15833333  :+ 1.21944439
  ,   0.06388889  :+ 1.20277774
  , (-0.05833333) :+ 1.21388888
  , (-0.22500001) :+ 1.17499995
  , (-0.34166667) :+ 1.16388893
  , (-0.48055553) :+ 1.19166672
  , (-0.59722221) :+ 1.13611114
  , (-0.69166666) :+ 1.06388891
  , (-0.80833334) :+ 0.96388888
  , (-0.76944447) :+ 0.13055556
  ]

You can download the program here: https://mathr.co.uk/misc/2017-03-21_inflection-mapping-dynamic-precision.hs

It's not really practical for live exploring though, 24bit float on GPU is pretty much instant, while this variable precision software floating point on CPU takes several minutes at the same resolution - probably it would be beneficial to just use double precision, or double-double if required for some pixels...
Logged
claude
Fractal Bachius
*
Posts: 563



WWW
« Reply #9 on: March 21, 2017, 03:35:34 PM »

Made a double-precision version of inflector-gadget, it needs OpenGL 4:

source:
https://mathr.co.uk/mandelbrot/inflector-gadget-0.2.tar.bz2
https://mathr.co.uk/mandelbrot/inflector-gadget-0.2.tar.bz2.sig

windows binaries:
https://mathr.co.uk/mandelbrot/inflector-gadget-0.2-win.zip
https://mathr.co.uk/mandelbrot/inflector-gadget-0.2-win.zip.sig

It's noticeably slower than the single precision version here, a slight lag, on NVIDIA GeForce GTX 550 Ti.
Logged
Pages: [1]   Go Down
  Print  
 
Jump to:  


Powered by MySQL Powered by PHP Powered by SMF 1.1.21 | SMF © 2015, Simple Machines

Valid XHTML 1.0! Valid CSS! Dilber MC Theme by HarzeM
Page created in 0.171 seconds with 26 queries. (Pretty URLs adds 0.009s, 2q)