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 |
A monoid transformer that allows deleting information from a concatenation of monoidal values.
Documentation
If m
is a Monoid
, then Deletable m
(intuitively speaking)
adds two distinguished new elements [
and ]
, such that an
occurrence of [ "deletes" everything from it to the next ]. For
example,
abc[def]gh == abcgh
This is all you really need to know to use Deletable m
values; to understand the actual implementation, read on.
To properly deal with nesting and associativity we need to be
able to assign meanings to things like [[
, ][
, and so on. (We
cannot just define, say, [[ == [
, since then ([[)] == [] ==
id
but [([]) == [id == [
.) Formally, elements of Deletable
m
are triples of the form (r, m, l) representing words ]^r m
[^l
. When combining two triples (r1, m1, l1) and (r2, m2, l2)
there are three cases:
- If l1 == r2 then the [s from the left and ]s from the right exactly cancel, and we are left with (r1, m1 <> m2, l2).
- If l1 < r2 then all of the [s cancel with some of the ]s, but m1 is still inside the remaining ]s and is deleted, yielding (r1 + r2 - l1, m2, l2)
- The remaining case is symmetric with the second.
Instances
Functor Deletable Source # | |
Foldable Deletable Source # | |
Defined in Data.Monoid.Deletable fold :: Monoid m => Deletable m -> m # foldMap :: Monoid m => (a -> m) -> Deletable a -> m # foldMap' :: Monoid m => (a -> m) -> Deletable a -> m # foldr :: (a -> b -> b) -> b -> Deletable a -> b # foldr' :: (a -> b -> b) -> b -> Deletable a -> b # foldl :: (b -> a -> b) -> b -> Deletable a -> b # foldl' :: (b -> a -> b) -> b -> Deletable a -> b # foldr1 :: (a -> a -> a) -> Deletable a -> a # foldl1 :: (a -> a -> a) -> Deletable a -> a # toList :: Deletable a -> [a] # length :: Deletable a -> Int # elem :: Eq a => a -> Deletable a -> Bool # maximum :: Ord a => Deletable a -> a # minimum :: Ord a => Deletable a -> a # | |
Traversable Deletable Source # | |
Data m => Data (Deletable m) Source # | |
Defined in Data.Monoid.Deletable gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Deletable m -> c (Deletable m) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Deletable m) # toConstr :: Deletable m -> Constr # dataTypeOf :: Deletable m -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Deletable m)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Deletable m)) # gmapT :: (forall b. Data b => b -> b) -> Deletable m -> Deletable m # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Deletable m -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Deletable m -> r # gmapQ :: (forall d. Data d => d -> u) -> Deletable m -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Deletable m -> u # gmapM :: Monad m0 => (forall d. Data d => d -> m0 d) -> Deletable m -> m0 (Deletable m) # gmapMp :: MonadPlus m0 => (forall d. Data d => d -> m0 d) -> Deletable m -> m0 (Deletable m) # gmapMo :: MonadPlus m0 => (forall d. Data d => d -> m0 d) -> Deletable m -> m0 (Deletable m) # | |
Read m => Read (Deletable m) Source # | |
Show m => Show (Deletable m) Source # | |
Semigroup m => Semigroup (Deletable m) Source # | |
(Semigroup m, Monoid m) => Monoid (Deletable m) Source # | |
toDeletable :: m -> Deletable m Source #
Inject a value into a Deletable
wrapper. Satisfies the
property
unDelete . toDeletable === id