diagrams-lib-1.4: Embedded domain-specific language for declarative graphics

Copyright(c) 2013-2015 diagrams-lib team (see LICENSE)
LicenseBSD-style (see LICENSE)
Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone
LanguageHaskell2010

Diagrams.TwoD.Arrow

Contents

Description

Drawing arrows in two dimensions. For a tutorial on drawing arrows using this module, see the diagrams website: http://projects.haskell.org/diagrams/doc/arrow.html.

Synopsis

Examples

Example 1

-- Connecting two diagrams at their origins.

sq = square 2 # showOrigin # lc darkgray # lw ultraThick
ds = (sq # named "left") ||| strutX 3 ||| (sq # named "right")

shaft  = cubicSpline False ( map p2 [(0, 0), (1, 0), (1, 0.2), (2, 0.2)])

example1 = ds # connect' (with & arrowHead .~ dart & arrowTail .~ quill
                               & arrowShaft .~ shaft
                               & headLength .~ huge & tailLength .~ veryLarge)
                               "left" "right" # pad 1.1

Example 2

-- Comparing connect, connectPerim, and arrowAt.

oct  = octagon 1 # lc darkgray # lw ultraThick # showOrigin
dias = oct # named "first" ||| strut 3 ||| oct # named "second"

-- Connect two diagrams and two points on their trails.
ex12 = dias # connect' (with & lengths .~ veryLarge) "first" "second"
            # connectPerim' (with & lengths .~ veryLarge)
       "first" "second" (15/16 @@ turn) (9/16 @@ turn)

-- Place an arrow at (0,0) the size and direction of (0,1).
ex3 = arrowAt origin unit_Y

example2 = (ex12 <> ex3) # centerXY # pad 1.1

Creating arrows

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

arrowV v creates an arrow with the direction and norm of the vector v (with its tail at the origin), using default parameters.

arrowV' :: (TypeableFloat n, Renderable (Path V2 n) b) => ArrowOpts n -> V2 n -> QDiagram b V2 n Any Source #

arrowV' v creates an arrow with the direction and norm of the vector v (with its tail at the origin).

arrowAt :: (TypeableFloat n, Renderable (Path V2 n) b) => Point V2 n -> V2 n -> QDiagram b V2 n Any Source #

Create an arrow starting at s with length and direction determined by the vector v.

arrowBetween :: (TypeableFloat n, Renderable (Path V2 n) b) => Point V2 n -> Point V2 n -> QDiagram b V2 n Any Source #

arrowBetween s e creates an arrow pointing from s to e with default parameters.

arrowBetween' :: (TypeableFloat n, Renderable (Path V2 n) b) => ArrowOpts n -> Point V2 n -> Point V2 n -> QDiagram b V2 n Any Source #

arrowBetween' opts s e creates an arrow pointing from s to e using the given options. In particular, it scales and rotates arrowShaft to go between s and e, taking head, tail, and gaps into account.

connect :: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2) => n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any Source #

Connect two diagrams with a straight arrow.

connect' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2) => ArrowOpts n -> n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any Source #

Connect two diagrams with an arbitrary arrow.

connectPerim :: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2) => n1 -> n2 -> Angle n -> Angle n -> QDiagram b V2 n Any -> QDiagram b V2 n Any Source #

Connect two diagrams at point on the perimeter of the diagrams, choosen by angle.

connectPerim' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2) => ArrowOpts n -> n1 -> n2 -> Angle n -> Angle n -> QDiagram b V2 n Any -> QDiagram b V2 n Any Source #

connectOutside :: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2) => n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any Source #

Draw an arrow from diagram named "n1" to diagram named "n2". The arrow lies on the line between the centres of the diagrams, but is drawn so that it stops at the boundaries of the diagrams, using traces to find the intersection points.

connectOutside' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2) => ArrowOpts n -> n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any Source #

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

arrow len creates an arrow of length len with default parameters, starting at the origin and ending at the point (len,0).

arrow' :: (TypeableFloat n, Renderable (Path V2 n) b) => ArrowOpts n -> n -> QDiagram b V2 n Any Source #

arrow' opts len creates an arrow of length len using the given options, starting at the origin and ending at the point (len,0). In particular, it scales the given arrowShaft so that the entire arrow has length len.

arrowFromLocatedTrail :: (Renderable (Path V2 n) b, RealFloat n, Typeable n) => Located (Trail V2 n) -> QDiagram b V2 n Any Source #

Turn a located trail into a default arrow by putting an arrowhead at the end of the trail.

arrowFromLocatedTrail' :: (Renderable (Path V2 n) b, RealFloat n, Typeable n) => ArrowOpts n -> Located (Trail V2 n) -> QDiagram b V2 n Any Source #

Turn a located trail into an arrow using the given options.

Options

arrowHead :: Lens' (ArrowOpts n) (ArrowHT n) Source #

A shape to place at the head of the arrow.

arrowTail :: Lens' (ArrowOpts n) (ArrowHT n) Source #

A shape to place at the tail of the arrow.

arrowShaft :: Lens' (ArrowOpts n) (Trail V2 n) Source #

The trail to use for the arrow shaft.

headGap :: Lens' (ArrowOpts n) (Measure n) Source #

Distance to leave between the head and the target point.

tailGap :: Lens' (ArrowOpts n) (Measure n) Source #

Distance to leave between the starting point and the tail.

gaps :: Traversal' (ArrowOpts n) (Measure n) Source #

Set both the headGap and tailGap simultaneously.

gap :: Traversal' (ArrowOpts n) (Measure n) Source #

Same as gaps, provided for backward compatiiblity.

headTexture :: TypeableFloat n => Lens' (ArrowOpts n) (Texture n) Source #

A lens for setting or modifying the texture of an arrowhead. For example, one may write ... (with & headTexture .~ grad) to get an arrow with a head filled with a gradient, assuming grad has been defined. Or ... (with & headTexture .~ solid blue to set the head color to blue. For more general control over the style of arrowheads, see headStyle.

headStyle :: Lens' (ArrowOpts n) (Style V2 n) Source #

Style to apply to the head. headStyle is modified by using the lens combinator %~ to change the current style. For example, to change an opaque black arrowhead to translucent orange: (with & headStyle %~ fc orange . opacity 0.75).

headLength :: Lens' (ArrowOpts n) (Measure n) Source #

The length from the start of the joint to the tip of the head.

tailTexture :: TypeableFloat n => Lens' (ArrowOpts n) (Texture n) Source #

A lens for setting or modifying the texture of an arrow tail. This is *not* a valid lens (see committed).

tailStyle :: Lens' (ArrowOpts n) (Style V2 n) Source #

Style to apply to the tail. See headStyle.

tailLength :: Lens' (ArrowOpts n) (Measure n) Source #

The length of the tail plus its joint.

lengths :: Traversal' (ArrowOpts n) (Measure n) Source #

Set both the headLength and tailLength simultaneously.

shaftTexture :: TypeableFloat n => Lens' (ArrowOpts n) (Texture n) Source #

A lens for setting or modifying the texture of an arrow shaft.

shaftStyle :: Lens' (ArrowOpts n) (Style V2 n) Source #

Style to apply to the shaft. See headStyle.

straightShaft :: OrderedField n => Trail V2 n Source #

Straight line arrow shaft.

See Diagrams.TwoD.Arrowheads for a list of standard arrowheads and help creating your own.