Copyright | (c) 2015 diagrams-lib team (see LICENSE) |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | diagrams-discuss@googlegroups.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
This module only contains exports defined in diagrams-lib
or
diagrams-core
. This module can be used if you want to avoid some
potential conflicts with other modules, but importing
Diagrams.Prelude (which includes re-exports from other packages)
is often more convenient.
Synopsis
- module Diagrams.Core
- module Diagrams.Attributes
- module Diagrams.Align
- data BoundingBox v n
- emptyBox :: BoundingBox v n
- fromCorners :: (Additive v, Foldable v, Ord n) => Point v n -> Point v n -> BoundingBox v n
- fromPoint :: Point v n -> BoundingBox v n
- fromPoints :: (Additive v, Ord n) => [Point v n] -> BoundingBox v n
- boundingBox :: (InSpace v n a, HasBasis v, Enveloped a) => a -> BoundingBox v n
- isEmptyBox :: BoundingBox v n -> Bool
- getCorners :: BoundingBox v n -> Maybe (Point v n, Point v n)
- getAllCorners :: (Additive v, Traversable v) => BoundingBox v n -> [Point v n]
- boxExtents :: (Additive v, Num n) => BoundingBox v n -> v n
- boxCenter :: (Additive v, Fractional n) => BoundingBox v n -> Maybe (Point v n)
- mCenterPoint :: (InSpace v n a, HasBasis v, Enveloped a) => a -> Maybe (Point v n)
- centerPoint :: (InSpace v n a, HasBasis v, Enveloped a) => a -> Point v n
- boxTransform :: (Additive v, Fractional n) => BoundingBox v n -> BoundingBox v n -> Maybe (Transformation v n)
- boxFit :: (InSpace v n a, HasBasis v, Enveloped a, Transformable a, Monoid a) => BoundingBox v n -> a -> a
- contains' :: (Additive v, Foldable v, Ord n) => BoundingBox v n -> Point v n -> Bool
- inside' :: (Additive v, Foldable v, Ord n) => BoundingBox v n -> BoundingBox v n -> Bool
- outside' :: (Additive v, Foldable v, Ord n) => BoundingBox v n -> BoundingBox v n -> Bool
- boxGrid :: (Traversable v, Additive v, Num n, Enum n) => n -> BoundingBox v n -> [Point v n]
- module Diagrams.Combinators
- module Diagrams.Located
- module Diagrams.Segment
- data Line
- data Trail v n where
- data Trail' l v n where
- data Loop
- newtype SegTree v n = SegTree (FingerTree (SegMeasure v n) (Segment Closed v n))
- newtype GetSegment t = GetSegment t
- newtype GetSegmentCodomain v n = GetSegmentCodomain (Maybe (v n, Segment Closed v n, AnIso' n n))
- isLine :: Trail v n -> Bool
- offset :: (OrderedField n, Metric v, Measured (SegMeasure v n) t) => t -> v n
- glueLine :: (Metric v, OrderedField n) => Trail' Line v n -> Trail' Loop v n
- closeLine :: Trail' Line v n -> Trail' Loop v n
- cutLoop :: forall v n. (Metric v, OrderedField n) => Trail' Loop v n -> Trail' Line v n
- _Line :: Prism' (Trail v n) (Trail' Line v n)
- _Loop :: Prism' (Trail v n) (Trail' Loop v n)
- _LocLine :: Prism' (Located (Trail v n)) (Located (Trail' Line v n))
- _LocLoop :: Prism' (Located (Trail v n)) (Located (Trail' Loop v n))
- wrapTrail :: Trail' l v n -> Trail v n
- wrapLine :: Trail' Line v n -> Trail v n
- wrapLoop :: Trail' Loop v n -> Trail v n
- onTrail :: (Trail' Line v n -> Trail' l1 v n) -> (Trail' Loop v n -> Trail' l2 v n) -> Trail v n -> Trail v n
- onLine :: (Metric v, OrderedField n) => (Trail' Line v n -> Trail' Line v n) -> Trail v n -> Trail v n
- glueTrail :: (Metric v, OrderedField n) => Trail v n -> Trail v n
- closeTrail :: Trail v n -> Trail v n
- cutTrail :: (Metric v, OrderedField n) => Trail v n -> Trail v n
- emptyLine :: (Metric v, OrderedField n) => Trail' Line v n
- emptyTrail :: (Metric v, OrderedField n) => Trail v n
- lineFromVertices :: (Metric v, OrderedField n) => [Point v n] -> Trail' Line v n
- trailFromVertices :: (Metric v, OrderedField n) => [Point v n] -> Trail v n
- lineFromOffsets :: (Metric v, OrderedField n) => [v n] -> Trail' Line v n
- trailFromOffsets :: (Metric v, OrderedField n) => [v n] -> Trail v n
- lineFromSegments :: (Metric v, OrderedField n) => [Segment Closed v n] -> Trail' Line v n
- trailFromSegments :: (Metric v, OrderedField n) => [Segment Closed v n] -> Trail v n
- loopFromSegments :: (Metric v, OrderedField n) => [Segment Closed v n] -> Segment Open v n -> Trail' Loop v n
- withTrail' :: (Trail' Line v n -> r) -> (Trail' Loop v n -> r) -> Trail' l v n -> r
- withTrail :: (Trail' Line v n -> r) -> (Trail' Loop v n -> r) -> Trail v n -> r
- withLine :: (Metric v, OrderedField n) => (Trail' Line v n -> r) -> Trail v n -> r
- isLineEmpty :: (Metric v, OrderedField n) => Trail' Line v n -> Bool
- isTrailEmpty :: (Metric v, OrderedField n) => Trail v n -> Bool
- isLoop :: Trail v n -> Bool
- trailSegments :: (Metric v, OrderedField n) => Trail v n -> [Segment Closed v n]
- lineSegments :: Trail' Line v n -> [Segment Closed v n]
- loopSegments :: Trail' Loop v n -> ([Segment Closed v n], Segment Open v n)
- onLineSegments :: (Metric v, OrderedField n) => ([Segment Closed v n] -> [Segment Closed v n]) -> Trail' Line v n -> Trail' Line v n
- trailOffsets :: (Metric v, OrderedField n) => Trail v n -> [v n]
- trailOffset :: (Metric v, OrderedField n) => Trail v n -> v n
- lineOffsets :: Trail' Line v n -> [v n]
- lineOffset :: (Metric v, OrderedField n) => Trail' Line v n -> v n
- loopOffsets :: (Metric v, OrderedField n) => Trail' Loop v n -> [v n]
- trailVertices' :: (Metric v, OrderedField n) => n -> Located (Trail v n) -> [Point v n]
- lineVertices' :: (Metric v, OrderedField n) => n -> Located (Trail' Line v n) -> [Point v n]
- loopVertices' :: (Metric v, OrderedField n) => n -> Located (Trail' Loop v n) -> [Point v n]
- trailVertices :: (Metric v, OrderedField n) => Located (Trail v n) -> [Point v n]
- lineVertices :: (Metric v, OrderedField n) => Located (Trail' Line v n) -> [Point v n]
- loopVertices :: (Metric v, OrderedField n) => Located (Trail' Loop v n) -> [Point v n]
- trailLocSegments :: (Metric v, OrderedField n) => Located (Trail v n) -> [Located (Segment Closed v n)]
- fixTrail :: (Metric v, OrderedField n) => Located (Trail v n) -> [FixedSegment v n]
- unfixTrail :: (Metric v, Ord n, Floating n) => [FixedSegment v n] -> Located (Trail v n)
- reverseTrail :: (Metric v, OrderedField n) => Trail v n -> Trail v n
- reverseLocTrail :: (Metric v, OrderedField n) => Located (Trail v n) -> Located (Trail v n)
- reverseLine :: (Metric v, OrderedField n) => Trail' Line v n -> Trail' Line v n
- reverseLocLine :: (Metric v, OrderedField n) => Located (Trail' Line v n) -> Located (Trail' Line v n)
- reverseLoop :: (Metric v, OrderedField n) => Trail' Loop v n -> Trail' Loop v n
- reverseLocLoop :: (Metric v, OrderedField n) => Located (Trail' Loop v n) -> Located (Trail' Loop v n)
- trailMeasure :: (SegMeasure v n :>: m, Measured (SegMeasure v n) t) => a -> (m -> a) -> t -> a
- numSegs :: (Num c, Measured (SegMeasure v n) a) => a -> c
- getSegment :: t -> GetSegment t
- module Diagrams.Parametric
- module Diagrams.Parametric.Adjust
- module Diagrams.Tangent
- module Diagrams.TrailLike
- newtype Path v n = Path [Located (Trail v n)]
- class ToPath t where
- pathTrails :: Path v n -> [Located (Trail v n)]
- pathFromTrail :: (Metric v, OrderedField n) => Trail v n -> Path v n
- pathFromTrailAt :: (Metric v, OrderedField n) => Trail v n -> Point v n -> Path v n
- pathFromLocTrail :: (Metric v, OrderedField n) => Located (Trail v n) -> Path v n
- pathVertices' :: (Metric v, OrderedField n) => n -> Path v n -> [[Point v n]]
- pathVertices :: (Metric v, OrderedField n) => Path v n -> [[Point v n]]
- pathOffsets :: (Metric v, OrderedField n) => Path v n -> [v n]
- pathCentroid :: (Metric v, OrderedField n) => Path v n -> Point v n
- pathLocSegments :: (Metric v, OrderedField n) => Path v n -> [[Located (Segment Closed v n)]]
- fixPath :: (Metric v, OrderedField n) => Path v n -> [[FixedSegment v n]]
- scalePath :: (HasLinearMap v, Metric v, OrderedField n) => n -> Path v n -> Path v n
- reversePath :: (Metric v, OrderedField n) => Path v n -> Path v n
- explodePath :: (V t ~ v, N t ~ n, TrailLike t) => Path v n -> [[t]]
- partitionPath :: (Located (Trail v n) -> Bool) -> Path v n -> (Path v n, Path v n)
- module Diagrams.CubicSpline
- module Diagrams.Transform
- module Diagrams.Deform
- module Diagrams.Names
- module Diagrams.Envelope
- module Diagrams.Trace
- module Diagrams.Query
- module Diagrams.Points
- module Diagrams.Size
- module Diagrams.Angle
- module Diagrams.Coordinates
- data Direction v n
- _Dir :: Iso' (Direction v n) (v n)
- direction :: v n -> Direction v n
- fromDirection :: (Metric v, Floating n) => Direction v n -> v n
- fromDir :: (Metric v, Floating n) => Direction v n -> v n
- angleBetweenDirs :: (Metric v, Floating n, Ord n) => Direction v n -> Direction v n -> Angle n
- dirBetween :: (Additive v, Num n) => Point v n -> Point v n -> Direction v n
- module Diagrams.TwoD
- module Diagrams.ThreeD
- module Diagrams.Animation
- module Diagrams.Util
Core library
The core definitions of transformations, diagrams, backends, and so on.
module Diagrams.Core
Standard library
Attributes (color, line style, etc.) and styles.
module Diagrams.Attributes
Alignment of diagrams relative to their envelopes.
module Diagrams.Align
Creating and using bounding boxes.
data BoundingBox v n Source #
A bounding box is an axis-aligned region determined by two points
indicating its "lower" and "upper" corners. It can also represent
an empty bounding box - the points are wrapped in Maybe
.
Instances
emptyBox :: BoundingBox v n Source #
An empty bounding box. This is the same thing as mempty
, but it doesn't
require the same type constraints that the Monoid
instance does.
fromCorners :: (Additive v, Foldable v, Ord n) => Point v n -> Point v n -> BoundingBox v n Source #
Create a bounding box from a point that is component-wise (<=)
than the
other. If this is not the case, then mempty
is returned.
fromPoint :: Point v n -> BoundingBox v n Source #
Create a degenerate bounding "box" containing only a single point.
fromPoints :: (Additive v, Ord n) => [Point v n] -> BoundingBox v n Source #
Create the smallest bounding box containing all the given points.
boundingBox :: (InSpace v n a, HasBasis v, Enveloped a) => a -> BoundingBox v n Source #
Create a bounding box for any enveloped object (such as a diagram or path).
isEmptyBox :: BoundingBox v n -> Bool Source #
Queries whether the BoundingBox is empty.
getCorners :: BoundingBox v n -> Maybe (Point v n, Point v n) Source #
Gets the lower and upper corners that define the bounding box.
getAllCorners :: (Additive v, Traversable v) => BoundingBox v n -> [Point v n] Source #
Computes all of the corners of the bounding box.
boxExtents :: (Additive v, Num n) => BoundingBox v n -> v n Source #
Get the size of the bounding box - the vector from the (component-wise) lesser point to the greater point.
boxCenter :: (Additive v, Fractional n) => BoundingBox v n -> Maybe (Point v n) Source #
Get the center point in a bounding box.
mCenterPoint :: (InSpace v n a, HasBasis v, Enveloped a) => a -> Maybe (Point v n) Source #
Get the center of a the bounding box of an enveloped object, return
Nothing
for object with empty envelope.
centerPoint :: (InSpace v n a, HasBasis v, Enveloped a) => a -> Point v n Source #
Get the center of a the bounding box of an enveloped object, return the origin for object with empty envelope.
boxTransform :: (Additive v, Fractional n) => BoundingBox v n -> BoundingBox v n -> Maybe (Transformation v n) Source #
Create a transformation mapping points from one bounding box to the
other. Returns Nothing
if either of the boxes are empty.
boxFit :: (InSpace v n a, HasBasis v, Enveloped a, Transformable a, Monoid a) => BoundingBox v n -> a -> a Source #
Transforms an enveloped thing to fit within a BoundingBox
. If the
bounding box is empty, then the result is also mempty
.
contains' :: (Additive v, Foldable v, Ord n) => BoundingBox v n -> Point v n -> Bool Source #
Check whether a point is strictly contained in a bounding box.
inside' :: (Additive v, Foldable v, Ord n) => BoundingBox v n -> BoundingBox v n -> Bool Source #
Test whether the first bounding box is strictly contained inside the second.
outside' :: (Additive v, Foldable v, Ord n) => BoundingBox v n -> BoundingBox v n -> Bool Source #
Test whether the first bounding box lies strictly outside the second (they do not intersect at all).
boxGrid :: (Traversable v, Additive v, Num n, Enum n) => n -> BoundingBox v n -> [Point v n] Source #
boxGrid f box
returns a grid of regularly spaced points inside
the box, such that there are (1/f)
points along each dimension.
For example, for a 3D box with corners at (0,0,0) and (2,2,2),
boxGrid 0.1
would yield a grid of approximately 1000 points (it
might actually be 11^3
instead of 10^3
) spaced 0.2
units
apart.
Combining multiple diagrams into one.
module Diagrams.Combinators
Giving concrete locations to translation-invariant things.
module Diagrams.Located
Linear and cubic bezier segments.
module Diagrams.Segment
Trails.
Type tag for trails with distinct endpoints.
Instances
(Metric v, OrderedField n) => EndValues (GetSegment (Trail' Line v n)) Source # | |
Defined in Diagrams.Trail atStart :: GetSegment (Trail' Line v n) -> Codomain (GetSegment (Trail' Line v n)) (N (GetSegment (Trail' Line v n))) Source # atEnd :: GetSegment (Trail' Line v n) -> Codomain (GetSegment (Trail' Line v n)) (N (GetSegment (Trail' Line v n))) Source # | |
(Metric v, OrderedField n) => Parametric (GetSegment (Trail' Line v n)) Source # | Parameters less than 0 yield the first segment; parameters greater than 1 yield the last. A parameter exactly at the junction of two segments yields the second segment (i.e. the one with higher parameter values). |
Defined in Diagrams.Trail atParam :: GetSegment (Trail' Line v n) -> N (GetSegment (Trail' Line v n)) -> Codomain (GetSegment (Trail' Line v n)) (N (GetSegment (Trail' Line v n))) Source # | |
(Metric v, OrderedField n) => Monoid (Trail' Line v n) Source # | The empty trail is constantly the zero vector. Trails are composed via concatenation. Note that only lines have a monoid instance (and not loops). |
(OrderedField n, Metric v) => Semigroup (Trail' Line v n) Source # | |
(Metric v, OrderedField n, Real n) => Sectionable (Trail' Line v n) Source # | |
(Metric v, OrderedField n) => TrailLike (Trail' Line v n) Source # | Lines are trail-like. If given a |
(Metric v, OrderedField n) => AsEmpty (Trail' Line v n) Source # | |
Wrapped (Trail' Line v n) Source # | |
Rewrapped (Trail' Line v n) (Trail' Line v' n') Source # | |
Defined in Diagrams.Trail | |
(Metric v, OrderedField n, Metric u, OrderedField n') => Cons (Trail' Line v n) (Trail' Line u n') (Segment Closed v n) (Segment Closed u n') Source # | |
(Metric v, OrderedField n, Metric u, OrderedField n') => Snoc (Trail' Line v n) (Trail' Line u n') (Segment Closed v n) (Segment Closed u n') Source # | |
type Unwrapped (Trail' Line v n) Source # | |
Defined in Diagrams.Trail |
Trail
is a wrapper around Trail'
, hiding whether the
underlying Trail'
is a line or loop (though which it is can be
recovered; see e.g. withTrail
).
Instances
(Metric v, OrderedField n, Real n) => EndValues (Tangent (Trail v n)) Source # | |
(Metric v, OrderedField n, Real n) => EndValues (GetSegment (Trail v n)) Source # | |
Defined in Diagrams.Trail atStart :: GetSegment (Trail v n) -> Codomain (GetSegment (Trail v n)) (N (GetSegment (Trail v n))) Source # atEnd :: GetSegment (Trail v n) -> Codomain (GetSegment (Trail v n)) (N (GetSegment (Trail v n))) Source # | |
(Metric v, OrderedField n, Real n) => Parametric (Tangent (Trail v n)) Source # | |
(Metric v, OrderedField n, Real n) => Parametric (GetSegment (Trail v n)) Source # | |
Defined in Diagrams.Trail atParam :: GetSegment (Trail v n) -> N (GetSegment (Trail v n)) -> Codomain (GetSegment (Trail v n)) (N (GetSegment (Trail v n))) Source # | |
ToPath (Located (Trail v n)) Source # | |
(Metric v, OrderedField n) => Reversing (Located (Trail v n)) Source # | Same as |
(Metric v, Metric u, OrderedField n, r ~ Located (Trail u n)) => Deformable (Located (Trail v n)) r Source # | |
RealFloat n => HasQuery (Located (Trail V2 n)) Crossings Source # | |
(Metric v, OrderedField n) => Monoid (Trail v n) Source # |
|
(OrderedField n, Metric v) => Semigroup (Trail v n) Source # | Two |
Show (v n) => Show (Trail v n) Source # | |
(Serialize (v n), OrderedField n, Metric v) => Serialize (Trail v n) Source # | |
(Metric v, OrderedField n) => Enveloped (Trail v n) Source # | |
Defined in Diagrams.Trail | |
RealFloat n => Traced (Trail V2 n) Source # | |
(HasLinearMap v, Metric v, OrderedField n) => Transformable (Trail v n) Source # | |
Defined in Diagrams.Trail | |
Num n => DomainBounds (Trail v n) Source # | |
Defined in Diagrams.Trail | |
(Metric v, OrderedField n, Real n) => EndValues (Trail v n) Source # | |
(Metric v, OrderedField n, Real n) => HasArcLength (Trail v n) Source # | |
Defined in Diagrams.Trail arcLengthBounded :: N (Trail v n) -> Trail v n -> Interval (N (Trail v n)) Source # arcLength :: N (Trail v n) -> Trail v n -> N (Trail v n) Source # stdArcLength :: Trail v n -> N (Trail v n) Source # arcLengthToParam :: N (Trail v n) -> Trail v n -> N (Trail v n) -> N (Trail v n) Source # stdArcLengthToParam :: Trail v n -> N (Trail v n) -> N (Trail v n) Source # | |
(Metric v, OrderedField n, Real n) => Parametric (Trail v n) Source # | |
(Metric v, OrderedField n, Real n) => Sectionable (Trail v n) Source # | Note that there is no |
ToPath (Trail v n) Source # | |
(Metric v, OrderedField n) => TrailLike (Trail v n) Source # |
|
Eq (v n) => Eq (Trail v n) Source # | |
Ord (v n) => Ord (Trail v n) Source # | |
Defined in Diagrams.Trail | |
(Metric v, OrderedField n) => AsEmpty (Trail v n) Source # | |
Defined in Diagrams.Trail | |
(Metric v, OrderedField n) => Reversing (Trail v n) Source # | Same as |
Defined in Diagrams.Trail | |
Wrapped (Trail v n) Source # | |
(Metric v, Metric u, OrderedField n, r ~ Trail u n) => AffineMappable (Trail v n) r Source # | |
(Metric v, Metric u, OrderedField n, OrderedField m, r ~ Trail u m) => LinearMappable (Trail v n) r Source # | |
Rewrapped (Trail v n) (Trail v' n') Source # | |
Defined in Diagrams.Trail | |
Cons (Path v n) (Path v' n') (Located (Trail v n)) (Located (Trail v' n')) Source # | |
Snoc (Path v n) (Path v' n') (Located (Trail v n)) (Located (Trail v' n')) Source # | |
Each (Path v n) (Path v' n') (Located (Trail v n)) (Located (Trail v' n')) Source # | |
type N (Trail v n) Source # | |
Defined in Diagrams.Trail | |
type V (Trail v n) Source # | |
Defined in Diagrams.Trail | |
type Codomain (Trail v n) Source # | |
Defined in Diagrams.Trail | |
type Unwrapped (Trail v n) Source # | |
data Trail' l v n where Source #
Intuitively, a trail is a single, continuous path through space. However, a trail has no fixed starting point; it merely specifies how to move through space, not where. For example, "take three steps forward, then turn right twenty degrees and take two more steps" is an intuitive analog of a trail; these instructions specify a path through space from any given starting location. To be precise, trails are translation-invariant; applying a translation to a trail has no effect.
A
, on the other hand, is a trail paired with
some concrete starting location ("start at the big tree on the
corner, then take three steps forward, ..."). See the
Diagrams.Located module for help working with Located
TrailLocated
values.
Formally, the semantics of a trail is a continuous (though not
necessarily differentiable) function from the real interval [0,1]
to vectors in some vector space. (In contrast, a Located
trail
is a continuous function from [0,1] to points in some affine
space.)
There are two types of trails:
- A "line" (think of the "train", "subway", or "bus"
variety, rather than the "straight" variety...) is a trail
with two distinct endpoints. Actually, a line can have the
same start and end points, but it is still drawn as if it had
distinct endpoints: the two endpoints will have the appropriate
end caps, and the trail will not be filled. Lines have a
Monoid
instance wheremappend
corresponds to concatenation, i.e. chaining one line after the other. - A "loop" is required to end in the same place it starts (that
is, t(0) = t(1)). Loops are filled and are drawn as one
continuous loop, with the appropriate join at the
start/endpoint rather than end caps. Loops do not have a
Monoid
instance.
To convert between lines and loops, see glueLine
,
closeLine
, and cutLoop
.
To construct trails, see emptyTrail
, trailFromSegments
,
trailFromVertices
, trailFromOffsets
, and friends. You can
also get any type of trail from any function which returns a
TrailLike
(e.g. functions in Diagrams.TwoD.Shapes, and many
others; see Diagrams.TrailLike).
To extract information from trails, see withLine
, isLoop
,
trailSegments
, trailOffsets
, trailVertices
, and friends.
Instances
Type tag for "loopy" trails which return to their starting point.
Instances
(Metric v, OrderedField n, Real n) => EndValues (GetSegment (Trail' Loop v n)) Source # | |
Defined in Diagrams.Trail atStart :: GetSegment (Trail' Loop v n) -> Codomain (GetSegment (Trail' Loop v n)) (N (GetSegment (Trail' Loop v n))) Source # atEnd :: GetSegment (Trail' Loop v n) -> Codomain (GetSegment (Trail' Loop v n)) (N (GetSegment (Trail' Loop v n))) Source # | |
(Metric v, OrderedField n, Real n) => Parametric (GetSegment (Trail' Loop v n)) Source # | The parameterization for loops wraps around, i.e. parameters are first reduced "mod 1". |
Defined in Diagrams.Trail atParam :: GetSegment (Trail' Loop v n) -> N (GetSegment (Trail' Loop v n)) -> Codomain (GetSegment (Trail' Loop v n)) (N (GetSegment (Trail' Loop v n))) Source # | |
(Metric v, OrderedField n) => TrailLike (Trail' Loop v n) Source # | Loops are trail-like. If given a |
A SegTree
represents a sequence of closed segments, stored in a
fingertree so we can easily recover various monoidal measures of
the segments (number of segments, arc length, envelope...) and
also easily slice and dice them according to the measures
(e.g., split off the smallest number of segments from the
beginning which have a combined arc length of at least 5).
SegTree (FingerTree (SegMeasure v n) (Segment Closed v n)) |
Instances
newtype GetSegment t Source #
A newtype wrapper around trails which exists solely for its
Parametric
, DomainBounds
and EndValues
instances. The idea
is that if tr
is a trail, you can write, e.g.
getSegment tr atParam
0.6
or
atStart (getSegment tr)
to get the segment at parameter 0.6 or the first segment in the trail, respectively.
The codomain for GetSegment
, i.e. the result you get from
calling atParam
, atStart
, or atEnd
, is
GetSegmentCodomain
, which is a newtype wrapper around Maybe
(v, Segment Closed v, AnIso' n n)
. Nothing
results if the
trail is empty; otherwise, you get:
- the offset from the start of the trail to the beginning of the segment,
- the segment itself, and
- a reparameterization isomorphism: in the forward direction, it
translates from parameters on the whole trail to a parameters
on the segment. Note that for technical reasons you have to
call
cloneIso
on theAnIso'
value to get a real isomorphism you can use.
Instances
newtype GetSegmentCodomain v n Source #
GetSegmentCodomain (Maybe (v n, Segment Closed v n, AnIso' n n)) |
offset :: (OrderedField n, Metric v, Measured (SegMeasure v n) t) => t -> v n Source #
Compute the total offset of anything measured by SegMeasure
.
glueLine :: (Metric v, OrderedField n) => Trail' Line v n -> Trail' Loop v n Source #
Make a line into a loop by "gluing" the endpoint to the
starting point. In particular, the offset of the final segment
is modified so that it ends at the starting point of the entire
trail. Typically, you would first construct a line which you
know happens to end where it starts, and then call glueLine
to
turn it into a loop.
glueLineEx = pad 1.1 . hsep 1 $ [almostClosed # strokeLine, almostClosed # glueLine # strokeLoop] almostClosed :: Trail' Line V2 Double almostClosed = fromOffsets $ map r2 [(2, -1), (-3, -0.5), (-2, 1), (1, 0.5)]
glueLine
is left inverse to cutLoop
, that is,
glueLine . cutLoop === id
closeLine :: Trail' Line v n -> Trail' Loop v n Source #
Make a line into a loop by adding a new linear segment from the line's end to its start.
closeLine
does not have any particularly nice theoretical
properties, but can be useful e.g. when you want to make a
closed polygon out of a list of points where the initial point is
not repeated at the end. To use glueLine
, one would first have
to duplicate the initial vertex, like
glueLine
.lineFromVertices
$ ps ++ [head ps]
Using closeLine
, however, one can simply
closeLine . lineFromVertices $ ps
closeLineEx = pad 1.1 . centerXY . hcat' (with & sep .~ 1) $ [almostClosed # strokeLine, almostClosed # closeLine # strokeLoop]
cutLoop :: forall v n. (Metric v, OrderedField n) => Trail' Loop v n -> Trail' Line v n Source #
Turn a loop into a line by "cutting" it at the common start/end point, resulting in a line which just happens to start and end at the same place.
cutLoop
is right inverse to glueLine
, that is,
glueLine . cutLoop === id
onTrail :: (Trail' Line v n -> Trail' l1 v n) -> (Trail' Loop v n -> Trail' l2 v n) -> Trail v n -> Trail v n Source #
Modify a Trail
, specifying two separate transformations for the
cases of a line or a loop.
onLine :: (Metric v, OrderedField n) => (Trail' Line v n -> Trail' Line v n) -> Trail v n -> Trail v n Source #
Modify a Trail
by specifying a transformation on lines. If the
trail is a line, the transformation will be applied directly. If
it is a loop, it will first be cut using cutLoop
, the
transformation applied, and then glued back into a loop with
glueLine
. That is,
onLine f === onTrail f (glueLine . f . cutLoop)
Note that there is no corresponding onLoop
function, because
there is no nice way in general to convert a line into a loop,
operate on it, and then convert back.
closeTrail :: Trail v n -> Trail v n Source #
emptyLine :: (Metric v, OrderedField n) => Trail' Line v n Source #
The empty line, which is the identity for concatenation of lines.
emptyTrail :: (Metric v, OrderedField n) => Trail v n Source #
A wrapped variant of emptyLine
.
lineFromVertices :: (Metric v, OrderedField n) => [Point v n] -> Trail' Line v n Source #
Construct a line containing only linear segments from a list of
vertices. Note that only the relative offsets between the
vertices matters; the information about their absolute position
will be discarded. That is, for all vectors v
,
lineFromVertices === lineFromVertices . translate
v
If you want to retain the position information, you should
instead use the more general fromVertices
function to
construct, say, a
or a Located
(Trail'
Line
v)
.Located
(Trail
v)
import Diagrams.Coordinates lineFromVerticesEx = pad 1.1 . centerXY . strokeLine $ lineFromVertices [origin, 0 ^& 1, 1 ^& 2, 5 ^& 1]
trailFromVertices :: (Metric v, OrderedField n) => [Point v n] -> Trail v n Source #
trailFromVertices ===
, for
conveniently constructing a wrapTrail
. lineFromVertices
Trail
instead of a Trail' Line
.
lineFromOffsets :: (Metric v, OrderedField n) => [v n] -> Trail' Line v n Source #
Construct a line containing only linear segments from a list of
vectors, where each vector represents the offset from one vertex
to the next. See also fromOffsets
.
import Diagrams.Coordinates lineFromOffsetsEx = strokeLine $ lineFromOffsets [ 2 ^& 1, 2 ^& (-1), 2 ^& 0.5 ]
trailFromOffsets :: (Metric v, OrderedField n) => [v n] -> Trail v n Source #
trailFromOffsets ===
, for
conveniently constructing a wrapTrail
. lineFromOffsets
Trail
instead of a Trail' Line
.
lineFromSegments :: (Metric v, OrderedField n) => [Segment Closed v n] -> Trail' Line v n Source #
Construct a line from a list of closed segments.
trailFromSegments :: (Metric v, OrderedField n) => [Segment Closed v n] -> Trail v n Source #
trailFromSegments ===
, for
conveniently constructing a wrapTrail
. lineFromSegments
Trail
instead of a Trail'
.
loopFromSegments :: (Metric v, OrderedField n) => [Segment Closed v n] -> Segment Open v n -> Trail' Loop v n Source #
Construct a loop from a list of closed segments and an open segment that completes the loop.
withTrail' :: (Trail' Line v n -> r) -> (Trail' Loop v n -> r) -> Trail' l v n -> r Source #
A generic eliminator for Trail'
, taking functions specifying
what to do in the case of a line or a loop.
withTrail :: (Trail' Line v n -> r) -> (Trail' Loop v n -> r) -> Trail v n -> r Source #
A generic eliminator for Trail
, taking functions specifying
what to do in the case of a line or a loop.
isLineEmpty :: (Metric v, OrderedField n) => Trail' Line v n -> Bool Source #
Test whether a line is empty.
isTrailEmpty :: (Metric v, OrderedField n) => Trail v n -> Bool Source #
Test whether a trail is empty. Note that loops are never empty.
trailSegments :: (Metric v, OrderedField n) => Trail v n -> [Segment Closed v n] Source #
Extract the segments of a trail. If the trail is a loop it will
first have cutLoop
applied.
lineSegments :: Trail' Line v n -> [Segment Closed v n] Source #
Extract the segments comprising a line.
loopSegments :: Trail' Loop v n -> ([Segment Closed v n], Segment Open v n) Source #
Extract the segments comprising a loop: a list of closed segments, and one final open segment.
onLineSegments :: (Metric v, OrderedField n) => ([Segment Closed v n] -> [Segment Closed v n]) -> Trail' Line v n -> Trail' Line v n Source #
Modify a line by applying a function to its list of segments.
trailOffsets :: (Metric v, OrderedField n) => Trail v n -> [v n] Source #
Extract the offsets of the segments of a trail.
trailOffset :: (Metric v, OrderedField n) => Trail v n -> v n Source #
Compute the offset from the start of a trail to the end. Satisfies
trailOffset === sumV . trailOffsets
but is more efficient.
trailOffsetEx = (strokeLine almostClosed <> showOffset) # centerXY # pad 1.1 where showOffset = fromOffsets [trailOffset (wrapLine almostClosed)] # strokeP # lc red
lineOffsets :: Trail' Line v n -> [v n] Source #
Extract the offsets of the segments of a line.
lineOffset :: (Metric v, OrderedField n) => Trail' Line v n -> v n Source #
Compute the offset from the start of a line to the end. (Note,
there is no corresponding loopOffset
function because by
definition it would be constantly zero.)
loopOffsets :: (Metric v, OrderedField n) => Trail' Loop v n -> [v n] Source #
Extract the offsets of the segments of a loop.
trailVertices' :: (Metric v, OrderedField n) => n -> Located (Trail v n) -> [Point v n] Source #
Extract the vertices of a concretely located trail. Here a vertex
is defined as a non-differentiable point on the trail, i.e. a
sharp corner. (Vertices are thus a subset of the places where
segments join; if you want all joins between segments, see
trailPoints
.) The tolerance determines how close the tangents
of two segments must be at their endpoints to consider the
transition point to be differentiable.
Note that for loops, the starting vertex will not be repeated
at the end. If you want this behavior, you can use cutTrail
to
make the loop into a line first, which happens to repeat the same
vertex at the start and end, e.g. with trailVertices . mapLoc
cutTrail
.
It does not make sense to ask for the vertices of a Trail
by
itself; if you want the vertices of a trail with the first vertex
at, say, the origin, you can use trailVertices . (`at`
origin)
.
lineVertices' :: (Metric v, OrderedField n) => n -> Located (Trail' Line v n) -> [Point v n] Source #
Extract the vertices of a concretely located line. See
trailVertices
for more information.
loopVertices' :: (Metric v, OrderedField n) => n -> Located (Trail' Loop v n) -> [Point v n] Source #
Extract the vertices of a concretely located loop. Note that the
initial vertex is not repeated at the end. See trailVertices
for
more information.
trailVertices :: (Metric v, OrderedField n) => Located (Trail v n) -> [Point v n] Source #
Like trailVertices'
, with a default tolerance.
lineVertices :: (Metric v, OrderedField n) => Located (Trail' Line v n) -> [Point v n] Source #
Like lineVertices'
, with a default tolerance.
loopVertices :: (Metric v, OrderedField n) => Located (Trail' Loop v n) -> [Point v n] Source #
Same as loopVertices'
, with a default tolerance.
trailLocSegments :: (Metric v, OrderedField n) => Located (Trail v n) -> [Located (Segment Closed v n)] Source #
Convert a concretely located trail into a list of located segments.
fixTrail :: (Metric v, OrderedField n) => Located (Trail v n) -> [FixedSegment v n] Source #
Convert a concretely located trail into a list of fixed segments.
unfixTrail
is almost its left inverse.
unfixTrail :: (Metric v, Ord n, Floating n) => [FixedSegment v n] -> Located (Trail v n) Source #
Convert a list of fixed segments into a located trail. Note that
this may lose information: it throws away the locations of all
but the first FixedSegment
. This does not matter precisely
when each FixedSegment
begins where the previous one ends.
This is almost left inverse to fixTrail
, that is, unfixTrail
. fixTrail == id
, except for the fact that unfixTrail
will
never yield a Loop
. In the case of a loop, we instead have
glueTrail . unfixTrail . fixTrail == id
. On the other hand, it
is not the case that fixTrail . unfixTrail == id
since
unfixTrail
may lose information.
reverseTrail :: (Metric v, OrderedField n) => Trail v n -> Trail v n Source #
Reverse a trail. Semantically, if a trail given by a function t
from [0,1] to vectors, then the reverse of t is given by t'(s) =
t(1-s). reverseTrail
is an involution, that is,
reverseTrail . reverseTrail === id
reverseLocTrail :: (Metric v, OrderedField n) => Located (Trail v n) -> Located (Trail v n) Source #
Reverse a concretely located trail. The endpoint of the original
trail becomes the starting point of the reversed trail, so the
original and reversed trails comprise exactly the same set of
points. reverseLocTrail
is an involution, i.e.
reverseLocTrail . reverseLocTrail === id
reverseLine :: (Metric v, OrderedField n) => Trail' Line v n -> Trail' Line v n Source #
Reverse a line. See reverseTrail
.
reverseLocLine :: (Metric v, OrderedField n) => Located (Trail' Line v n) -> Located (Trail' Line v n) Source #
Reverse a concretely located line. See reverseLocTrail
.
reverseLoop :: (Metric v, OrderedField n) => Trail' Loop v n -> Trail' Loop v n Source #
Reverse a loop. See reverseTrail
.
reverseLocLoop :: (Metric v, OrderedField n) => Located (Trail' Loop v n) -> Located (Trail' Loop v n) Source #
Reverse a concretely located loop. See reverseLocTrail
. Note
that this is guaranteed to preserve the location.
trailMeasure :: (SegMeasure v n :>: m, Measured (SegMeasure v n) t) => a -> (m -> a) -> t -> a Source #
Given a default result (to be used in the case of an empty trail), and a function to map a single measure to a result, extract the given measure for a trail and use it to compute a result. Put another way, lift a function on a single measure (along with a default value) to a function on an entire trail.
numSegs :: (Num c, Measured (SegMeasure v n) a) => a -> c Source #
Compute the number of segments of anything measured by
SegMeasure
(e.g. SegMeasure
itself, Segment
, SegTree
,
Trail
s...)
getSegment :: t -> GetSegment t Source #
Create a GetSegment
wrapper around a trail, after which you can
call atParam
, atStart
, or atEnd
to extract a segment.
Parametrization of segments and trails.
module Diagrams.Parametric
Adjusting the length of parameterized objects.
module Diagrams.Parametric.Adjust
Computing tangent and normal vectors of segments and trails.
module Diagrams.Tangent
Trail-like things.
module Diagrams.TrailLike
Paths.
A path is a (possibly empty) list of Located
Trail
s.
Hence, unlike trails, paths are not translationally invariant,
and they form a monoid under superposition (placing one path on
top of another) rather than concatenation.
Instances
Type class for things that can be converted to a Path
.
Note that this class is very different from TrailLike
. TrailLike
is
usually the result of a library function to give you a convenient,
polymorphic result (Path
, Diagram
etc.).
Instances
ToPath (Located (Segment Closed v n)) Source # | |
ToPath (Located (Trail v n)) Source # | |
ToPath (Located (Trail' l v n)) Source # | |
ToPath (Located [Segment Closed v n]) Source # | |
ToPath a => ToPath [a] Source # | |
ToPath (Path v n) Source # | |
ToPath (FixedSegment v n) Source # | |
Defined in Diagrams.Path toPath :: FixedSegment v n -> Path (V (FixedSegment v n)) (N (FixedSegment v n)) Source # | |
ToPath (Trail v n) Source # | |
ToPath (Trail' l v n) Source # | |
pathTrails :: Path v n -> [Located (Trail v n)] Source #
Extract the located trails making up a Path
.
pathFromTrail :: (Metric v, OrderedField n) => Trail v n -> Path v n Source #
Convert a trail to a path beginning at the origin.
pathFromTrailAt :: (Metric v, OrderedField n) => Trail v n -> Point v n -> Path v n Source #
Convert a trail to a path with a particular starting point.
pathFromLocTrail :: (Metric v, OrderedField n) => Located (Trail v n) -> Path v n Source #
Convert a located trail to a singleton path. This is equivalent
to trailLike
, but provided with a more specific name and type
for convenience.
pathVertices' :: (Metric v, OrderedField n) => n -> Path v n -> [[Point v n]] Source #
Extract the vertices of a path, resulting in a separate list of
vertices for each component trail. Here a vertex is defined as
a non-differentiable point on the trail, i.e. a sharp corner.
(Vertices are thus a subset of the places where segments join; if
you want all joins between segments, see pathPoints
.) The
tolerance determines how close the tangents of two segments must be
at their endpoints to consider the transition point to be
differentiable. See trailVertices
for more information.
pathVertices :: (Metric v, OrderedField n) => Path v n -> [[Point v n]] Source #
Like pathVertices'
, with a default tolerance.
pathOffsets :: (Metric v, OrderedField n) => Path v n -> [v n] Source #
Compute the total offset of each trail comprising a path (see trailOffset
).
pathCentroid :: (Metric v, OrderedField n) => Path v n -> Point v n Source #
Compute the centroid of a path (i.e. the average location of
its vertices; see pathVertices
).
pathLocSegments :: (Metric v, OrderedField n) => Path v n -> [[Located (Segment Closed v n)]] Source #
Convert a path into a list of lists of located segments.
fixPath :: (Metric v, OrderedField n) => Path v n -> [[FixedSegment v n]] Source #
Convert a path into a list of lists of FixedSegment
s.
scalePath :: (HasLinearMap v, Metric v, OrderedField n) => n -> Path v n -> Path v n Source #
Scale a path using its centroid (see pathCentroid
) as the base
point for the scale.
reversePath :: (Metric v, OrderedField n) => Path v n -> Path v n Source #
Reverse all the component trails of a path.
explodePath :: (V t ~ v, N t ~ n, TrailLike t) => Path v n -> [[t]] Source #
"Explode" a path by exploding every component trail (see
explodeTrail
).
partitionPath :: (Located (Trail v n) -> Bool) -> Path v n -> (Path v n, Path v n) Source #
Partition a path into two paths based on a predicate on trails:
the first containing all the trails for which the predicate returns
True
, and the second containing the remaining trails.
Cubic splines.
module Diagrams.CubicSpline
Some additional transformation-related functions, like conjugation of transformations.
module Diagrams.Transform
Projective transformations and other deformations lacking an inverse.
module Diagrams.Deform
Giving names to subdiagrams and later retrieving subdiagrams by name.
module Diagrams.Names
Envelopes, aka functional bounding regions.
module Diagrams.Envelope
Traces, aka embedded raytracers, for finding points on the boundary of a diagram.
module Diagrams.Trace
A query is a function that maps points in a vector space to values in some monoid; they can be used to annotate the points of a diagram with some values.
module Diagrams.Query
Utilities for working with points.
module Diagrams.Points
Utilities for working with size.
module Diagrams.Size
Angles
module Diagrams.Angle
Convenience infix operators for working with coordinates.
module Diagrams.Coordinates
Directions, distinguished from angles or vectors
A vector is described by a Direction
and a magnitude. So we
can think of a Direction
as a vector that has forgotten its
magnitude. Direction
s can be used with fromDirection
and the
lenses provided by its instances.
Instances
Functor v => Functor (Direction v) Source # | |
HasPhi v => HasPhi (Direction v) Source # | |
HasTheta v => HasTheta (Direction v) Source # | |
Read (v n) => Read (Direction v n) Source # | |
Show (v n) => Show (Direction v n) Source # | |
(V (v n) ~ v, N (v n) ~ n, Transformable (v n)) => Transformable (Direction v n) Source # | |
Defined in Diagrams.Direction | |
Eq (v n) => Eq (Direction v n) Source # | |
Ord (v n) => Ord (Direction v n) Source # | |
Defined in Diagrams.Direction compare :: Direction v n -> Direction v n -> Ordering # (<) :: Direction v n -> Direction v n -> Bool # (<=) :: Direction v n -> Direction v n -> Bool # (>) :: Direction v n -> Direction v n -> Bool # (>=) :: Direction v n -> Direction v n -> Bool # | |
type N (Direction v n) Source # | |
Defined in Diagrams.Direction | |
type V (Direction v n) Source # | |
Defined in Diagrams.Direction |
_Dir :: Iso' (Direction v n) (v n) Source #
_Dir is provided to allow efficient implementations of functions in particular vector-spaces, but should be used with care as it exposes too much information.
direction :: v n -> Direction v n Source #
direction v
is the direction in which v
points. Returns an
unspecified value when given the zero vector as input.
fromDirection :: (Metric v, Floating n) => Direction v n -> v n Source #
fromDirection d
is the unit vector in the direction d
.
angleBetweenDirs :: (Metric v, Floating n, Ord n) => Direction v n -> Direction v n -> Angle n Source #
compute the positive angle between the two directions in their common plane
dirBetween :: (Additive v, Num n) => Point v n -> Point v n -> Direction v n Source #
dirBetween p q
returns the direction from p
to q
.
A wide range of things (shapes, transformations, combinators) specific to creating two-dimensional diagrams.
module Diagrams.TwoD
Extra things for three-dimensional diagrams.
module Diagrams.ThreeD
Tools for making animations.
module Diagrams.Animation
Various utility definitions.
module Diagrams.Util