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

Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone

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 attriubtes 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

Width

data LineWidth Source

Line widths specified on child nodes always override line widths specified at parent nodes.

lineWidth :: (HasStyle a, V a ~ R2) => Measure R2 -> a -> aSource

Set the line (stroke) width.

lineWidthA :: (HasStyle a, V a ~ R2) => LineWidth -> a -> aSource

Apply a LineWidth attribute.

lw :: (HasStyle a, V a ~ R2) => Measure R2 -> a -> aSource

Default for lineWidth.

lwN :: (HasStyle a, V a ~ R2) => Double -> a -> aSource

A convenient synonym for 'lineWidth (Normalized w)'.

lwO :: (HasStyle a, V a ~ R2) => Double -> a -> aSource

A convenient synonym for 'lineWidth (Output w)'.

lwL :: (HasStyle a, V a ~ R2) => Double -> a -> aSource

A convenient sysnonym for 'lineWidth (Local w)'.

lwG :: (HasStyle a, V a ~ R2) => Double -> a -> aSource

A convenient synonym for 'lineWidth (Global w)'.

ultraThin :: Measure R2Source

Standard Measures.

veryThin :: Measure R2Source

Standard Measures.

thin :: Measure R2Source

Standard Measures.

medium :: Measure R2Source

Standard Measures.

thick :: Measure R2Source

Standard Measures.

veryThick :: Measure R2Source

Standard Measures.

ultraThick :: Measure R2Source

Standard Measures.

none :: Measure R2Source

Standard Measures.

tiny :: Measure R2Source

Standard Measures.

verySmall :: Measure R2Source

Standard Measures.

small :: Measure R2Source

Standard Measures.

normal :: Measure R2Source

Standard Measures.

large :: Measure R2Source

Standard Measures.

veryLarge :: Measure R2Source

Standard Measures.

huge :: Measure R2Source

Standard Measures.

Dashing

data Dashing Source

Create lines that are dashing... er, dashed.

Constructors

Dashing [Measure R2] (Measure R2) 

dashingSource

Arguments

:: (HasStyle a, V a ~ R2) 
=> [Measure R2]

A list specifying alternate lengths of on and off portions of the stroke. The empty list indicates no dashing.

-> Measure R2

An offset into the dash pattern at which the stroke should start.

-> a 
-> a 

Set the line dashing style.

dashingN :: (HasStyle a, V a ~ R2) => [Double] -> Double -> a -> aSource

A convenient synonym for 'dashing (Normalized w)'.

dashingO :: (HasStyle a, V a ~ R2) => [Double] -> Double -> a -> aSource

A convenient synonym for 'dashing (Output w)'.

dashingL :: (HasStyle a, V a ~ R2) => [Double] -> Double -> a -> aSource

A convenient sysnonym for 'dashing (Local w)'.

dashingG :: (HasStyle a, V a ~ R2) => [Double] -> Double -> a -> aSource

A convenient synonym for 'dashing (Global w)'.

Textures

data Texture 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.

Instances

solid :: Color a => a -> TextureSource

Convert a solid colour into a texture.

defaultLG :: TextureSource

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 :: TextureSource

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 Source

A gradient stop contains a color and fraction (usually between 0 and 1)

stopColor :: Lens' GradientStop SomeColorSource

A color for the stop.

stopFraction :: Lens' GradientStop DoubleSource

The fraction for stop.

mkStops :: [(Colour Double, Double, Double)] -> [GradientStop]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 :: (HasStyle a, V a ~ R2) => LGradient -> a -> aSource

Apply a linear gradient.

lineRGradient :: (HasStyle a, V a ~ R2) => RGradient -> a -> aSource

Apply a radial gradient.

Linear Gradients

lGradStops :: Lens' LGradient [GradientStop]Source

A list of stops (colors and fractions).

lGradTrans :: Lens' LGradient T2Source

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 P2Source

The starting point for the first gradient stop. The coordinates are in Local units and the default is (-0.5, 0).

lGradEnd :: Lens' LGradient P2Source

The ending point for the last gradient stop.The coordinates are in Local units and the default is (0.5, 0).

lGradSpreadMethod :: Lens' LGradient SpreadMethodSource

For setting the spread method.

mkLinearGradient :: [GradientStop] -> P2 -> P2 -> SpreadMethod -> TextureSource

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

rGradStops :: Lens' RGradient [GradientStop]Source

A list of stops (colors and fractions).

rGradTrans :: Lens' RGradient T2Source

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 P2Source

The center point of the inner circle.

rGradRadius0 :: Lens' RGradient DoubleSource

The radius of the inner cirlce in Local coordinates.

rGradCenter1 :: Lens' RGradient P2Source

The center of the outer circle.

rGradRadius1 :: Lens' RGradient DoubleSource

The radius of the outer circle in Local coordinates.

rGradSpreadMethod :: Lens' RGradient SpreadMethodSource

For setting the spread method.

mkRadialGradient :: [GradientStop] -> P2 -> Double -> P2 -> Double -> SpreadMethod -> TextureSource

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 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) 

lineTexture :: (HasStyle a, V a ~ R2) => Texture -> a -> aSource

lineTextureA :: (HasStyle a, V a ~ R2) => LineTexture -> a -> aSource

Line color

lineColor :: (Color c, HasStyle a, V a ~ R2) => c -> a -> aSource

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 :: (HasStyle a, V a ~ R2) => Colour Double -> a -> aSource

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

lcA :: (HasStyle a, V a ~ R2) => AlphaColour Double -> a -> aSource

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

Fill texture

newtype FillTexture 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)) 

fillTexture :: (HasStyle a, V a ~ R2) => Texture -> a -> aSource

Fill color

fillColor :: (Color c, HasStyle a, V a ~ R2) => c -> a -> aSource

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 :: (HasStyle a, V a ~ R2) => Colour Double -> a -> aSource

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

fcA :: (HasStyle a, V a ~ R2) => AlphaColour Double -> a -> aSource

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

recommendFillColor :: (Color c, HasStyle a, V a ~ R2) => c -> a -> aSource

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 a. Typeable v => RTree b v a -> RTree b v aSource

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.