diagrams-contrib-1.3.0: 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 = vcat' (with & sep .~ 0.3) . map strokeLine . take 5
            $ iterTrail koch

General version

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 XXX.

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.

Examples

Example seed trails

 

koch :: (TrailLike t, V t ~ V2, N t ~ n, Floating 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

See Brain-filling XXX

Other stuff

A random collection of other fun things you can do with iterTrail. 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

seed :: Trail' Line V2 n

The seed trail

color :: Colour Double

The line color to use

iters :: Int

Number of iterations

randITC :: (MonadRandom m, Applicative 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!