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 | Safe |
Language | Haskell2010 |
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 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 :: k -> Type) (a :: k) = Alt {
- getAlt :: f a
- newtype Ap (f :: k -> Type) (a :: k) = 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.
Identity of mappend
Examples
>>>
"Hello world" <> mempty
"Hello world"
>>>
mempty <> [1, 2, 3]
[1,2,3]
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
Monoid ByteArray Source # | Since: base-4.17.0.0 |
Monoid All | Since: base-2.1 |
Monoid Any | Since: base-2.1 |
Monoid Event | Since: base-4.4.0.0 |
Monoid EventLifetime | Since: base-4.8.0.0 |
Monoid Lifetime |
Since: base-4.8.0.0 |
Monoid ExceptionContext | |
Defined in GHC.Internal.Exception.Context | |
Monoid Ordering | Since: base-2.1 |
Monoid () | Since: base-2.1 |
Monoid (Comparison a) Source # |
mempty :: Comparison a mempty = Comparison _ _ -> EQ |
Defined in Data.Functor.Contravariant mempty :: Comparison a Source # mappend :: Comparison a -> Comparison a -> Comparison a Source # mconcat :: [Comparison a] -> Comparison a Source # | |
Monoid (Equivalence a) Source # |
mempty :: Equivalence a mempty = Equivalence _ _ -> True |
Defined in Data.Functor.Contravariant mempty :: Equivalence a Source # mappend :: Equivalence a -> Equivalence a -> Equivalence a Source # mconcat :: [Equivalence a] -> Equivalence a Source # | |
Monoid (Predicate a) Source # |
mempty :: Predicate a mempty = _ -> True |
(Ord a, Bounded a) => Monoid (Max a) Source # | Since: base-4.9.0.0 |
(Ord a, Bounded a) => Monoid (Min a) Source # | Since: base-4.9.0.0 |
Monoid m => Monoid (WrappedMonoid m) Source # | Since: base-4.9.0.0 |
Defined in Data.Semigroup mempty :: WrappedMonoid m Source # mappend :: WrappedMonoid m -> WrappedMonoid m -> WrappedMonoid m Source # mconcat :: [WrappedMonoid m] -> WrappedMonoid m Source # | |
Monoid a => Monoid (STM a) | Since: base-4.17.0.0 |
FiniteBits a => Monoid (And a) | This constraint is arguably too strong. However,
as some types (such as Since: base-4.16 |
FiniteBits a => Monoid (Iff a) | This constraint is arguably
too strong. However, as some types (such as Since: base-4.16 |
Bits a => Monoid (Ior a) | Since: base-4.16 |
Bits a => Monoid (Xor a) | Since: base-4.16 |
Monoid a => Monoid (Identity a) | Since: base-4.9.0.0 |
Ord a => Monoid (Max a) | Since: base-4.8.0.0 |
Ord a => Monoid (Min a) | Since: base-4.8.0.0 |
Monoid (First a) | Since: base-2.1 |
Monoid (Last a) | Since: base-2.1 |
Monoid a => Monoid (Down a) | Since: base-4.11.0.0 |
Monoid a => Monoid (Dual a) | Since: base-2.1 |
Monoid (Endo a) | Since: base-2.1 |
Num a => Monoid (Product a) | Since: base-2.1 |
Num a => Monoid (Sum a) | Since: base-2.1 |
(Generic a, Monoid (Rep a ())) => Monoid (Generically a) | Since: base-4.17.0.0 |
Defined in GHC.Internal.Generics mempty :: Generically a Source # mappend :: Generically a -> Generically a -> Generically a Source # mconcat :: [Generically a] -> Generically a Source # | |
Monoid p => Monoid (Par1 p) | Since: base-4.12.0.0 |
Monoid a => Monoid (IO a) | Since: base-4.9.0.0 |
Semigroup a => Monoid (Maybe a) | Lift a semigroup into Since 4.11.0: constraint on inner Since: base-2.1 |
Monoid a => Monoid (Solo a) | Since: base-4.15 |
Monoid [a] | Since: base-2.1 |
Monoid a => Monoid (Op a b) Source # |
mempty :: Op a b mempty = Op _ -> mempty |
Monoid (Proxy s) | Since: base-4.7.0.0 |
Monoid (U1 p) | Since: base-4.12.0.0 |
Monoid a => Monoid (ST s a) | Since: base-4.11.0.0 |
(Monoid a, Monoid b) => Monoid (a, b) | Since: base-2.1 |
Monoid b => Monoid (a -> b) | Since: base-2.1 |
Monoid a => Monoid (Const a b) | Since: base-4.9.0.0 |
(Applicative f, Monoid a) => Monoid (Ap f a) | Since: base-4.12.0.0 |
Alternative f => Monoid (Alt f a) | Since: base-4.8.0.0 |
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 |
(Monoid (f a), Monoid (g a)) => Monoid (Product f g a) Source # | Since: base-4.16.0.0 |
(Monoid (f p), Monoid (g p)) => Monoid ((f :*: g) p) | Since: base-4.12.0.0 |
Monoid c => Monoid (K1 i c 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 (g a)) => Monoid (Compose f g a) Source # | Since: base-4.16.0.0 |
Monoid (f (g p)) => Monoid ((f :.: g) p) | Since: base-4.12.0.0 |
Monoid (f p) => Monoid (M1 i c f 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.
Examples
>>>
[1,2,3] <> [4,5,6]
[1,2,3,4,5,6]
>>>
Just [1, 2, 3] <> Just [4, 5, 6]
Just [1,2,3,4,5,6]
>>>
putStr "Hello, " <> putStrLn "World!"
Hello, World!
The dual of a Monoid
, obtained by swapping the arguments of (<>)
.
Dual a <> Dual b == Dual (b <> a)
Examples
>>>
Dual "Hello" <> Dual "World"
Dual {getDual = "WorldHello"}
>>>
Dual (Dual "Hello") <> Dual (Dual "World")
Dual {getDual = Dual {getDual = "HelloWorld"}}
Instances
MonadZip Dual Source # | Since: base-4.8.0.0 | ||||
Foldable1 Dual Source # | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 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 # | |||||
Applicative Dual | Since: base-4.8.0.0 | ||||
Functor Dual | Since: base-4.8.0.0 | ||||
Monad Dual | Since: base-4.8.0.0 | ||||
MonadFix Dual | Since: base-4.8.0.0 | ||||
Foldable Dual | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Foldable 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 | ||||
Generic1 Dual | |||||
Defined in GHC.Internal.Data.Semigroup.Internal
| |||||
Monoid a => Monoid (Dual a) | Since: base-2.1 | ||||
Semigroup a => Semigroup (Dual a) | Since: base-4.9.0.0 | ||||
Data a => Data (Dual a) | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Data 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 # | |||||
Bounded a => Bounded (Dual a) | Since: base-2.1 | ||||
Generic (Dual a) | |||||
Defined in GHC.Internal.Data.Semigroup.Internal
| |||||
Read a => Read (Dual a) | Since: base-2.1 | ||||
Show a => Show (Dual a) | Since: base-2.1 | ||||
Eq a => Eq (Dual a) | Since: base-2.1 | ||||
Ord a => Ord (Dual a) | Since: base-2.1 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
type Rep1 Dual | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
type Rep (Dual a) | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal |
The monoid of endomorphisms under composition.
Endo f <> Endo g == Endo (f . g)
Examples
>>>
let computation = Endo ("Hello, " ++) <> Endo (++ "!")
>>>
appEndo computation "Haskell"
"Hello, Haskell!"
>>>
let computation = Endo (*3) <> Endo (+1)
>>>
appEndo computation 1
6
Instances
Monoid (Endo a) | Since: base-2.1 | ||||
Semigroup (Endo a) | Since: base-4.9.0.0 | ||||
Generic (Endo a) | |||||
Defined in GHC.Internal.Data.Semigroup.Internal
| |||||
type Rep (Endo a) | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal |
Bool
wrappers
Boolean monoid under conjunction (&&)
.
All x <> All y = All (x && y)
Examples
>>>
All True <> mempty <> All False)
All {getAll = False}
>>>
mconcat (map (\x -> All (even x)) [2,4,6,7,8])
All {getAll = False}
>>>
All True <> mempty
All {getAll = True}
Instances
Monoid All | Since: base-2.1 | ||||
Semigroup All | Since: base-4.9.0.0 | ||||
Data All | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Data 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 # | |||||
Bounded All | Since: base-2.1 | ||||
Generic All | |||||
Defined in GHC.Internal.Data.Semigroup.Internal
| |||||
Read All | Since: base-2.1 | ||||
Show All | Since: base-2.1 | ||||
Eq All | Since: base-2.1 | ||||
Ord All | Since: base-2.1 | ||||
type Rep All | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal |
Boolean monoid under disjunction (||)
.
Any x <> Any y = Any (x || y)
Examples
>>>
Any True <> mempty <> Any False
Any {getAny = True}
>>>
mconcat (map (\x -> Any (even x)) [2,4,6,7,8])
Any {getAny = True}
>>>
Any False <> mempty
Any {getAny = False}
Instances
Monoid Any | Since: base-2.1 | ||||
Semigroup Any | Since: base-4.9.0.0 | ||||
Data Any | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Data 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 # | |||||
Bounded Any | Since: base-2.1 | ||||
Generic Any | |||||
Defined in GHC.Internal.Data.Semigroup.Internal
| |||||
Read Any | Since: base-2.1 | ||||
Show Any | Since: base-2.1 | ||||
Eq Any | Since: base-2.1 | ||||
Ord Any | Since: base-2.1 | ||||
type Rep Any | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal |
Num
wrappers
Monoid under addition.
Sum a <> Sum b = Sum (a + b)
Examples
>>>
Sum 1 <> Sum 2 <> mempty
Sum {getSum = 3}
>>>
mconcat [ Sum n | n <- [3 .. 9]]
Sum {getSum = 42}
Instances
MonadZip Sum Source # | Since: base-4.8.0.0 | ||||
Foldable1 Sum Source # | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 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 # | |||||
Applicative Sum | Since: base-4.8.0.0 | ||||
Functor Sum | Since: base-4.8.0.0 | ||||
Monad Sum | Since: base-4.8.0.0 | ||||
MonadFix Sum | Since: base-4.8.0.0 | ||||
Foldable Sum | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Foldable 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 | ||||
Generic1 Sum | |||||
Defined in GHC.Internal.Data.Semigroup.Internal
| |||||
Num a => Monoid (Sum a) | Since: base-2.1 | ||||
Num a => Semigroup (Sum a) | Since: base-4.9.0.0 | ||||
Data a => Data (Sum a) | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Data 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 # | |||||
Bounded a => Bounded (Sum a) | Since: base-2.1 | ||||
Generic (Sum a) | |||||
Defined in GHC.Internal.Data.Semigroup.Internal
| |||||
Num a => Num (Sum a) | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
Read a => Read (Sum a) | Since: base-2.1 | ||||
Show a => Show (Sum a) | Since: base-2.1 | ||||
Eq a => Eq (Sum a) | Since: base-2.1 | ||||
Ord a => Ord (Sum a) | Since: base-2.1 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
type Rep1 Sum | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
type Rep (Sum a) | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal |
Monoid under multiplication.
Product x <> Product y == Product (x * y)
Examples
>>>
Product 3 <> Product 4 <> mempty
Product {getProduct = 12}
>>>
mconcat [ Product n | n <- [2 .. 10]]
Product {getProduct = 3628800}
Product | |
|
Instances
MonadZip Product Source # | Since: base-4.8.0.0 | ||||
Foldable1 Product Source # | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 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 # | |||||
Applicative Product | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
Functor Product | Since: base-4.8.0.0 | ||||
Monad Product | Since: base-4.8.0.0 | ||||
MonadFix Product | Since: base-4.8.0.0 | ||||
Foldable Product | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Foldable 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 GHC.Internal.Data.Traversable | |||||
Generic1 Product | |||||
Defined in GHC.Internal.Data.Semigroup.Internal
| |||||
Num a => Monoid (Product a) | Since: base-2.1 | ||||
Num a => Semigroup (Product a) | Since: base-4.9.0.0 | ||||
Data a => Data (Product a) | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Data 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 # | |||||
Bounded a => Bounded (Product a) | Since: base-2.1 | ||||
Generic (Product a) | |||||
Defined in GHC.Internal.Data.Semigroup.Internal
| |||||
Num a => Num (Product a) | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal (+) :: 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 # | |||||
Read a => Read (Product a) | Since: base-2.1 | ||||
Show a => Show (Product a) | Since: base-2.1 | ||||
Eq a => Eq (Product a) | Since: base-2.1 | ||||
Ord a => Ord (Product a) | Since: base-2.1 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
type Rep1 Product | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
type Rep (Product a) | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal |
Maybe
wrappers
Maybe monoid returning the leftmost non-Nothing
value.
is isomorphic to First
a
, but precedes it
historically.Alt
Maybe
a
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
.
Examples
>>>
First (Just "hello") <> First Nothing <> First (Just "world")
First {getFirst = Just "hello"}
>>>
First Nothing <> mempty
First {getFirst = Nothing}
Instances
MonadZip First Source # | Since: base-4.8.0.0 | ||||
Applicative First | Since: base-4.8.0.0 | ||||
Functor First | Since: base-4.8.0.0 | ||||
Monad First | Since: base-4.8.0.0 | ||||
MonadFix First | Since: base-4.8.0.0 | ||||
Foldable First | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Foldable 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 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Generic1 First | |||||
Defined in GHC.Internal.Data.Monoid
| |||||
Monoid (First a) | Since: base-2.1 | ||||
Semigroup (First a) | Since: base-4.9.0.0 | ||||
Data a => Data (First a) | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Data 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 # | |||||
Generic (First a) | |||||
Defined in GHC.Internal.Data.Monoid
| |||||
Read a => Read (First a) | Since: base-2.1 | ||||
Show a => Show (First a) | Since: base-2.1 | ||||
Eq a => Eq (First a) | Since: base-2.1 | ||||
Ord a => Ord (First a) | Since: base-2.1 | ||||
Defined in GHC.Internal.Data.Monoid | |||||
type Rep1 First | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Monoid | |||||
type Rep (First a) | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.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)
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
.
Examples
>>>
Last (Just "hello") <> Last Nothing <> Last (Just "world")
Last {getLast = Just "world"}
>>>
Last Nothing <> mempty
Last {getLast = Nothing}
Instances
MonadZip Last Source # | Since: base-4.8.0.0 | ||||
Applicative Last | Since: base-4.8.0.0 | ||||
Functor Last | Since: base-4.8.0.0 | ||||
Monad Last | Since: base-4.8.0.0 | ||||
MonadFix Last | Since: base-4.8.0.0 | ||||
Foldable Last | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Foldable 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 | ||||
Generic1 Last | |||||
Defined in GHC.Internal.Data.Monoid
| |||||
Monoid (Last a) | Since: base-2.1 | ||||
Semigroup (Last a) | Since: base-4.9.0.0 | ||||
Data a => Data (Last a) | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Data 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 # | |||||
Generic (Last a) | |||||
Defined in GHC.Internal.Data.Monoid
| |||||
Read a => Read (Last a) | Since: base-2.1 | ||||
Show a => Show (Last a) | Since: base-2.1 | ||||
Eq a => Eq (Last a) | Since: base-2.1 | ||||
Ord a => Ord (Last a) | Since: base-2.1 | ||||
Defined in GHC.Internal.Data.Monoid | |||||
type Rep1 Last | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Monoid | |||||
type Rep (Last a) | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Monoid |
Alternative
wrapper
newtype Alt (f :: k -> Type) (a :: k) Source #
Monoid under <|>
.
Alt l <> Alt r == Alt (l <|> r)
Examples
>>>
Alt (Just 12) <> Alt (Just 24)
Alt {getAlt = Just 12}
>>>
Alt Nothing <> Alt (Just 24)
Alt {getAlt = Just 24}
Since: base-4.8.0.0
Instances
Generic1 (Alt f :: k -> Type) | |||||
Defined in GHC.Internal.Data.Semigroup.Internal
| |||||
MonadZip f => MonadZip (Alt f) Source # | Since: base-4.8.0.0 | ||||
Foldable1 f => Foldable1 (Alt f) Source # | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 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 # | |||||
Contravariant f => Contravariant (Alt f) Source # | |||||
Alternative f => Alternative (Alt f) | Since: base-4.8.0.0 | ||||
Applicative f => Applicative (Alt f) | Since: base-4.8.0.0 | ||||
Functor f => Functor (Alt f) | Since: base-4.8.0.0 | ||||
Monad f => Monad (Alt f) | Since: base-4.8.0.0 | ||||
MonadPlus f => MonadPlus (Alt f) | Since: base-4.8.0.0 | ||||
MonadFix f => MonadFix (Alt f) | Since: base-4.8.0.0 | ||||
Foldable f => Foldable (Alt f) | Since: base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Foldable 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 GHC.Internal.Data.Traversable | |||||
Alternative f => Monoid (Alt f a) | Since: base-4.8.0.0 | ||||
Alternative f => Semigroup (Alt f a) | Since: base-4.9.0.0 | ||||
(Data (f a), Data a, Typeable f) => Data (Alt f a) | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Data 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 # | |||||
Enum (f a) => Enum (Alt f a) | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal 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 # | |||||
Generic (Alt f a) | |||||
Defined in GHC.Internal.Data.Semigroup.Internal
| |||||
Num (f a) => Num (Alt f a) | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.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 | ||||
Eq (f a) => Eq (Alt f a) | Since: base-4.8.0.0 | ||||
Ord (f a) => Ord (Alt f a) | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
type Rep1 (Alt f :: k -> Type) | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
type Rep (Alt f a) | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal |
Applicative
wrapper
newtype Ap (f :: k -> Type) (a :: k) Source #
This data type witnesses the lifting of a Monoid
into an
Applicative
pointwise.
Examples
>>>
Ap (Just [1, 2, 3]) <> Ap Nothing
Ap {getAp = Nothing}
>>>
Ap [Sum 10, Sum 20] <> Ap [Sum 1, Sum 2]
Ap {getAp = [Sum {getSum = 11},Sum {getSum = 12},Sum {getSum = 21},Sum {getSum = 22}]}
Since: base-4.12.0.0
Instances
Generic1 (Ap f :: k -> Type) | |||||
Defined in GHC.Internal.Data.Monoid
| |||||
Foldable1 f => Foldable1 (Ap f) Source # | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 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 # | |||||
Alternative f => Alternative (Ap f) | Since: base-4.12.0.0 | ||||
Applicative f => Applicative (Ap f) | Since: base-4.12.0.0 | ||||
Functor f => Functor (Ap f) | Since: base-4.12.0.0 | ||||
Monad f => Monad (Ap f) | Since: base-4.12.0.0 | ||||
MonadPlus f => MonadPlus (Ap f) | Since: base-4.12.0.0 | ||||
MonadFail f => MonadFail (Ap f) | Since: base-4.12.0.0 | ||||
MonadFix f => MonadFix (Ap f) | Since: base-4.12.0.0 | ||||
Foldable f => Foldable (Ap f) | Since: base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Foldable 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 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
(Applicative f, Monoid a) => Monoid (Ap f a) | Since: base-4.12.0.0 | ||||
(Applicative f, Semigroup a) => Semigroup (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 GHC.Internal.Data.Data 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, 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 GHC.Internal.Data.Monoid 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 # | |||||
Generic (Ap f a) | |||||
Defined in GHC.Internal.Data.Monoid
| |||||
(Applicative f, Num a) => Num (Ap f a) | Note that even if the underlying Commutativity:
Additive inverse:
Distributivity:
Since: base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Monoid | |||||
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 | ||||
Eq (f a) => Eq (Ap f a) | Since: base-4.12.0.0 | ||||
Ord (f a) => Ord (Ap f a) | Since: base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Monoid | |||||
type Rep1 (Ap f :: k -> Type) | Since: base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Monoid | |||||
type Rep (Ap f a) | Since: base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Monoid |