PenroseKiteDart-1.0.0: Library to explore Penrose's Kite and Dart Tilings.
Copyright(c) Chris Reade 2021
LicenseBSD-style
Maintainerchrisreade@mac.com
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010

TileLib

Description

This module introduces Pieces and Patches for drawing finite tilings using Penrose's Dart and Kite tiles. It includes several primitives for drawing half tiles (Pieces), a class Drawable with instance Patch and commonly used operations for the Drawable class (draw, drawj, fillDK,..). There is also a decompose operation for Patches (decompPatch) and sun and star example Patches.

Synopsis

Pieces

type Piece = HalfTile (V2 Double) Source #

Piece type for tile halves: Left Dart, Right Dart, Left Kite, Right Kite with a vector from their origin along the join edge where origin for a dart is the tip, origin for a kite is the vertex with smallest internal angle. Using Imported polymorphic HalfTile.

Pieces are Transformable

joinVector :: Piece -> V2 Double Source #

get the vector representing the join edge in the direction away from the origin of a piece

ldart :: Piece Source #

ldart,rdart,lkite,rkite are the 4 pieces (with join edge oriented along the x axis, unit length for darts, length phi for kites).

rdart :: Piece Source #

ldart,rdart,lkite,rkite are the 4 pieces (with join edge oriented along the x axis, unit length for darts, length phi for kites).

lkite :: Piece Source #

ldart,rdart,lkite,rkite are the 4 pieces (with join edge oriented along the x axis, unit length for darts, length phi for kites).

rkite :: Piece Source #

ldart,rdart,lkite,rkite are the 4 pieces (with join edge oriented along the x axis, unit length for darts, length phi for kites).

Drawing Pieces

type Diagram2D b = QDiagram b V2 Double Any Source #

Abbreviation for 2D diagrams for any Backend b.

phi :: Double Source #

All edge lengths are powers of the golden ratio (phi). We also have the interesting property of the golden ratio that phi^2 == phi + 1 and so 1/phi = phi-1 (also phi^3 = 2phi +1 and 1/phi^2 = 2-phi)

ttangle :: Int -> Angle Double Source #

All angles used are multiples of tt where tt is a tenth of a turn (so 36 degrees). ttangle n is n multiples of tt.

pieceEdges :: Piece -> [V2 Double] Source #

produces a list of the two adjacent non-join tile directed edges of a piece starting from the origin.

Perhaps confusingly we regard left and right of a dart differently from left and right of a kite. This is in line with common sense view but darts are reversed from origin point of view.

So for right dart and left kite the edges are directed and ordered clockwise from the piece origin, and for left dart and right kite these are directed and ordered anti-clockwise from the piece origin.

wholeTileEdges :: Piece -> [V2 Double] Source #

the 4 tile edges of a completed half-tile piece (used for colour fill). These are directed and ordered clockwise from the origin of the tile.

drawPiece :: Renderable (Path V2 Double) b => Piece -> Diagram2D b Source #

drawing lines for the 2 non-join edges of a piece.

When a specific Backend B is in scope, drawPiece:: Piece -> Diagram B

dashjPiece :: Renderable (Path V2 Double) b => Piece -> Diagram2D b Source #

same as drawPiece but with join edge added as dashed-line.

When a specific Backend B is in scope, dashjPiece:: Piece -> Diagram B

dashjOnly :: Renderable (Path V2 Double) b => Piece -> Diagram2D b Source #

draw join edge only (as dashed line).

When a specific Backend B is in scope, dashjOnly:: Piece -> Diagram B

drawRoundPiece :: Renderable (Path V2 Double) b => Piece -> Diagram2D b Source #

same as drawPiece but with added join edge (also fillable as a loop).

When a specific Backend B is in scope, drawRoundPiece:: Piece -> Diagram B

drawJoin :: Renderable (Path V2 Double) b => Piece -> Diagram2D b Source #

draw join edge only.

When a specific Backend B is in scope, drawJoin:: Piece -> Diagram B

fillOnlyPiece :: Renderable (Path V2 Double) b => Colour Double -> Piece -> Diagram2D b Source #

fillOnlyPiece col piece - fills piece with colour col without drawing any lines.

When a specific Backend B is in scope, fillOnlyPiece:: Colour Double -> Piece -> Diagram B

