Copyright | (c) 2011 diagrams-lib team (see LICENSE) |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | diagrams-discuss@googlegroups.com |
Safe Haskell | None |
Language | Haskell2010 |
Diagrams may have attributes which affect the way they are rendered. This module defines some common attributes; particular backends may also define more backend-specific attributes.
Every attribute type must have a semigroup structure, that is, an
associative binary operation for combining two attributes into one.
Unless otherwise noted, all the attributes defined here use the
Last
structure, that is, combining two attributes simply keeps
the second one and throws away the first. This means that child
attributes always override parent attributes.
- class Color c where
- toAlphaColour :: c -> AlphaColour Double
- fromAlphaColour :: AlphaColour Double -> c
- data SomeColor = forall c . Color c => SomeColor c
- someToAlpha :: SomeColor -> AlphaColour Double
- data LineColor
- getLineColor :: LineColor -> SomeColor
- mkLineColor :: Color c => c -> LineColor
- styleLineColor :: (Color c, Color c') => Setter (Style v) (Style v) c c'
- lineColor :: (Color c, HasStyle a) => c -> a -> a
- lineColorA :: HasStyle a => LineColor -> a -> a
- lc :: HasStyle a => Colour Double -> a -> a
- lcA :: HasStyle a => AlphaColour Double -> a -> a
- data FillColor
- getFillColor :: FillColor -> SomeColor
- mkFillColor :: Color c => c -> FillColor
- styleFillColor :: (Color c, Color c') => Setter (Style v) (Style v) c c'
- recommendFillColor :: (Color c, HasStyle a) => c -> a -> a
- fillColor :: (Color c, HasStyle a) => c -> a -> a
- fc :: HasStyle a => Colour Double -> a -> a
- fcA :: HasStyle a => AlphaColour Double -> a -> a
- data Opacity
- getOpacity :: Opacity -> Double
- opacity :: HasStyle a => Double -> a -> a
- colorToSRGBA :: Color c => c -> (Double, Double, Double, Double)
- colorToRGBA :: Color c => c -> (Double, Double, Double, Double)
- data LineWidth
- getLineWidth :: LineWidth -> Double
- lineWidth :: HasStyle a => Double -> a -> a
- lineWidthA :: HasStyle a => LineWidth -> a -> a
- lw :: HasStyle a => Double -> a -> a
- data LineCap
- data LineCapA
- getLineCap :: LineCapA -> LineCap
- lineCap :: HasStyle a => LineCap -> a -> a
- data LineJoin
- data LineJoinA
- getLineJoin :: LineJoinA -> LineJoin
- lineJoin :: HasStyle a => LineJoin -> a -> a
- newtype LineMiterLimit = LineMiterLimit (Last Double)
- getLineMiterLimit :: LineMiterLimit -> Double
- lineMiterLimit :: HasStyle a => Double -> a -> a
- lineMiterLimitA :: HasStyle a => LineMiterLimit -> a -> a
- data Dashing = Dashing [Double] Double
- data DashingA
- getDashing :: DashingA -> Dashing
- dashing :: HasStyle a => [Double] -> Double -> a -> a
- splitFills :: forall b v a. Typeable v => RTree b v a -> RTree b v a
Color
Diagrams outsources all things color-related to Russell O'Connor's very nice colour package (http://hackage.haskell.org/package/colour). For starters, it provides a large collection of standard color names. However, it also provides a rich set of combinators for combining and manipulating colors; see its documentation for more information.
The Color
type class encompasses color representations which
can be used by the Diagrams library. Instances are provided for
both the Colour
and AlphaColour
types
from the Data.Colour library.
toAlphaColour :: c -> AlphaColour Double Source
Convert a color to its standard representation, AlphaColour.
fromAlphaColour :: AlphaColour Double -> c Source
Convert from an AlphaColour Double. Note that this direction
may lose some information. For example, the instance for
Colour
drops the alpha channel.
An existential wrapper for instances of the Color
class.
Line color
getLineColor :: LineColor -> SomeColor Source
mkLineColor :: Color c => c -> LineColor Source
lineColor :: (Color c, HasStyle a) => c -> a -> a Source
Set the line (stroke) color. This function is polymorphic in the
color type (so it can be used with either Colour
or
AlphaColour
), but this can sometimes create problems for type
inference, so the lc
and lcA
variants are provided with more
concrete types.
lineColorA :: HasStyle a => LineColor -> a -> a Source
Apply a lineColor
attribute.
lcA :: HasStyle a => AlphaColour Double -> a -> a Source
A synonym for lineColor
, specialized to
(i.e. colors with transparency).AlphaColour
Double
Fill color
getFillColor :: FillColor -> SomeColor Source
mkFillColor :: Color c => c -> FillColor Source
recommendFillColor :: (Color c, HasStyle a) => c -> a -> a Source
fillColor :: (Color c, HasStyle a) => c -> a -> a Source
Set the fill color. This function is polymorphic in the color
type (so it can be used with either Colour
or AlphaColour
),
but this can sometimes create problems for type inference, so the
fc
and fcA
variants are provided with more concrete types.
fcA :: HasStyle a => AlphaColour Double -> a -> a Source
A synonym for fillColor
, specialized to
(i.e. colors with transparency).AlphaColour
Double
Opacity
Although the individual colors in a diagram can have
transparency, the opacity/transparency of a diagram as a whole
can be specified with the Opacity
attribute. The opacity is a
value between 1 (completely opaque, the default) and 0
(completely transparent). Opacity is multiplicative, that is,
. In other
words, for example, opacity
o1 . opacity
o2 === opacity
(o1 * o2)opacity 0.8
means "decrease this diagram's
opacity to 80% of its previous opacity".
getOpacity :: Opacity -> Double Source
opacity :: HasStyle a => Double -> a -> a Source
Multiply the opacity (see Opacity
) by the given value. For
example, opacity 0.8
means "decrease this diagram's opacity to
80% of its previous opacity".
Converting colors
colorToRGBA :: Color c => c -> (Double, Double, Double, Double) Source
Deprecated: Renamed to colorToSRGBA.
Convert to sRGBA.
Lines
Width
The width of lines. By default, the line width is measured with
respect to the final coordinate system of a rendered diagram,
as opposed to the local coordinate systems in effect at the time
the line width was set for various subdiagrams. This is so that
it is easy to combine a variety of shapes (some created by
scaling) and have them all drawn using a consistent line width.
However, sometimes it is desirable for scaling to affect line
width; the freeze
operation is provided for this purpose. The
line width of frozen diagrams is affected by transformations.
Line widths specified on child nodes always override line widths specified at parent nodes.
getLineWidth :: LineWidth -> Double Source
lineWidthA :: HasStyle a => LineWidth -> a -> a Source
Apply a LineWidth
attribute.
Cap style
What sort of shape should be placed at the endpoints of lines?
LineCapButt | Lines end precisely at their endpoints. |
LineCapRound | Lines are capped with semicircles centered on endpoints. |
LineCapSquare | Lines are capped with a squares centered on endpoints. |
getLineCap :: LineCapA -> LineCap Source
Join style
How should the join points between line segments be drawn?
LineJoinMiter | Use a "miter" shape (whatever that is). |
LineJoinRound | Use rounded join points. |
LineJoinBevel | Use a "bevel" shape (whatever that is). Are these... carpentry terms? |
getLineJoin :: LineJoinA -> LineJoin Source
Miter limit
newtype LineMiterLimit Source
Miter limit attribute affecting the LineJoinMiter
joins.
For some backends this value may have additional effects.
lineMiterLimit :: HasStyle a => Double -> a -> a Source
Set the miter limit for joins with LineJoinMiter
.
lineMiterLimitA :: HasStyle a => LineMiterLimit -> a -> a Source
Apply a LineMiterLimit
attribute.
Dashing
Create lines that are dashing... er, dashed.
getDashing :: DashingA -> Dashing Source
:: HasStyle a | |
=> [Double] | A list specifying alternate lengths of on and off portions of the stroke. The empty list indicates no dashing. |
-> Double | An offset into the dash pattern at which the stroke should start. |
-> a | |
-> a |
Set the line dashing style.
Compilation utilities
splitFills :: forall b v a. Typeable v => RTree b v a -> RTree b v a Source
Push fill attributes down until they are at the root of subtrees containing only loops. This makes life much easier for backends, which typically have a semantics where fill attributes are applied to linesnon-closed paths as well as loopsclosed paths, whereas in the semantics of diagrams, fill attributes only apply to loops.