| 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
Contents
Description
A class for monoids (types with an associative binary operation that has an identity) with various general-purpose instances.
Monoid typeclassclassSemigroup a =>Monoid awhereSource#
The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following laws:
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 definenewtypes and make those instances ofMonoid, e.g.Sum andProduct.
Minimal complete definition
Methods
Identity ofmappend
An associative operation
NOTE: This method is redundant and has the default implementation sincebase-4.11.0.0.mappend = '(<>)'
Fold a list using the monoid.
For most types, the default definition formconcat will be used, but the function is included in the class definition so that an optimized version can be provided for specific types.
| MonoidOrderingSource# | Since: 2.1 |
| Monoid ()Source# | Since: 2.1 |
| MonoidAnySource# | Since: 2.1 |
| MonoidAllSource# | Since: 2.1 |
| MonoidLifetimeSource# |
Since: 4.8.0.0 |
| MonoidEventSource# | Since: 4.4.0.0 |
| Monoid [a]Source# | Since: 2.1 |
| Semigroup a =>Monoid (Maybe a)Source# | Lift a semigroup into Since 4.11.0: constraint on inner Since: 2.1 |
| Monoid a =>Monoid (IO a)Source# | Since: 4.9.0.0 |
| Monoid p =>Monoid (Par1 p)Source# | Since: 4.12.0.0 |
| Monoid a =>Monoid (Down a)Source# | Since: 4.11.0.0 |
| Num a =>Monoid (Product a)Source# | Since: 2.1 |
| Num a =>Monoid (Sum a)Source# | Since: 2.1 |
| Monoid (Endo a)Source# | Since: 2.1 |
| Monoid a =>Monoid (Dual a)Source# | Since: 2.1 |
| Monoid (Last a)Source# | Since: 2.1 |
| Monoid (First a)Source# | Since: 2.1 |
| Monoid a =>Monoid (Identity a)Source# | Since: 4.9.0.0 |
| Semigroup a =>Monoid (Option a)Source# | Since: 4.9.0.0 |
| Monoid m =>Monoid (WrappedMonoid m)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Semigroup Methods mempty ::WrappedMonoid mSource# mappend ::WrappedMonoid m ->WrappedMonoid m ->WrappedMonoid mSource# mconcat :: [WrappedMonoid m] ->WrappedMonoid mSource# | |
| (Ord a,Bounded a) =>Monoid (Max a)Source# | Since: 4.9.0.0 |
| (Ord a,Bounded a) =>Monoid (Min a)Source# | Since: 4.9.0.0 |
| Monoid (Equivalence a)Source# | |
Instance detailsDefined inData.Functor.Contravariant Methods mappend ::Equivalence a ->Equivalence a ->Equivalence aSource# mconcat :: [Equivalence a] ->Equivalence aSource# | |
| Monoid (Comparison a)Source# | |
Instance detailsDefined inData.Functor.Contravariant Methods mappend ::Comparison a ->Comparison a ->Comparison aSource# mconcat :: [Comparison a] ->Comparison aSource# | |
| Monoid (Predicate a)Source# | |
| Monoid b =>Monoid (a -> b)Source# | Since: 2.1 |
| Monoid (U1 p)Source# | Since: 4.12.0.0 |
| (Monoid a,Monoid b) =>Monoid (a, b)Source# | Since: 2.1 |
| Monoid a =>Monoid (ST s a)Source# | Since: 4.11.0.0 |
| Monoid (Proxy s)Source# | Since: 4.7.0.0 |
| Monoid a =>Monoid (Op a b)Source# | |
| Monoid (f p) =>Monoid (Rec1 f p)Source# | Since: 4.12.0.0 |
| (Monoid a,Monoid b,Monoid c) =>Monoid (a, b, c)Source# | Since: 2.1 |
| Alternative f =>Monoid (Alt f a)Source# | Since: 4.8.0.0 |
| (Applicative f,Monoid a) =>Monoid (Ap f a)Source# | Since: 4.12.0.0 |
| Monoid a =>Monoid (Const a b)Source# | Since: 4.9.0.0 |
| Monoid c =>Monoid (K1 i c p)Source# | Since: 4.12.0.0 |
| (Monoid (f p),Monoid (g p)) =>Monoid ((f:*: g) p)Source# | Since: 4.12.0.0 |
| (Monoid a,Monoid b,Monoid c,Monoid d) =>Monoid (a, b, c, d)Source# | Since: 2.1 |
| Monoid (f p) =>Monoid (M1 i c f p)Source# | Since: 4.12.0.0 |
| Monoid (f (g p)) =>Monoid ((f:.: g) p)Source# | Since: 4.12.0.0 |
| (Monoid a,Monoid b,Monoid c,Monoid d,Monoid e) =>Monoid (a, b, c, d, e)Source# | Since: 2.1 |
The dual of aMonoid, obtained by swapping the arguments ofmappend.
>>>getDual (mappend (Dual "Hello") (Dual "World"))"WorldHello"
| MonadDualSource# | Since: 4.8.0.0 |
| FunctorDualSource# | Since: 4.8.0.0 |
| MonadFixDualSource# | Since: 4.8.0.0 |
| ApplicativeDualSource# | Since: 4.8.0.0 |
| FoldableDualSource# | Since: 4.8.0.0 |
Instance detailsDefined inData.Foldable Methods fold ::Monoid m =>Dual m -> mSource# foldMap ::Monoid m => (a -> m) ->Dual a -> mSource# foldr :: (a -> b -> b) -> b ->Dual a -> bSource# foldr' :: (a -> b -> b) -> b ->Dual a -> bSource# foldl :: (b -> a -> b) -> b ->Dual a -> bSource# foldl' :: (b -> a -> b) -> b ->Dual a -> bSource# foldr1 :: (a -> a -> a) ->Dual a -> aSource# foldl1 :: (a -> a -> a) ->Dual a -> aSource# elem ::Eq a => a ->Dual a ->BoolSource# maximum ::Ord a =>Dual a -> aSource# minimum ::Ord a =>Dual a -> aSource# | |
| TraversableDualSource# | Since: 4.8.0.0 |
| MonadZipDualSource# | Since: 4.8.0.0 |
| Bounded a =>Bounded (Dual a)Source# | Since: 2.1 |
| Eq a =>Eq (Dual a)Source# | Since: 2.1 |
| Data a =>Data (Dual a)Source# | Since: 4.8.0.0 |
Instance detailsDefined inData.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 ->ConstrSource# dataTypeOf ::Dual a ->DataTypeSource# 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 aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Dual a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Dual a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Dual a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Dual a -> uSource# 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)Source# | Since: 2.1 |
| Read a =>Read (Dual a)Source# | Since: 2.1 |
| Show a =>Show (Dual a)Source# | Since: 2.1 |
| Generic (Dual a)Source# | |
| Semigroup a =>Semigroup (Dual a)Source# | Since: 4.9.0.0 |
| Monoid a =>Monoid (Dual a)Source# | Since: 2.1 |
| Generic1DualSource# | |
| typeRep (Dual a)Source# | Since: 4.7.0.0 |
Instance detailsDefined inData.Semigroup.Internal | |
| typeRep1DualSource# | Since: 4.7.0.0 |
Instance detailsDefined inData.Semigroup.Internal | |
The monoid of endomorphisms under composition.
>>>let computation = Endo ("Hello, " ++) <> Endo (++ "!")>>>appEndo computation "Haskell""Hello, Haskell!"
Bool wrappersBoolean monoid under conjunction (&&).
>>>getAll (All True <> mempty <> All False)False
>>>getAll (mconcat (map (\x -> All (even x)) [2,4,6,7,8]))False
| BoundedAllSource# | Since: 2.1 |
| EqAllSource# | Since: 2.1 |
| DataAllSource# | Since: 4.8.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->All -> cAllSource# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> cAllSource# toConstr ::All ->ConstrSource# dataTypeOf ::All ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (cAll)Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (cAll)Source# gmapT :: (forall b.Data b => b -> b) ->All ->AllSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->All -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->All -> rSource# gmapQ :: (forall d.Data d => d -> u) ->All -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->All -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->All -> mAllSource# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->All -> mAllSource# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->All -> mAllSource# | |
| OrdAllSource# | Since: 2.1 |
| ReadAllSource# | Since: 2.1 |
| ShowAllSource# | Since: 2.1 |
| GenericAllSource# | |
| SemigroupAllSource# | Since: 4.9.0.0 |
| MonoidAllSource# | Since: 2.1 |
| typeRepAllSource# | Since: 4.7.0.0 |
Instance detailsDefined inData.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
| BoundedAnySource# | Since: 2.1 |
| EqAnySource# | Since: 2.1 |
| DataAnySource# | Since: 4.8.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Any -> cAnySource# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> cAnySource# toConstr ::Any ->ConstrSource# dataTypeOf ::Any ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (cAny)Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (cAny)Source# gmapT :: (forall b.Data b => b -> b) ->Any ->AnySource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Any -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Any -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Any -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Any -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Any -> mAnySource# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Any -> mAnySource# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Any -> mAnySource# | |
| OrdAnySource# | Since: 2.1 |
| ReadAnySource# | Since: 2.1 |
| ShowAnySource# | Since: 2.1 |
| GenericAnySource# | |
| SemigroupAnySource# | Since: 4.9.0.0 |
| MonoidAnySource# | Since: 2.1 |
| typeRepAnySource# | Since: 4.7.0.0 |
Instance detailsDefined inData.Semigroup.Internal | |
Num wrappersMonoid under addition.
>>>getSum (Sum 1 <> Sum 2 <> mempty)3
| MonadSumSource# | Since: 4.8.0.0 |
| FunctorSumSource# | Since: 4.8.0.0 |
| MonadFixSumSource# | Since: 4.8.0.0 |
| ApplicativeSumSource# | Since: 4.8.0.0 |
| FoldableSumSource# | Since: 4.8.0.0 |
Instance detailsDefined inData.Foldable Methods fold ::Monoid m =>Sum m -> mSource# foldMap ::Monoid m => (a -> m) ->Sum a -> mSource# foldr :: (a -> b -> b) -> b ->Sum a -> bSource# foldr' :: (a -> b -> b) -> b ->Sum a -> bSource# foldl :: (b -> a -> b) -> b ->Sum a -> bSource# foldl' :: (b -> a -> b) -> b ->Sum a -> bSource# foldr1 :: (a -> a -> a) ->Sum a -> aSource# foldl1 :: (a -> a -> a) ->Sum a -> aSource# elem ::Eq a => a ->Sum a ->BoolSource# maximum ::Ord a =>Sum a -> aSource# minimum ::Ord a =>Sum a -> aSource# | |
| TraversableSumSource# | Since: 4.8.0.0 |
| MonadZipSumSource# | Since: 4.8.0.0 |
| Bounded a =>Bounded (Sum a)Source# | Since: 2.1 |
| Eq a =>Eq (Sum a)Source# | Since: 2.1 |
| Data a =>Data (Sum a)Source# | Since: 4.8.0.0 |
Instance detailsDefined inData.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 ->ConstrSource# dataTypeOf ::Sum a ->DataTypeSource# 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 aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Sum a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Sum a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Sum a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Sum a -> uSource# 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)Source# | Since: 4.7.0.0 |
| Ord a =>Ord (Sum a)Source# | Since: 2.1 |
| Read a =>Read (Sum a)Source# | Since: 2.1 |
| Show a =>Show (Sum a)Source# | Since: 2.1 |
| Generic (Sum a)Source# | |
| Num a =>Semigroup (Sum a)Source# | Since: 4.9.0.0 |
| Num a =>Monoid (Sum a)Source# | Since: 2.1 |
| Generic1SumSource# | |
| typeRep (Sum a)Source# | Since: 4.7.0.0 |
Instance detailsDefined inData.Semigroup.Internal | |
| typeRep1SumSource# | Since: 4.7.0.0 |
Instance detailsDefined inData.Semigroup.Internal | |
Monoid under multiplication.
>>>getProduct (Product 3 <> Product 4 <> mempty)12
Constructors
| Product | |
Fields
| |
| MonadProductSource# | Since: 4.8.0.0 |
| FunctorProductSource# | Since: 4.8.0.0 |
| MonadFixProductSource# | Since: 4.8.0.0 |
| ApplicativeProductSource# | Since: 4.8.0.0 |
| FoldableProductSource# | Since: 4.8.0.0 |
Instance detailsDefined inData.Foldable Methods fold ::Monoid m =>Product m -> mSource# foldMap ::Monoid m => (a -> m) ->Product a -> mSource# foldr :: (a -> b -> b) -> b ->Product a -> bSource# foldr' :: (a -> b -> b) -> b ->Product a -> bSource# foldl :: (b -> a -> b) -> b ->Product a -> bSource# foldl' :: (b -> a -> b) -> b ->Product a -> bSource# foldr1 :: (a -> a -> a) ->Product a -> aSource# foldl1 :: (a -> a -> a) ->Product a -> aSource# toList ::Product a -> [a]Source# null ::Product a ->BoolSource# length ::Product a ->IntSource# elem ::Eq a => a ->Product a ->BoolSource# maximum ::Ord a =>Product a -> aSource# minimum ::Ord a =>Product a -> aSource# | |
| TraversableProductSource# | Since: 4.8.0.0 |
Instance detailsDefined inData.Traversable | |
| MonadZipProductSource# | Since: 4.8.0.0 |
| Bounded a =>Bounded (Product a)Source# | Since: 2.1 |
| Eq a =>Eq (Product a)Source# | Since: 2.1 |
| Data a =>Data (Product a)Source# | Since: 4.8.0.0 |
Instance detailsDefined inData.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 ->ConstrSource# dataTypeOf ::Product a ->DataTypeSource# 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 aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Product a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Product a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Product a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Product a -> uSource# 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)Source# | Since: 4.7.0.0 |
Instance detailsDefined inData.Semigroup.Internal | |
| Ord a =>Ord (Product a)Source# | Since: 2.1 |
Instance detailsDefined inData.Semigroup.Internal | |
| Read a =>Read (Product a)Source# | Since: 2.1 |
| Show a =>Show (Product a)Source# | Since: 2.1 |
| Generic (Product a)Source# | |
| Num a =>Semigroup (Product a)Source# | Since: 4.9.0.0 |
| Num a =>Monoid (Product a)Source# | Since: 2.1 |
| Generic1ProductSource# | |
| typeRep (Product a)Source# | Since: 4.7.0.0 |
Instance detailsDefined inData.Semigroup.Internal | |
| typeRep1ProductSource# | Since: 4.7.0.0 |
Instance detailsDefined inData.Semigroup.Internal | |
Maybe wrappersTo implementfind orfindLast on anyFoldable:
findLast :: Foldable t => (a -> Bool) -> t a -> Maybe afindLast pred = getLast . foldMap (x -> if pred x then Last (Just x) else Last Nothing)
Much of Data.Map's interface can be implemented with Data.Map.alter. Some of the rest can be implemented with a newalterA function and eitherFirst orLast:
alterA :: (Applicative f, Ord k) => (Maybe a -> f (Maybe a)) -> k -> Map k a -> f (Map k a)instance Monoid a => Applicative ((,) a) -- from Control.Applicative
insertLookupWithKey :: Ord k => (k -> v -> v -> v) -> k -> v -> Map k v -> (Maybe v, Map k v)insertLookupWithKey combine key value = Arrow.first getFirst . alterA 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.
is isomorphic toFirst a, but precedes it historically.AltMaybe 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 haveMonoid 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 fromData.Semigroup and wrap it inMaybe.
| MonadFirstSource# | Since: 4.8.0.0 |
| FunctorFirstSource# | Since: 4.8.0.0 |
| MonadFixFirstSource# | Since: 4.8.0.0 |
| ApplicativeFirstSource# | Since: 4.8.0.0 |
| FoldableFirstSource# | Since: 4.8.0.0 |
Instance detailsDefined inData.Foldable Methods fold ::Monoid m =>First m -> mSource# foldMap ::Monoid m => (a -> m) ->First a -> mSource# foldr :: (a -> b -> b) -> b ->First a -> bSource# foldr' :: (a -> b -> b) -> b ->First a -> bSource# foldl :: (b -> a -> b) -> b ->First a -> bSource# foldl' :: (b -> a -> b) -> b ->First a -> bSource# foldr1 :: (a -> a -> a) ->First a -> aSource# foldl1 :: (a -> a -> a) ->First a -> aSource# toList ::First a -> [a]Source# elem ::Eq a => a ->First a ->BoolSource# maximum ::Ord a =>First a -> aSource# minimum ::Ord a =>First a -> aSource# | |
| TraversableFirstSource# | Since: 4.8.0.0 |
| MonadZipFirstSource# | Since: 4.8.0.0 |
| Eq a =>Eq (First a)Source# | Since: 2.1 |
| Data a =>Data (First a)Source# | Since: 4.8.0.0 |
Instance detailsDefined inData.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 ->ConstrSource# dataTypeOf ::First a ->DataTypeSource# 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 aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->First a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->First a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->First a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->First a -> uSource# 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)Source# | Since: 2.1 |
| Read a =>Read (First a)Source# | Since: 2.1 |
| Show a =>Show (First a)Source# | Since: 2.1 |
| Generic (First a)Source# | |
| Semigroup (First a)Source# | Since: 4.9.0.0 |
| Monoid (First a)Source# | Since: 2.1 |
| Generic1FirstSource# | |
| typeRep (First a)Source# | Since: 4.7.0.0 |
Instance detailsDefined inData.Monoid | |
| typeRep1FirstSource# | Since: 4.7.0.0 |
Instance detailsDefined inData.Monoid | |
Maybe monoid returning the rightmost non-Nothing value.
is isomorphic toLast a, and thus toDual (First a)Dual (AltMaybe 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 haveMonoid 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 fromData.Semigroup and wrap it inMaybe.
| MonadLastSource# | Since: 4.8.0.0 |
| FunctorLastSource# | Since: 4.8.0.0 |
| MonadFixLastSource# | Since: 4.8.0.0 |
| ApplicativeLastSource# | Since: 4.8.0.0 |
| FoldableLastSource# | Since: 4.8.0.0 |
Instance detailsDefined inData.Foldable Methods fold ::Monoid m =>Last m -> mSource# foldMap ::Monoid m => (a -> m) ->Last a -> mSource# foldr :: (a -> b -> b) -> b ->Last a -> bSource# foldr' :: (a -> b -> b) -> b ->Last a -> bSource# foldl :: (b -> a -> b) -> b ->Last a -> bSource# foldl' :: (b -> a -> b) -> b ->Last a -> bSource# foldr1 :: (a -> a -> a) ->Last a -> aSource# foldl1 :: (a -> a -> a) ->Last a -> aSource# elem ::Eq a => a ->Last a ->BoolSource# maximum ::Ord a =>Last a -> aSource# minimum ::Ord a =>Last a -> aSource# | |
| TraversableLastSource# | Since: 4.8.0.0 |
| MonadZipLastSource# | Since: 4.8.0.0 |
| Eq a =>Eq (Last a)Source# | Since: 2.1 |
| Data a =>Data (Last a)Source# | Since: 4.8.0.0 |
Instance detailsDefined inData.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 ->ConstrSource# dataTypeOf ::Last a ->DataTypeSource# 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 aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Last a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Last a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Last a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Last a -> uSource# 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)Source# | Since: 2.1 |
| Read a =>Read (Last a)Source# | Since: 2.1 |
| Show a =>Show (Last a)Source# | Since: 2.1 |
| Generic (Last a)Source# | |
| Semigroup (Last a)Source# | Since: 4.9.0.0 |
| Monoid (Last a)Source# | Since: 2.1 |
| Generic1LastSource# | |
| typeRep (Last a)Source# | Since: 4.7.0.0 |
Instance detailsDefined inData.Monoid | |
| typeRep1LastSource# | Since: 4.7.0.0 |
Instance detailsDefined inData.Monoid | |
Alternative wrapperMonoid under<|>.
Since: 4.8.0.0
| Generic1 (Alt f :: k ->Type)Source# | |
| Monad f =>Monad (Alt f)Source# | Since: 4.8.0.0 |
| Functor f =>Functor (Alt f)Source# | Since: 4.8.0.0 |
| MonadFix f =>MonadFix (Alt f)Source# | Since: 4.8.0.0 |
| Applicative f =>Applicative (Alt f)Source# | Since: 4.8.0.0 |
| Foldable f =>Foldable (Alt f)Source# | Since: 4.12.0.0 |
Instance detailsDefined inData.Foldable Methods fold ::Monoid m =>Alt f m -> mSource# foldMap ::Monoid m => (a -> m) ->Alt f a -> mSource# foldr :: (a -> b -> b) -> b ->Alt f a -> bSource# foldr' :: (a -> b -> b) -> b ->Alt f a -> bSource# foldl :: (b -> a -> b) -> b ->Alt f a -> bSource# foldl' :: (b -> a -> b) -> b ->Alt f a -> bSource# foldr1 :: (a -> a -> a) ->Alt f a -> aSource# foldl1 :: (a -> a -> a) ->Alt f a -> aSource# toList ::Alt f a -> [a]Source# elem ::Eq a => a ->Alt f a ->BoolSource# maximum ::Ord a =>Alt f a -> aSource# minimum ::Ord a =>Alt f a -> aSource# | |
| Traversable f =>Traversable (Alt f)Source# | Since: 4.12.0.0 |
Instance detailsDefined inData.Traversable | |
| MonadPlus f =>MonadPlus (Alt f)Source# | Since: 4.8.0.0 |
| Alternative f =>Alternative (Alt f)Source# | Since: 4.8.0.0 |
| MonadZip f =>MonadZip (Alt f)Source# | Since: 4.8.0.0 |
| Contravariant f =>Contravariant (Alt f)Source# | |
| Enum (f a) =>Enum (Alt f a)Source# | Since: 4.8.0.0 |
Instance detailsDefined inData.Semigroup.Internal Methods succ ::Alt f a ->Alt f aSource# pred ::Alt f a ->Alt f aSource# fromEnum ::Alt f a ->IntSource# 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)Source# | Since: 4.8.0.0 |
| (Data (f a),Data a,Typeable f) =>Data (Alt f a)Source# | Since: 4.8.0.0 |
Instance detailsDefined inData.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 ->ConstrSource# dataTypeOf ::Alt f a ->DataTypeSource# 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 aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Alt f a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Alt f a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Alt f a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Alt f a -> uSource# 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)Source# | Since: 4.8.0.0 |
Instance detailsDefined inData.Semigroup.Internal | |
| Ord (f a) =>Ord (Alt f a)Source# | Since: 4.8.0.0 |
| Read (f a) =>Read (Alt f a)Source# | Since: 4.8.0.0 |
| Show (f a) =>Show (Alt f a)Source# | Since: 4.8.0.0 |
| Generic (Alt f a)Source# | |
| Alternative f =>Semigroup (Alt f a)Source# | Since: 4.9.0.0 |
| Alternative f =>Monoid (Alt f a)Source# | Since: 4.8.0.0 |
| typeRep1 (Alt f :: k ->Type)Source# | Since: 4.8.0.0 |
Instance detailsDefined inData.Semigroup.Internal | |
| typeRep (Alt f a)Source# | Since: 4.8.0.0 |
Instance detailsDefined inData.Semigroup.Internal | |
Applicative wrapperThis data type witnesses the lifting of aMonoid into anApplicative pointwise.
Since: 4.12.0.0
| Generic1 (Ap f :: k ->Type)Source# | |
| Monad f =>Monad (Ap f)Source# | Since: 4.12.0.0 |
| Functor f =>Functor (Ap f)Source# | Since: 4.12.0.0 |
| MonadFix f =>MonadFix (Ap f)Source# | Since: 4.12.0.0 |
| MonadFail f =>MonadFail (Ap f)Source# | Since: 4.12.0.0 |
| Applicative f =>Applicative (Ap f)Source# | Since: 4.12.0.0 |
| Foldable f =>Foldable (Ap f)Source# | Since: 4.12.0.0 |
Instance detailsDefined inData.Foldable Methods fold ::Monoid m =>Ap f m -> mSource# foldMap ::Monoid m => (a -> m) ->Ap f a -> mSource# foldr :: (a -> b -> b) -> b ->Ap f a -> bSource# foldr' :: (a -> b -> b) -> b ->Ap f a -> bSource# foldl :: (b -> a -> b) -> b ->Ap f a -> bSource# foldl' :: (b -> a -> b) -> b ->Ap f a -> bSource# foldr1 :: (a -> a -> a) ->Ap f a -> aSource# foldl1 :: (a -> a -> a) ->Ap f a -> aSource# elem ::Eq a => a ->Ap f a ->BoolSource# maximum ::Ord a =>Ap f a -> aSource# minimum ::Ord a =>Ap f a -> aSource# | |
| Traversable f =>Traversable (Ap f)Source# | Since: 4.12.0.0 |
| MonadPlus f =>MonadPlus (Ap f)Source# | Since: 4.12.0.0 |
| Alternative f =>Alternative (Ap f)Source# | Since: 4.12.0.0 |
| (Applicative f,Bounded a) =>Bounded (Ap f a)Source# | Since: 4.12.0.0 |
| Enum (f a) =>Enum (Ap f a)Source# | Since: 4.12.0.0 |
| Eq (f a) =>Eq (Ap f a)Source# | Since: 4.12.0.0 |
| (Data (f a),Data a,Typeable f) =>Data (Ap f a)Source# | Since: 4.12.0.0 |
Instance detailsDefined inData.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 ->ConstrSource# dataTypeOf ::Ap f a ->DataTypeSource# 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 aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Ap f a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Ap f a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Ap f a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Ap f a -> uSource# 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)Source# | Since: 4.12.0.0 |
| Ord (f a) =>Ord (Ap f a)Source# | Since: 4.12.0.0 |
| Read (f a) =>Read (Ap f a)Source# | Since: 4.12.0.0 |
| Show (f a) =>Show (Ap f a)Source# | Since: 4.12.0.0 |
| Generic (Ap f a)Source# | |
| (Applicative f,Semigroup a) =>Semigroup (Ap f a)Source# | Since: 4.12.0.0 |
| (Applicative f,Monoid a) =>Monoid (Ap f a)Source# | Since: 4.12.0.0 |
| typeRep1 (Ap f :: k ->Type)Source# | Since: 4.12.0.0 |
Instance detailsDefined inData.Monoid | |
| typeRep (Ap f a)Source# | Since: 4.12.0.0 |
Instance detailsDefined inData.Monoid | |
Produced byHaddock version 2.20.0