diagrams-lib-1.3: Embedded domain-specific language for declarative graphics

Copyright(c) 2013-2015 diagrams-lib team (see LICENSE)
LicenseBSD-style (see LICENSE)
Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone
LanguageHaskell2010

Diagrams.TwoD.Attributes

Contents

Description

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.

Synopsis

Textures

data Texture n Source

A Texture is either a color SC, linear gradient LG, or radial gradient RG. An object can have only one texture which is determined by the Last semigroup structure.

Constructors

SC SomeColor 
LG (LGradient n) 
RG (RGradient n) 

Instances

Floating n => Transformable (Texture n) 
Typeable (* -> *) Texture 
type V (Texture n) = V2 
type N (Texture n) = n 

solid :: Color a => a -> Texture n Source

Convert a solid colour into a texture.

_SC :: forall n. Prism' (Texture n) SomeColor Source

_AC :: Prism' (Texture n) (AlphaColour Double) Source

Prism onto an AlphaColour Double of a SC texture.

_LG :: forall n. Prism' (Texture n) (LGradient n) Source

_RG :: forall n. Prism' (Texture n) (RGradient n) Source

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)

Constructors

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

data LGradient n Source

Linear Gradient

Instances

Fractional n => Transformable (LGradient n) 
type V (LGradient n) = V2 
type N (LGradient n) = n 

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

data RGradient n Source

Radial Gradient

Instances

Fractional n => Transformable (RGradient n) 
type V (RGradient n) = V2 
type N (RGradient n) = n 

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.

rGradCenter0 :: Lens' (RGradient n) (Point V2 n) Source

The center point of the inner circle.

rGradRadius0 :: Lens' (RGradient n) n Source

The radius of the inner cirlce in local coordinates.

rGradCenter1 :: Lens' (RGradient n) (Point V2 n) Source

The center of the outer circle.

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.

Constructors

LineTexture (Last (Texture n)) 

lineTexture :: (InSpace V2 n a, Typeable n, Floating n, HasStyle a) => Texture n -> a -> a 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.

lc :: (InSpace V2 n a, Typeable n, Floating n, HasStyle a) => Colour Double -> a -> a Source

A synonym for lineColor, specialized to Colour Double (i.e. opaque colors). See comment in lineColor about backends.

lcA :: (InSpace V2 n a, Typeable n, Floating n, HasStyle a) => AlphaColour Double -> a -> a Source

A synonym for lineColor, specialized to AlphaColour Double (i.e. colors with transparency). See comment in lineColor 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'.

Constructors

FillTexture (Recommend (Last (Texture n))) 

fillTexture :: (InSpace V2 n a, Typeable n, Floating n, HasStyle a) => Texture n -> a -> a 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.

fc :: (InSpace V2 n a, Floating n, Typeable n, HasStyle a) => Colour Double -> a -> a Source

A synonym for fillColor, specialized to Colour Double (i.e. opaque colors). See comment after fillColor about backends.

fcA :: (InSpace V2 n a, Floating n, Typeable n, HasStyle a) => AlphaColour Double -> a -> a Source

A synonym for fillColor, specialized to AlphaColour Double (i.e. colors with transparency). See comment after fillColor about backends.

recommendFillColor :: (InSpace V2 n a, Color c, Typeable n, Floating n, HasStyle a) => c -> a -> a Source

Set a "recommended" fill color, to be used only if no explicit calls to fillColor (or fc, or fcA) are used. See comment after fillColor about backends.

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.