| Copyright | (c) Andy Gill 2001 (c) Oregon Graduate Institute of Science and Technology 2001 | 
|---|---|
| License | BSD-style (see the file libraries/base/LICENSE) | 
| Maintainer | libraries@haskell.org | 
| Stability | experimental | 
| Portability | portable | 
| Safe Haskell | Trustworthy | 
| Language | Haskell2010 | 
Data.Monoid
Description
A type a is a Monoid if it provides an associative function (<>)
 that lets you combine any two values of type a into one, and a neutral
 element (mempty) such that
a <> mempty == mempty <> a == a
A Monoid is a Semigroup with the added requirement of a neutral element.
 Thus any Monoid is a Semigroup, but not the other way around.
Examples
The Sum monoid is defined by the numerical addition operator and `0` as neutral element:
>>>mempty :: Sum IntSum 0>>>Sum 1 <> Sum 2 <> Sum 3 <> Sum 4 :: Sum IntSum {getSum = 10}
We can combine multiple values in a list into a single value using the mconcat function.
 Note that we have to specify the type here since Int is a monoid under several different
 operations:
>>>mconcat [1,2,3,4] :: Sum IntSum {getSum = 10}>>>mconcat [] :: Sum IntSum {getSum = 0}
Another valid monoid instance of Int is Product It is defined by multiplication
 and `1` as neutral element:
