ruff-0.4.0.1: relatively useful fractal functions

Copyright(c) Claude Heiland-Allen 201020112015
LicenseBSD3
Maintainerclaude@mathr.co.uk
Stabilityunstable
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Fractal.RUFF.Mandelbrot.Address

Description

External angles give rise to kneading sequences under the angle doubling map. Internal addresses encode kneading sequences in human-readable form, when extended to angled internal addresses they distinguish hyperbolic components in a concise and meaningful way.

The algorithms are mostly based on Dierk Schleicher's papers Internal Addresses Of The Mandelbrot Set And Galois Groups Of Polynomials (version of February 5, 2008) http://arxiv.org/abs/math/9411238v2 and Rational parameter rays of the Mandelbrot set (version of August 11, 1998) http://arxiv.org/abs/math/9711213v2.

Synopsis

Documentation

type Angle = Rational Source #

Angle as a fraction of a turn, usually in [0, 1).

tune :: Angle -> (Angle, Angle) -> Angle Source #

Tuning transformation for angles. Probably only valid for angle pairs representing hyperbolic components.

prettyAngle :: Angle -> String Source #

Convert to human readable form.

prettyAngles :: [Angle] -> String Source #

Convert to human readable form.

angles :: Angle -> [Angle] Source #

All external angles landing at the same location as the given external angle.

type BinAngle = ([Bool], [Bool]) Source #

Binary representation of a (pre-)periodic angle.

binary :: Angle -> BinAngle Source #

Convert an angle to binary representation.

unbinary :: BinAngle -> Angle Source #

Convert an angle from binary representation.

btune :: BinAngle -> (BinAngle, BinAngle) -> BinAngle Source #

Tuning transformation for binary represented periodic angles. Probably only valid for angle pairs representing hyperbolic components.

prettyBinAngle :: BinAngle -> String Source #

Convert to human readable form.

parseBinAngle :: String -> Maybe BinAngle Source #

Convert from human readable form.

bperiod :: BinAngle -> Int Source #

Period under angle doubling.

bpreperiod :: BinAngle -> Int Source #

Preperiod under angle doubling.

bangles :: BinAngle -> [BinAngle] Source #

All external angles landing at the same location as the given external angle (binary angle variant).

data Knead Source #

Elements of kneading sequences.

Constructors

Zero 
One 
Star 

Instances

Bounded Knead Source # 
Enum Knead Source # 
Eq Knead Source # 

Methods

(==) :: Knead -> Knead -> Bool #

(/=) :: Knead -> Knead -> Bool #

Data Knead Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Knead -> c Knead #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Knead #

toConstr :: Knead -> Constr #

dataTypeOf :: Knead -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Knead) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Knead) #

gmapT :: (forall b. Data b => b -> b) -> Knead -> Knead #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Knead -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Knead -> r #

gmapQ :: (forall d. Data d => d -> u) -> Knead -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Knead -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Knead -> m Knead #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Knead -> m Knead #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Knead -> m Knead #

Ord Knead Source # 

Methods

compare :: Knead -> Knead -> Ordering #

(<) :: Knead -> Knead -> Bool #

(<=) :: Knead -> Knead -> Bool #

(>) :: Knead -> Knead -> Bool #

(>=) :: Knead -> Knead -> Bool #

max :: Knead -> Knead -> Knead #

min :: Knead -> Knead -> Knead #

Read Knead Source # 
Show Knead Source # 

Methods

showsPrec :: Int -> Knead -> ShowS #

show :: Knead -> String #

showList :: [Knead] -> ShowS #

kneadChar :: Knead -> Char Source #

Knead character representation.

data Kneading Source #

Kneading sequences. Note that the Aperiodic case has an infinite list.

Instances

Eq Kneading Source # 
Data Kneading Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Kneading -> c Kneading #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Kneading #

toConstr :: Kneading -> Constr #

dataTypeOf :: Kneading -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Kneading) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Kneading) #

gmapT :: (forall b. Data b => b -> b) -> Kneading -> Kneading #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Kneading -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Kneading -> r #

gmapQ :: (forall d. Data d => d -> u) -> Kneading -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Kneading -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Kneading -> m Kneading #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Kneading -> m Kneading #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Kneading -> m Kneading #

Ord Kneading Source # 
Read Kneading Source # 
Show Kneading Source # 

prettyKneading :: Kneading -> String Source #

Kneading sequence as a string. The Aperiodic case is truncated arbitrarily.

