diagrams-contrib-1.4.0.1: Collection of user contributions to diagrams EDSL

Copyright(c) 2011, 2016 Brent Yorgey
LicenseBSD-style (see LICENSE)
Maintainerbyorgey@cis.upenn.edu
Safe HaskellNone
LanguageHaskell2010

Diagrams.TwoD.Apollonian

Contents

Description

Generation of Apollonian gaskets. Any three mutually tangent circles uniquely determine exactly two others which are mutually tangent to all three. This process can be repeated, generating a fractal circle packing.

See J. Lagarias, C. Mallows, and A. Wilks, "Beyond the Descartes circle theorem", Amer. Math. Monthly 109 (2002), 338--361. http://arxiv.org/abs/math/0101066.

A few examples:

import Diagrams.TwoD.Apollonian
apollonian1 = apollonianGasket 0.01 2 2 2

import Diagrams.TwoD.Apollonian
apollonian2 = apollonianGasket 0.01 2 3 3

import Diagrams.TwoD.Apollonian
apollonian3 = apollonianGasket 0.01 2 4 7

Synopsis

Circles

data Circle n Source #

Representation for circles that lets us quickly compute an Apollonian gasket.

Constructors

Circle 

Fields

  • bend :: n

    The bend is the reciprocal of signed radius: a negative radius means the outside and inside of the circle are switched. The bends of any four mutually tangent circles satisfy Descartes' Theorem.

  • cb :: Complex n

    Product of bend and center represented as a complex number. Amazingly, these products also satisfy the equation of Descartes' Theorem.

Instances

Eq n => Eq (Circle n) Source # 

Methods

(==) :: Circle n -> Circle n -> Bool #

(/=) :: Circle n -> Circle n -> Bool #

RealFloat n => Floating (Circle n) Source #

