diagrams-core-0.1.1: Core libraries for diagrams EDSL

Maintainerdiagrams-discuss@googlegroups.com

Graphics.Rendering.Diagrams.Monoids

Contents

Description

Various monoid-related definitions (monoid actions, split monoids, applicative monoids) used in the core diagrams library.

Synopsis

Monoid actions

class Action m s whereSource

Type class for monoid actions, where monoidal values of type m "act" on values of another type s. Instances are required to satisfy the laws

  • act mempty = id
  • act (m1 `mappend` m2) = act m1 . act m2

Additionally, if the type s has any algebraic structure, act m should be a homomorphism. For example, if s is also a monoid we should have act m mempty = mempty and act m (s1 `mappend` s2) = (act m s1) `mappend` (act m s2).

By default, act = const id, so for a monoidal type M which should have no action on anything, it suffices to write

 instance Action M s

with no method implementations.

Methods

act :: m -> s -> sSource

Convert a monoidal value of type m to an action on s values.

Instances

Action Style m

Styles have no action on other monoids.

Action Nil l 
Action Name a

Names don't act on anything else.

Action Name (NameMap v)

A name acts on a name map by qualifying every name in it.

Action m n => Action (Split m) n

By default, the action of a split monoid is the same as for the underlying monoid, as if the split were removed.

Monoid a => Action (SM a) Nil 
(v ~ V a, HasLinearMap v, Transformable a) => Action (Transformation v) a

Transformations can act on transformable things.

(Action a a', Action (SM a) l) => Action (SM a) (::: a' l) 
(Action m n, Foldable f, Functor f, Monoid n) => Action (AM f m) n

An applicative monoid acts on a value of a monoidal type by having each element in the structure act on the value independently, and then folding the resulting structure.

(Monoid a, Action (SM a) l2, Action l1 l2) => Action (::: a l1) l2 

Split monoids

Sometimes we want to accumulate values from some monoid, but have the ability to introduce a "split" which separates values on either side. For example, this is used when accumulating transformations to be applied to primitive diagrams: the freeze operation introduces a split, since only transformations occurring outside the freeze should be applied to attributes.

data Split m Source

A value of type Split m is either a single m, or a pair of m's separated by a divider.

Constructors

M m 
m :| m 

Instances

Monoid m => Monoid (Split m)

If m is a Monoid, then Split m is a monoid which combines values on either side of a split, keeping only the rightmost split.

Action m n => Action (Split m) n

By default, the action of a split monoid is the same as for the underlying monoid, as if the split were removed.

split :: Monoid m => Split mSource

A convenient name for mempty :| mempty, so a <> split <> b == a :| b.

Applicative monoids

newtype AM f m Source

A wrapper for an Applicative structure containing a monoid. Such structures have a Monoid instance based on "idiomatic" application of mappend within the Applicative context. instance Monoid m => Monoid (e -> m) is one well-known special case. (However, the standard Monoid instance for Maybe is not an instance of this pattern; nor is the standard instance for lists.)

Constructors

AM (f m) 

Instances

Functor f => Functor (AM f) 
Applicative f => Applicative (AM f) 
(Applicative f, Monoid m) => Monoid (AM f m)

f1 `mappend` f2 is defined as mappend <$> f1 <*> f2.

(Action m n, Foldable f, Functor f, Monoid n) => Action (AM f m) n

An applicative monoid acts on a value of a monoidal type by having each element in the structure act on the value independently, and then folding the resulting structure.

inAM2 :: (f m -> f m -> f m) -> AM f m -> AM f m -> AM f mSource

Apply a binary function inside an AM newtype wrapper.