kneading :: Angle -> Kneading Source #

The kneading sequence for an external angle.

period :: Kneading -> Maybe Int Source #

The period of a kneading sequence, or Nothing when it isn't periodic.

unwrap :: Kneading -> [Knead] Source #

Unwrap a kneading sequence to an infinite list.

associated :: Kneading -> Maybe (Kneading, Kneading) Source #

A star-periodic kneading sequence's upper and lower associated kneading sequences.

upper :: Kneading -> Maybe Kneading Source #

The upper associated kneading sequence.

lower :: Kneading -> Maybe Kneading Source #

The lower associated kneading sequence.

data InternalAddress Source #

Internal addresses are a non-empty sequence of strictly increasing integers beginning with '1'.

Constructors

InternalAddress [Int] 

Instances

Eq InternalAddress Source # 
Data InternalAddress Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InternalAddress -> c InternalAddress #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InternalAddress #

toConstr :: InternalAddress -> Constr #

dataTypeOf :: InternalAddress -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c InternalAddress) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InternalAddress) #

gmapT :: (forall b. Data b => b -> b) -> InternalAddress -> InternalAddress #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InternalAddress -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InternalAddress -> r #

gmapQ :: (forall d. Data d => d -> u) -> InternalAddress -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InternalAddress -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InternalAddress -> m InternalAddress #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InternalAddress -> m InternalAddress #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InternalAddress -> m InternalAddress #

Ord InternalAddress Source # 
Read InternalAddress Source # 
Show InternalAddress Source # 

prettyInternalAddress :: InternalAddress -> String Source #

Internal address as a string.

internalAddress :: Kneading -> Maybe InternalAddress Source #

Construct an InternalAddress from a kneading sequence.

internalFromList :: [Int] -> Maybe InternalAddress Source #

Construct a valid InternalAddress, checking the precondition.

internalToList :: InternalAddress -> [Int] Source #

Extract the sequence of integers.

data AngledInternalAddress Source #

Angled internal addresses have angles between each integer in an internal address.

Instances

Eq AngledInternalAddress Source # 
Data AngledInternalAddress Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AngledInternalAddress -> c AngledInternalAddress #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AngledInternalAddress #

toConstr :: AngledInternalAddress -> Constr #

dataTypeOf :: AngledInternalAddress -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AngledInternalAddress) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AngledInternalAddress) #

gmapT :: (forall b. Data b => b -> b) -> AngledInternalAddress -> AngledInternalAddress #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AngledInternalAddress -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AngledInternalAddress -> r #

gmapQ :: (forall d. Data d => d -> u) -> AngledInternalAddress -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AngledInternalAddress -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AngledInternalAddress -> m AngledInternalAddress #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AngledInternalAddress -> m AngledInternalAddress #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AngledInternalAddress -> m AngledInternalAddress #

Ord AngledInternalAddress Source # 
Read AngledInternalAddress Source # 
Show AngledInternalAddress Source # 

prettyAngledInternalAddress :: AngledInternalAddress -> String Source #

Angled internal address as a string.

angledInternalAddress :: Angle -> Maybe AngledInternalAddress Source #

The angled internal address corresponding to an external angle.

angledFromList :: [(Int, Maybe Angle)] -> Maybe AngledInternalAddress Source #

Builds a valid AngledInternalAddress from a list, checking the precondition that only the last 'Maybe Angle' should be Nothing, and the Integer must be strictly increasing.

externalAngles :: AngledInternalAddress -> Maybe (Angle, Angle) Source #

The pair of external angles whose rays land at the root of the hyperbolic component described by the angled internal address.

stripAngles :: AngledInternalAddress -> InternalAddress Source #

Discard angle information from an internal address.

splitAddress :: AngledInternalAddress -> (AngledInternalAddress, [Angle]) Source #

Split an angled internal address at the last island.

addressPeriod :: AngledInternalAddress -> Int Source #

The period of an angled internal address.

parseAngle :: String -> Maybe Angle Source #

Parse an angle.

parseAngles :: String -> Maybe [Angle] Source #

Parse a list of angles.

parseKnead :: String -> Maybe Knead Source #

Parse a kneading element.

parseKneading :: String -> Maybe Kneading Source #

Parse a non-aperiodic kneading sequence.

parseInternalAddress :: String -> Maybe InternalAddress Source #

Parse an internal address.

parseAngledInternalAddress :: String -> Maybe AngledInternalAddress Source #

Parse an angled internal address, accepting some unambiguous abbreviations.