Copyright | (c) 2011 diagrams-core team (see LICENSE) |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | diagrams-discuss@googlegroups.com |
Safe Haskell | None |
Language | Haskell2010 |
A definition of styles for diagrams as extensible, heterogeneous collections of attributes.
- class (Typeable a, Semigroup a) => AttributeClass a
- data Attribute v :: * where
- Attribute :: AttributeClass a => a -> Attribute v
- TAttribute :: (AttributeClass a, Transformable a, V a ~ v) => a -> Attribute v
- GTAttribute :: (AttributeClass a, Data a, Transformable a, V a ~ v) => a -> Attribute v
- mkAttr :: AttributeClass a => a -> Attribute v
- mkTAttr :: (AttributeClass a, Transformable a, V a ~ v) => a -> Attribute v
- mkGTAttr :: (AttributeClass a, Data a, Transformable a, V a ~ v) => a -> Attribute v
- unwrapAttr :: AttributeClass a => Attribute v -> Maybe a
- applyAttr :: (AttributeClass a, HasStyle d) => a -> d -> d
- applyTAttr :: (AttributeClass a, Transformable a, V a ~ V d, HasStyle d) => a -> d -> d
- applyGTAttr :: (AttributeClass a, Data a, Transformable a, V a ~ V d, HasStyle d) => a -> d -> d
- newtype Style v = Style (Map String (Attribute v))
- attrToStyle :: forall a v. AttributeClass a => a -> Style v
- tAttrToStyle :: forall a v. (AttributeClass a, Transformable a, V a ~ v) => a -> Style v
- gtAttrToStyle :: forall a v. (AttributeClass a, Data a, Transformable a, V a ~ v) => a -> Style v
- getAttr :: forall a v. AttributeClass a => Style v -> Maybe a
- setAttr :: forall a v. AttributeClass a => a -> Style v -> Style v
- addAttr :: AttributeClass a => a -> Style v -> Style v
- combineAttr :: AttributeClass a => a -> Style v -> Style v
- gmapAttrs :: forall v a. Typeable a => (a -> a) -> Style v -> Style v
- class HasStyle a where
- applyStyle :: Style (V a) -> a -> a
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
data Attribute v :: * where Source
An existential wrapper type to hold attributes. Some attributes are simply inert/static; some are affected by transformations; and some are affected by transformations and can be modified generically.
Attribute :: AttributeClass a => a -> Attribute v | |
TAttribute :: (AttributeClass a, Transformable a, V a ~ v) => a -> Attribute v | |
GTAttribute :: (AttributeClass a, Data a, Transformable a, V a ~ v) => a -> Attribute v |
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.
mkGTAttr :: (AttributeClass a, Data a, Transformable a, V a ~ v) => a -> Attribute v Source
Wrap up a transformable and generic 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.
applyGTAttr :: (AttributeClass a, Data a, Transformable a, V a ~ V d, HasStyle d) => a -> d -> d Source
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.
A Style
is a heterogeneous collection of attributes, containing
at most one attribute of any given type.
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.
gtAttrToStyle :: forall a v. (AttributeClass a, Data a, Transformable a, V a ~ v) => a -> Style v Source
Create a style from a single transformable, generic 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.
gmapAttrs :: forall v a. Typeable a => (a -> a) -> Style v -> Style v Source
Map generically over all generic attributes in a style, applying
the given function to any values with the given type, even deeply
nested ones. Note that only attributes wrapped in GTAttribute
are affected.
Type class for things which have a style.
applyStyle :: Style (V a) -> a -> a Source
Apply a style by combining it (on the left) with the existing style.
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) |