>>>Product 1 <> Product 2 <> Product 3 <> Product 4 :: Product IntProduct {getProduct = 24}>>>mconcat [1,2,3,4] :: Product IntProduct {getProduct = 24}>>>mconcat [] :: Product IntProduct {getProduct = 1}
Synopsis
- class Semigroup a => Monoid a where
- (<>) :: Semigroup a => a -> a -> a
- newtype Dual a = Dual {- getDual :: a
 
- newtype Endo a = Endo {- appEndo :: a -> a
 
- newtype All = All {}
- newtype Any = Any {}
- newtype Sum a = Sum {- getSum :: a
 
- newtype Product a = Product {- getProduct :: a
 
- newtype First a = First {}
- newtype Last a = Last {}
- newtype Alt f a = Alt {- getAlt :: f a
 
- newtype Ap f a = Ap {- getAp :: f a
 
Monoid typeclass
class Semigroup a => Monoid a where Source #
The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following:
- Right identity
- x- <>- mempty= x
- Left identity
- mempty- <>x = x
- Associativity
- x(- <>(y- <>z) = (x- <>y)- <>z- Semigrouplaw)
- Concatenation
- mconcat=- foldr(- <>)- mempty
The method names refer to the monoid of lists under concatenation, but there are many other instances.
Some types can be viewed as a monoid in more than one way,
 e.g. both addition and multiplication on numbers.
 In such cases we often define newtypes and make those instances
 of Monoid, e.g. Sum and Product.
NOTE: Semigroup is a superclass of Monoid since base-4.11.0.0.
Minimal complete definition
Methods
Identity of mappend
>>>"Hello world" <> mempty"Hello world"
mappend :: a -> a -> a Source #
An associative operation
NOTE: This method is redundant and has the default
 implementation mappend = (<>)mappend is a synonym for
 (<>), it is expected that the two functions are defined the same
 way. In a future GHC release mappend will be removed from Monoid.
Fold a list using the monoid.
For most types, the default definition for mconcat will be
 used, but the function is included in the class definition so
 that an optimized version can be provided for specific types.
>>>mconcat ["Hello", " ", "Haskell", "!"]"Hello Haskell!"
Instances
| Monoid Ordering # | Since: base-2.1 | 
| Monoid () # | Since: base-2.1 | 
| Monoid Any # | Since: base-2.1 | 
| Monoid All # | Since: base-2.1 | 
| Monoid Lifetime # | 
 Since: base-4.8.0.0 | 
| Monoid Event # | Since: base-4.4.0.0 | 
| Monoid [a] # | Since: base-2.1 | 
| Semigroup a => Monoid (Maybe a) # | Lift a semigroup into  Since 4.11.0: constraint on inner  Since: base-2.1 | 
| Monoid a => Monoid (IO a) # | Since: base-4.9.0.0 | 
| Monoid p => Monoid (Par1 p) # | Since: base-4.12.0.0 | 
| Monoid a => Monoid (Down a) # | Since: base-4.11.0.0 | 
| Num a => Monoid (Product a) # | Since: base-2.1 | 
| Num a => Monoid (Sum a) # | Since: base-2.1 | 
| Monoid (Endo a) # | Since: base-2.1 | 
| Monoid a => Monoid (Dual a) # | Since: base-2.1 | 
| Monoid (Last a) # | Since: base-2.1 | 
| Monoid (First a) # | Since: base-2.1 | 
| Monoid a => Monoid (Identity a) # | Since: base-4.9.0.0 | 
| Semigroup a => Monoid (Option a) # | Since: base-4.9.0.0 | 
| Monoid m => Monoid (WrappedMonoid m) # | Since: base-4.9.0.0 | 
| Defined in Data.Semigroup Methods mempty :: WrappedMonoid m Source # mappend :: WrappedMonoid m -> WrappedMonoid m -> WrappedMonoid m Source # mconcat :: [WrappedMonoid m] -> WrappedMonoid m Source # | |
| (Ord a, Bounded a) => Monoid (Max a) # | Since: base-4.9.0.0 | 
| (Ord a, Bounded a) => Monoid (Min a) # | Since: base-4.9.0.0 | 
| Monoid (Equivalence a) # | |
| Defined in Data.Functor.Contravariant Methods mempty :: Equivalence a Source # mappend :: Equivalence a -> Equivalence a -> Equivalence a Source # mconcat :: [Equivalence a] -> Equivalence a Source # | |
| Monoid (Comparison a) # | |
| Defined in Data.Functor.Contravariant Methods mempty :: Comparison a Source # mappend :: Comparison a -> Comparison a -> Comparison a Source # mconcat :: [Comparison a] -> Comparison a Source # | |
| Monoid (Predicate a) # | |
| Monoid b => Monoid (a -> b) # | Since: base-2.1 | 
| Monoid (U1 p) # | Since: base-4.12.0.0 | 
| (Monoid a, Monoid b) => Monoid (a, b) # | Since: base-2.1 | 
| Monoid a => Monoid (ST s a) # | Since: base-4.11.0.0 | 
| Monoid (Proxy s) # | Since: base-4.7.0.0 | 
| Monoid a => Monoid (Op a b) # | |
| Monoid (f p) => Monoid (Rec1 f p) # | Since: base-4.12.0.0 | 
| (Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) # | Since: base-2.1 | 
| Alternative f => Monoid (Alt f a) # | Since: base-4.8.0.0 | 
| (Applicative f, Monoid a) => Monoid (Ap f a) # | Since: base-4.12.0.0 | 
| Monoid a => Monoid (Const a b) # | Since: base-4.9.0.0 | 
| Monoid c => Monoid (K1 i c p) # | Since: base-4.12.0.0 | 
| (Monoid (f p), Monoid (g p)) => Monoid ((f :*: g) p) # | Since: base-4.12.0.0 | 
| (Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d) # | Since: base-2.1 | 
| Monoid (f p) => Monoid (M1 i c f p) # | Since: base-4.12.0.0 | 
| Monoid (f (g p)) => Monoid ((f :.: g) p) # | Since: base-4.12.0.0 | 
| (Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e) # | Since: base-2.1 | 
(<>) :: Semigroup a => a -> a -> a infixr 6 Source #
An associative operation.
>>>[1,2,3] <> [4,5,6][1,2,3,4,5,6]
The dual of a Monoid, obtained by swapping the arguments of mappend.
>>>getDual (mappend (Dual "Hello") (Dual "World"))"WorldHello"
Instances
| Monad Dual # | Since: base-4.8.0.0 | 
| Functor Dual # | Since: base-4.8.0.0 | 
| MonadFix Dual # | Since: base-4.8.0.0 | 
| Applicative Dual # | Since: base-4.8.0.0 | 
| Foldable Dual # | Since: base-4.8.0.0 | 
| Defined in Data.Foldable Methods fold :: Monoid m => Dual m -> m Source # foldMap :: Monoid m => (a -> m) -> Dual a -> m Source # foldMap' :: Monoid m => (a -> m) -> Dual a -> m Source # foldr :: (a -> b -> b) -> b -> Dual a -> b Source # foldr' :: (a -> b -> b) -> b -> Dual a -> b Source # foldl :: (b -> a -> b) -> b -> Dual a -> b Source # foldl' :: (b -> a -> b) -> b -> Dual a -> b Source # foldr1 :: (a -> a -> a) -> Dual a -> a Source # foldl1 :: (a -> a -> a) -> Dual a -> a Source # toList :: Dual a -> [a] Source # null :: Dual a -> Bool Source # length :: Dual a -> Int Source # elem :: Eq a => a -> Dual a -> Bool Source # maximum :: Ord a => Dual a -> a Source # minimum :: Ord a => Dual a -> a Source # | |
| Traversable Dual # | Since: base-4.8.0.0 | 
| MonadZip Dual # | Since: base-4.8.0.0 | 
| Bounded a => Bounded (Dual a) # | Since: base-2.1 | 
| Eq a => Eq (Dual a) # | Since: base-2.1 | 
| Data a => Data (Dual a) # | Since: base-4.8.0.0 | 
| Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Dual a -> c (Dual a) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Dual a) Source # toConstr :: Dual a -> Constr Source # dataTypeOf :: Dual a -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Dual a)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Dual a)) Source # gmapT :: (forall b. Data b => b -> b) -> Dual a -> Dual a Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Dual a -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Dual a -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Dual a -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Dual a -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Dual a -> m (Dual a) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Dual a -> m (Dual a) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Dual a -> m (Dual a) Source # | |
| Ord a => Ord (Dual a) # | Since: base-2.1 | 
| Read a => Read (Dual a) # | Since: base-2.1 | 
| Show a => Show (Dual a) # | Since: base-2.1 | 
| Generic (Dual a) # | Since: base-4.7.0.0 | 
| Semigroup a => Semigroup (Dual a) # | Since: base-4.9.0.0 | 
| Monoid a => Monoid (Dual a) # | Since: base-2.1 | 
| Generic1 Dual # | Since: base-4.7.0.0 | 
| type Rep (Dual a) # | |
| Defined in Data.Semigroup.Internal | |
| type Rep1 Dual # | |
| Defined in Data.Semigroup.Internal | |
The monoid of endomorphisms under composition.
>>>let computation = Endo ("Hello, " ++) <> Endo (++ "!")>>>appEndo computation "Haskell""Hello, Haskell!"
Bool wrappers
Boolean monoid under conjunction (&&).
>>>getAll (All True <> mempty <> All False)False
>>>getAll (mconcat (map (\x -> All (even x)) [2,4,6,7,8]))False
Instances
| Bounded All # | Since: base-2.1 | 
| Eq All # | Since: base-2.1 | 
| Data All # | Since: base-4.8.0.0 | 
| Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> All -> c All Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c All Source # toConstr :: All -> Constr Source # dataTypeOf :: All -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c All) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c All) Source # gmapT :: (forall b. Data b => b -> b) -> All -> All Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> All -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> All -> r Source # gmapQ :: (forall d. Data d => d -> u) -> All -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> All -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> All -> m All Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> All -> m All Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> All -> m All Source # | |
| Ord All # | Since: base-2.1 | 
| Read All # | Since: base-2.1 | 
| Show All # | Since: base-2.1 | 
| Generic All # | Since: base-4.7.0.0 | 
| Semigroup All # | Since: base-4.9.0.0 | 
| Monoid All # | Since: base-2.1 | 
| type Rep All # | |
| Defined in Data.Semigroup.Internal | |
Boolean monoid under disjunction (||).
>>>getAny (Any True <> mempty <> Any False)True
>>>getAny (mconcat (map (\x -> Any (even x)) [2,4,6,7,8]))True
Instances
| Bounded Any # | Since: base-2.1 | 
| Eq Any # | Since: base-2.1 | 
| Data Any # | Since: base-4.8.0.0 | 
| Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Any -> c Any Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Any Source # toConstr :: Any -> Constr Source # dataTypeOf :: Any -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Any) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Any) Source # gmapT :: (forall b. Data b => b -> b) -> Any -> Any Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Any -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Any -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Any -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Any -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Any -> m Any Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Any -> m Any Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Any -> m Any Source # | |
| Ord Any # | Since: base-2.1 | 
| Read Any # | Since: base-2.1 | 
| Show Any # | Since: base-2.1 | 
| Generic Any # | Since: base-4.7.0.0 | 
| Semigroup Any # | Since: base-4.9.0.0 | 
| Monoid Any # | Since: base-2.1 | 
| type Rep Any # | |
| Defined in Data.Semigroup.Internal | |
Num wrappers
Monoid under addition.
>>>getSum (Sum 1 <> Sum 2 <> mempty)3
Instances
| Monad Sum # | Since: base-4.8.0.0 | 
| Functor Sum # | Since: base-4.8.0.0 | 
| MonadFix Sum # | Since: base-4.8.0.0 | 
| Applicative Sum # | Since: base-4.8.0.0 | 
| Foldable Sum # | Since: base-4.8.0.0 | 
| Defined in Data.Foldable Methods fold :: Monoid m => Sum m -> m Source # foldMap :: Monoid m => (a -> m) -> Sum a -> m Source # foldMap' :: Monoid m => (a -> m) -> Sum a -> m Source # foldr :: (a -> b -> b) -> b -> Sum a -> b Source # foldr' :: (a -> b -> b) -> b -> Sum a -> b Source # foldl :: (b -> a -> b) -> b -> Sum a -> b Source # foldl' :: (b -> a -> b) -> b -> Sum a -> b Source # foldr1 :: (a -> a -> a) -> Sum a -> a Source # foldl1 :: (a -> a -> a) -> Sum a -> a Source # toList :: Sum a -> [a] Source # null :: Sum a -> Bool Source # length :: Sum a -> Int Source # elem :: Eq a => a -> Sum a -> Bool Source # maximum :: Ord a => Sum a -> a Source # minimum :: Ord a => Sum a -> a Source # | |
| Traversable Sum # | Since: base-4.8.0.0 | 
| MonadZip Sum # | Since: base-4.8.0.0 | 
| Bounded a => Bounded (Sum a) # | Since: base-2.1 | 
| Eq a => Eq (Sum a) # | Since: base-2.1 | 
| Data a => Data (Sum a) # | Since: base-4.8.0.0 | 
| Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Sum a -> c (Sum a) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Sum a) Source # toConstr :: Sum a -> Constr Source # dataTypeOf :: Sum a -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Sum a)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Sum a)) Source # gmapT :: (forall b. Data b => b -> b) -> Sum a -> Sum a Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sum a -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sum a -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Sum a -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Sum a -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Sum a -> m (Sum a) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Sum a -> m (Sum a) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Sum a -> m (Sum a) Source # | |
| Num a => Num (Sum a) # | Since: base-4.7.0.0 | 
| Ord a => Ord (Sum a) # | Since: base-2.1 | 
| Defined in Data.Semigroup.Internal | |
| Read a => Read (Sum a) # | Since: base-2.1 | 
| Show a => Show (Sum a) # | Since: base-2.1 | 
| Generic (Sum a) # | Since: base-4.7.0.0 | 
| Num a => Semigroup (Sum a) # | Since: base-4.9.0.0 | 
| Num a => Monoid (Sum a) # | Since: base-2.1 | 
| Generic1 Sum # | Since: base-4.7.0.0 | 
| type Rep (Sum a) # | |
| Defined in Data.Semigroup.Internal | |
| type Rep1 Sum # | |
| Defined in Data.Semigroup.Internal | |
Monoid under multiplication.
>>>getProduct (Product 3 <> Product 4 <> mempty)12
Constructors
| Product | |
| Fields 
 | |
Instances
| Monad Product # | Since: base-4.8.0.0 | 
| Functor Product # | Since: base-4.8.0.0 | 
| MonadFix Product # | Since: base-4.8.0.0 | 
| Applicative Product # | Since: base-4.8.0.0 | 
| Defined in Data.Semigroup.Internal | |
| Foldable Product # | Since: base-4.8.0.0 | 
| Defined in Data.Foldable Methods fold :: Monoid m => Product m -> m Source # foldMap :: Monoid m => (a -> m) -> Product a -> m Source # foldMap' :: Monoid m => (a -> m) -> Product a -> m Source # foldr :: (a -> b -> b) -> b -> Product a -> b Source # foldr' :: (a -> b -> b) -> b -> Product a -> b Source # foldl :: (b -> a -> b) -> b -> Product a -> b Source # foldl' :: (b -> a -> b) -> b -> Product a -> b Source # foldr1 :: (a -> a -> a) -> Product a -> a Source # foldl1 :: (a -> a -> a) -> Product a -> a Source # toList :: Product a -> [a] Source # null :: Product a -> Bool Source # length :: Product a -> Int Source # elem :: Eq a => a -> Product a -> Bool Source # maximum :: Ord a => Product a -> a Source # minimum :: Ord a => Product a -> a Source # | |
| Traversable Product # | Since: base-4.8.0.0 | 
| Defined in Data.Traversable | |
| MonadZip Product # | Since: base-4.8.0.0 | 
| Bounded a => Bounded (Product a) # | Since: base-2.1 | 
| Eq a => Eq (Product a) # | Since: base-2.1 | 
| Data a => Data (Product a) # | Since: base-4.8.0.0 | 
| Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Product a -> c (Product a) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Product a) Source # toConstr :: Product a -> Constr Source # dataTypeOf :: Product a -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Product a)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Product a)) Source # gmapT :: (forall b. Data b => b -> b) -> Product a -> Product a Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Product a -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Product a -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Product a -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Product a -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Product a -> m (Product a) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Product a -> m (Product a) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Product a -> m (Product a) Source # | |
| Num a => Num (Product a) # | Since: base-4.7.0.0 | 
| Defined in Data.Semigroup.Internal Methods (+) :: Product a -> Product a -> Product a Source # (-) :: Product a -> Product a -> Product a Source # (*) :: Product a -> Product a -> Product a Source # negate :: Product a -> Product a Source # abs :: Product a -> Product a Source # signum :: Product a -> Product a Source # fromInteger :: Integer -> Product a Source # | |
| Ord a => Ord (Product a) # | Since: base-2.1 | 
| Defined in Data.Semigroup.Internal | |
| Read a => Read (Product a) # | Since: base-2.1 | 
| Show a => Show (Product a) # | Since: base-2.1 | 
| Generic (Product a) # | Since: base-4.7.0.0 | 
| Num a => Semigroup (Product a) # | Since: base-4.9.0.0 | 
| Num a => Monoid (Product a) # | Since: base-2.1 | 
| Generic1 Product # | Since: base-4.7.0.0 | 
| type Rep (Product a) # | |
| Defined in Data.Semigroup.Internal | |
| type Rep1 Product # | |
| Defined in Data.Semigroup.Internal | |
Maybe wrappers
To implement find or findLast on any Foldable:
findLast :: Foldable t => (a -> Bool) -> t a -> Maybe a
findLast pred = getLast . foldMap (x -> if pred x
                                           then Last (Just x)
                                           else Last Nothing)
Much of Maps interface can be implemented with
 alter. Some of the rest can be implemented with a new
 alterF function and either First or Last:
alterF :: (Functor f, Ord k) =>
          (Maybe a -> f (Maybe a)) -> k -> Map k a -> f (Map k a)
instance Monoid a => Functor ((,) a)  -- from Data.FunctorinsertLookupWithKey :: Ord k => (k -> v -> v -> v) -> k -> v
                    -> Map k v -> (Maybe v, Map k v)
insertLookupWithKey combine key value =
  Arrow.first getFirst . alterF doChange key
  where
  doChange Nothing = (First Nothing, Just value)
  doChange (Just oldValue) =
    (First (Just oldValue),
     Just (combine key value oldValue))
Maybe monoid returning the leftmost non-Nothing value.
First aAlt Maybe a
>>>getFirst (First (Just "hello") <> First Nothing <> First (Just "world"))Just "hello"
Use of this type is discouraged. Note the following equivalence:
Data.Monoid.First x === Maybe (Data.Semigroup.First x)
In addition to being equivalent in the structural sense, the two
 also have Monoid instances that behave the same. This type will
 be marked deprecated in GHC 8.8, and removed in GHC 8.10.
 Users are advised to use the variant from Data.Semigroup and wrap
 it in Maybe.
Instances
| Monad First # | Since: base-4.8.0.0 | 
| Functor First # | Since: base-4.8.0.0 | 
| MonadFix First # | Since: base-4.8.0.0 | 
| Applicative First # | Since: base-4.8.0.0 | 
| Foldable First # | Since: base-4.8.0.0 | 
| Defined in Data.Foldable Methods fold :: Monoid m => First m -> m Source # foldMap :: Monoid m => (a -> m) -> First a -> m Source # foldMap' :: Monoid m => (a -> m) -> First a -> m Source # foldr :: (a -> b -> b) -> b -> First a -> b Source # foldr' :: (a -> b -> b) -> b -> First a -> b Source # foldl :: (b -> a -> b) -> b -> First a -> b Source # foldl' :: (b -> a -> b) -> b -> First a -> b Source # foldr1 :: (a -> a -> a) -> First a -> a Source # foldl1 :: (a -> a -> a) -> First a -> a Source # toList :: First a -> [a] Source # null :: First a -> Bool Source # length :: First a -> Int Source # elem :: Eq a => a -> First a -> Bool Source # maximum :: Ord a => First a -> a Source # minimum :: Ord a => First a -> a Source # | |
| Traversable First # | Since: base-4.8.0.0 | 
| MonadZip First # | Since: base-4.8.0.0 | 
| Eq a => Eq (First a) # | Since: base-2.1 | 
| Data a => Data (First a) # | Since: base-4.8.0.0 | 
| Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> First a -> c (First a) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (First a) Source # toConstr :: First a -> Constr Source # dataTypeOf :: First a -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (First a)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (First a)) Source # gmapT :: (forall b. Data b => b -> b) -> First a -> First a Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> First a -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> First a -> r Source # gmapQ :: (forall d. Data d => d -> u) -> First a -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> First a -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> First a -> m (First a) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> First a -> m (First a) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> First a -> m (First a) Source # | |
| Ord a => Ord (First a) # | Since: base-2.1 | 
| Read a => Read (First a) # | Since: base-2.1 | 
| Show a => Show (First a) # | Since: base-2.1 | 
| Generic (First a) # | Since: base-4.7.0.0 | 
| Semigroup (First a) # | Since: base-4.9.0.0 | 
| Monoid (First a) # | Since: base-2.1 | 
| Generic1 First # | Since: base-4.7.0.0 | 
| type Rep (First a) # | |
| Defined in Data.Monoid | |
| type Rep1 First # | |
| Defined in Data.Monoid | |
Maybe monoid returning the rightmost non-Nothing value.
Last aDual (First a)Dual (Alt Maybe a)
>>>getLast (Last (Just "hello") <> Last Nothing <> Last (Just "world"))Just "world"
Use of this type is discouraged. Note the following equivalence:
Data.Monoid.Last x === Maybe (Data.Semigroup.Last x)
In addition to being equivalent in the structural sense, the two
 also have Monoid instances that behave the same. This type will
 be marked deprecated in GHC 8.8, and removed in GHC 8.10.
 Users are advised to use the variant from Data.Semigroup and wrap
 it in Maybe.
Instances
| Monad Last # | Since: base-4.8.0.0 | 
| Functor Last # | Since: base-4.8.0.0 | 
| MonadFix Last # | Since: base-4.8.0.0 | 
| Applicative Last # | Since: base-4.8.0.0 | 
| Foldable Last # | Since: base-4.8.0.0 | 
| Defined in Data.Foldable Methods fold :: Monoid m => Last m -> m Source # foldMap :: Monoid m => (a -> m) -> Last a -> m Source # foldMap' :: Monoid m => (a -> m) -> Last a -> m Source # foldr :: (a -> b -> b) -> b -> Last a -> b Source # foldr' :: (a -> b -> b) -> b -> Last a -> b Source # foldl :: (b -> a -> b) -> b -> Last a -> b Source # foldl' :: (b -> a -> b) -> b -> Last a -> b Source # foldr1 :: (a -> a -> a) -> Last a -> a Source # foldl1 :: (a -> a -> a) -> Last a -> a Source # toList :: Last a -> [a] Source # null :: Last a -> Bool Source # length :: Last a -> Int Source # elem :: Eq a => a -> Last a -> Bool Source # maximum :: Ord a => Last a -> a Source # minimum :: Ord a => Last a -> a Source # | |
| Traversable Last # | Since: base-4.8.0.0 | 
| MonadZip Last # | Since: base-4.8.0.0 | 
| Eq a => Eq (Last a) # | Since: base-2.1 | 
| Data a => Data (Last a) # | Since: base-4.8.0.0 | 
| Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Last a -> c (Last a) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Last a) Source # toConstr :: Last a -> Constr Source # dataTypeOf :: Last a -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Last a)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Last a)) Source # gmapT :: (forall b. Data b => b -> b) -> Last a -> Last a Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Last a -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Last a -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Last a -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Last a -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Last a -> m (Last a) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Last a -> m (Last a) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Last a -> m (Last a) Source # | |
| Ord a => Ord (Last a) # | Since: base-2.1 | 
| Read a => Read (Last a) # | Since: base-2.1 | 
| Show a => Show (Last a) # | Since: base-2.1 | 
| Generic (Last a) # | Since: base-4.7.0.0 | 
| Semigroup (Last a) # | Since: base-4.9.0.0 | 
| Monoid (Last a) # | Since: base-2.1 | 
| Generic1 Last # | Since: base-4.7.0.0 | 
| type Rep (Last a) # | |
| Defined in Data.Monoid | |
| type Rep1 Last # | |
| Defined in Data.Monoid | |
Alternative wrapper
Monoid under <|>.
>>>getAlt (Alt (Just 12) <> Alt (Just 24))Just 12
>>>getAlt $ Alt Nothing <> Alt (Just 24)Just 24
Since: base-4.8.0.0
Instances
| Generic1 (Alt f :: k -> Type) # | Since: base-4.8.0.0 | 
| Monad f => Monad (Alt f) # | Since: base-4.8.0.0 | 
| Functor f => Functor (Alt f) # | Since: base-4.8.0.0 | 
| MonadFix f => MonadFix (Alt f) # | Since: base-4.8.0.0 | 
| Applicative f => Applicative (Alt f) # | Since: base-4.8.0.0 | 
| Foldable f => Foldable (Alt f) # | Since: base-4.12.0.0 | 
| Defined in Data.Foldable Methods fold :: Monoid m => Alt f m -> m Source # foldMap :: Monoid m => (a -> m) -> Alt f a -> m Source # foldMap' :: Monoid m => (a -> m) -> Alt f a -> m Source # foldr :: (a -> b -> b) -> b -> Alt f a -> b Source # foldr' :: (a -> b -> b) -> b -> Alt f a -> b Source # foldl :: (b -> a -> b) -> b -> Alt f a -> b Source # foldl' :: (b -> a -> b) -> b -> Alt f a -> b Source # foldr1 :: (a -> a -> a) -> Alt f a -> a Source # foldl1 :: (a -> a -> a) -> Alt f a -> a Source # toList :: Alt f a -> [a] Source # null :: Alt f a -> Bool Source # length :: Alt f a -> Int Source # elem :: Eq a => a -> Alt f a -> Bool Source # maximum :: Ord a => Alt f a -> a Source # minimum :: Ord a => Alt f a -> a Source # | |
| Traversable f => Traversable (Alt f) # | Since: base-4.12.0.0 | 
| Defined in Data.Traversable | |
| MonadPlus f => MonadPlus (Alt f) # | Since: base-4.8.0.0 | 
| Alternative f => Alternative (Alt f) # | Since: base-4.8.0.0 | 
| MonadZip f => MonadZip (Alt f) # | Since: base-4.8.0.0 | 
| Contravariant f => Contravariant (Alt f) # | |
| Enum (f a) => Enum (Alt f a) # | Since: base-4.8.0.0 | 
| Defined in Data.Semigroup.Internal Methods succ :: Alt f a -> Alt f a Source # pred :: Alt f a -> Alt f a Source # toEnum :: Int -> Alt f a Source # fromEnum :: Alt f a -> Int Source # enumFrom :: Alt f a -> [Alt f a] Source # enumFromThen :: Alt f a -> Alt f a -> [Alt f a] Source # enumFromTo :: Alt f a -> Alt f a -> [Alt f a] Source # enumFromThenTo :: Alt f a -> Alt f a -> Alt f a -> [Alt f a] Source # | |
| Eq (f a) => Eq (Alt f a) # | Since: base-4.8.0.0 | 
| (Data (f a), Data a, Typeable f) => Data (Alt f a) # | Since: base-4.8.0.0 | 
| Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Alt f a -> c (Alt f a) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Alt f a) Source # toConstr :: Alt f a -> Constr Source # dataTypeOf :: Alt f a -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Alt f a)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Alt f a)) Source # gmapT :: (forall b. Data b => b -> b) -> Alt f a -> Alt f a Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Alt f a -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Alt f a -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Alt f a -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Alt f a -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Alt f a -> m (Alt f a) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Alt f a -> m (Alt f a) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Alt f a -> m (Alt f a) Source # | |
| Num (f a) => Num (Alt f a) # | Since: base-4.8.0.0 | 
| Defined in Data.Semigroup.Internal | |
| Ord (f a) => Ord (Alt f a) # | Since: base-4.8.0.0 | 
| Defined in Data.Semigroup.Internal | |
| Read (f a) => Read (Alt f a) # | Since: base-4.8.0.0 | 
| Show (f a) => Show (Alt f a) # | Since: base-4.8.0.0 | 
| Generic (Alt f a) # | Since: base-4.8.0.0 | 
| Alternative f => Semigroup (Alt f a) # | Since: base-4.9.0.0 | 
| Alternative f => Monoid (Alt f a) # | Since: base-4.8.0.0 | 
| type Rep1 (Alt f :: k -> Type) # | |
| Defined in Data.Semigroup.Internal | |
| type Rep (Alt f a) # | |
| Defined in Data.Semigroup.Internal | |
Applicative wrapper
This data type witnesses the lifting of a Monoid into an
 Applicative pointwise.
Since: base-4.12.0.0
Instances
| Generic1 (Ap f :: k -> Type) # | Since: base-4.12.0.0 | 
| Monad f => Monad (Ap f) # | Since: base-4.12.0.0 | 
| Functor f => Functor (Ap f) # | Since: base-4.12.0.0 | 
| MonadFix f => MonadFix (Ap f) # | Since: base-4.12.0.0 | 
| MonadFail f => MonadFail (Ap f) # | Since: base-4.12.0.0 | 
| Applicative f => Applicative (Ap f) # | Since: base-4.12.0.0 | 
| Foldable f => Foldable (Ap f) # | Since: base-4.12.0.0 | 
| Defined in Data.Foldable Methods fold :: Monoid m => Ap f m -> m Source # foldMap :: Monoid m => (a -> m) -> Ap f a -> m Source # foldMap' :: Monoid m => (a -> m) -> Ap f a -> m Source # foldr :: (a -> b -> b) -> b -> Ap f a -> b Source # foldr' :: (a -> b -> b) -> b -> Ap f a -> b Source # foldl :: (b -> a -> b) -> b -> Ap f a -> b Source # foldl' :: (b -> a -> b) -> b -> Ap f a -> b Source # foldr1 :: (a -> a -> a) -> Ap f a -> a Source # foldl1 :: (a -> a -> a) -> Ap f a -> a Source # toList :: Ap f a -> [a] Source # null :: Ap f a -> Bool Source # length :: Ap f a -> Int Source # elem :: Eq a => a -> Ap f a -> Bool Source # maximum :: Ord a => Ap f a -> a Source # minimum :: Ord a => Ap f a -> a Source # | |
| Traversable f => Traversable (Ap f) # | Since: base-4.12.0.0 | 
| MonadPlus f => MonadPlus (Ap f) # | Since: base-4.12.0.0 | 
| Alternative f => Alternative (Ap f) # | Since: base-4.12.0.0 | 
| (Applicative f, Bounded a) => Bounded (Ap f a) # | Since: base-4.12.0.0 | 
| Enum (f a) => Enum (Ap f a) # | Since: base-4.12.0.0 | 
| Defined in Data.Monoid Methods succ :: Ap f a -> Ap f a Source # pred :: Ap f a -> Ap f a Source # toEnum :: Int -> Ap f a Source # fromEnum :: Ap f a -> Int Source # enumFrom :: Ap f a -> [Ap f a] Source # enumFromThen :: Ap f a -> Ap f a -> [Ap f a] Source # enumFromTo :: Ap f a -> Ap f a -> [Ap f a] Source # enumFromThenTo :: Ap f a -> Ap f a -> Ap f a -> [Ap f a] Source # | |
| Eq (f a) => Eq (Ap f a) # | Since: base-4.12.0.0 | 
| (Data (f a), Data a, Typeable f) => Data (Ap f a) # | Since: base-4.12.0.0 | 
| Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ap f a -> c (Ap f a) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Ap f a) Source # toConstr :: Ap f a -> Constr Source # dataTypeOf :: Ap f a -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Ap f a)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Ap f a)) Source # gmapT :: (forall b. Data b => b -> b) -> Ap f a -> Ap f a Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ap f a -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ap f a -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Ap f a -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Ap f a -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ap f a -> m (Ap f a) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ap f a -> m (Ap f a) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ap f a -> m (Ap f a) Source # | |
| (Applicative f, Num a) => Num (Ap f a) # | Since: base-4.12.0.0 | 
| Ord (f a) => Ord (Ap f a) # | Since: base-4.12.0.0 | 
| Read (f a) => Read (Ap f a) # | Since: base-4.12.0.0 | 
| Show (f a) => Show (Ap f a) # | Since: base-4.12.0.0 | 
| Generic (Ap f a) # | Since: base-4.12.0.0 | 
| (Applicative f, Semigroup a) => Semigroup (Ap f a) # | Since: base-4.12.0.0 | 
| (Applicative f, Monoid a) => Monoid (Ap f a) # | Since: base-4.12.0.0 | 
| type Rep1 (Ap f :: k -> Type) # | |
| Defined in Data.Monoid | |
| type Rep (Ap f a) # | |
| Defined in Data.Monoid | |