diagrams-lib-1.4.4: Embedded domain-specific language for declarative graphics
Copyright(c) 2011 diagrams-lib team (see LICENSE)
LicenseBSD-style (see LICENSE)
Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone
LanguageHaskell2010

Diagrams.TwoD.Polygons

Description

This module defines a general API for creating various types of polygons.

Synopsis

Polygons

data PolyType n Source #

Method used to determine the vertices of a polygon.

Constructors

PolyPolar [Angle n] [n]

A "polar" polygon.

  • The first argument is a list of central angles from each vertex to the next.
  • The second argument is a list of radii from the origin to each successive vertex.

To construct an n-gon, use a list of n-1 angles and n radii. Extra angles or radii are ignored.

Cyclic polygons (with all vertices lying on a circle) can be constructed using a second argument of (repeat r).

PolySides [Angle n] [n]

A polygon determined by the distance between successive vertices and the external angles formed by each three successive vertices. In other words, a polygon specified by "turtle graphics": go straight ahead x1 units; turn by external angle a1; go straight ahead x2 units; turn by external angle a2; etc. The polygon will be centered at the centroid of its vertices.

  • The first argument is a list of vertex angles, giving the external angle at each vertex from the previous vertex to the next. The first angle in the list is the external angle at the second vertex; the first edge always starts out heading in the positive y direction from the first vertex.
  • The second argument is a list of distances between successive vertices.

To construct an n-gon, use a list of n-2 angles and n-1 edge lengths. Extra angles or lengths are ignored.

PolyRegular Int n

A regular polygon with the given number of sides (first argument) and the given radius (second argument).

data PolyOrientation n Source #

Determine how a polygon should be oriented.

Constructors

NoOrient

No special orientation; the first vertex will be at (1,0).

OrientH

Orient horizontally, so the bottommost edge is parallel to the x-axis. This is the default.

OrientV

Orient vertically, so the leftmost edge is parallel to the y-axis.

OrientTo (V2 n)

Orient so some edge is facing in the direction of, that is, perpendicular to, the given vector.

data PolygonOpts n Source #

Options for specifying a polygon.

Instances

Instances details
Num n => Default (PolygonOpts n) Source #

The default polygon is a regular pentagon of radius 1, centered at the origin, aligned to the x-axis.

Instance details

Defined in Diagrams.TwoD.Polygons

Methods

def :: PolygonOpts n #

polyType :: Lens' (PolygonOpts n) (PolyType n) Source #

Specification for the polygon's vertices.

polyOrient :: Lens' (PolygonOpts n) (PolyOrientation n) Source #

Should a rotation be applied to the polygon in order to orient it in a particular way?

polyCenter :: Lens' (PolygonOpts n) (Point V2 n) Source #

Should a translation be applied to the polygon in order to place the center at a particular location?

polygon :: (InSpace V2 n t, TrailLike t) => PolygonOpts n -> t Source #

Generate the polygon described by the given options.

polyTrail :: OrderedField n => PolygonOpts n -> Located (Trail V2 n) Source #

Generate a polygon. See PolygonOpts for more information.

Generating polygon vertices

polyPolarTrail :: OrderedField n => [Angle n] -> [n] -> Located (Trail V2 n) Source #

Generate the located trail of a polygon specified by polar data (central angles and radii). See PolyPolar.

polySidesTrail :: OrderedField n => [Angle n] -> [n] -> Located (Trail V2 n) Source #

Generate the vertices of a polygon specified by side length and angles, and a starting point for the trail such that the origin is at the centroid of the vertices. See PolySides.

polyRegularTrail :: OrderedField n => Int -> n -> Located (Trail V2 n) Source #

Generate the vertices of a regular polygon. See PolyRegular.

orient :: OrderedField n => V2 n -> Located (Trail V2 n) -> Transformation V2 n Source #

Generate a transformation to orient a trail. orient v t generates the smallest rotation such that one of the segments adjacent to the vertex furthest in the direction of v is perpendicular to v.

Star polygons

data StarOpts Source #

Options for creating "star" polygons, where the edges connect possibly non-adjacent vertices.

Constructors

StarFun (Int -> Int)

Specify the order in which the vertices should be connected by a function that maps each vertex index to the index of the vertex that should come next. Indexing of vertices begins at 0.

StarSkip Int

Specify a star polygon by a "skip". A skip of 1 indicates a normal polygon, where edges go between successive vertices. A skip of 2 means that edges will connect every second vertex, skipping one in between. Generally, a skip of n means that edges will connect every nth vertex.

star :: OrderedField n => StarOpts -> [Point V2 n] -> Path V2 n Source #

Create a generalized star polygon. The StarOpts are used to determine in which order the given vertices should be connected. The intention is that the second argument of type [Point v] could be generated by a call to polygon, regPoly, or the like, since a list of vertices is TrailLike. But of course the list can be generated any way you like. A Path v is returned (instead of any TrailLike) because the resulting path may have more than one component, for example if the vertices are to be connected in several disjoint cycles.

Function graphs

These functions are used to implement star, but are exported on the offchance that someone else finds them useful.

data GraphPart a Source #

Pieces of a function graph can either be cycles or "hairs".

Constructors

Cycle [a] 
Hair [a] 

Instances

Instances details
Functor GraphPart Source # 
Instance details

Defined in Diagrams.TwoD.Polygons

Methods

fmap :: (a -> b) -> GraphPart a -> GraphPart b #

(<$) :: a -> GraphPart b -> GraphPart a #

Show a => Show (GraphPart a) Source # 
Instance details

Defined in Diagrams.TwoD.Polygons

orbits :: (Int -> Int) -> Int -> [GraphPart Int] Source #

orbits f n computes the graph of f on the integers mod n.

mkGraph :: (Int -> Int) -> [a] -> [GraphPart a] Source #

Generate a function graph from the given function and labels.