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

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

Diagrams.TwoD.Path.IteratedSubset

Contents

Description

Generate fractal trails by the "iterated subset" construction, iteratively replacing each segment with a given pattern.

Synopsis

Iterated subset algorithm

Simplified version

refineSegment :: RealFloat n => Trail' Line V2 n -> V2 n -> Maybe (Trail' Line V2 n) Source #

Use a trail to "refine" a linear segment (represented by a vector), returning a scaled and/or rotated copy of the trail with the same endpoint as the segment.

iterTrail :: RealFloat n => Trail' Line V2 n -> [Trail' Line V2 n] Source #

Given a "seed pattern", produce a list of successive refinements: the zeroth trail in the output list is a horizontal unit segment, and the nth trail is formed by replacing each segment of the seed pattern with the (n-1)st trail. (Equivalently, the nth trail consists of the (n-1)st trail with every segment replaced by the seed pattern.)

See iterGenerator for a more sophisticated variant which can associate one of four orientations with each segment of the seed pattern.

import Diagrams.TwoD.Path.IteratedSubset
iterTrailEx = vsep 0.3 . map strokeLine . take 5
            $ iterTrail koch

General version

Much of the approach here is taken from Jeffrey Ventrella, Brain-filling Curves. EyeBrain Books, 2nd edition, 2012. ISBN 9780983054627. http://www.fractalcurves.com/, http://www.brainfillingcurves.com/

Each generator consists of a sequence of linear segments with endpoints on a square or triangular grid. Each segment can also have one of four orientations which determines how it is replaced by a copy of the entire fractal path. Generators are classified by the distance between their start and end points; generators for which the sum of the squared lengths of their segments is equal to the square of this overall distance have fractal dimension 2 and thus are candidates to be space-filling curves.

data GeneratorSegment n Source #

A generator segment is a vector along with two bits' worth of orientation information: whether there is a reflection swapping its start and end, and whether there is a reflection across its axis. When a generator segment is replaced by a complex path, the endpoints of the path will match the endpoints of the segment, but the path may first have some reflections applied to it according to the orientation of the segment.

Constructors

GS (V2 n) Bool Bool 

mkGS :: (n, n, Int, Int) -> GeneratorSegment n Source #

Make a generator segment by specifying an x component, a y component, a "horizontal" orientation (1 means normal, -1 means reversing the start and end of the segment) and a "vertical" orientation (1 means normal, -1 means reflecting across the axis of the segment). This corresponds to the notation used by Ventrella in Brainfilling Curves.

mkGS3 :: Floating n => (n, n, Int, Int) -> GeneratorSegment n Source #

Make a generator segment on a triangular grid, by specifying a segment on a square grid and then applying a shear and a scale to transform the square grid into a triangular grid, as in the diagram below:

type Generator n = [GeneratorSegment n] Source #

A generator is a sequence of consecutive generator segments.

refineGeneratorSegment :: RealFloat n => Trail' Line V2 n -> GeneratorSegment n -> Maybe (Trail' Line V2 n) Source #

Use a trail to "refine" a generator segment, returning a scaled and/or rotated copy of the trail with the same endpoints as the segment, and with appropriate reflections applied depending on the orientation of the segment.

