monoid-extras-0.6: Various extra monoid-related definitions and utilities
Copyright(c) 2012-2015 diagrams-core team (see LICENSE)
LicenseBSD-style (see LICENSE)
Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Monoid.Cut

Description

The Cut monoid transformer introduces "cut points" such that all values between any two cut points are thrown away. That is,

a b c | d e | f g h i | j k  ==  a b c | j k
Synopsis

Documentation

data Cut m Source #

A value of type Cut m is either a single m, or a pair of m's separated by a divider. The divider represents a "cut point".

Cut is similar to Data.Monoid.Split, but split keeps only the rightmost divider and accumulates all values, whereas cut always keeps the leftmost and rightmost divider, coalescing them into one and throwing away all the information in between.

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.

Constructors

Uncut m 
m :||: m infix 5 

Instances

Instances details
Functor Cut Source # 
Instance details

Defined in Data.Monoid.Cut

Methods

fmap :: (a -> b) -> Cut a -> Cut b #

(<$) :: a -> Cut b -> Cut a #

Foldable Cut Source # 
Instance details

Defined in Data.Monoid.Cut

Methods

fold :: Monoid m => Cut m -> m #

foldMap :: Monoid m => (a -> m) -> Cut a -> m #

foldMap' :: Monoid m => (a -> m) -> Cut a -> m #

foldr :: (a -> b -> b) -> b -> Cut a -> b #

foldr' :: (a -> b -> b) -> b -> Cut a -> b #

foldl :: (b -> a -> b) -> b -> Cut a -> b #

foldl' :: (b -> a -> b) -> b -> Cut a -> b #

foldr1 :: (a -> a -> a) -> Cut a -> a #

foldl1 :: (a -> a -> a) -> Cut a -> a #

toList :: Cut a -> [a] #

null :: Cut a -> Bool #

length :: Cut a -> Int #

elem :: Eq a => a -> Cut a -> Bool #

maximum :: Ord a => Cut a -> a #

minimum :: Ord a => Cut a -> a #

sum :: Num a => Cut a -> a #

product :: Num a => Cut a -> a #

Traversable Cut Source # 
Instance details

Defined in Data.Monoid.Cut

Methods

traverse :: Applicative f => (a -> f b) -> Cut a -> f (Cut b) #

sequenceA :: Applicative f => Cut (f a) -> f (Cut a) #

mapM :: Monad m => (a -> m b) -> Cut a -> m (Cut b) #

sequence :: Monad m => Cut (m a) -> m (Cut a) #

Data m => Data (Cut m) Source # 
Instance details

Defined in Data.Monoid.Cut

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Cut m -> c (Cut m) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Cut m) #

toConstr :: Cut m -> Constr #

dataTypeOf :: Cut m -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Cut m)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Cut m)) #

gmapT :: (forall b. Data b => b -> b) -> Cut m -> Cut m #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cut m -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Cut m -> r #

gmapQ :: (forall d. Data d => d -> u) -> Cut m -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Cut m -> u #

gmapM :: Monad m0 => (forall d. Data d => d -> m0 d) -> Cut m -> m0 (Cut m) #

gmapMp :: MonadPlus m0 => (forall d. Data d => d -> m0 d) -> Cut m -> m0 (Cut m) #

gmapMo :: MonadPlus m0 => (forall d. Data d => d -> m0 d) -> Cut m -> m0 (Cut m) #

Read m => Read (Cut m) Source # 
Instance details

Defined in Data.Monoid.Cut

Show m => Show (Cut m) Source # 
Instance details

Defined in Data.Monoid.Cut

Methods

showsPrec :: Int -> Cut m -> ShowS #

show :: Cut m -> String #

showList :: [Cut m] -> ShowS #

Semigroup m => Semigroup (Cut m) Source #

If m is a Semigroup, then Cut m is a semigroup which contains m as a sub-semigroup, but also contains elements of the form m1 :||: m2. When elements of m combine with such "cut" elements they are combined with the value on the corresponding side of the cut (e.g. (Uncut m1) <> (m1' :||: m2) = (m1 <> m1') :||: m2). When two "cut" elements meet, the two inside values are thrown away and only the outside values are kept.

Instance details

Defined in Data.Monoid.Cut

Methods

(<>) :: Cut m -> Cut m -> Cut m #

sconcat :: NonEmpty (Cut m) -> Cut m #

stimes :: Integral b => b -> Cut m -> Cut m #

(Semigroup m, Monoid m) => Monoid (Cut m) Source # 
Instance details

Defined in Data.Monoid.Cut

Methods

mempty :: Cut m #

mappend :: Cut m -> Cut m -> Cut m #

mconcat :: [Cut m] -> Cut m #

cut :: Monoid m => Cut m Source #

A convenient name for mempty :||: mempty, so composing with cut introduces a cut point. For example, Uncut a <> cut <> Uncut b == a :||: b.