Copyright | (c) 2013 Michael Sloan |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | Michael Sloan <mgsloan at gmail> |
Safe Haskell | None |
Language | Haskell2010 |
This module provides utilities for using Control.Lens with diagrams,
including orphan instances for the Wrapped
class.
- _P :: Iso (Point v) (Point v') v v'
- _envelopeVMove :: (Monoid a, HasOrigin a, Enveloped a, Num (Scalar (V a))) => V a -> Traversal' a (V a)
- _alignedVMove :: (Monoid a, HasOrigin a, Enveloped a, Num (Scalar (V a))) => V a -> Scalar (V a) -> Traversal' a (V a)
- _corners :: (HasBasis v, Ord (Basis v), AdditiveGroup (Scalar v), Ord (Scalar v), HasBasis v', Ord (Basis v'), AdditiveGroup (Scalar v'), Ord (Scalar v')) => Traversal (BoundingBox v) (BoundingBox v') (Point v) (Point v')
- _boxExtents :: (HasBasis v, Ord (Basis v), AdditiveGroup (Scalar v), Ord (Scalar v)) => Lens' (BoundingBox v) v
- _attr :: AttributeClass a => Lens' (Style v) (Maybe a)
- _mkAttr :: AttributeClass a => Prism' (Attribute v) a
- _mkTAttr :: (AttributeClass a, Transformable a, V a ~ v) => Prism' (Attribute v) a
- _location :: (HasLinearMap v, InnerSpace v, OrderedField (Scalar v)) => Lens' (Subdiagram b v m) (Point v)
- _mkSubdiagram :: (HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Semigroup m) => Iso' (QDiagram b v m) (Subdiagram b v m)
- _Loc :: Iso (Located a) (Located a') (Point (V a), a) (Point (V a'), a')
- _mkFixedSeg :: (AdditiveGroup v, AdditiveGroup v') => Iso (Located (Segment Closed v)) (Located (Segment Closed v')) (FixedSegment v) (FixedSegment v')
- _straight :: Prism' (Segment Closed v) v
- _bezier3 :: Prism' (Segment Closed v) (v, v, v)
- _lineVertices :: (InnerSpace v, OrderedField (Scalar v), InnerSpace v', OrderedField (Scalar v')) => Iso (Located (Trail' Line v)) (Located (Trail' Line v')) [Point v] [Point v']
- _lineOffsets :: (InnerSpace v, OrderedField (Scalar v), InnerSpace v', OrderedField (Scalar v')) => Iso (Trail' Line v) (Trail' Line v') [v] [v']
- _lineSegments :: (InnerSpace v, OrderedField (Scalar v), InnerSpace v', OrderedField (Scalar v')) => Iso (Trail' Line v) (Trail' Line v') [Segment Closed v] [Segment Closed v']
Documentation
Diagrams.Align
_envelopeVMove :: (Monoid a, HasOrigin a, Enveloped a, Num (Scalar (V a))) => V a -> Traversal' a (V a) Source
A singleton Traversal
for an envelope vector, where modification of the
vector moves the origin appropriately. No vector is traversed when the
envelope is empty.
This is the same as _alignedVMove
with 1
as the interpolation
parameter.
_alignedVMove :: (Monoid a, HasOrigin a, Enveloped a, Num (Scalar (V a))) => V a -> Scalar (V a) -> Traversal' a (V a) Source
A singleton Traversal
for an alignment vector, where modification of the
vector moves the origin appropriately. No vector is traversed when the
envelope is empty.
The interface mimics "Diagrams.Align.alignBy" in that the d
parameter
specifies an interpolation between two extremes of the envelope. d = 1
is on the envelope along the vector, whereas d = -1
is on the envelope,
away from the vector.
If you need a Point
instead of a vector, then compose with _P
.
Diagrams.BoundingBox
_corners :: (HasBasis v, Ord (Basis v), AdditiveGroup (Scalar v), Ord (Scalar v), HasBasis v', Ord (Basis v'), AdditiveGroup (Scalar v'), Ord (Scalar v')) => Traversal (BoundingBox v) (BoundingBox v') (Point v) (Point v') Source
A traversal that either has 0 (empty box) or 2 points. These points are the lower and upper corners, respectively.
_boxExtents :: (HasBasis v, Ord (Basis v), AdditiveGroup (Scalar v), Ord (Scalar v)) => Lens' (BoundingBox v) v Source
A lens that gets the extents of the box. In order to change the extents, this modifies the upper corner.
Diagrams.Core.Style
_mkAttr :: AttributeClass a => Prism' (Attribute v) a Source
_mkTAttr :: (AttributeClass a, Transformable a, V a ~ v) => Prism' (Attribute v) a Source
Diagrams.Core.Types
_location :: (HasLinearMap v, InnerSpace v, OrderedField (Scalar v)) => Lens' (Subdiagram b v m) (Point v) Source
Gets or set the location
of a Subdiagram
.
_mkSubdiagram :: (HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Semigroup m) => Iso' (QDiagram b v m) (Subdiagram b v m) Source
Diagrams.Located
Diagrams.Parametric
Diagrams.Segment
_mkFixedSeg :: (AdditiveGroup v, AdditiveGroup v') => Iso (Located (Segment Closed v)) (Located (Segment Closed v')) (FixedSegment v) (FixedSegment v') Source
_straight :: Prism' (Segment Closed v) v Source
Prism that constructs linear segments. Can also destruct them, if the segment is Linear.
_bezier3 :: Prism' (Segment Closed v) (v, v, v) Source
Prism that constructs cubic bezier segments. Can also destruct them, if
segment is a Cubic
.
Diagrams.Trail
_lineVertices :: (InnerSpace v, OrderedField (Scalar v), InnerSpace v', OrderedField (Scalar v')) => Iso (Located (Trail' Line v)) (Located (Trail' Line v')) [Point v] [Point v'] Source
_lineOffsets :: (InnerSpace v, OrderedField (Scalar v), InnerSpace v', OrderedField (Scalar v')) => Iso (Trail' Line v) (Trail' Line v') [v] [v'] Source
_lineSegments :: (InnerSpace v, OrderedField (Scalar v), InnerSpace v', OrderedField (Scalar v')) => Iso (Trail' Line v) (Trail' Line v') [Segment Closed v] [Segment Closed v'] Source