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

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

Diagrams.TwoD.Tilings

Contents

Description

Tools for generating and drawing plane tilings made of regular polygons.

Synopsis

The ring Q[sqrt 2, sqrt 3]

data Q236 Source

Q236 a b c d represents a + b sqrt(2) + c sqrt(3) + d sqrt(6). Note that the Ord instance is suitable for use in Map and Set, but does not correspond to numeric ordering (Q236 is not an ordered field under this ordering).

toFloating :: Floating n => Q236 -> n Source

Convert a Q236 value to a Double.

type Q2 = V2 Q236 Source

toV2 :: Floating n => Q2 -> V2 n Source

toP2 :: Floating n => Q2 -> P2 n Source

Regular polygons

data TilingPoly Source

Regular polygons which may appear in a tiling of the plane.

polyFromSides :: (Num a, Eq a, Show a) => a -> TilingPoly Source

polyCos :: TilingPoly -> Q236 Source

Cosine of a polygon's internal angle.

polySin :: TilingPoly -> Q236 Source

Sine of a polygon's internal angle.

polyRotation :: TilingPoly -> Q2 -> Q2 Source

Rotate by polygon internal angle.

polyExtRotation :: TilingPoly -> Q2 -> Q2 Source

Rotate by polygon external angle.

Tilings

Types

data Tiling Source

A tiling, represented as a sort of zipper. curConfig indicates the polygons around the current vertex, in couterclockwise order starting from the edge along which we entered the vertex. follow allows one to move along an edge to an adjacent vertex, where the edges are numbered counterclockwise from zero, beginning with the edge along which we entered the current vertex.

Constructors

Tiling 

Fields

curConfig :: [TilingPoly]
 
follow :: Int -> Tiling
 

data Edge Source

An edge is represented by a pair of vertices. Do not use the Edge constructor directly; use mkEdge instead.

Instances

mkEdge :: Q2 -> Q2 -> Edge Source

Smart constructor for Edge, which puts the vertices in a canonical order.

newtype Polygon Source

A polygon is represented by a list of its vertices, in counterclockwise order. However, the Eq and Ord instances for polygons ignore the order.

Constructors

Polygon 

Fields

polygonVertices :: [Q2]
 

Generation

data TilingState Source

The state maintained while generating a tiling, recording which vertices have been visited and which edges and polygons have been drawn.

type TilingM w a = WriterT w (State TilingState) a Source

The TilingM monad tracks a TilingState, and can output elements of some monoid w along the way.

generateTiling Source

Arguments

:: forall w . Monoid w 
=> Tiling

The tiling to generate

-> Q2

The location of the starting vertex.

-> Q2

The starting direction, i.e. the direction along which we came into the starting vertex.

-> (Q2 -> Bool)

Predicate on vertices specifying which should be visited. The vertices for which the predicate evaluates to True must form a single connected component.

-> (Edge -> w)

what to do with edges

-> (Polygon -> w)

what to do with polygons

-> w 

Pre-defined tilings

mk3Tiling :: [Int] -> Tiling Source

Create a tiling with the same 3 polygons surrounding each vertex. The argument is the number of sides of the polygons surrounding a vertex.

semiregular Source

Arguments

:: [Int]

The number of sides of the polygons surrounding a typical vertex, counterclockwise starting from edge 0.

-> [Int]

The transition list: if the ith entry of this list is j, it indicates that the edge labeled i is labeled j with respect to the vertex on its other end.

-> Tiling 

Create a tiling where every vertex is the same up to rotation and translation (but not reflection). Arbitrarily pick one of the edges emanating from a vertex and number the edges counterclockwise starting with 0 for the chosen edge.

rot :: (Num a, Eq a) => a -> [t] -> [t] Source

Diagrams

drawEdge :: (Renderable (Path V2 n) b, TypeableFloat n) => Style V2 n -> Edge -> QDiagram b V2 n Any Source

Draw an edge with the given style.

drawPoly :: (Renderable (Path V2 n) b, TypeableFloat n) => (Polygon -> Style V2 n) -> Polygon -> QDiagram b V2 n Any Source

Draw a polygon with the given style.

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

Draw a tiling, with a given width and height and default colors for the polygons.

drawTilingStyled :: forall b n. (Renderable (Path V2 n) b, TypeableFloat n) => Style V2 n -> (Polygon -> Style V2 n) -> Tiling -> n -> n -> QDiagram b V2 n Any Source

Draw a tiling with customizable styles for the polygons. This is just an example, which you can use as the basis of your own tiling-drawing routine.