The Num, Fractional, and Floating instances for Circle (all simply lifted elementwise over Circle's fields) let us use Descartes' Theorem directly on circles.

Methods

pi :: Circle n #

exp :: Circle n -> Circle n #

log :: Circle n -> Circle n #

sqrt :: Circle n -> Circle n #

(**) :: Circle n -> Circle n -> Circle n #

logBase :: Circle n -> Circle n -> Circle n #

sin :: Circle n -> Circle n #

cos :: Circle n -> Circle n #

tan :: Circle n -> Circle n #

asin :: Circle n -> Circle n #

acos :: Circle n -> Circle n #

atan :: Circle n -> Circle n #

sinh :: Circle n -> Circle n #

cosh :: Circle n -> Circle n #

tanh :: Circle n -> Circle n #

asinh :: Circle n -> Circle n #

acosh :: Circle n -> Circle n #

atanh :: Circle n -> Circle n #

log1p :: Circle n -> Circle n #

expm1 :: Circle n -> Circle n #

log1pexp :: Circle n -> Circle n #

log1mexp :: Circle n -> Circle n #

RealFloat n => Fractional (Circle n) Source # 

Methods

(/) :: Circle n -> Circle n -> Circle n #

recip :: Circle n -> Circle n #

fromRational :: Rational -> Circle n #

RealFloat n => Num (Circle n) Source # 

Methods

(+) :: Circle n -> Circle n -> Circle n #

(-) :: Circle n -> Circle n -> Circle n #

(*) :: Circle n -> Circle n -> Circle n #

negate :: Circle n -> Circle n #

abs :: Circle n -> Circle n #

signum :: Circle n -> Circle n #

fromInteger :: Integer -> Circle n #

Show n => Show (Circle n) Source # 

Methods

showsPrec :: Int -> Circle n -> ShowS #

show :: Circle n -> String #

showList :: [Circle n] -> ShowS #

mkCircle Source #

Arguments

:: Fractional n 
=> n

signed radius

-> P2 n

center

-> Circle n 

Create a Circle given a signed radius and a location for its center.

center :: Fractional n => Circle n -> P2 n Source #

Get the center of a circle.

radius :: Fractional n => Circle n -> n Source #

Get the (unsigned) radius of a circle.

Descartes' Theorem

descartes :: Floating n => [n] -> [n] Source #

Descartes' Theorem states that if b1, b2, b3 and b4 are the bends of four mutually tangent circles, then

    b1^2 + b2^2 + b3^2 + b4^2 = 1/2 * (b1 + b2 + b3 + b4)^2.
  

Surprisingly, if we replace each of the bi with the product of bi and the center of the corresponding circle (represented as a complex number), the equation continues to hold! (See the paper referenced at the top of the module.)

descartes [b1,b2,b3] solves for b4, returning both solutions. Notably, descartes works for any instance of Floating, which includes both Double (for bends), Complex Double (for bend/center product), and Circle (for both at once).

other :: Num n => [n] -> n -> n Source #

If we have four mutually tangent circles we can choose one of them to replace; the remaining three determine exactly one other circle which is mutually tangent. However, in this situation there is no need to apply descartes again, since the two solutions b4 and b4' satisfy

    b4 + b4' = 2 * (b1 + b2 + b3)
  

Hence, to replace b4 with its dual, we need only sum the other three, multiply by two, and subtract b4. Again, this works for bends as well as bend/center products.

initialConfig :: RealFloat n => n -> n -> n -> [Circle n] Source #

Generate an initial configuration of four mutually tangent circles, given just the signed bends of three of them.

Apollonian gasket generation

apollonian :: RealFloat n => n -> [Circle n] -> [Circle n] Source #

Given a threshold radius and a list of four mutually tangent circles, generate the Apollonian gasket containing those circles. Stop the recursion when encountering a circle with an (unsigned) radius smaller than the threshold.

Kissing sets

data KissingSet n Source #

The basic idea of a kissing set is supposed to represent a set of four mutually tangent circles with one selected, though in fact it is more general than that: it represents any set of objects with one distinguished object selected.

Constructors

KS 

Fields

Instances

kissingSets :: [n] -> [KissingSet n] Source #

Generate all possible kissing sets from a set of objects by selecting each object in turn.

flipSelected :: Num n => KissingSet n -> KissingSet n Source #

"Flip" the selected circle to the other circle mutually tangent to the other three. The new circle remains selected.

selectOthers :: KissingSet n -> [KissingSet n] Source #

Make the selected circle unselected, and select each of the others, generating a new kissing set for each.

Apollonian trees

apollonianTrees :: RealFloat n => [Circle n] -> [Tree (KissingSet (Circle n))] Source #

Given a set of four mutually tangent circles, generate the infinite Apollonian tree rooted at the given set, represented as a list of four subtrees. Each node in the tree is a kissing set with one circle selected which has just been flipped. The three children of a node represent the kissing sets obtained by selecting each of the other three circles and flipping them. The initial roots of the four trees are chosen by selecting and flipping each of the circles in the starting set. This representation has the property that each circle in the Apollonian gasket is the selected circle in exactly one node (except that the initial four circles never appear as the selected circle in any node).

apollonianTree :: RealFloat n => KissingSet (Circle n) -> Tree (KissingSet (Circle n)) Source #

Generate a single Apollonian tree from a root kissing set. See the documentation for apollonianTrees for an explanation.

Diagram generation

drawCircle :: (Renderable (Path V2 n) b, TypeableFloat n) => Circle n -> QDiagram b V2 n Any Source #

Draw a circle.

drawGasket :: (Renderable (Path V2 n) b, TypeableFloat n) => [Circle n] -> QDiagram b V2 n Any Source #

Draw a generated gasket, using a line width 0.003 times the radius of the largest circle.

apollonianGasket :: (Renderable (Path V2 n) b, TypeableFloat n) => n -> n -> n -> n -> QDiagram b V2 n Any Source #

Draw an Apollonian gasket: the first argument is the threshold; the recursion will stop upon reaching circles with radii less than it. The next three arguments are bends of three circles.