diagrams-core-1.1.0.3: Core libraries for diagrams EDSL

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

Diagrams.Core.Style

Contents

Description

A definition of styles for diagrams as extensible, heterogeneous collections of attributes.

Synopsis

Attributes

An attribute is anything that determines some aspect of a diagram's rendering. The standard diagrams library defines several standard attributes (line color, line width, fill color, etc.) but additional attributes may easily be created. Additionally, a given backend need not handle (or even know about) attributes used in diagrams it renders.

The attribute code is inspired by xmonad's Message type, which was in turn based on ideas in:

Simon Marlow. An Extensible Dynamically-Typed Hierarchy of Exceptions. Proceedings of the 2006 ACM SIGPLAN workshop on Haskell. http://research.microsoft.com/apps/pubs/default.aspx?id=67968.

class (Typeable a, Semigroup a) => AttributeClass a Source

Every attribute must be an instance of AttributeClass, which simply guarantees Typeable and Semigroup constraints. The Semigroup instance for an attribute determines how it will combine with other attributes of the same type.

data Attribute v :: * where Source

An existential wrapper type to hold attributes. Some attributes are affected by transformations and some are not.

Constructors

Attribute :: AttributeClass a => a -> Attribute v 
TAttribute :: (AttributeClass a, Transformable a, V a ~ v) => a -> Attribute v 

Instances

Semigroup (Attribute v)

Attributes form a semigroup, where the semigroup operation simply returns the right-hand attribute when the types do not match, and otherwise uses the semigroup operation specific to the (matching) types.

HasLinearMap v => Transformable (Attribute v) 
type V (Attribute v) = v 

mkAttr :: AttributeClass a => a -> Attribute v Source

Wrap up an attribute.

mkTAttr :: (AttributeClass a, Transformable a, V a ~ v) => a -> Attribute v Source

Wrap up a transformable attribute.

unwrapAttr :: AttributeClass a => Attribute v -> Maybe a Source

Unwrap an unknown Attribute type, performing a dynamic (but safe) check on the type of the result. If the required type matches the type of the attribute, the attribute value is returned wrapped in Just; if the types do not match, Nothing is returned.

applyAttr :: (AttributeClass a, HasStyle d) => a -> d -> d Source

Apply an attribute to an instance of HasStyle (such as a diagram or a style). If the object already has an attribute of the same type, the new attribute is combined on the left with the existing attribute, according to their semigroup structure.

applyTAttr :: (AttributeClass a, Transformable a, V a ~ V d, HasStyle d) => a -> d -> d Source

Apply a transformable attribute to an instance of HasStyle (such as a diagram or a style). If the object already has an attribute of the same type, the new attribute is combined on the left with the existing attribute, according to their semigroup structure.

Styles

A Style is a heterogeneous collection of attributes, containing at most one attribute of any given type. This is also based on ideas stolen from xmonad, specifically xmonad's implementation of user-extensible state.

newtype Style v Source

A Style is a heterogeneous collection of attributes, containing at most one attribute of any given type.

Constructors

Style (Map String (Attribute v)) 

Instances

Monoid (Style v)

The empty style contains no attributes; composition of styles is a union of attributes; if the two styles have attributes of the same type they are combined according to their semigroup structure.

Semigroup (Style v) 
Wrapped (Style v) 
HasLinearMap v => Transformable (Style v) 
HasStyle (Style v) 
Action (Style v) m

Styles have no action on other monoids.

Rewrapped (Style v) (Style v') 
type Unwrapped (Style v) = Map String (Attribute v) 
type V (Style v) = v 

attrToStyle :: forall a v. AttributeClass a => a -> Style v Source

Create a style from a single attribute.

tAttrToStyle :: forall a v. (AttributeClass a, Transformable a, V a ~ v) => a -> Style v Source

Create a style from a single transformable attribute.

getAttr :: forall a v. AttributeClass a => Style v -> Maybe a Source

Extract an attribute from a style of a particular type. If the style contains an attribute of the requested type, it will be returned wrapped in Just; otherwise, Nothing is returned.

setAttr :: forall a v. AttributeClass a => a -> Style v -> Style v Source

Add a new attribute to a style, or replace the old attribute of the same type if one exists.

addAttr :: AttributeClass a => a -> Style v -> Style v Source

Attempt to add a new attribute to a style, but if an attribute of the same type already exists, do not replace it.

combineAttr :: AttributeClass a => a -> Style v -> Style v Source

Add a new attribute to a style that does not already contain an attribute of this type, or combine it on the left with an existing attribute.

class HasStyle a where Source

Type class for things which have a style.

Methods

applyStyle :: Style (V a) -> a -> a Source

Apply a style by combining it (on the left) with the existing style.

Instances

HasStyle a => HasStyle [a] 
(HasStyle a, Ord a) => HasStyle (Set a) 
HasStyle (Style v) 
HasStyle b => HasStyle (a -> b) 
(HasStyle a, HasStyle b, (~) * (V a) (V b)) => HasStyle (a, b) 
HasStyle a => HasStyle (Map k a) 
(HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Semigroup m) => HasStyle (QDiagram b v m)