iterGenerator :: RealFloat n => Generator n -> [Trail' Line V2 n] Source #

Given a generator, produce a list of successive refinements: the zeroth trail in the output list is a horizontal unit segment, and the nth trail is formed by refining each segment of the generator with the (n-1)st trail.

import Diagrams.TwoD.Path.IteratedSubset
iterGenEx = hsep 0.3 . map strokeLine . take 7
          $ iterGenerator dragonGen

Utilities

averageLine :: (Metric v, Floating n, Ord n) => Trail' Line v n -> Trail' Line v n Source #

Perform a "level-1 smoothing" by replacing a list of segments by the segments between their midpoints. Can be a useful technique for visualizing degenerate space-filling curves, e.g. which touch at corners or even share entire edges.

bevelLine :: (Metric v, Floating n, Ord n) => Trail' Line v n -> Trail' Line v n Source #

Bevel a line by "chopping off each corner", connecting points 1/3 and 2/3 of the way along each segment. Can be a useful technique for visualizing degenerate space-filling curves, e.g. which touch at corners or even share entire edges.

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

Create a graphical representation of a generator, using half arrowheads to show the orientation of each segment.

Examples

Example seed trails

 

koch :: (TrailLike t, V t ~ V2, N t ~ n) => t Source #

Seed for the Koch curve (side of the famous Koch snowflake).

levy :: (TrailLike t, V t ~ V2, N t ~ n) => t Source #

Seed for the Lévy dragon curve.

zag :: (TrailLike t, V t ~ V2, N t ~ n) => t Source #

Strange zig-zag seed that produces a dense fractal path with lots of triangles.

sqUp :: (TrailLike t, V t ~ V2, N t ~ n) => t Source #

A "square impulse" seed which produces a quadratic von Koch curve.

sqUpDown :: (TrailLike t, V t ~ V2, N t ~ n) => t Source #

A "double square impulse" seed which produces fantastic rectilinear spiral patterns.

Example generators

Many of these generators are taken from Jeffrey Ventrella, Brain-filling Curves, which has a large number of other examples as well (see http://www.brainfillingcurves.com/).

dragonGen :: Generator Double Source #

Generator for the classic Harter-Heighway Dragon (Ventrella p. 52, sqrt 2 family).

polyaGen :: Generator Double Source #

Generator for the Pólya sweep (Ventrella p. 52, sqrt 2 family).

terDragonGen :: Generator Double Source #

Generator for the Ter-Dragon (Ventrella p. 55, sqrt 3 family).

invTerDragonGen :: Generator Double Source #

Inverted Ter-Dragon (Ventrella p. 56, sqrt 3 family).

ventrella56b :: Generator Double Source #

Ventrella p. 56b, sqrt 3 family.

yinDragonGen :: Generator Double Source #

Yin Dragon (Ventrella p. 59, sqrt 3 family).

ventrella67 :: Generator Double Source #

Ventrella p. 67, sqrt 4 family.

innerFlipQuartetGen :: Generator Double Source #

"Inner-flip Quartet" (Ventrella p. 85, sqrt 5 family).

antiGosperGen :: Generator Double Source #

"Anti-Gosper" (Ventrella p. 97, sqrt 7 family).

mandelbrotSnowflakeGen :: Generator Double Source #

"Mandelbrot Snowflake Sweep #2" (Ventrella p. 197, sqrt 27 family).

Other stuff

A random collection of other fun things you can do with iterTrail or iterGenerator. There is no particular emphasis on making these configurable or generic; the point is just to suggest some fun things you can do. If you want to play with them, copy the source code and modify it as you see fit.

snowflake :: RealFloat n => Int -> Trail V2 n Source #

The famous Koch snowflake, made by putting three Koch curves together. snowflake n yields an order-n snowflake.

data IterTrailConfig n Source #

Parameters to generate an iterated subset fractal.

Constructors

ITC 

Fields

randITC :: (MonadRandom m, Ord n, Floating n, Random n) => m (IterTrailConfig n) Source #

Generate a random IterTrailConfig. This features many hard-coded values. If you want to play with it just copy the code and modify it to suit.

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

Generate an iterated subset fractal based on the given parameters.

drawITCScaled :: (Renderable (Path V2 n) b, RealFloat n, Typeable n) => IterTrailConfig n -> QDiagram b V2 n Any Source #

Like drawITC, but also scales, centers, and pads the result so that it fits nicely inside a 4x4 box.

randIterGrid :: (Renderable (Path V2 n) b, Random n, TypeableFloat n) => IO (QDiagram b V2 n Any) Source #

Create a grid of 25 random iterated subset fractals. Impress your friends!