Copyright | (c) 2011-2015 diagrams-core team (see LICENSE) |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | diagrams-discuss@googlegroups.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Sometimes we want to accumulate values from some monoid, but have the ability to introduce a "split" which separates values on either side. Only the rightmost split is kept. For example,
a b c | d e | f g h == a b c d e | f g h
In the diagrams graphics framework 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.
Documentation
A value of type Split m
is either a single m
, or a pair of
m
's separated by a divider. Single m
's combine as usual;
single m
's combine with split values by combining with the
value on the appropriate side; when two split values meet only
the rightmost split is kept, with both the values from the left
split combining with the left-hand value of the right split.
Data.Monoid.Cut is similar, but uses a different scheme for
composition. Split
uses the asymmetric constructor :|
, and
Cut
the symmetric constructor :||:
, to emphasize the inherent
asymmetry of Split
and symmetry of Cut
. Split
keeps only
the rightmost split and combines everything on the left; Cut
keeps the outermost splits and throws away everything in between.
Instances
Foldable Split Source # | |
Defined in Data.Monoid.Split fold :: Monoid m => Split m -> m # foldMap :: Monoid m => (a -> m) -> Split a -> m # foldMap' :: Monoid m => (a -> m) -> Split a -> m # foldr :: (a -> b -> b) -> b -> Split a -> b # foldr' :: (a -> b -> b) -> b -> Split a -> b # foldl :: (b -> a -> b) -> b -> Split a -> b # foldl' :: (b -> a -> b) -> b -> Split a -> b # foldr1 :: (a -> a -> a) -> Split a -> a # foldl1 :: (a -> a -> a) -> Split a -> a # elem :: Eq a => a -> Split a -> Bool # maximum :: Ord a => Split a -> a # minimum :: Ord a => Split a -> a # | |
Traversable Split Source # | |
Functor Split Source # | |
Data m => Data (Split m) Source # | |
Defined in Data.Monoid.Split gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Split m -> c (Split m) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Split m) # toConstr :: Split m -> Constr # dataTypeOf :: Split m -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Split m)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Split m)) # gmapT :: (forall b. Data b => b -> b) -> Split m -> Split m # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Split m -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Split m -> r # gmapQ :: (forall d. Data d => d -> u) -> Split m -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Split m -> u # gmapM :: Monad m0 => (forall d. Data d => d -> m0 d) -> Split m -> m0 (Split m) # gmapMp :: MonadPlus m0 => (forall d. Data d => d -> m0 d) -> Split m -> m0 (Split m) # gmapMo :: MonadPlus m0 => (forall d. Data d => d -> m0 d) -> Split m -> m0 (Split m) # | |
(Semigroup m, Monoid m) => Monoid (Split m) Source # | |
Semigroup m => Semigroup (Split m) Source # | If |
Read m => Read (Split m) Source # | |
Show m => Show (Split m) Source # | |
Eq m => Eq (Split m) Source # | |
Action m n => Action (Split m) n Source # | By default, the action of a split monoid is the same as for the underlying monoid, as if the split were removed. |
Defined in Data.Monoid.Split |