Copyright | (C) 2011-2015 Edward Kmett |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | libraries@haskell.org |
Stability | provisional |
Portability | portable |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Data.Semigroup
Description
A type a
is a Semigroup
if it provides an associative function (<>
)
that lets you combine any two values of type a
into one. Where being
associative means that the following must always hold:
(a <> b) <> c == a <> (b <> c)
Examples
The Min
Semigroup
instance for Int
is defined to always pick the smaller
number:
>>>
Min 1 <> Min 2 <> Min 3 <> Min 4 :: Min Int
Min {getMin = 1}
If we need to combine multiple values we can use the sconcat
function
to do so. We need to ensure however that we have at least one value to
operate on, since otherwise our result would be undefined. It is for this
reason that sconcat
uses Data.List.NonEmpty.NonEmpty - a list that
can never be empty:
>>>
(1 :| [])
1 :| []
- - equivalent to [1] but guaranteed to be non-empty.
>>>
(1 :| [2, 3, 4])
1 :| [2,3,4]
- - equivalent to [1,2,3,4] but guaranteed to be non-empty.
Equipped with this guaranteed to be non-empty data structure, we can combine
values using sconcat
and a Semigroup
of our choosing. We can try the Min
and Max
instances of Int
which pick the smallest, or largest number
respectively:
>>>
sconcat (1 :| [2, 3, 4]) :: Min Int
Min {getMin = 1}
>>>
sconcat (1 :| [2, 3, 4]) :: Max Int
Max {getMax = 4}
String concatenation is another example of a Semigroup
instance:
>>>
"foo" <> "bar"
"foobar"
A Semigroup
is a generalization of a Monoid
. Yet unlike the Semigroup
, the Monoid
requires the presence of a neutral element (mempty
) in addition to the associative
operator. The requirement for a neutral element prevents many types from being a full Monoid,
like Data.List.NonEmpty.NonEmpty.
Note that the use of (<>)
in this module conflicts with an operator with the same
name that is being exported by Data.Monoid. However, this package
re-exports (most of) the contents of Data.Monoid, so to use semigroups
and monoids in the same package just
import Data.Semigroup
Since: base-4.9.0.0
Synopsis
- class Semigroup a where
- stimesMonoid :: (Integral b, Monoid a) => b -> a -> a
- stimesIdempotent :: Integral b => b -> a -> a
- stimesIdempotentMonoid :: (Integral b, Monoid a) => b -> a -> a
- mtimesDefault :: (Integral b, Monoid a) => b -> a -> a
- newtype Min a = Min {
- getMin :: a
- newtype Max a = Max {
- getMax :: a
- newtype First a = First {
- getFirst :: a
- newtype Last a = Last {
- getLast :: a
- newtype WrappedMonoid m = WrapMonoid {
- unwrapMonoid :: m
- 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
- diff :: Semigroup m => m -> Endo m
- cycle1 :: Semigroup m => m -> m
- data Arg a b = Arg a b
- type ArgMin a b = Min (Arg a b)
- type ArgMax a b = Max (Arg a b)
Documentation
class Semigroup a where Source #
The class of semigroups (types with an associative binary operation).
Instances should satisfy the following:
You can alternatively define sconcat
instead of (<>
), in which case the
laws are:
Since: base-4.9.0.0
Methods
(<>) :: 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!
sconcat :: NonEmpty a -> a Source #
Reduce a non-empty list with <>
The default definition should be sufficient, but this can be overridden for efficiency.
Examples
For the following examples, we will assume that we have:
>>>
import Data.List.NonEmpty (NonEmpty (..))
>>>
sconcat $ "Hello" :| [" ", "Haskell", "!"]
"Hello Haskell!"
>>>
sconcat $ Just [1, 2, 3] :| [Nothing, Just [4, 5, 6]]
Just [1,2,3,4,5,6]
>>>
sconcat $ Left 1 :| [Right 2, Left 3, Right 4]
Right 2
stimes :: Integral b => b -> a -> a Source #
Repeat a value n
times.
The default definition will raise an exception for a multiplier that is <= 0
.
This may be overridden with an implementation that is total. For monoids
it is preferred to use stimesMonoid
.
By making this a member of the class, idempotent semigroups
and monoids can upgrade this to execute in O(1) by
picking stimes =
or stimesIdempotent
stimes =
respectively.stimesIdempotentMonoid
Examples
>>>
stimes 4 [1]
[1,1,1,1]
>>>
stimes 5 (putStr "hi!")
hi!hi!hi!hi!hi!
>>>
stimes 3 (Right ":)")
Right ":)"
Instances
Semigroup ByteArray Source # | Since: base-4.17.0.0 |
Semigroup Void Source # | Since: base-4.9.0.0 |
Semigroup All Source # | Since: base-4.9.0.0 |
Semigroup Any Source # | Since: base-4.9.0.0 |
Semigroup Event Source # | Since: base-4.10.0.0 |
Semigroup EventLifetime Source # | Since: base-4.11.0.0 |
Semigroup Lifetime Source # | Since: base-4.10.0.0 |
Semigroup ExceptionContext Source # | |
Defined in GHC.Internal.Exception.Context Methods (<>) :: ExceptionContext -> ExceptionContext -> ExceptionContext Source # sconcat :: NonEmpty ExceptionContext -> ExceptionContext Source # stimes :: Integral b => b -> ExceptionContext -> ExceptionContext Source # | |
Semigroup Ordering Source # | Since: base-4.9.0.0 |
Semigroup () Source # | Since: base-4.9.0.0 |
Semigroup (Comparison a) Source # |
(<>) :: Comparison a -> Comparison a -> Comparison a Comparison cmp <> Comparison cmp' = Comparison a a' -> cmp a a' <> cmp a a' |
Defined in Data.Functor.Contravariant Methods (<>) :: Comparison a -> Comparison a -> Comparison a Source # sconcat :: NonEmpty (Comparison a) -> Comparison a Source # stimes :: Integral b => b -> Comparison a -> Comparison a Source # | |
Semigroup (Equivalence a) Source # |
(<>) :: Equivalence a -> Equivalence a -> Equivalence a Equivalence equiv <> Equivalence equiv' = Equivalence a b -> equiv a b && equiv' a b |
Defined in Data.Functor.Contravariant Methods (<>) :: Equivalence a -> Equivalence a -> Equivalence a Source # sconcat :: NonEmpty (Equivalence a) -> Equivalence a Source # stimes :: Integral b => b -> Equivalence a -> Equivalence a Source # | |
Semigroup (Predicate a) Source # |
(<>) :: Predicate a -> Predicate a -> Predicate a Predicate pred <> Predicate pred' = Predicate a -> pred a && pred' a |
Semigroup (First a) Source # | Since: base-4.9.0.0 |
Semigroup (Last a) Source # | Since: base-4.9.0.0 |
Ord a => Semigroup (Max a) Source # | Since: base-4.9.0.0 |
Ord a => Semigroup (Min a) Source # | Since: base-4.9.0.0 |
Monoid m => Semigroup (WrappedMonoid m) Source # | Since: base-4.9.0.0 |
Defined in Data.Semigroup Methods (<>) :: WrappedMonoid m -> WrappedMonoid m -> WrappedMonoid m Source # sconcat :: NonEmpty (WrappedMonoid m) -> WrappedMonoid m Source # stimes :: Integral b => b -> WrappedMonoid m -> WrappedMonoid m Source # | |
Semigroup (NonEmpty a) Source # | Since: base-4.9.0.0 |
Semigroup a => Semigroup (STM a) Source # | Since: base-4.17.0.0 |
Bits a => Semigroup (And a) Source # | Since: base-4.16 |
FiniteBits a => Semigroup (Iff a) Source # | This constraint is arguably
too strong. However, as some types (such as Since: base-4.16 |
Bits a => Semigroup (Ior a) Source # | Since: base-4.16 |
Bits a => Semigroup (Xor a) Source # | Since: base-4.16 |
Semigroup a => Semigroup (Identity a) Source # | Since: base-4.9.0.0 |
Ord a => Semigroup (Max a) Source # | Since: base-4.11.0.0 |
Ord a => Semigroup (Min a) Source # | Since: base-4.11.0.0 |
Semigroup (First a) Source # | Since: base-4.9.0.0 |
Semigroup (Last a) Source # | Since: base-4.9.0.0 |
Semigroup a => Semigroup (Down a) Source # | Since: base-4.11.0.0 |
Semigroup a => Semigroup (Dual a) Source # | Since: base-4.9.0.0 |
Semigroup (Endo a) Source # | Since: base-4.9.0.0 |
Num a => Semigroup (Product a) Source # | Since: base-4.9.0.0 |
Num a => Semigroup (Sum a) Source # | Since: base-4.9.0.0 |
(Generic a, Semigroup (Rep a ())) => Semigroup (Generically a) Source # | Since: base-4.17.0.0 |
Defined in GHC.Internal.Generics Methods (<>) :: Generically a -> Generically a -> Generically a Source # sconcat :: NonEmpty (Generically a) -> Generically a Source # stimes :: Integral b => b -> Generically a -> Generically a Source # | |
Semigroup p => Semigroup (Par1 p) Source # | Since: base-4.12.0.0 |
Semigroup a => Semigroup (Q a) Source # | Since: ghc-internal-2.17.0.0 |
Semigroup a => Semigroup (IO a) Source # | Since: base-4.10.0.0 |
Semigroup a => Semigroup (Maybe a) Source # | Since: base-4.9.0.0 |
Semigroup a => Semigroup (Solo a) Source # | Since: base-4.15 |
Semigroup [a] Source # | Since: base-4.9.0.0 |
Semigroup a => Semigroup (Op a b) Source # |
(<>) :: Op a b -> Op a b -> Op a b Op f <> Op g = Op a -> f a <> g a |
Semigroup (Either a b) Source # | Since: base-4.9.0.0 |
Semigroup (Proxy s) Source # | Since: base-4.9.0.0 |
Semigroup (U1 p) Source # | Since: base-4.12.0.0 |
Semigroup (V1 p) Source # | Since: base-4.12.0.0 |
Semigroup a => Semigroup (ST s a) Source # | Since: base-4.11.0.0 |
(Semigroup a, Semigroup b) => Semigroup (a, b) Source # | Since: base-4.9.0.0 |
Semigroup b => Semigroup (a -> b) Source # | Since: base-4.9.0.0 |
Semigroup a => Semigroup (Const a b) Source # | Since: base-4.9.0.0 |
(Applicative f, Semigroup a) => Semigroup (Ap f a) Source # | Since: base-4.12.0.0 |
Alternative f => Semigroup (Alt f a) Source # | Since: base-4.9.0.0 |
Semigroup (f p) => Semigroup (Rec1 f p) Source # | Since: base-4.12.0.0 |
(Semigroup a, Semigroup b, Semigroup c) => Semigroup (a, b, c) Source # | Since: base-4.9.0.0 |
(Semigroup (f a), Semigroup (g a)) => Semigroup (Product f g a) Source # | Since: base-4.16.0.0 |
(Semigroup (f p), Semigroup (g p)) => Semigroup ((f :*: g) p) Source # | Since: base-4.12.0.0 |
Semigroup c => Semigroup (K1 i c p) Source # | Since: base-4.12.0.0 |
(Semigroup a, Semigroup b, Semigroup c, Semigroup d) => Semigroup (a, b, c, d) Source # | Since: base-4.9.0.0 |
Semigroup (f (g a)) => Semigroup (Compose f g a) Source # | Since: base-4.16.0.0 |
Semigroup (f (g p)) => Semigroup ((f :.: g) p) Source # | Since: base-4.12.0.0 |
Semigroup (f p) => Semigroup (M1 i c f p) Source # | Since: base-4.12.0.0 |
(Semigroup a, Semigroup b, Semigroup c, Semigroup d, Semigroup e) => Semigroup (a, b, c, d, e) Source # | Since: base-4.9.0.0 |
stimesMonoid :: (Integral b, Monoid a) => b -> a -> a Source #
stimesIdempotent :: Integral b => b -> a -> a Source #
stimesIdempotentMonoid :: (Integral b, Monoid a) => b -> a -> a Source #
mtimesDefault :: (Integral b, Monoid a) => b -> a -> a Source #
Repeat a value n
times.
mtimesDefault n a = a <> a <> ... <> a -- using <> (n-1) times
In many cases,
for a stimes
0 aMonoid
will produce mempty
.
However, there are situations when it cannot do so. In particular,
the following situation is fairly common:
data T a = ... class Constraint1 a class Constraint1 a => Constraint2 a
instance Constraint1 a =>Semigroup
(T a) instance Constraint2 a =>Monoid
(T a)
Since Constraint1
is insufficient to implement mempty
,
stimes
for T a
cannot do so.
When working with such a type, or when working polymorphically with
Semigroup
instances, mtimesDefault
should be used when the
multiplier might be zero. It is implemented using stimes
when
the multiplier is nonzero and mempty
when it is zero.
Examples
>>>
mtimesDefault 0 "bark"
""
>>>
mtimesDefault 3 "meow"
"meowmeowmeow"
Semigroups
The Min
Monoid
and Semigroup
always choose the smaller element as
by the Ord
instance and min
of the contained type.
Examples
>>>
Min 42 <> Min 3
Min {getMin = 3}
>>>
sconcat $ Min 1 :| [ Min n | n <- [2 .. 100]]
Min {getMin = 1}
Instances
Foldable1 Min Source # | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 Methods fold1 :: Semigroup m => Min m -> m Source # foldMap1 :: Semigroup m => (a -> m) -> Min a -> m Source # foldMap1' :: Semigroup m => (a -> m) -> Min a -> m Source # toNonEmpty :: Min a -> NonEmpty a Source # maximum :: Ord a => Min a -> a Source # minimum :: Ord a => Min a -> a Source # foldrMap1 :: (a -> b) -> (a -> b -> b) -> Min a -> b Source # foldlMap1' :: (a -> b) -> (b -> a -> b) -> Min a -> b Source # foldlMap1 :: (a -> b) -> (b -> a -> b) -> Min a -> b Source # foldrMap1' :: (a -> b) -> (a -> b -> b) -> Min a -> b Source # | |||||
Applicative Min Source # | Since: base-4.9.0.0 | ||||
Functor Min Source # | Since: base-4.9.0.0 | ||||
Monad Min Source # | Since: base-4.9.0.0 | ||||
MonadFix Min Source # | Since: base-4.9.0.0 | ||||
Foldable Min Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Semigroup Methods fold :: Monoid m => Min m -> m Source # foldMap :: Monoid m => (a -> m) -> Min a -> m Source # foldMap' :: Monoid m => (a -> m) -> Min a -> m Source # foldr :: (a -> b -> b) -> b -> Min a -> b Source # foldr' :: (a -> b -> b) -> b -> Min a -> b Source # foldl :: (b -> a -> b) -> b -> Min a -> b Source # foldl' :: (b -> a -> b) -> b -> Min a -> b Source # foldr1 :: (a -> a -> a) -> Min a -> a Source # foldl1 :: (a -> a -> a) -> Min a -> a Source # toList :: Min a -> [a] Source # null :: Min a -> Bool Source # length :: Min a -> Int Source # elem :: Eq a => a -> Min a -> Bool Source # maximum :: Ord a => Min a -> a Source # minimum :: Ord a => Min a -> a Source # | |||||
Traversable Min Source # | Since: base-4.9.0.0 | ||||
Generic1 Min Source # | |||||
Defined in Data.Semigroup Associated Types
| |||||
(Ord a, Bounded a) => Monoid (Min a) Source # | Since: base-4.9.0.0 | ||||
Ord a => Semigroup (Min a) Source # | Since: base-4.9.0.0 | ||||
Data a => Data (Min a) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Semigroup Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Min a -> c (Min a) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Min a) Source # toConstr :: Min a -> Constr Source # dataTypeOf :: Min a -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Min a)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Min a)) Source # gmapT :: (forall b. Data b => b -> b) -> Min a -> Min a Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Min a -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Min a -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Min a -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Min a -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Min a -> m (Min a) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Min a -> m (Min a) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Min a -> m (Min a) Source # | |||||
Bounded a => Bounded (Min a) Source # | Since: base-4.9.0.0 | ||||
Enum a => Enum (Min a) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Semigroup Methods succ :: Min a -> Min a Source # pred :: Min a -> Min a Source # toEnum :: Int -> Min a Source # fromEnum :: Min a -> Int Source # enumFrom :: Min a -> [Min a] Source # enumFromThen :: Min a -> Min a -> [Min a] Source # enumFromTo :: Min a -> Min a -> [Min a] Source # enumFromThenTo :: Min a -> Min a -> Min a -> [Min a] Source # | |||||
Generic (Min a) Source # | |||||
Defined in Data.Semigroup Associated Types
| |||||
Num a => Num (Min a) Source # | Since: base-4.9.0.0 | ||||
Read a => Read (Min a) Source # | Since: base-4.9.0.0 | ||||
Show a => Show (Min a) Source # | Since: base-4.9.0.0 | ||||
Eq a => Eq (Min a) Source # | Since: base-4.9.0.0 | ||||
Ord a => Ord (Min a) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Semigroup | |||||
type Rep1 Min Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Semigroup | |||||
type Rep (Min a) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Semigroup |
The Max
Monoid
and Semigroup
always choose the bigger element as
by the Ord
instance and max
of the contained type.
Examples
>>>
Max 42 <> Max 3
Max {getMax = 42}
>>>
sconcat $ Max 1 :| [ Max n | n <- [2 .. 100]]
Max {getMax = 100}
Instances
Foldable1 Max Source # | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 Methods fold1 :: Semigroup m => Max m -> m Source # foldMap1 :: Semigroup m => (a -> m) -> Max a -> m Source # foldMap1' :: Semigroup m => (a -> m) -> Max a -> m Source # toNonEmpty :: Max a -> NonEmpty a Source # maximum :: Ord a => Max a -> a Source # minimum :: Ord a => Max a -> a Source # foldrMap1 :: (a -> b) -> (a -> b -> b) -> Max a -> b Source # foldlMap1' :: (a -> b) -> (b -> a -> b) -> Max a -> b Source # foldlMap1 :: (a -> b) -> (b -> a -> b) -> Max a -> b Source # foldrMap1' :: (a -> b) -> (a -> b -> b) -> Max a -> b Source # | |||||
Applicative Max Source # | Since: base-4.9.0.0 | ||||
Functor Max Source # | Since: base-4.9.0.0 | ||||
Monad Max Source # | Since: base-4.9.0.0 | ||||
MonadFix Max Source # | Since: base-4.9.0.0 | ||||
Foldable Max Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Semigroup Methods fold :: Monoid m => Max m -> m Source # foldMap :: Monoid m => (a -> m) -> Max a -> m Source # foldMap' :: Monoid m => (a -> m) -> Max a -> m Source # foldr :: (a -> b -> b) -> b -> Max a -> b Source # foldr' :: (a -> b -> b) -> b -> Max a -> b Source # foldl :: (b -> a -> b) -> b -> Max a -> b Source # foldl' :: (b -> a -> b) -> b -> Max a -> b Source # foldr1 :: (a -> a -> a) -> Max a -> a Source # foldl1 :: (a -> a -> a) -> Max a -> a Source # toList :: Max a -> [a] Source # null :: Max a -> Bool Source # length :: Max a -> Int Source # elem :: Eq a => a -> Max a -> Bool Source # maximum :: Ord a => Max a -> a Source # minimum :: Ord a => Max a -> a Source # | |||||
Traversable Max Source # | Since: base-4.9.0.0 | ||||
Generic1 Max Source # | |||||
Defined in Data.Semigroup Associated Types
| |||||
(Ord a, Bounded a) => Monoid (Max a) Source # | Since: base-4.9.0.0 | ||||
Ord a => Semigroup (Max a) Source # | Since: base-4.9.0.0 | ||||
Data a => Data (Max a) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Semigroup Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Max a -> c (Max a) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Max a) Source # toConstr :: Max a -> Constr Source # dataTypeOf :: Max a -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Max a)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Max a)) Source # gmapT :: (forall b. Data b => b -> b) -> Max a -> Max a Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Max a -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Max a -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Max a -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Max a -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Max a -> m (Max a) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Max a -> m (Max a) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Max a -> m (Max a) Source # | |||||
Bounded a => Bounded (Max a) Source # | Since: base-4.9.0.0 | ||||
Enum a => Enum (Max a) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Semigroup Methods succ :: Max a -> Max a Source # pred :: Max a -> Max a Source # toEnum :: Int -> Max a Source # fromEnum :: Max a -> Int Source # enumFrom :: Max a -> [Max a] Source # enumFromThen :: Max a -> Max a -> [Max a] Source # enumFromTo :: Max a -> Max a -> [Max a] Source # enumFromThenTo :: Max a -> Max a -> Max a -> [Max a] Source # | |||||
Generic (Max a) Source # | |||||
Defined in Data.Semigroup Associated Types
| |||||
Num a => Num (Max a) Source # | Since: base-4.9.0.0 | ||||
Read a => Read (Max a) Source # | Since: base-4.9.0.0 | ||||
Show a => Show (Max a) Source # | Since: base-4.9.0.0 | ||||
Eq a => Eq (Max a) Source # | Since: base-4.9.0.0 | ||||
Ord a => Ord (Max a) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Semigroup | |||||
type Rep1 Max Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Semigroup | |||||
type Rep (Max a) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Semigroup |
Beware that Data.Semigroup.
First
is different from
Data.Monoid.
First
. The former simply returns the first value,
so Data.Semigroup.First Nothing <> x = Data.Semigroup.First Nothing
.
The latter returns the first non-Nothing
,
thus Data.Monoid.First Nothing <> x = x
.
Examples
>>>
First 0 <> First 10
First {getFirst = 0}
>>>
sconcat $ First 1 :| [ First n | n <- [2 ..] ]
First {getFirst = 1}
Instances
Foldable1 First Source # | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 Methods fold1 :: Semigroup m => First m -> m Source # foldMap1 :: Semigroup m => (a -> m) -> First a -> m Source # foldMap1' :: Semigroup m => (a -> m) -> First a -> m Source # toNonEmpty :: First a -> NonEmpty a Source # maximum :: Ord a => First a -> a Source # minimum :: Ord a => First a -> a Source # foldrMap1 :: (a -> b) -> (a -> b -> b) -> First a -> b Source # foldlMap1' :: (a -> b) -> (b -> a -> b) -> First a -> b Source # foldlMap1 :: (a -> b) -> (b -> a -> b) -> First a -> b Source # foldrMap1' :: (a -> b) -> (a -> b -> b) -> First a -> b Source # | |||||
Applicative First Source # | Since: base-4.9.0.0 | ||||
Functor First Source # | Since: base-4.9.0.0 | ||||
Monad First Source # | Since: base-4.9.0.0 | ||||
MonadFix First Source # | Since: base-4.9.0.0 | ||||
Foldable First Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Semigroup Methods fold :: Monoid m => First m -> m Source # foldMap :: Monoid m => (a -> m) -> First a -> m Source # foldMap' :: Monoid m => (a -> m) -> First a -> m Source # foldr :: (a -> b -> b) -> b -> First a -> b Source # foldr' :: (a -> b -> b) -> b -> First a -> b Source # foldl :: (b -> a -> b) -> b -> First a -> b Source # foldl' :: (b -> a -> b) -> b -> First a -> b Source # foldr1 :: (a -> a -> a) -> First a -> a Source # foldl1 :: (a -> a -> a) -> First a -> a Source # toList :: First a -> [a] Source # null :: First a -> Bool Source # length :: First a -> Int Source # elem :: Eq a => a -> First a -> Bool Source # maximum :: Ord a => First a -> a Source # minimum :: Ord a => First a -> a Source # | |||||
Traversable First Source # | Since: base-4.9.0.0 | ||||
Generic1 First Source # | |||||
Defined in Data.Semigroup Associated Types
| |||||
Semigroup (First a) Source # | Since: base-4.9.0.0 | ||||
Data a => Data (First a) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Semigroup 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 # | |||||
Bounded a => Bounded (First a) Source # | Since: base-4.9.0.0 | ||||
Enum a => Enum (First a) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Semigroup Methods succ :: First a -> First a Source # pred :: First a -> First a Source # toEnum :: Int -> First a Source # fromEnum :: First a -> Int Source # enumFrom :: First a -> [First a] Source # enumFromThen :: First a -> First a -> [First a] Source # enumFromTo :: First a -> First a -> [First a] Source # enumFromThenTo :: First a -> First a -> First a -> [First a] Source # | |||||
Generic (First a) Source # | |||||
Defined in Data.Semigroup Associated Types
| |||||
Read a => Read (First a) Source # | Since: base-4.9.0.0 | ||||
Show a => Show (First a) Source # | Since: base-4.9.0.0 | ||||
Eq a => Eq (First a) Source # | Since: base-4.9.0.0 | ||||
Ord a => Ord (First a) Source # | Since: base-4.9.0.0 | ||||
type Rep1 First Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Semigroup | |||||
type Rep (First a) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Semigroup |
Beware that Data.Semigroup.
Last
is different from
Data.Monoid.
Last
. The former simply returns the last value,
so x <> Data.Semigroup.Last Nothing = Data.Semigroup.Last Nothing
.
The latter returns the last non-Nothing
,
thus x <> Data.Monoid.Last Nothing = x
.
Examples
>>>
Last 0 <> Last 10
Last {getLast = 10}
>>>
sconcat $ Last 1 :| [ Last n | n <- [2..]]
* Hangs forever *
Instances
Foldable1 Last Source # | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 Methods fold1 :: Semigroup m => Last m -> m Source # foldMap1 :: Semigroup m => (a -> m) -> Last a -> m Source # foldMap1' :: Semigroup m => (a -> m) -> Last a -> m Source # toNonEmpty :: Last a -> NonEmpty a Source # maximum :: Ord a => Last a -> a Source # minimum :: Ord a => Last a -> a Source # foldrMap1 :: (a -> b) -> (a -> b -> b) -> Last a -> b Source # foldlMap1' :: (a -> b) -> (b -> a -> b) -> Last a -> b Source # foldlMap1 :: (a -> b) -> (b -> a -> b) -> Last a -> b Source # foldrMap1' :: (a -> b) -> (a -> b -> b) -> Last a -> b Source # | |||||
Applicative Last Source # | Since: base-4.9.0.0 | ||||
Functor Last Source # | Since: base-4.9.0.0 | ||||
Monad Last Source # | Since: base-4.9.0.0 | ||||
MonadFix Last Source # | Since: base-4.9.0.0 | ||||
Foldable Last Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Semigroup Methods fold :: Monoid m => Last m -> m Source # foldMap :: Monoid m => (a -> m) -> Last a -> m Source # foldMap' :: Monoid m => (a -> m) -> Last a -> m Source # foldr :: (a -> b -> b) -> b -> Last a -> b Source # foldr' :: (a -> b -> b) -> b -> Last a -> b Source # foldl :: (b -> a -> b) -> b -> Last a -> b Source # foldl' :: (b -> a -> b) -> b -> Last a -> b Source # foldr1 :: (a -> a -> a) -> Last a -> a Source # foldl1 :: (a -> a -> a) -> Last a -> a Source # toList :: Last a -> [a] Source # null :: Last a -> Bool Source # length :: Last a -> Int Source # elem :: Eq a => a -> Last a -> Bool Source # maximum :: Ord a => Last a -> a Source # minimum :: Ord a => Last a -> a Source # | |||||
Traversable Last Source # | Since: base-4.9.0.0 | ||||
Generic1 Last Source # | |||||
Defined in Data.Semigroup Associated Types
| |||||
Semigroup (Last a) Source # | Since: base-4.9.0.0 | ||||
Data a => Data (Last a) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Semigroup 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 # | |||||
Bounded a => Bounded (Last a) Source # | Since: base-4.9.0.0 | ||||
Enum a => Enum (Last a) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Semigroup Methods succ :: Last a -> Last a Source # pred :: Last a -> Last a Source # toEnum :: Int -> Last a Source # fromEnum :: Last a -> Int Source # enumFrom :: Last a -> [Last a] Source # enumFromThen :: Last a -> Last a -> [Last a] Source # enumFromTo :: Last a -> Last a -> [Last a] Source # enumFromThenTo :: Last a -> Last a -> Last a -> [Last a] Source # | |||||
Generic (Last a) Source # | |||||
Defined in Data.Semigroup Associated Types
| |||||
Read a => Read (Last a) Source # | Since: base-4.9.0.0 | ||||
Show a => Show (Last a) Source # | Since: base-4.9.0.0 | ||||
Eq a => Eq (Last a) Source # | Since: base-4.9.0.0 | ||||
Ord a => Ord (Last a) Source # | Since: base-4.9.0.0 | ||||
type Rep1 Last Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Semigroup | |||||
type Rep (Last a) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Semigroup |
newtype WrappedMonoid m Source #
Provide a Semigroup for an arbitrary Monoid.
NOTE: This is not needed anymore since Semigroup
became a superclass of
Monoid
in base-4.11 and this newtype be deprecated at some point in the future.
Constructors
WrapMonoid | |
Fields
|
Instances
Re-exported monoids
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
Foldable1 Dual Source # | Since: base-4.18.0.0 | ||||
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 # | |||||
Applicative Dual Source # | Since: base-4.8.0.0 | ||||
Functor Dual Source # | Since: base-4.8.0.0 | ||||
Monad Dual Source # | Since: base-4.8.0.0 | ||||
MonadFix Dual Source # | Since: base-4.8.0.0 | ||||
MonadZip Dual Source # | Since: ghc-internal-4.8.0.0 | ||||
Foldable Dual Source # | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Foldable Methods fold :: Monoid m => Dual m -> m Source # foldMap :: Monoid m => (a -> m) -> Dual a -> m Source # foldMap' :: Monoid m => (a -> m) -> Dual a -> m Source # foldr :: (a -> b -> b) -> b -> Dual a -> b Source # foldr' :: (a -> b -> b) -> b -> Dual a -> b Source # foldl :: (b -> a -> b) -> b -> Dual a -> b Source # foldl' :: (b -> a -> b) -> b -> Dual a -> b Source # foldr1 :: (a -> a -> a) -> Dual a -> a Source # foldl1 :: (a -> a -> a) -> Dual a -> a Source # toList :: Dual a -> [a] Source # null :: Dual a -> Bool Source # length :: Dual a -> Int Source # elem :: Eq a => a -> Dual a -> Bool Source # maximum :: Ord a => Dual a -> a Source # minimum :: Ord a => Dual a -> a Source # | |||||
Traversable Dual Source # | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Generic1 Dual Source # | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
Monoid a => Monoid (Dual a) Source # | Since: base-2.1 | ||||
Semigroup a => Semigroup (Dual a) Source # | Since: base-4.9.0.0 | ||||
Data a => Data (Dual a) Source # | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.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 # | |||||
Bounded a => Bounded (Dual a) Source # | Since: base-2.1 | ||||
Generic (Dual a) Source # | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
Read a => Read (Dual a) Source # | Since: base-2.1 | ||||
Show a => Show (Dual a) Source # | Since: base-2.1 | ||||
Eq a => Eq (Dual a) Source # | Since: base-2.1 | ||||
Ord a => Ord (Dual a) Source # | Since: base-2.1 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
type Rep1 Dual Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
type Rep (Dual a) Source # | 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) Source # | Since: base-2.1 | ||||
Semigroup (Endo a) Source # | Since: base-4.9.0.0 | ||||
Generic (Endo a) Source # | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
type Rep (Endo a) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal |
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 Source # | Since: base-2.1 | ||||
Semigroup All Source # | Since: base-4.9.0.0 | ||||
Data All Source # | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.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 # | |||||
Bounded All Source # | Since: base-2.1 | ||||
Generic All Source # | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
Read All Source # | Since: base-2.1 | ||||
Show All Source # | Since: base-2.1 | ||||
Eq All Source # | Since: base-2.1 | ||||
Ord All Source # | Since: base-2.1 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
type Rep All Source # | 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 Source # | Since: base-2.1 | ||||
Semigroup Any Source # | Since: base-4.9.0.0 | ||||
Data Any Source # | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.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 # | |||||
Bounded Any Source # | Since: base-2.1 | ||||
Generic Any Source # | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
Read Any Source # | Since: base-2.1 | ||||
Show Any Source # | Since: base-2.1 | ||||
Eq Any Source # | Since: base-2.1 | ||||
Ord Any Source # | Since: base-2.1 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
type Rep Any Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal |
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
Foldable1 Sum Source # | Since: base-4.18.0.0 | ||||
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 # | |||||
Applicative Sum Source # | Since: base-4.8.0.0 | ||||
Functor Sum Source # | Since: base-4.8.0.0 | ||||
Monad Sum Source # | Since: base-4.8.0.0 | ||||
MonadFix Sum Source # | Since: base-4.8.0.0 | ||||
MonadZip Sum Source # | Since: ghc-internal-4.8.0.0 | ||||
Foldable Sum Source # | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Foldable Methods fold :: Monoid m => Sum m -> m Source # foldMap :: Monoid m => (a -> m) -> Sum a -> m Source # foldMap' :: Monoid m => (a -> m) -> Sum a -> m Source # foldr :: (a -> b -> b) -> b -> Sum a -> b Source # foldr' :: (a -> b -> b) -> b -> Sum a -> b Source # foldl :: (b -> a -> b) -> b -> Sum a -> b Source # foldl' :: (b -> a -> b) -> b -> Sum a -> b Source # foldr1 :: (a -> a -> a) -> Sum a -> a Source # foldl1 :: (a -> a -> a) -> Sum a -> a Source # toList :: Sum a -> [a] Source # null :: Sum a -> Bool Source # length :: Sum a -> Int Source # elem :: Eq a => a -> Sum a -> Bool Source # maximum :: Ord a => Sum a -> a Source # minimum :: Ord a => Sum a -> a Source # | |||||
Traversable Sum Source # | Since: base-4.8.0.0 | ||||
Generic1 Sum Source # | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
Num a => Monoid (Sum a) Source # | Since: base-2.1 | ||||
Num a => Semigroup (Sum a) Source # | Since: base-4.9.0.0 | ||||
Data a => Data (Sum a) Source # | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.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 # | |||||
Bounded a => Bounded (Sum a) Source # | Since: base-2.1 | ||||
Generic (Sum a) Source # | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
Num a => Num (Sum a) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
Read a => Read (Sum a) Source # | Since: base-2.1 | ||||
Show a => Show (Sum a) Source # | Since: base-2.1 | ||||
Eq a => Eq (Sum a) Source # | Since: base-2.1 | ||||
Ord a => Ord (Sum a) Source # | Since: base-2.1 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
type Rep1 Sum Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
type Rep (Sum a) Source # | 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}
Constructors
Product | |
Fields
|
Instances
Foldable1 Product Source # | Since: base-4.18.0.0 | ||||
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 # | |||||
Applicative Product Source # | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
Functor Product Source # | Since: base-4.8.0.0 | ||||
Monad Product Source # | Since: base-4.8.0.0 | ||||
MonadFix Product Source # | Since: base-4.8.0.0 | ||||
MonadZip Product Source # | Since: ghc-internal-4.8.0.0 | ||||
Foldable Product Source # | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Foldable Methods fold :: Monoid m => Product m -> m Source # foldMap :: Monoid m => (a -> m) -> Product a -> m Source # foldMap' :: Monoid m => (a -> m) -> Product a -> m Source # foldr :: (a -> b -> b) -> b -> Product a -> b Source # foldr' :: (a -> b -> b) -> b -> Product a -> b Source # foldl :: (b -> a -> b) -> b -> Product a -> b Source # foldl' :: (b -> a -> b) -> b -> Product a -> b Source # foldr1 :: (a -> a -> a) -> Product a -> a Source # foldl1 :: (a -> a -> a) -> Product a -> a Source # toList :: Product a -> [a] Source # null :: Product a -> Bool Source # length :: Product a -> Int Source # elem :: Eq a => a -> Product a -> Bool Source # maximum :: Ord a => Product a -> a Source # minimum :: Ord a => Product a -> a Source # | |||||
Traversable Product Source # | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Generic1 Product Source # | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
Num a => Monoid (Product a) Source # | Since: base-2.1 | ||||
Num a => Semigroup (Product a) Source # | Since: base-4.9.0.0 | ||||
Data a => Data (Product a) Source # | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.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 # | |||||
Bounded a => Bounded (Product a) Source # | Since: base-2.1 | ||||
Generic (Product a) Source # | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
Num a => Num (Product a) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.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 # | |||||
Read a => Read (Product a) Source # | Since: base-2.1 | ||||
Show a => Show (Product a) Source # | Since: base-2.1 | ||||
Eq a => Eq (Product a) Source # | Since: base-2.1 | ||||
Ord a => Ord (Product a) Source # | Since: base-2.1 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
type Rep1 Product Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
type Rep (Product a) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal |
Difference lists of a semigroup
diff :: Semigroup m => m -> Endo m Source #
This lets you use a difference list of a Semigroup
as a Monoid
.
Examples
>>>
let hello = diff "Hello, "
>>>
appEndo hello "World!"
"Hello, World!"
>>>
appEndo (hello <> mempty) "World!"
"Hello, World!"
>>>
appEndo (mempty <> hello) "World!"
"Hello, World!"
>>>
let world = diff "World"
>>>
let excl = diff "!"
>>>
appEndo (hello <> (world <> excl)) mempty
"Hello, World!"
>>>
appEndo ((hello <> world) <> excl) mempty
"Hello, World!"
ArgMin, ArgMax
Arg
isn't itself a Semigroup
in its own right, but it can be
placed inside Min
and Max
to compute an arg min or arg max. In
the event of ties, the leftmost qualifying Arg
is chosen; contrast
with the behavior of minimum
and maximum
for many other types,
where ties are broken by considering elements to the left in the
structure to be less than elements to the right.
Examples
>>>
minimum [ Arg (x * x) x | x <- [-10 .. 10] ]
Arg 0 0
>>>
maximum [ Arg (-0.2*x^2 + 1.5*x + 1) x | x <- [-10 .. 10] ]
Arg 3.8 4.0
>>>
minimum [ Arg (-0.2*x^2 + 1.5*x + 1) x | x <- [-10 .. 10] ]
Arg (-34.0) (-10.0)
Constructors
Arg | |
Instances
Bifoldable Arg Source # | Since: base-4.10.0.0 | ||||
Bifoldable1 Arg Source # | |||||
Bifunctor Arg Source # | Since: base-4.9.0.0 | ||||
Bitraversable Arg Source # | Since: base-4.10.0.0 | ||||
Defined in Data.Semigroup Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Arg a b -> f (Arg c d) Source # | |||||
Generic1 (Arg a :: Type -> Type) Source # | |||||
Defined in Data.Semigroup Associated Types
| |||||
Functor (Arg a) Source # | Since: base-4.9.0.0 | ||||
Foldable (Arg a) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Semigroup Methods fold :: Monoid m => Arg a m -> m Source # foldMap :: Monoid m => (a0 -> m) -> Arg a a0 -> m Source # foldMap' :: Monoid m => (a0 -> m) -> Arg a a0 -> m Source # foldr :: (a0 -> b -> b) -> b -> Arg a a0 -> b Source # foldr' :: (a0 -> b -> b) -> b -> Arg a a0 -> b Source # foldl :: (b -> a0 -> b) -> b -> Arg a a0 -> b Source # foldl' :: (b -> a0 -> b) -> b -> Arg a a0 -> b Source # foldr1 :: (a0 -> a0 -> a0) -> Arg a a0 -> a0 Source # foldl1 :: (a0 -> a0 -> a0) -> Arg a a0 -> a0 Source # toList :: Arg a a0 -> [a0] Source # null :: Arg a a0 -> Bool Source # length :: Arg a a0 -> Int Source # elem :: Eq a0 => a0 -> Arg a a0 -> Bool Source # maximum :: Ord a0 => Arg a a0 -> a0 Source # minimum :: Ord a0 => Arg a a0 -> a0 Source # | |||||
Traversable (Arg a) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Semigroup | |||||
(Data a, Data b) => Data (Arg a b) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Semigroup Methods gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Arg a b -> c (Arg a b) Source # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Arg a b) Source # toConstr :: Arg a b -> Constr Source # dataTypeOf :: Arg a b -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Arg a b)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Arg a b)) Source # gmapT :: (forall b0. Data b0 => b0 -> b0) -> Arg a b -> Arg a b Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Arg a b -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Arg a b -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Arg a b -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Arg a b -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Arg a b -> m (Arg a b) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Arg a b -> m (Arg a b) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Arg a b -> m (Arg a b) Source # | |||||
Generic (Arg a b) Source # | |||||
Defined in Data.Semigroup Associated Types
| |||||
(Read a, Read b) => Read (Arg a b) Source # | Since: base-4.9.0.0 | ||||
(Show a, Show b) => Show (Arg a b) Source # | Since: base-4.9.0.0 | ||||
Eq a => Eq (Arg a b) Source # | Note that
Since: base-4.9.0.0 | ||||
Ord a => Ord (Arg a b) Source # | Note that Since: base-4.9.0.0 | ||||
type Rep1 (Arg a :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Semigroup type Rep1 (Arg a :: Type -> Type) = D1 ('MetaData "Arg" "Data.Semigroup" "base-4.21.0.0-8e62" 'False) (C1 ('MetaCons "Arg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1)) | |||||
type Rep (Arg a b) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Semigroup type Rep (Arg a b) = D1 ('MetaData "Arg" "Data.Semigroup" "base-4.21.0.0-8e62" 'False) (C1 ('MetaCons "Arg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b))) |