fillPieceDK :: Renderable (Path V2 Double) b => Colour Double -> Colour Double -> HalfTile (V2 Double) -> Diagram2D b Source #

fillPieceDK dcol kcol piece - draws and fills the half-tile piece with colour dcol for darts and kcol for kites. Note the order D K.

When a specific Backend B is in scope, fillPieceDK:: Colour Double -> Colour Double -> Piece -> Diagram B

fillMaybePieceDK :: Renderable (Path V2 Double) b => Maybe (Colour Double) -> Maybe (Colour Double) -> Piece -> Diagram2D b Source #

fillMaybePieceDK d k piece - draws the half-tile piece and possibly fills as well: darts with dcol if d = Just dcol, kites with kcol if k = Just kcol Nothing indicates no fill for either darts or kites or both.

When a specific Backend B is in scope, fillMaybePieceDK:: Maybe (Colour Double) -> Maybe (Colour Double) -> Piece -> Diagram B

leftFillPieceDK :: Renderable (Path V2 Double) b => Colour Double -> Colour Double -> HalfTile (V2 Double) -> Diagram2D b Source #

leftFillPieceDK dcol kcol pc fills the whole tile when pc is a left half-tile, darts are filled with colour dcol and kites with colour kcol. (Right half-tiles produce nothing, so whole tiles are not drawn twice).

When a specific Backend B is in scope, leftFillPieceDK:: Colour Double -> Colour Double -> Piece -> Diagram B

experiment :: Renderable (Path V2 Double) b => Piece -> Diagram2D b Source #

experiment uses a different rule for drawing half tiles. This clearly displays the larger kites and darts. Half tiles are first drawn with dashed lines, then certain edges are overlayed to emphasise them. Half darts have the join edge emphasised in red, while Half kites have the long edge emphasised in black.

When a specific Backend B is in scope, experiment:: Piece -> Diagram B

Patches and Drawable Class

class Drawable a where Source #

A class for things that can be turned to diagrams when given a function to draw pieces.

Methods

drawWith :: Renderable (Path V2 Double) b => (Piece -> Diagram2D b) -> a -> Diagram2D b Source #

Instances

Instances details
Drawable Tgraph Source #

Tgraphs are Drawable

Instance details

Defined in Tgraph.Prelude

Drawable VPatch Source #

VPatches are drawable

Instance details

Defined in Tgraph.Prelude

Drawable Patch Source #

Patches are drawable

Instance details

Defined in TileLib

type Patch = [Located Piece] Source #

A patch is a list of Located pieces (the point associated with each piece locates its originV) Patches are Transformable

draw :: (Drawable a, Renderable (Path V2 Double) b) => a -> Diagram2D b Source #

the main default case for drawing using drawPiece.

When a specific Backend B is in scope, draw :: Drawable a => a -> Diagram B

drawj :: (Drawable a, Renderable (Path V2 Double) b) => a -> Diagram2D b Source #

alternative default case for drawing adding dashed lines for join edges.

When a specific Backend B is in scope, drawj :: Drawable a => a -> Diagram B

fillDK :: (Drawable a, Renderable (Path V2 Double) b) => Colour Double -> Colour Double -> a -> Diagram2D b Source #

fillDK dcol kcol a - draws and fills a with colour dcol for darts and kcol for kites. Note the order D K.

When a specific Backend B is in scope, fillDK:: Drawable a => Colour Double -> Colour Double -> a -> Diagram B

fillKD :: (Drawable a, Renderable (Path V2 Double) b) => Colour Double -> Colour Double -> a -> Diagram2D b Source #

fillKD kcol dcol a - draws and fills a with colour kcol for kites and dcol for darts. Note the order K D.

When a specific Backend B is in scope, fillKD:: Drawable a => Colour Double -> Colour Double -> a -> Diagram B

fillMaybeDK :: (Drawable a, Renderable (Path V2 Double) b) => Maybe (Colour Double) -> Maybe (Colour Double) -> a -> Diagram2D b Source #

fillMaybeDK c1 c2 a - draws a and maybe fills as well: darts with dcol if d = Just dcol, kites with kcol if k = Just kcol Nothing indicates no fill for either darts or kites or both Note the order D K.

When a specific Backend B is in scope, fillMaybeDK:: Drawable a => Maybe (Colour Double) -> Maybe (Colour Double) -> a -> Diagram B

