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 | stable |
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
Expand
The Sum
monoid is defined by the numerical addition operator and `0` as neutral element:
>>>
mempty :: Sum Int
Sum {getSum = 0}>>>
Sum 1 <> Sum 2 <> Sum 3 <> Sum 4 :: Sum Int
Sum {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 Int
Sum {getSum = 10}>>>
mconcat [] :: Sum Int
Sum {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 Int
Product {getProduct = 24}>>>
mconcat [1,2,3,4] :: Product Int
Product {getProduct = 24}>>>
mconcat [] :: Product Int
Product {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)<>
zSemigroup
law)- Concatenation
mconcat
=foldr
(<>
)mempty
You can alternatively define mconcat
instead of mempty
, in which case the
laws are:
- Unit
mconcat
(pure
x) = x- Multiplication
mconcat
(join
xss) =mconcat
(fmap
mconcat
xss)- Subclass
mconcat
(toList
xs) =sconcat
xs
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 newtype
s and make those instances
of Monoid
, e.g. Sum
and Product
.
NOTE: Semigroup
is a superclass of Monoid
since base-4.11.0.0.
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
since base-4.11.0.0.
Should it be implemented manually, since 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
Instances details
This constraint is arguably too strong. However,
as some types (such as Natural
) have undefined complement
, this is the
only safe choice.
Since: base-4.16
This constraint is arguably
too strong. However, as some types (such as Natural
) have undefined
complement
, this is the only safe choice.
Since: base-4.16
on comparisons always returns mempty
EQ
. Without
newtypes this equals
.pure
(pure
EQ)
mempty :: Comparison a mempty = Comparison _ _ -> EQ
Instance details
Defined in Data.Functor.Contravariant
Methods
mempty :: Comparison a Source #
mappend :: Comparison a -> Comparison a -> Comparison a Source #
mconcat :: [Comparison a] -> Comparison a Source #
on equivalences always returns mempty
True
. Without
newtypes this equals
.pure
(pure
True)
mempty :: Equivalence a mempty = Equivalence _ _ -> True
Instance details
Defined in Data.Functor.Contravariant
Methods
mempty :: Equivalence a Source #
mappend :: Equivalence a -> Equivalence a -> Equivalence a Source #
mconcat :: [Equivalence a] -> Equivalence a Source #
on predicates always returns mempty
True
. Without
newtypes this equals
.pure
True
mempty :: Predicate a mempty = _ -> True
Instance details
Defined in Data.Semigroup
Methods
mempty :: WrappedMonoid m Source #
mappend :: WrappedMonoid m -> WrappedMonoid m -> WrappedMonoid m Source #
mconcat :: [WrappedMonoid m] -> WrappedMonoid m Source #
Instance details
Defined in GHC.Generics
Methods
mempty :: Generically a Source #
mappend :: Generically a -> Generically a -> Generically a Source #
mconcat :: [Generically a] -> Generically a Source #
Lift a semigroup into Maybe
forming a Monoid
according to
http://en.wikipedia.org/wiki/Monoid: "Any semigroup S
may be
turned into a monoid simply by adjoining an element e
not in S
and defining e*e = e
and e*s = s = s*e
for all s ∈ S
."
Since 4.11.0: constraint on inner a
value generalised from
Monoid
to Semigroup
.
Since: base-2.1
without newtypes is mempty
@(Op a b)mempty @(b->a)
= _ -> mempty
.
mempty :: Op a b mempty = Op _ -> mempty
(<>) :: 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
Instances details
Instance details
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 #
Instance details
Defined in Data.Foldable1
Methods
fold1 :: Semigroup m => Dual m -> m Source #
foldMap1 :: Semigroup m => (a -> m) -> Dual a -> m Source #
foldMap1' :: Semigroup m => (a -> m) -> Dual a -> m Source #
toNonEmpty :: Dual a -> NonEmpty a Source #
maximum :: Ord a => Dual a -> a Source #
minimum :: Ord a => Dual a -> a Source #
foldrMap1 :: (a -> b) -> (a -> b -> b) -> Dual a -> b Source #
foldlMap1' :: (a -> b) -> (b -> a -> b) -> Dual a -> b Source #
foldlMap1 :: (a -> b) -> (b -> a -> b) -> Dual a -> b Source #
foldrMap1' :: (a -> b) -> (a -> b -> b) -> Dual a -> b Source #
Instance details
Defined in Data.Traversable
Instance details
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 #
Instance details
Defined in Data.Semigroup.Internal
Instance details
Defined in Data.Semigroup.Internal
Instance details
Defined in Data.Semigroup.Internal
The monoid of endomorphisms under composition.
>>>
let computation = Endo ("Hello, " ++) <> Endo (++ "!")
>>>
appEndo computation "Haskell"
"Hello, Haskell!"
Instances
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
Instances details
Instance details
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 #
Instance details
Defined in Data.Semigroup.Internal
Instance details
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
Instances details
Instance details
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 #
Instance details
Defined in Data.Semigroup.Internal
Instance details
Defined in Data.Semigroup.Internal
Num
wrappers
Monoid under addition.
>>>
getSum (Sum 1 <> Sum 2 <> mempty)
3
Instances
Instances details
Instance details
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 #
Instance details
Defined in Data.Foldable1
Methods
fold1 :: Semigroup m => Sum m -> m Source #
foldMap1 :: Semigroup m => (a -> m) -> Sum a -> m Source #
foldMap1' :: Semigroup m => (a -> m) -> Sum a -> m Source #
toNonEmpty :: Sum a -> NonEmpty a Source #
maximum :: Ord a => Sum a -> a Source #
minimum :: Ord a => Sum a -> a Source #
foldrMap1 :: (a -> b) -> (a -> b -> b) -> Sum a -> b Source #
foldlMap1' :: (a -> b) -> (b -> a -> b) -> Sum a -> b Source #
foldlMap1 :: (a -> b) -> (b -> a -> b) -> Sum a -> b Source #
foldrMap1' :: (a -> b) -> (a -> b -> b) -> Sum a -> b Source #
Instance details
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 #
Instance details
Defined in Data.Semigroup.Internal
Instance details
Defined in Data.Semigroup.Internal
Instance details
Defined in Data.Semigroup.Internal
Instance details
Defined in Data.Semigroup.Internal
Monoid under multiplication.
>>>
getProduct (Product 3 <> Product 4 <> mempty)
12
Instances
Instances details
Instance details
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 #
Instance details
Defined in Data.Foldable1
Methods
fold1 :: Semigroup m => Product m -> m Source #
foldMap1 :: Semigroup m => (a -> m) -> Product a -> m Source #
foldMap1' :: Semigroup m => (a -> m) -> Product a -> m Source #
toNonEmpty :: Product a -> NonEmpty a Source #
maximum :: Ord a => Product a -> a Source #
minimum :: Ord a => Product a -> a Source #
head :: Product a -> a Source #
last :: Product a -> a Source #
foldrMap1 :: (a -> b) -> (a -> b -> b) -> Product a -> b Source #
foldlMap1' :: (a -> b) -> (b -> a -> b) -> Product a -> b Source #
foldlMap1 :: (a -> b) -> (b -> a -> b) -> Product a -> b Source #
foldrMap1' :: (a -> b) -> (a -> b -> b) -> Product a -> b Source #
Instance details
Defined in Data.Traversable
Instance details
Defined in Data.Semigroup.Internal
Instance details
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 #
Instance details
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 #
Instance details
Defined in Data.Semigroup.Internal
Methods
compare :: Product a -> Product a -> Ordering Source #
(<) :: Product a -> Product a -> Bool Source #
(<=) :: Product a -> Product a -> Bool Source #
(>) :: Product a -> Product a -> Bool Source #
(>=) :: Product a -> Product a -> Bool Source #
Instance details
Defined in Data.Semigroup.Internal
Instance details
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 Map
s 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.Functor
insertLookupWithKey :: 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.
is isomorphic to First
a
, but precedes it
historically.Alt
Maybe
a
>>>
getFirst (First (Just "hello") <> First Nothing <> First (Just "world"))
Just "hello"
Beware that Data.Monoid.
First
is different from
Data.Semigroup.
First
. The former returns the first non-Nothing
,
so Data.Monoid.First Nothing <> x = x
. The latter simply returns the first value,
thus Data.Semigroup.First Nothing <> x = Data.Semigroup.First Nothing
.
Instances
Instances details
Instance details
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 #
Instance details
Defined in Data.Traversable
Instance details
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 #
Instance details
Defined in Data.Monoid
Instance details
Defined in Data.Monoid
Instance details
Defined in Data.Monoid
Maybe monoid returning the rightmost non-Nothing
value.
is isomorphic to Last
a
, and thus to
Dual
(First
a)Dual
(Alt
Maybe
a)
>>>
getLast (Last (Just "hello") <> Last Nothing <> Last (Just "world"))
Just "world"
Beware that Data.Monoid.
Last
is different from
Data.Semigroup.
Last
. The former returns the last non-Nothing
,
so x <> Data.Monoid.Last Nothing = x
. The latter simply returns the last value,
thus x <> Data.Semigroup.Last Nothing = Data.Semigroup.Last Nothing
.
Instances
Instances details
Instance details
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 #
Instance details
Defined in Data.Traversable
Instance details
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 #
Instance details
Defined in Data.Monoid
Instance details
Defined in Data.Monoid
Instance details
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
Instances details
Instance details
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 #
Instance details
Defined in Data.Foldable1
Methods
fold1 :: Semigroup m => Alt f m -> m Source #
foldMap1 :: Semigroup m => (a -> m) -> Alt f a -> m Source #
foldMap1' :: Semigroup m => (a -> m) -> Alt f a -> m Source #
toNonEmpty :: Alt f a -> NonEmpty a Source #
maximum :: Ord a => Alt f a -> a Source #
minimum :: Ord a => Alt f a -> a Source #
foldrMap1 :: (a -> b) -> (a -> b -> b) -> Alt f a -> b Source #
foldlMap1' :: (a -> b) -> (b -> a -> b) -> Alt f a -> b Source #
foldlMap1 :: (a -> b) -> (b -> a -> b) -> Alt f a -> b Source #
foldrMap1' :: (a -> b) -> (a -> b -> b) -> Alt f a -> b Source #
Instance details
Defined in Data.Traversable
Instance details
Defined in Data.Semigroup.Internal
Instance details
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 #
Instance details
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 #
Instance details
Defined in Data.Semigroup.Internal
Instance details
Defined in Data.Semigroup.Internal
Instance details
Defined in Data.Semigroup.Internal
Instance details
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
Instances details
Instance details
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 #
Instance details
Defined in Data.Foldable1
Methods
fold1 :: Semigroup m => Ap f m -> m Source #
foldMap1 :: Semigroup m => (a -> m) -> Ap f a -> m Source #
foldMap1' :: Semigroup m => (a -> m) -> Ap f a -> m Source #
toNonEmpty :: Ap f a -> NonEmpty a Source #
maximum :: Ord a => Ap f a -> a Source #
minimum :: Ord a => Ap f a -> a Source #
foldrMap1 :: (a -> b) -> (a -> b -> b) -> Ap f a -> b Source #
foldlMap1' :: (a -> b) -> (b -> a -> b) -> Ap f a -> b Source #
foldlMap1 :: (a -> b) -> (b -> a -> b) -> Ap f a -> b Source #
foldrMap1' :: (a -> b) -> (a -> b -> b) -> Ap f a -> b Source #
Instance details
Defined in Data.Traversable
Instance details
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 #
Instance details
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 #
Note that even if the underlying Num
and Applicative
instances are
lawful, for most Applicative
s, this instance will not be lawful. If you use
this instance with the list Applicative
, the following customary laws will
not hold:
Commutativity:
>>>
Ap [10,20] + Ap [1,2]
Ap {getAp = [11,12,21,22]}>>>
Ap [1,2] + Ap [10,20]
Ap {getAp = [11,21,12,22]}
Additive inverse:
>>>
Ap [] + negate (Ap [])
Ap {getAp = []}>>>
fromInteger 0 :: Ap [] Int
Ap {getAp = [0]}
Distributivity:
>>>
Ap [1,2] * (3 + 4)
Ap {getAp = [7,14]}>>>
(Ap [1,2] * 3) + (Ap [1,2] * 4)
Ap {getAp = [7,11,10,14]}
Since: base-4.12.0.0
Instance details
Defined in Data.Monoid
Instance details
Defined in Data.Monoid
Instance details
Defined in Data.Monoid
Instance details
Defined in Data.Monoid