Copyright | (c) 2013-2015 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 Textures (Gradients and Colors) in two
dimensions. Like the attributes defined in the Diagrams.Attributes module,
all attributes defined here use the Last
or Recommend
semigroup structure.
FillColor
and LineColor
attributes are provided so that backends that
don't support gradients need not be concerned with using textures. Backends
should only implement color attributes or textures attributes, not both.
- data Texture n
- solid :: Color a => a -> Texture n
- _SC :: forall n. Prism' (Texture n) SomeColor
- _AC :: Prism' (Texture n) (AlphaColour Double)
- _LG :: forall n. Prism' (Texture n) (LGradient n)
- _RG :: forall n. Prism' (Texture n) (RGradient n)
- defaultLG :: Fractional n => Texture n
- defaultRG :: Fractional n => Texture n
- data GradientStop d = GradientStop {
- _stopColor :: SomeColor
- _stopFraction :: d
- stopColor :: Lens' (GradientStop n) SomeColor
- stopFraction :: Lens' (GradientStop n) n
- mkStops :: [(Colour Double, d, Double)] -> [GradientStop d]
- data SpreadMethod
- lineLGradient :: (InSpace V2 n a, Typeable n, Floating n, HasStyle a) => LGradient n -> a -> a
- lineRGradient :: (InSpace V2 n a, Typeable n, Floating n, HasStyle a) => RGradient n -> a -> a
- data LGradient n = LGradient {
- _lGradStops :: [GradientStop n]
- _lGradStart :: Point V2 n
- _lGradEnd :: Point V2 n
- _lGradTrans :: Transformation V2 n
- _lGradSpreadMethod :: SpreadMethod
- lGradStops :: Lens' (LGradient n) [GradientStop n]
- lGradTrans :: Lens' (LGradient n) (Transformation V2 n)
- lGradStart :: Lens' (LGradient n) (Point V2 n)
- lGradEnd :: Lens' (LGradient n) (Point V2 n)
- lGradSpreadMethod :: Lens' (LGradient n) SpreadMethod
- mkLinearGradient :: Num n => [GradientStop n] -> Point V2 n -> Point V2 n -> SpreadMethod -> Texture n
- data RGradient n = RGradient {
- _rGradStops :: [GradientStop n]
- _rGradCenter0 :: Point V2 n
- _rGradRadius0 :: n
- _rGradCenter1 :: Point V2 n
- _rGradRadius1 :: n
- _rGradTrans :: Transformation V2 n
- _rGradSpreadMethod :: SpreadMethod
- rGradStops :: Lens' (RGradient n) [GradientStop n]
- rGradTrans :: Lens' (RGradient n) (Transformation V2 n)
- rGradCenter0 :: Lens' (RGradient n) (Point V2 n)
- rGradRadius0 :: Lens' (RGradient n) n
- rGradCenter1 :: Lens' (RGradient n) (Point V2 n)
- rGradRadius1 :: Lens' (RGradient n) n
- rGradSpreadMethod :: Lens' (RGradient n) SpreadMethod
- mkRadialGradient :: Num n => [GradientStop n] -> Point V2 n -> n -> Point V2 n -> n -> SpreadMethod -> Texture n
- newtype LineTexture n = LineTexture (Last (Texture n))
- _LineTexture :: Iso (LineTexture n) (LineTexture n') (Texture n) (Texture n')
- getLineTexture :: LineTexture n -> Texture n
- lineTexture :: (InSpace V2 n a, Typeable n, Floating n, HasStyle a) => Texture n -> a -> a
- lineTextureA :: (InSpace V2 n a, Typeable n, Floating n, HasStyle a) => LineTexture n -> a -> a
- mkLineTexture :: Texture n -> LineTexture n
- _lineTexture :: (Floating n, Typeable n) => Lens' (Style V2 n) (Texture n)
- lineColor :: (InSpace V2 n a, Color c, Typeable n, Floating n, HasStyle a) => c -> a -> a
- lc :: (InSpace V2 n a, Typeable n, Floating n, HasStyle a) => Colour Double -> a -> a
- lcA :: (InSpace V2 n a, Typeable n, Floating n, HasStyle a) => AlphaColour Double -> a -> a
- newtype FillTexture n = FillTexture (Recommend (Last (Texture n)))
- _FillTexture :: Iso' (FillTexture n) (Recommend (Texture n))
- getFillTexture :: FillTexture n -> Texture n
- fillTexture :: (InSpace V2 n a, Typeable n, Floating n, HasStyle a) => Texture n -> a -> a
- mkFillTexture :: Texture n -> FillTexture n
- _fillTexture :: (Typeable n, Floating n) => Lens' (Style V2 n) (Texture n)
- _fillTextureR :: (Typeable n, Floating n) => Lens' (Style V2 n) (Recommend (Texture n))
- fillColor :: (InSpace V2 n a, Color c, Typeable n, Floating n, HasStyle a) => c -> a -> a
- fc :: (InSpace V2 n a, Floating n, Typeable n, HasStyle a) => Colour Double -> a -> a
- fcA :: (InSpace V2 n a, Floating n, Typeable n, HasStyle a) => AlphaColour Double -> a -> a
- recommendFillColor :: (InSpace V2 n a, Color c, Typeable n, Floating n, HasStyle a) => c -> a -> a
- splitTextureFills :: forall b v n a. (Typeable v, Typeable n) => RTree b v n a -> RTree b v n a
Textures
_AC :: Prism' (Texture n) (AlphaColour Double) Source
Prism onto an AlphaColour
Double
of a SC
texture.
defaultLG :: Fractional n => Texture n Source
A default is provided so that linear gradients can easily be created using
lenses. For example, lg = defaultLG & lGradStart .~ (0.25 ^& 0.33)
. Note that
no default value is provided for lGradStops
, this must be set before
the gradient value is used, otherwise the object will appear transparent.
defaultRG :: Fractional n => Texture n Source
A default is provided so that radial gradients can easily be created using
lenses. For example, rg = defaultRG & rGradRadius1 .~ 0.25
. Note that
no default value is provided for rGradStops
, this must be set before
the gradient value is used, otherwise the object will appear transparent.
data GradientStop d Source
A gradient stop contains a color and fraction (usually between 0 and 1)
GradientStop | |
|
stopColor :: Lens' (GradientStop n) SomeColor Source
A color for the stop.
stopFraction :: Lens' (GradientStop n) n Source
The fraction for stop.
mkStops :: [(Colour Double, d, Double)] -> [GradientStop d] Source
A convenient function for making gradient stops from a list of triples. (An opaque color, a stop fraction, an opacity).
data SpreadMethod Source
The SpreadMethod
determines what happens before lGradStart
and after
lGradEnd
. GradPad
fills the space before the start of the gradient
with the color of the first stop and the color after end of the gradient
with the color of the last stop. GradRepeat
restarts the gradient and
GradReflect
restarts the gradient with the stops in reverse order.
lineLGradient :: (InSpace V2 n a, Typeable n, Floating n, HasStyle a) => LGradient n -> a -> a Source
Apply a linear gradient.
lineRGradient :: (InSpace V2 n a, Typeable n, Floating n, HasStyle a) => RGradient n -> a -> a Source
Apply a radial gradient.
Linear Gradients
Linear Gradient
LGradient | |
|
lGradStops :: Lens' (LGradient n) [GradientStop n] Source
A list of stops (colors and fractions).
lGradTrans :: Lens' (LGradient n) (Transformation V2 n) Source
A transformation to be applied to the gradient. Usually this field will start as the identity transform and capture the transforms that are applied to the gradient.
lGradStart :: Lens' (LGradient n) (Point V2 n) Source
The starting point for the first gradient stop. The coordinates are in
local
units and the default is (-0.5, 0).
lGradEnd :: Lens' (LGradient n) (Point V2 n) Source
The ending point for the last gradient stop.The coordinates are in
local
units and the default is (0.5, 0).
lGradSpreadMethod :: Lens' (LGradient n) SpreadMethod Source
For setting the spread method.
mkLinearGradient :: Num n => [GradientStop n] -> Point V2 n -> Point V2 n -> SpreadMethod -> Texture n Source
Make a linear gradient texture from a stop list, start point, end point,
and SpreadMethod
. The lGradTrans
field is set to the identity
transfrom, to change it use the lGradTrans
lens.
Radial Gradients
Radial Gradient
RGradient | |
|
rGradStops :: Lens' (RGradient n) [GradientStop n] Source
A list of stops (colors and fractions).
rGradTrans :: Lens' (RGradient n) (Transformation V2 n) Source
A transformation to be applied to the gradient. Usually this field will start as the identity transform and capture the transforms that are applied to the gradient.
rGradRadius0 :: Lens' (RGradient n) n Source
The radius of the inner cirlce in local
coordinates.
rGradRadius1 :: Lens' (RGradient n) n Source
The radius of the outer circle in local
coordinates.
rGradSpreadMethod :: Lens' (RGradient n) SpreadMethod Source
For setting the spread method.
mkRadialGradient :: Num n => [GradientStop n] -> Point V2 n -> n -> Point V2 n -> n -> SpreadMethod -> Texture n Source
Make a radial gradient texture from a stop list, radius, start point,
end point, and SpreadMethod
. The rGradTrans
field is set to the identity
transfrom, to change it use the rGradTrans
lens.
Line texture
newtype LineTexture n Source
The texture with which lines are drawn. Note that child
textures always override parent textures.
More precisely, the semigroup structure on line texture attributes
is that of Last
.
LineTexture (Last (Texture n)) |
Semigroup (LineTexture n) Source | |
Default (LineTexture n) Source | |
Typeable * n => AttributeClass (LineTexture n) Source | |
Floating n => Transformable (LineTexture n) Source | |
type V (LineTexture n) = V2 Source | |
type N (LineTexture n) = n Source |
_LineTexture :: Iso (LineTexture n) (LineTexture n') (Texture n) (Texture n') Source
getLineTexture :: LineTexture n -> Texture n Source
lineTextureA :: (InSpace V2 n a, Typeable n, Floating n, HasStyle a) => LineTexture n -> a -> a Source
mkLineTexture :: Texture n -> LineTexture n Source
Line color
lineColor :: (InSpace V2 n a, Color c, Typeable n, Floating n, 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.
lcA :: (InSpace V2 n a, Typeable n, Floating n, HasStyle a) => AlphaColour Double -> a -> a Source
A synonym for lineColor
, specialized to
(i.e. colors with transparency). See comment in AlphaColour
DoublelineColor
about backends.
Fill texture
newtype FillTexture n Source
The texture with which objects are filled. The semigroup structure on fill texture attributes is that of 'Recommed . Last'.
FillTexture (Recommend (Last (Texture n))) |
Semigroup (FillTexture n) Source | |
Default (FillTexture n) Source | |
Typeable * n => AttributeClass (FillTexture n) Source | |
Floating n => Transformable (FillTexture n) Source | |
type V (FillTexture n) = V2 Source | |
type N (FillTexture n) = n Source |
_FillTexture :: Iso' (FillTexture n) (Recommend (Texture n)) Source
getFillTexture :: FillTexture n -> Texture n Source
mkFillTexture :: Texture n -> FillTexture n Source
_fillTexture :: (Typeable n, Floating n) => Lens' (Style V2 n) (Texture n) Source
Commit a fill texture in a style. This is not a valid setter
because it doesn't abide the functor law (see committed
).
_fillTextureR :: (Typeable n, Floating n) => Lens' (Style V2 n) (Recommend (Texture n)) Source
Lens onto the Recommend
of a fill texture in a style.
Fill color
fillColor :: (InSpace V2 n a, Color c, Typeable n, Floating n, 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 :: (InSpace V2 n a, Floating n, Typeable n, HasStyle a) => AlphaColour Double -> a -> a Source
A synonym for fillColor
, specialized to
(i.e. colors with transparency). See comment after AlphaColour
DoublefillColor
about backends.
recommendFillColor :: (InSpace V2 n a, Color c, Typeable n, Floating n, HasStyle a) => c -> a -> a Source
Compilation utilities
splitTextureFills :: forall b v n a. (Typeable v, Typeable n) => RTree b v n a -> RTree b v n 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.