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

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,..). It also introduces class OKBackend to summarise constraints on a Backend for drawing. There is also a decompose operation for Patches (decompPatch) and sun and star example Patches.

Synopsis

Documentation

class (V b ~ V2, N b ~ Double, Renderable (Path V2 Double) b, Renderable (Text Double) b) => OKBackend b Source #

Class OKBackend is a class synonym for a collection of constraints on a Backend b suitable for drawing tiles. That is 2 dimensional with Real numbers (Double) able to render paths and text.

Instances

Instances details
(V b ~ V2, N b ~ Double, Renderable (Path V2 Double) b, Renderable (Text Double) b) => OKBackend b Source #

Instance declaration for OKBackend requires UndecidableInstances to be enabled, but allows a suitable backend B to be recognised as an instance without explicitly writing instance OKBackend B Note B will be declared by user of this library and is not declared in the library

Instance details

Defined in CheckBackend

Pieces

type Piece = HalfTile (V2 Double) Source #

Piece is a type for (scaled and oriented) tile halves: Left Dart, Right Dart, Left Kite, Right Kite represented by a vector from their origin along the join edge where origin for a dart is the tip, origin for a kite is the vertex opposite the vertex with largest internal angle.

(This specialises polymorphic HalfTiles with 2D vectors).

Pieces are Transformable (but not translatable until they are located).

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 is a left dart at the origin with join edge oriented along the x axis, unit length.

rdart :: Piece Source #

rdart is a right dartat the origin with join edge oriented along the x axis, unit length.

lkite :: Piece Source #

lkite is a left kite at the origin with join edge oriented along the x axis, length phi.

rkite :: Piece Source #

rkite is a right kite at the origin with join edge oriented along the x axis, length phi.

Drawing Pieces

phi :: Double Source #

All edge lengths are powers of the golden ratio (phi). We have the following roperties of the golden ratio

phi^2 == phi + 1 and 1/phi = phi-1

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 #

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

We consider left and right as viewed from the origin. This means that darts are reversed with respect to a view from the tail, but kites are in keeping with a common view (the kite tail being the origin).

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.

Note: Most functions for drawing will have constraint OKBackend b and result type Diagram b

drawPiece :: OKBackend b => Piece -> Diagram b Source #

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

dashjPiece :: OKBackend b => Piece -> Diagram b Source #

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

joinDashing :: (HasStyle c, N c ~ Double) => c -> c Source #

changes line style to ultraThin dashed lines (for drawing join edges)

dashjOnly :: OKBackend b => Piece -> Diagram b Source #

draw join edge only (as faint dashed line).

drawRoundPiece :: OKBackend b => Piece -> Diagram b Source #

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

drawJoin :: OKBackend b => Piece -> Diagram b Source #

draw join edge only.

fillOnlyPiece :: (OKBackend b, Color c) => c -> Piece -> Diagram b Source #

fillOnlyPiece col piece - fills piece with colour col without drawing any lines. Can be used with both Colour and AlphaColour

fillPieceDK :: (OKBackend b, Color c1, Color c2) => c1 -> c2 -> HalfTile (V2 Double) -> Diagram 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. Can be used with both Colour and AlphaColour

leftFillPieceDK :: (OKBackend b, Color c1, Color c2) => c1 -> c2 -> HalfTile (V2 Double) -> Diagram 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). Works with AlphaColours as well as Colours.

experiment :: OKBackend b => Piece -> Diagram 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.

Patches and Drawable Class

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 (including translatable)

class Drawable a where Source #

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

Methods

drawWith :: OKBackend b => (Piece -> Diagram b) -> a -> Diagram b Source #

Instances

Instances details
Drawable Tgraph Source #

Tgraphs are Drawable

Instance details

Defined in Tgraph.Prelude

Methods

drawWith :: OKBackend b => (Piece -> Diagram b) -> Tgraph -> Diagram b Source #

Drawable VPatch Source #

VPatches are drawable

Instance details

Defined in Tgraph.Prelude

Methods

drawWith :: OKBackend b => (Piece -> Diagram b) -> VPatch -> Diagram b Source #

Drawable Patch Source #

Patches are drawable

Instance details

Defined in TileLib

Methods

drawWith :: OKBackend b => (Piece -> Diagram b) -> Patch -> Diagram b Source #

draw :: (Drawable a, OKBackend b) => a -> Diagram b Source #

the main default case for drawing using drawPiece.

drawj :: (Drawable a, OKBackend b) => a -> Diagram b Source #

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

fillDK :: (Drawable a, OKBackend b, Color c1, Color c2) => c1 -> c2 -> a -> Diagram b Source #

fillDK dcol kcol a - draws and fills a with colour dcol for darts and kcol for kites. Note the order D K. Works with AlphaColours as well as Colours.

fillKD :: (Drawable a, OKBackend b, Color c1, Color c2) => c1 -> c2 -> a -> Diagram b Source #

fillKD kcol dcol a - draws and fills a with colour kcol for kites and dcol for darts. Note the order K D. Works with AlphaColours as well as Colours.

colourDKG :: (Drawable a, OKBackend b, Color c1, Color c2, Color c3) => (c1, c2, c3) -> a -> Diagram 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. Can be used with both Colour and AlphaColour

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

Example Diagrams of Patches

sun6Fig :: OKBackend b => Diagram b Source #

diagram for sun6.

leftFilledSun6 :: OKBackend b => Diagram b Source #

Colour filled using leftFillPieceDK.

filledSun6 :: OKBackend b => Diagram b Source #

Colour filled using fillDK.

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