colourDKG :: (Drawable a, Renderable (Path V2 Double) b) => (Colour Double, Colour Double, Colour Double) -> a -> Diagram2D b Source #

colourDKG (c1,c2,c3) p - fill in a drawable with colour c1 for darts, colour c2 for kites and colour c3 for grout (that is, the non-join edges). Note the order D K G.

When a specific Backend B is in scope, colourDKG:: Drawable a => (Colour Double,Colour Double,Colour Double) -> a -> Diagram B

colourMaybeDKG :: (Drawable a, Renderable (Path V2 Double) b) => (Maybe (Colour Double), Maybe (Colour Double), Maybe (Colour Double)) -> a -> Diagram2D b Source #

colourMaybeDKG (d,k,g) a - draws a and possibly fills as well: darts with dcol if d = Just dcol, kites with kcol if k = Just kcol Nothing indicates no fill for either darts or kites or both The g argument is for grout - i.e the non-join edges round tiles. Edges are drawn with gcol if g = Just gcol and not drawn if g = Nothing.

When a specific Backend B is in scope, colourMaybeDKG:: Drawable a => (Maybe (Colour Double), Maybe (Colour Double), Maybe (Colour Double)) -> a -> Diagram B

Patch Decomposition and Compose choices

decompPatch :: Patch -> Patch Source #

Decomposing splits each located piece in a patch into a list of smaller located pieces to create a refined patch. (See also decompose in Tgraph.Decompose.hs for a more abstract version of this operation).

decompositionsP :: Patch -> [Patch] Source #

Create an infinite list of increasing decompositions of a patch

compChoices :: Located Piece -> [Located Piece] Source #

compChoices applied to a single located piece produces a list of alternative located pieces NOT a Patch. Each of these is a larger scale single piece with a location such that when decomposed the original piece in its original position is part of the decomposition)

compNChoices :: Int -> Located Piece -> [Located Piece] Source #

compNChoices n lp - gives a list of all the alternatives after n compChoices starting with lp Note that the result is not a Patch as the list represents alternatives.

Example Patches

penta :: Patch -> Patch Source #

combine 5 copies of a patch (each rotated by ttangle 2 successively) (ttAngle 2 is 72 degrees) Must be used with care to avoid creating a nonsense patch

sun :: Patch Source #

sun is a patch with five kites sharing common origin (base of kite)

star :: Patch Source #

star is a patch with five darts sharing common origin (tip of dart)

suns :: [Patch] Source #

An infinite list of patches of increasingly decomposed sun

sun5 :: Patch Source #

a patch of a 5 times decomposed sun

sun6 :: Patch Source #

a patch of a 6 times decomposed sun

Diagrams of Patches

sun6Fig :: Renderable (Path V2 Double) b => Diagram2D b Source #

diagram for sun6.

When a specific Backend B is in scope, sun6Fig::Diagram B

leftFilledSun6 :: Renderable (Path V2 Double) b => Diagram2D b Source #

Colour filled using leftFillPieceDK.

When a specific Backend B is in scope, leftFilledSun6::Diagram B

filledSun6 :: Renderable (Path V2 Double) b => Diagram2D b Source #

Colour filled using fillDK.

When a specific Backend B is in scope, filledSun6::Diagram B

Rotation and Scaling operations

rotations :: (Transformable a, V a ~ V2, N a ~ Double) => [Int] -> [a] -> [a] Source #

rotations takes a list of integers (representing ttangles) for respective rotations of items in the second list (things to be rotated). This includes Diagrams, Patches, VPatches. The integer list can be shorter than the list of items - the remaining items are left unrotated. It will raise an error if the integer list is longer than the list of items to be rotated. (Rotations by an angle are anti-clockwise)

scales :: (Transformable a, V a ~ V2, N a ~ Double) => [Double] -> [a] -> [a] Source #

scales takes a list of doubles for respective scalings of items in the second list (things to be scaled). This includes Diagrams, Pieces, Patches, VPatches. The list of doubles can be shorter than the list of items - the remaining items are left unscaled. It will raise an error if the integer list is longer than the list of items to be scaled.

phiScales :: (Transformable a, V a ~ V2, N a ~ Double) => [a] -> [a] Source #

increasing scales by a factor of phi along a list starting with 1.

phiScaling :: (Transformable a, V a ~ V2, N a ~ Double) => Double -> [a] -> [a] Source #

increasing scales by a factor of phi along a list starting with given first argument