| Copyright | (c) 2011 Brent Yorgey | 
|---|---|
| License | BSD-style (see LICENSE) | 
| Maintainer | byorgey@cis.upenn.edu | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Diagrams.TwoD.Tilings
Description
Tools for generating and drawing plane tilings made of regular polygons.
- data Q236
- rt2 :: Q236
- rt3 :: Q236
- rt6 :: Q236
- toDouble :: Q236 -> Double
- type Q2 = (Q236, Q236)
- toR2 :: Q2 -> R2
- toP2 :: Q2 -> P2
- data TilingPoly
- polySides :: Num a => TilingPoly -> a
- polyFromSides :: (Num a, Eq a, Show a) => a -> TilingPoly
- polyCos :: TilingPoly -> Q236
- polySin :: TilingPoly -> Q236
- polyRotation :: TilingPoly -> Q2 -> Q2
- polyExtRotation :: TilingPoly -> Q2 -> Q2
- data Tiling = Tiling {- curConfig :: [TilingPoly]
- follow :: Int -> Tiling
 
- data Edge
- mkEdge :: Q2 -> Q2 -> Edge
- newtype Polygon = Polygon {- polygonVertices :: [Q2]
 
- data TilingState = TP {}
- initTilingState :: TilingState
- type TilingM w a = WriterT w (State TilingState) a
- generateTiling :: forall w. Monoid w => Tiling -> Q2 -> Q2 -> (Q2 -> Bool) -> (Edge -> w) -> (Polygon -> w) -> w
- t3 :: Tiling
- t4 :: Tiling
- t6 :: Tiling
- mk3Tiling :: [Int] -> Tiling
- t4612 :: Tiling
- t488 :: Tiling
- t31212 :: Tiling
- t3636 :: Tiling
- semiregular :: [Int] -> [Int] -> Tiling
- rot :: (Num a, Eq a) => a -> [t] -> [t]
- t3464 :: Tiling
- t33434 :: Tiling
- t33344 :: Tiling
- t33336L :: Tiling
- t33336R :: Tiling
- drawEdge :: Renderable (Path R2) b => Style R2 -> Edge -> Diagram b R2
- drawPoly :: Renderable (Path R2) b => (Polygon -> Style R2) -> Polygon -> Diagram b R2
- polyColor :: (Floating a, Ord a) => TilingPoly -> Colour a
- drawTiling :: (Renderable (Path R2) b, Backend b R2) => Tiling -> Double -> Double -> Diagram b R2
- drawTilingStyled :: (Renderable (Path R2) b, Backend b R2) => Style R2 -> (Polygon -> Style R2) -> Tiling -> Double -> Double -> Diagram b R2
The ring Q[sqrt 2, sqrt 3]
Q236 a b c d represents a + b sqrt(2) + c sqrt(3) + d
   sqrt(6).
Regular polygons
data TilingPoly Source
Regular polygons which may appear in a tiling of the plane.
polySides :: Num a => TilingPoly -> a Source
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
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.
An edge is represented by a pair of vertices.  Do not use the
   Edge constructor directly; use mkEdge instead.
mkEdge :: Q2 -> Q2 -> Edge Source
Smart constructor for Edge, which puts the vertices in a
   canonical order.
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 
 | |
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.
Constructors
| TP | |
| Fields 
 | |
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.
Arguments
| :: 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.
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.
Diagrams
drawEdge :: Renderable (Path R2) b => Style R2 -> Edge -> Diagram b R2 Source
Draw an edge with the given style.
drawPoly :: Renderable (Path R2) b => (Polygon -> Style R2) -> Polygon -> Diagram b R2 Source
Draw a polygon with the given style.