| Maintainer | diagrams-discuss@googlegroups.com | 
|---|---|
| Safe Haskell | None | 
Diagrams.Combinators
Description
Higher-level tools for combining diagrams.
- withEnvelope :: (HasLinearMap (V a), Enveloped a, Monoid' m) => a -> QDiagram b (V a) m -> QDiagram b (V a) m
- withTrace :: (HasLinearMap (V a), Traced a, OrderedField (Scalar (V a)), InnerSpace (V a), Monoid' m) => a -> QDiagram b (V a) m -> QDiagram b (V a) m
- phantom :: (Backend b (V a), Typeable (V a), Enveloped a, Traced a, Monoid' m) => a -> QDiagram b (V a) m
- strut :: (Backend b v, Typeable v, InnerSpace v, OrderedField (Scalar v), Monoid' m) => v -> QDiagram b v m
- pad :: (Backend b v, InnerSpace v, OrderedField (Scalar v), Monoid' m) => Scalar v -> QDiagram b v m -> QDiagram b v m
- frame :: (Backend b v, InnerSpace v, OrderedField (Scalar v), Monoid' m) => Scalar v -> QDiagram b v m -> QDiagram b v m
- extrudeEnvelope :: (Ord (Scalar v), Num (Scalar v), AdditiveGroup (Scalar v), Floating (Scalar v), HasLinearMap v, InnerSpace v, Monoid' m) => v -> QDiagram b v m -> QDiagram b v m
- intrudeEnvelope :: (Ord (Scalar v), Num (Scalar v), AdditiveGroup (Scalar v), Floating (Scalar v), HasLinearMap v, InnerSpace v, Monoid' m) => v -> QDiagram b v m -> QDiagram b v m
- atop :: (HasLinearMap v, OrderedField (Scalar v), InnerSpace v, Semigroup m) => QDiagram b v m -> QDiagram b v m -> QDiagram b v m
- beneath :: (HasLinearMap v, OrderedField (Scalar v), InnerSpace v, Monoid' m) => QDiagram b v m -> QDiagram b v m -> QDiagram b v m
- beside :: (Juxtaposable a, Semigroup a) => V a -> a -> a -> a
- appends :: (Juxtaposable a, Monoid' a) => a -> [(V a, a)] -> a
- position :: (HasOrigin a, Monoid' a) => [(Point (V a), a)] -> a
- decorateTrail :: (InnerSpace (V a), OrderedField (Scalar (V a)), HasOrigin a, Monoid' a) => Trail (V a) -> [a] -> a
- decorateLocatedTrail :: (InnerSpace (V a), OrderedField (Scalar (V a)), HasOrigin a, Monoid' a) => Located (Trail (V a)) -> [a] -> a
- decoratePath :: (InnerSpace (V a), OrderedField (Scalar (V a)), HasOrigin a, Monoid' a) => Path (V a) -> [a] -> a
- cat :: (Juxtaposable a, Monoid' a, HasOrigin a, InnerSpace (V a), OrderedField (Scalar (V a))) => V a -> [a] -> a
- cat' :: (Juxtaposable a, Monoid' a, HasOrigin a, InnerSpace (V a), OrderedField (Scalar (V a))) => V a -> CatOpts (V a) -> [a] -> a
- data CatOpts v
- catMethod :: forall v. Lens' (CatOpts v) CatMethod
- sep :: forall v. Lens' (CatOpts v) (Scalar v)
- data CatMethod
Unary operations
withEnvelope :: (HasLinearMap (V a), Enveloped a, Monoid' m) => a -> QDiagram b (V a) m -> QDiagram b (V a) mSource
Use the envelope from some object as the envelope for a diagram, in place of the diagram's default envelope.
 sqNewEnv =
     circle 1 # fc green
     |||
     (    c # dashing [0.1,0.1] 0 # lc white
       <> square 2 # withEnvelope (c :: D R2) # fc blue
     )
 c = circle 0.8
 withEnvelopeEx = sqNewEnv # centerXY # pad 1.5
withTrace :: (HasLinearMap (V a), Traced a, OrderedField (Scalar (V a)), InnerSpace (V a), Monoid' m) => a -> QDiagram b (V a) m -> QDiagram b (V a) mSource
Use the trace from some object as the trace for a diagram, in place of the diagram's default trace.
phantom :: (Backend b (V a), Typeable (V a), Enveloped a, Traced a, Monoid' m) => a -> QDiagram b (V a) mSource
phantom x produces a "phantom" diagram, which has the same
   envelope and trace as x but produces no output.
strut :: (Backend b v, Typeable v, InnerSpace v, OrderedField (Scalar v), Monoid' m) => v -> QDiagram b v mSource
strut v is a diagram which produces no output, but with respect
   to alignment and envelope acts like a 1-dimensional segment
   oriented along the vector v, with local origin at its
   center. (Note, however, that it has an empty trace; for 2D struts
   with a nonempty trace see strutR2, strutX, and strutY from
   Diagrams.TwoD.Combinators.) Useful for manually creating
   separation between two diagrams.
strutEx = (circle 1 ||| strut unitX ||| circle 1) # centerXY # pad 1.1
pad :: (Backend b v, InnerSpace v, OrderedField (Scalar v), Monoid' m) => Scalar v -> QDiagram b v m -> QDiagram b v mSource
pad s "pads" a diagram, expanding its envelope by a factor of
   s (factors between 0 and 1 can be used to shrink the envelope).
   Note that the envelope will expand with respect to the local
   origin, so if the origin is not centered the padding may appear
   "uneven".  If this is not desired, the origin can be centered
   (using, e.g., centerXY for 2D diagrams) before applying pad.
frame :: (Backend b v, InnerSpace v, OrderedField (Scalar v), Monoid' m) => Scalar v -> QDiagram b v m -> QDiagram b v mSource
frame s increases the envelope of a diagram by and absolute amount s,
   s is in the local units of the diagram. This function is similar to pad,
   only it takes an absolute quantity and pre-centering should not be
   necessary.
extrudeEnvelope :: (Ord (Scalar v), Num (Scalar v), AdditiveGroup (Scalar v), Floating (Scalar v), HasLinearMap v, InnerSpace v, Monoid' m) => v -> QDiagram b v m -> QDiagram b v mSource
extrudeEnvelope v d asymmetrically "extrudes" the envelope of
   a diagram in the given direction.  All parts of the envelope
   within 90 degrees of this direction are modified, offset outwards
   by the magnitude of the vector.
This works by offsetting the envelope distance proportionally to the cosine of the difference in angle, and leaving it unchanged when this factor is negative.
intrudeEnvelope :: (Ord (Scalar v), Num (Scalar v), AdditiveGroup (Scalar v), Floating (Scalar v), HasLinearMap v, InnerSpace v, Monoid' m) => v -> QDiagram b v m -> QDiagram b v mSource
intrudeEnvelope v d asymmetrically "intrudes" the envelope of
   a diagram away from the given direction.  All parts of the envelope
   within 90 degrees of this direction are modified, offset inwards
   by the magnitude of the vector.
Note that this could create strange inverted envelopes, where
    diameter v d < 0 .
Binary operations
atop :: (HasLinearMap v, OrderedField (Scalar v), InnerSpace v, Semigroup m) => QDiagram b v m -> QDiagram b v m -> QDiagram b v m
A convenient synonym for mappend on diagrams, designed to be
   used infix (to help remember which diagram goes on top of which
   when combining them, namely, the first on top of the second).
beneath :: (HasLinearMap v, OrderedField (Scalar v), InnerSpace v, Monoid' m) => QDiagram b v m -> QDiagram b v m -> QDiagram b v mSource
beside :: (Juxtaposable a, Semigroup a) => V a -> a -> a -> aSource
Place two monoidal objects (i.e. diagrams, paths, animations...) next to each other along the given vector. In particular, place the second object so that the vector points from the local origin of the first object to the local origin of the second object, at a distance so that their envelopes are just tangent. The local origin of the new, combined object is the local origin of the first object (unless the first object is the identity element, in which case the second object is returned unchanged).
 besideEx = beside (r2 (20,30))
                   (circle 1 # fc orange)
                   (circle 1.5 # fc purple)
            # showOrigin
            # centerXY # pad 1.1
Note that beside v is associative, so objects under beside v
   form a semigroup for any given vector v.  In fact, they also
   form a monoid: mempty is clearly a right identity (beside v d1
   mempty === d1), and there should also be a special case to make
   it a left identity, as described above.
In older versions of diagrams, beside put the local origin of
   the result at the point of tangency between the two inputs.  That
   semantics can easily be recovered by performing an alignment on
   the first input before combining.  That is, if beside' denotes
   the old semantics,
beside' v x1 x2 = beside v (x1 # align v) x2
To get something like beside v x1 x2 whose local origin is
   identified with that of x2 instead of x1, use beside
   (negateV v) x2 x1.
n-ary operations
appends :: (Juxtaposable a, Monoid' a) => a -> [(V a, a)] -> aSource
appends x ys appends each of the objects in ys to the object
   x in the corresponding direction.  Note that each object in
   ys is positioned beside x without reference to the other
   objects in ys, so this is not the same as iterating beside.
 appendsEx = appends c (zip (iterateN 6 (rotateBy (1/6)) unitX) (repeat c))
             # centerXY # pad 1.1
   where c = circle 1
position :: (HasOrigin a, Monoid' a) => [(Point (V a), a)] -> aSource
Position things absolutely: combine a list of objects (e.g. diagrams or paths) by assigning them absolute positions in the vector space of the combined object.
 positionEx = position (zip (map mkPoint [-3, -2.8 .. 3]) (repeat dot))
   where dot       = circle 0.2 # fc black
         mkPoint x = p2 (x,x^2)
decorateTrail :: (InnerSpace (V a), OrderedField (Scalar (V a)), HasOrigin a, Monoid' a) => Trail (V a) -> [a] -> aSource
Combine a list of diagrams (or paths) by using them to "decorate" a trail, placing the local origin of one object at each successive vertex of the trail. The first vertex of the trail is placed at the origin. If the trail and list of objects have different lengths, the extra tail of the longer one is ignored.
decorateLocatedTrail :: (InnerSpace (V a), OrderedField (Scalar (V a)), HasOrigin a, Monoid' a) => Located (Trail (V a)) -> [a] -> aSource
Combine a list of diagrams (or paths) by using them to "decorate" a concretely located trail, placing the local origin of one object at each successive vertex of the trail. If the trail and list of objects have different lengths, the extra tail of the longer one is ignored.
decoratePath :: (InnerSpace (V a), OrderedField (Scalar (V a)), HasOrigin a, Monoid' a) => Path (V a) -> [a] -> aSource
Combine a list of diagrams (or paths) by using them to "decorate" a path, placing the local origin of one object at each successive vertex of the path. If the path and list of objects have different lengths, the extra tail of the longer one is ignored.
cat :: (Juxtaposable a, Monoid' a, HasOrigin a, InnerSpace (V a), OrderedField (Scalar (V a))) => V a -> [a] -> aSource
cat v positions a list of objects so that their local origins
   lie along a line in the direction of v.  Successive objects
   will have their envelopes just touching.  The local origin
   of the result will be the same as the local origin of the first
   object.
See also cat', which takes an extra options record allowing
   certain aspects of the operation to be tweaked.
cat' :: (Juxtaposable a, Monoid' a, HasOrigin a, InnerSpace (V a), OrderedField (Scalar (V a))) => V a -> CatOpts (V a) -> [a] -> aSource
Like cat, but taking an extra CatOpts arguments allowing the
   user to specify
- The spacing method: catenation (uniform spacing between envelopes) or distribution (uniform spacing between local origins). The default is catenation.
- The amount of separation between successive diagram envelopes/origins (depending on the spacing method). The default is 0.
CatOpts is an instance of Default, so with may be used for
   the second argument, as in cat' (1,2) (with & sep .~ 2).
Note that cat' v (with & catMethod .~ Distrib) === mconcat
   (distributing with a separation of 0 is the same as
   superimposing).
catMethod :: forall v. Lens' (CatOpts v) CatMethodSource
Which CatMethod should be used:
   normal catenation (default), or distribution?
sep :: forall v. Lens' (CatOpts v) (Scalar v)Source
How much separation should be used between successive diagrams
   (default: 0)?  When catMethod = Cat, this is the distance between
   envelopes; when catMethod = Distrib, this is the distance
   between origins.
Methods for concatenating diagrams.
Constructors
| Cat | Normal catenation: simply put diagrams next to one another (possibly with a certain distance in between each). The distance between successive diagram envelopes will be consistent; the distance between origins may vary if the diagrams are of different sizes. | 
| Distrib | Distribution: place the local origins of diagrams at regular intervals. With this method, the distance between successive origins will be consistent but the distance between envelopes may not be. Indeed, depending on the amount of separation, diagrams may overlap. |