| 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
Contents
Description
In mathematics, a semigroup is an algebraic structure consisting of a set together with an associative binary operation. A semigroup generalizes a monoid in that there might not exist an identity element. It also (originally) generalized a group (a monoid with all inverses) to a type where every element did not have to have an inverse, thus the name semigroup.
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: 4.9.0.0
The class of semigroups (types with an associative binary operation).
Instances should satisfy the associativity law:
Since: 4.9.0.0
Minimal complete definition
Methods
(<>) :: a -> a -> ainfixr 6Source#
An associative operation.
sconcat ::NonEmpty a -> aSource#
Reduce a non-empty list with<>
The default definition should be sufficient, but this can be overridden for efficiency.
stimes ::Integral b => b -> a -> aSource#
Repeat a valuen times.
Given that this works on aSemigroup it is allowed to fail if you request 0 or fewer repetitions, and the default definition will do so.
By making this a member of the class, idempotent semigroups and monoids can upgrade this to execute inO(1) by pickingstimes = orstimesIdempotentstimes = respectively.stimesIdempotentMonoid
stimesMonoid :: (Integral b,Monoid a) => b -> a -> aSource#
stimesIdempotent ::Integral b => b -> a -> aSource#
stimesIdempotentMonoid :: (Integral b,Monoid a) => b -> a -> aSource#
mtimesDefault :: (Integral b,Monoid a) => b -> a -> aSource#
| MonadMinSource# | Since: 4.9.0.0 |
| FunctorMinSource# | Since: 4.9.0.0 |
| MonadFixMinSource# | Since: 4.9.0.0 |
| ApplicativeMinSource# | Since: 4.9.0.0 |
| FoldableMinSource# | Since: 4.9.0.0 |
Instance detailsDefined inData.Semigroup Methods fold ::Monoid m =>Min m -> mSource# foldMap ::Monoid m => (a -> m) ->Min a -> mSource# foldr :: (a -> b -> b) -> b ->Min a -> bSource# foldr' :: (a -> b -> b) -> b ->Min a -> bSource# foldl :: (b -> a -> b) -> b ->Min a -> bSource# foldl' :: (b -> a -> b) -> b ->Min a -> bSource# foldr1 :: (a -> a -> a) ->Min a -> aSource# foldl1 :: (a -> a -> a) ->Min a -> aSource# elem ::Eq a => a ->Min a ->BoolSource# maximum ::Ord a =>Min a -> aSource# minimum ::Ord a =>Min a -> aSource# | |
| TraversableMinSource# | Since: 4.9.0.0 |
| Bounded a =>Bounded (Min a)Source# | Since: 4.9.0.0 |
| Enum a =>Enum (Min a)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Semigroup | |
| Eq a =>Eq (Min a)Source# | Since: 4.9.0.0 |
| Data a =>Data (Min a)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.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 ->ConstrSource# dataTypeOf ::Min a ->DataTypeSource# 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 aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Min a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Min a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Min a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Min a -> uSource# 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# | |
| Num a =>Num (Min a)Source# | Since: 4.9.0.0 |
| Ord a =>Ord (Min a)Source# | Since: 4.9.0.0 |
| Read a =>Read (Min a)Source# | Since: 4.9.0.0 |
| Show a =>Show (Min a)Source# | Since: 4.9.0.0 |
| Generic (Min a)Source# | |
| Ord a =>Semigroup (Min a)Source# | Since: 4.9.0.0 |
| (Ord a,Bounded a) =>Monoid (Min a)Source# | Since: 4.9.0.0 |
| Generic1MinSource# | |
| typeRep (Min a)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Semigroup | |
| typeRep1MinSource# | Since: 4.9.0.0 |
Instance detailsDefined inData.Semigroup | |
| MonadMaxSource# | Since: 4.9.0.0 |
| FunctorMaxSource# | Since: 4.9.0.0 |
| MonadFixMaxSource# | Since: 4.9.0.0 |
| ApplicativeMaxSource# | Since: 4.9.0.0 |
| FoldableMaxSource# | Since: 4.9.0.0 |
Instance detailsDefined inData.Semigroup Methods fold ::Monoid m =>Max m -> mSource# foldMap ::Monoid m => (a -> m) ->Max a -> mSource# foldr :: (a -> b -> b) -> b ->Max a -> bSource# foldr' :: (a -> b -> b) -> b ->Max a -> bSource# foldl :: (b -> a -> b) -> b ->Max a -> bSource# foldl' :: (b -> a -> b) -> b ->Max a -> bSource# foldr1 :: (a -> a -> a) ->Max a -> aSource# foldl1 :: (a -> a -> a) ->Max a -> aSource# elem ::Eq a => a ->Max a ->BoolSource# maximum ::Ord a =>Max a -> aSource# minimum ::Ord a =>Max a -> aSource# | |
| TraversableMaxSource# | Since: 4.9.0.0 |
| Bounded a =>Bounded (Max a)Source# | Since: 4.9.0.0 |
| Enum a =>Enum (Max a)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Semigroup | |
| Eq a =>Eq (Max a)Source# | Since: 4.9.0.0 |
| Data a =>Data (Max a)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.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 ->ConstrSource# dataTypeOf ::Max a ->DataTypeSource# 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 aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Max a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Max a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Max a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Max a -> uSource# 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# | |
| Num a =>Num (Max a)Source# | Since: 4.9.0.0 |
| Ord a =>Ord (Max a)Source# | Since: 4.9.0.0 |
| Read a =>Read (Max a)Source# | Since: 4.9.0.0 |
| Show a =>Show (Max a)Source# | Since: 4.9.0.0 |
| Generic (Max a)Source# | |
| Ord a =>Semigroup (Max a)Source# | Since: 4.9.0.0 |
| (Ord a,Bounded a) =>Monoid (Max a)Source# | Since: 4.9.0.0 |
| Generic1MaxSource# | |
| typeRep (Max a)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Semigroup | |
| typeRep1MaxSource# | Since: 4.9.0.0 |
Instance detailsDefined inData.Semigroup | |
Use to get the behavior ofOption (First a)First fromData.Monoid.
| MonadFirstSource# | Since: 4.9.0.0 |
| FunctorFirstSource# | Since: 4.9.0.0 |
| MonadFixFirstSource# | Since: 4.9.0.0 |
| ApplicativeFirstSource# | Since: 4.9.0.0 |
| FoldableFirstSource# | Since: 4.9.0.0 |
Instance detailsDefined inData.Semigroup Methods fold ::Monoid m =>First m -> mSource# foldMap ::Monoid m => (a -> m) ->First a -> mSource# foldr :: (a -> b -> b) -> b ->First a -> bSource# foldr' :: (a -> b -> b) -> b ->First a -> bSource# foldl :: (b -> a -> b) -> b ->First a -> bSource# foldl' :: (b -> a -> b) -> b ->First a -> bSource# foldr1 :: (a -> a -> a) ->First a -> aSource# foldl1 :: (a -> a -> a) ->First a -> aSource# toList ::First a -> [a]Source# elem ::Eq a => a ->First a ->BoolSource# maximum ::Ord a =>First a -> aSource# minimum ::Ord a =>First a -> aSource# | |
| TraversableFirstSource# | Since: 4.9.0.0 |
| Bounded a =>Bounded (First a)Source# | Since: 4.9.0.0 |
| Enum a =>Enum (First a)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Semigroup Methods succ ::First a ->First aSource# pred ::First a ->First aSource# fromEnum ::First a ->IntSource# 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# | |
| Eq a =>Eq (First a)Source# | Since: 4.9.0.0 |
| Data a =>Data (First a)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.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 ->ConstrSource# dataTypeOf ::First a ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (First a))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (First a))Source# gmapT :: (forall b.Data b => b -> b) ->First a ->First aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->First a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->First a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->First a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->First a -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->First a -> m (First a)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->First a -> m (First a)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->First a -> m (First a)Source# | |
| Ord a =>Ord (First a)Source# | Since: 4.9.0.0 |
| Read a =>Read (First a)Source# | Since: 4.9.0.0 |
| Show a =>Show (First a)Source# | Since: 4.9.0.0 |
| Generic (First a)Source# | |
| Semigroup (First a)Source# | Since: 4.9.0.0 |
| Generic1FirstSource# | |
| typeRep (First a)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Semigroup | |
| typeRep1FirstSource# | Since: 4.9.0.0 |
Instance detailsDefined inData.Semigroup | |
Use to get the behavior ofOption (Last a)Last fromData.Monoid
| MonadLastSource# | Since: 4.9.0.0 |
| FunctorLastSource# | Since: 4.9.0.0 |
| MonadFixLastSource# | Since: 4.9.0.0 |
| ApplicativeLastSource# | Since: 4.9.0.0 |
| FoldableLastSource# | Since: 4.9.0.0 |
Instance detailsDefined inData.Semigroup Methods fold ::Monoid m =>Last m -> mSource# foldMap ::Monoid m => (a -> m) ->Last a -> mSource# foldr :: (a -> b -> b) -> b ->Last a -> bSource# foldr' :: (a -> b -> b) -> b ->Last a -> bSource# foldl :: (b -> a -> b) -> b ->Last a -> bSource# foldl' :: (b -> a -> b) -> b ->Last a -> bSource# foldr1 :: (a -> a -> a) ->Last a -> aSource# foldl1 :: (a -> a -> a) ->Last a -> aSource# elem ::Eq a => a ->Last a ->BoolSource# maximum ::Ord a =>Last a -> aSource# minimum ::Ord a =>Last a -> aSource# | |
| TraversableLastSource# | Since: 4.9.0.0 |
| Bounded a =>Bounded (Last a)Source# | Since: 4.9.0.0 |
| Enum a =>Enum (Last a)Source# | Since: 4.9.0.0 |
| Eq a =>Eq (Last a)Source# | Since: 4.9.0.0 |
| Data a =>Data (Last a)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.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 ->ConstrSource# dataTypeOf ::Last a ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Last a))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Last a))Source# gmapT :: (forall b.Data b => b -> b) ->Last a ->Last aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Last a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Last a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Last a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Last a -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Last a -> m (Last a)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Last a -> m (Last a)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Last a -> m (Last a)Source# | |
| Ord a =>Ord (Last a)Source# | Since: 4.9.0.0 |
| Read a =>Read (Last a)Source# | Since: 4.9.0.0 |
| Show a =>Show (Last a)Source# | Since: 4.9.0.0 |
| Generic (Last a)Source# | |
| Semigroup (Last a)Source# | Since: 4.9.0.0 |
| Generic1LastSource# | |
| typeRep (Last a)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Semigroup | |
| typeRep1LastSource# | Since: 4.9.0.0 |
Instance detailsDefined inData.Semigroup | |
newtypeWrappedMonoid mSource#
Provide a Semigroup for an arbitrary Monoid.
NOTE: This is not needed anymore sinceSemigroup became a superclass ofMonoid inbase-4.11 and this newtype be deprecated at some point in the future.
Constructors
| WrapMonoid | |
Fields
| |
The dual of aMonoid, obtained by swapping the arguments ofmappend.
>>>getDual (mappend (Dual "Hello") (Dual "World"))"WorldHello"
| MonadDualSource# | Since: 4.8.0.0 |
| FunctorDualSource# | Since: 4.8.0.0 |
| MonadFixDualSource# | Since: 4.8.0.0 |
| ApplicativeDualSource# | Since: 4.8.0.0 |
| FoldableDualSource# | Since: 4.8.0.0 |
Instance detailsDefined inData.Foldable Methods fold ::Monoid m =>Dual m -> mSource# foldMap ::Monoid m => (a -> m) ->Dual a -> mSource# foldr :: (a -> b -> b) -> b ->Dual a -> bSource# foldr' :: (a -> b -> b) -> b ->Dual a -> bSource# foldl :: (b -> a -> b) -> b ->Dual a -> bSource# foldl' :: (b -> a -> b) -> b ->Dual a -> bSource# foldr1 :: (a -> a -> a) ->Dual a -> aSource# foldl1 :: (a -> a -> a) ->Dual a -> aSource# elem ::Eq a => a ->Dual a ->BoolSource# maximum ::Ord a =>Dual a -> aSource# minimum ::Ord a =>Dual a -> aSource# | |
| TraversableDualSource# | Since: 4.8.0.0 |
| MonadZipDualSource# | Since: 4.8.0.0 |
| Bounded a =>Bounded (Dual a)Source# | Since: 2.1 |
| Eq a =>Eq (Dual a)Source# | Since: 2.1 |
| Data a =>Data (Dual a)Source# | Since: 4.8.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Dual a -> c (Dual a)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Dual a)Source# toConstr ::Dual a ->ConstrSource# dataTypeOf ::Dual a ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Dual a))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Dual a))Source# gmapT :: (forall b.Data b => b -> b) ->Dual a ->Dual aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Dual a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Dual a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Dual a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Dual a -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Dual a -> m (Dual a)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Dual a -> m (Dual a)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Dual a -> m (Dual a)Source# | |
| Ord a =>Ord (Dual a)Source# | Since: 2.1 |
| Read a =>Read (Dual a)Source# | Since: 2.1 |
| Show a =>Show (Dual a)Source# | Since: 2.1 |
| Generic (Dual a)Source# | |
| Semigroup a =>Semigroup (Dual a)Source# | Since: 4.9.0.0 |
| Monoid a =>Monoid (Dual a)Source# | Since: 2.1 |
| Generic1DualSource# | |
| typeRep (Dual a)Source# | Since: 4.7.0.0 |
Instance detailsDefined inData.Semigroup.Internal | |
| typeRep1DualSource# | Since: 4.7.0.0 |
Instance detailsDefined inData.Semigroup.Internal | |
The monoid of endomorphisms under composition.
>>>let computation = Endo ("Hello, " ++) <> Endo (++ "!")>>>appEndo computation "Haskell""Hello, Haskell!"
Boolean monoid under conjunction (&&).
>>>getAll (All True <> mempty <> All False)False
>>>getAll (mconcat (map (\x -> All (even x)) [2,4,6,7,8]))False
| BoundedAllSource# | Since: 2.1 |
| EqAllSource# | Since: 2.1 |
| DataAllSource# | Since: 4.8.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->All -> cAllSource# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> cAllSource# toConstr ::All ->ConstrSource# dataTypeOf ::All ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (cAll)Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (cAll)Source# gmapT :: (forall b.Data b => b -> b) ->All ->AllSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->All -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->All -> rSource# gmapQ :: (forall d.Data d => d -> u) ->All -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->All -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->All -> mAllSource# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->All -> mAllSource# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->All -> mAllSource# | |
| OrdAllSource# | Since: 2.1 |
| ReadAllSource# | Since: 2.1 |
| ShowAllSource# | Since: 2.1 |
| GenericAllSource# | |
| SemigroupAllSource# | Since: 4.9.0.0 |
| MonoidAllSource# | Since: 2.1 |
| typeRepAllSource# | Since: 4.7.0.0 |
Instance detailsDefined inData.Semigroup.Internal | |
Boolean monoid under disjunction (||).
>>>getAny (Any True <> mempty <> Any False)True
>>>getAny (mconcat (map (\x -> Any (even x)) [2,4,6,7,8]))True
| BoundedAnySource# | Since: 2.1 |
| EqAnySource# | Since: 2.1 |
| DataAnySource# | Since: 4.8.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Any -> cAnySource# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> cAnySource# toConstr ::Any ->ConstrSource# dataTypeOf ::Any ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (cAny)Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (cAny)Source# gmapT :: (forall b.Data b => b -> b) ->Any ->AnySource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Any -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Any -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Any -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Any -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Any -> mAnySource# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Any -> mAnySource# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Any -> mAnySource# | |
| OrdAnySource# | Since: 2.1 |
| ReadAnySource# | Since: 2.1 |
| ShowAnySource# | Since: 2.1 |
| GenericAnySource# | |
| SemigroupAnySource# | Since: 4.9.0.0 |
| MonoidAnySource# | Since: 2.1 |
| typeRepAnySource# | Since: 4.7.0.0 |
Instance detailsDefined inData.Semigroup.Internal | |
Monoid under addition.
>>>getSum (Sum 1 <> Sum 2 <> mempty)3
| MonadSumSource# | Since: 4.8.0.0 |
| FunctorSumSource# | Since: 4.8.0.0 |
| MonadFixSumSource# | Since: 4.8.0.0 |
| ApplicativeSumSource# | Since: 4.8.0.0 |
| FoldableSumSource# | Since: 4.8.0.0 |
Instance detailsDefined inData.Foldable Methods fold ::Monoid m =>Sum m -> mSource# foldMap ::Monoid m => (a -> m) ->Sum a -> mSource# foldr :: (a -> b -> b) -> b ->Sum a -> bSource# foldr' :: (a -> b -> b) -> b ->Sum a -> bSource# foldl :: (b -> a -> b) -> b ->Sum a -> bSource# foldl' :: (b -> a -> b) -> b ->Sum a -> bSource# foldr1 :: (a -> a -> a) ->Sum a -> aSource# foldl1 :: (a -> a -> a) ->Sum a -> aSource# elem ::Eq a => a ->Sum a ->BoolSource# maximum ::Ord a =>Sum a -> aSource# minimum ::Ord a =>Sum a -> aSource# | |
| TraversableSumSource# | Since: 4.8.0.0 |
| MonadZipSumSource# | Since: 4.8.0.0 |
| Bounded a =>Bounded (Sum a)Source# | Since: 2.1 |
| Eq a =>Eq (Sum a)Source# | Since: 2.1 |
| Data a =>Data (Sum a)Source# | Since: 4.8.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Sum a -> c (Sum a)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Sum a)Source# toConstr ::Sum a ->ConstrSource# dataTypeOf ::Sum a ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Sum a))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Sum a))Source# gmapT :: (forall b.Data b => b -> b) ->Sum a ->Sum aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Sum a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Sum a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Sum a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Sum a -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Sum a -> m (Sum a)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Sum a -> m (Sum a)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Sum a -> m (Sum a)Source# | |
| Num a =>Num (Sum a)Source# | Since: 4.7.0.0 |
| Ord a =>Ord (Sum a)Source# | Since: 2.1 |
| Read a =>Read (Sum a)Source# | Since: 2.1 |
| Show a =>Show (Sum a)Source# | Since: 2.1 |
| Generic (Sum a)Source# | |
| Num a =>Semigroup (Sum a)Source# | Since: 4.9.0.0 |
| Num a =>Monoid (Sum a)Source# | Since: 2.1 |
| Generic1SumSource# | |
| typeRep (Sum a)Source# | Since: 4.7.0.0 |
Instance detailsDefined inData.Semigroup.Internal | |
| typeRep1SumSource# | Since: 4.7.0.0 |
Instance detailsDefined inData.Semigroup.Internal | |
Monoid under multiplication.
>>>getProduct (Product 3 <> Product 4 <> mempty)12
Constructors
| Product | |
Fields
| |
| MonadProductSource# | Since: 4.8.0.0 |
| FunctorProductSource# | Since: 4.8.0.0 |
| MonadFixProductSource# | Since: 4.8.0.0 |
| ApplicativeProductSource# | Since: 4.8.0.0 |
| FoldableProductSource# | Since: 4.8.0.0 |
Instance detailsDefined inData.Foldable Methods fold ::Monoid m =>Product m -> mSource# foldMap ::Monoid m => (a -> m) ->Product a -> mSource# foldr :: (a -> b -> b) -> b ->Product a -> bSource# foldr' :: (a -> b -> b) -> b ->Product a -> bSource# foldl :: (b -> a -> b) -> b ->Product a -> bSource# foldl' :: (b -> a -> b) -> b ->Product a -> bSource# foldr1 :: (a -> a -> a) ->Product a -> aSource# foldl1 :: (a -> a -> a) ->Product a -> aSource# toList ::Product a -> [a]Source# null ::Product a ->BoolSource# length ::Product a ->IntSource# elem ::Eq a => a ->Product a ->BoolSource# maximum ::Ord a =>Product a -> aSource# minimum ::Ord a =>Product a -> aSource# | |
| TraversableProductSource# | Since: 4.8.0.0 |
Instance detailsDefined inData.Traversable | |
| MonadZipProductSource# | Since: 4.8.0.0 |
| Bounded a =>Bounded (Product a)Source# | Since: 2.1 |
| Eq a =>Eq (Product a)Source# | Since: 2.1 |
| Data a =>Data (Product a)Source# | Since: 4.8.0.0 |
Instance detailsDefined inData.Data Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Product a -> c (Product a)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Product a)Source# toConstr ::Product a ->ConstrSource# dataTypeOf ::Product a ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Product a))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Product a))Source# gmapT :: (forall b.Data b => b -> b) ->Product a ->Product aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Product a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Product a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Product a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Product a -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Product a -> m (Product a)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Product a -> m (Product a)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Product a -> m (Product a)Source# | |
| Num a =>Num (Product a)Source# | Since: 4.7.0.0 |
Instance detailsDefined inData.Semigroup.Internal | |
| Ord a =>Ord (Product a)Source# | Since: 2.1 |
Instance detailsDefined inData.Semigroup.Internal | |
| Read a =>Read (Product a)Source# | Since: 2.1 |
| Show a =>Show (Product a)Source# | Since: 2.1 |
| Generic (Product a)Source# | |
| Num a =>Semigroup (Product a)Source# | Since: 4.9.0.0 |
| Num a =>Monoid (Product a)Source# | Since: 2.1 |
| Generic1ProductSource# | |
| typeRep (Product a)Source# | Since: 4.7.0.0 |
Instance detailsDefined inData.Semigroup.Internal | |
| typeRep1ProductSource# | Since: 4.7.0.0 |
Instance detailsDefined inData.Semigroup.Internal | |
Option is effectivelyMaybe with a better instance ofMonoid, built off of an underlyingSemigroup instead of an underlyingMonoid.
Ideally, this type would not exist at all and we would just fix theMonoid instance ofMaybe.
In GHC 8.4 and higher, theMonoid instance forMaybe has been corrected to lift aSemigroup instance instead of aMonoid instance. Consequently, this type is no longer useful. It will be marked deprecated in GHC 8.8 and removed in GHC 8.10.
| MonadOptionSource# | Since: 4.9.0.0 |
| FunctorOptionSource# | Since: 4.9.0.0 |
| MonadFixOptionSource# | Since: 4.9.0.0 |
| ApplicativeOptionSource# | Since: 4.9.0.0 |
| FoldableOptionSource# | Since: 4.9.0.0 |
Instance detailsDefined inData.Semigroup Methods fold ::Monoid m =>Option m -> mSource# foldMap ::Monoid m => (a -> m) ->Option a -> mSource# foldr :: (a -> b -> b) -> b ->Option a -> bSource# foldr' :: (a -> b -> b) -> b ->Option a -> bSource# foldl :: (b -> a -> b) -> b ->Option a -> bSource# foldl' :: (b -> a -> b) -> b ->Option a -> bSource# foldr1 :: (a -> a -> a) ->Option a -> aSource# foldl1 :: (a -> a -> a) ->Option a -> aSource# toList ::Option a -> [a]Source# length ::Option a ->IntSource# elem ::Eq a => a ->Option a ->BoolSource# maximum ::Ord a =>Option a -> aSource# minimum ::Ord a =>Option a -> aSource# | |
| TraversableOptionSource# | Since: 4.9.0.0 |
Instance detailsDefined inData.Semigroup | |
| MonadPlusOptionSource# | Since: 4.9.0.0 |
| AlternativeOptionSource# | Since: 4.9.0.0 |
| Eq a =>Eq (Option a)Source# | Since: 4.9.0.0 |
| Data a =>Data (Option a)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Semigroup Methods gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Option a -> c (Option a)Source# gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Option a)Source# toConstr ::Option a ->ConstrSource# dataTypeOf ::Option a ->DataTypeSource# dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Option a))Source# dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Option a))Source# gmapT :: (forall b.Data b => b -> b) ->Option a ->Option aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Option a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Option a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Option a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Option a -> uSource# gmapM ::Monad m => (forall d.Data d => d -> m d) ->Option a -> m (Option a)Source# gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Option a -> m (Option a)Source# gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Option a -> m (Option a)Source# | |
| Ord a =>Ord (Option a)Source# | Since: 4.9.0.0 |
| Read a =>Read (Option a)Source# | Since: 4.9.0.0 |
| Show a =>Show (Option a)Source# | Since: 4.9.0.0 |
| Generic (Option a)Source# | |
| Semigroup a =>Semigroup (Option a)Source# | Since: 4.9.0.0 |
| Semigroup a =>Monoid (Option a)Source# | Since: 4.9.0.0 |
| Generic1OptionSource# | |
| typeRep (Option a)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Semigroup | |
| typeRep1OptionSource# | Since: 4.9.0.0 |
Instance detailsDefined inData.Semigroup | |
Arg isn't itself aSemigroup in its own right, but it can be placed insideMin andMax to compute an arg min or arg max.
Constructors
| Arg a b |
| BifunctorArgSource# | Since: 4.9.0.0 |
| BifoldableArgSource# | Since: 4.10.0.0 |
| BitraversableArgSource# | Since: 4.10.0.0 |
Instance detailsDefined inData.Semigroup Methods bitraverse ::Applicative f => (a -> f c) -> (b -> f d) ->Arg a b -> f (Arg c d)Source# | |
| Functor (Arg a)Source# | Since: 4.9.0.0 |
| Foldable (Arg a)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Semigroup Methods fold ::Monoid m =>Arg a m -> mSource# foldMap ::Monoid m => (a0 -> m) ->Arg a a0 -> mSource# foldr :: (a0 -> b -> b) -> b ->Arg a a0 -> bSource# foldr' :: (a0 -> b -> b) -> b ->Arg a a0 -> bSource# foldl :: (b -> a0 -> b) -> b ->Arg a a0 -> bSource# foldl' :: (b -> a0 -> b) -> b ->Arg a a0 -> bSource# foldr1 :: (a0 -> a0 -> a0) ->Arg a a0 -> a0Source# foldl1 :: (a0 -> a0 -> a0) ->Arg a a0 -> a0Source# toList ::Arg a a0 -> [a0]Source# length ::Arg a a0 ->IntSource# elem ::Eq a0 => a0 ->Arg a a0 ->BoolSource# maximum ::Ord a0 =>Arg a a0 -> a0Source# minimum ::Ord a0 =>Arg a a0 -> a0Source# | |
| Traversable (Arg a)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Semigroup | |
| Generic1 (Arg a ::Type ->Type)Source# | |
| Eq a =>Eq (Arg a b)Source# | Since: 4.9.0.0 |
| (Data a,Data b) =>Data (Arg a b)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.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 ->ConstrSource# dataTypeOf ::Arg a b ->DataTypeSource# 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 bSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Arg a b -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Arg a b -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Arg a b -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Arg a b -> uSource# 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# | |
| Ord a =>Ord (Arg a b)Source# | Since: 4.9.0.0 |
| (Read a,Read b) =>Read (Arg a b)Source# | Since: 4.9.0.0 |
| (Show a,Show b) =>Show (Arg a b)Source# | Since: 4.9.0.0 |
| Generic (Arg a b)Source# | |
| typeRep1 (Arg a ::Type ->Type)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Semigroup typeRep1 (Arg a ::Type ->Type) =D1 (MetaData "Arg" "Data.Semigroup" "base"False) (C1 (MetaCons "Arg"PrefixIFalse) (S1 (MetaSel (Nothing ::MaybeSymbol)NoSourceUnpackednessNoSourceStrictnessDecidedLazy) (Rec0 a):*:S1 (MetaSel (Nothing ::MaybeSymbol)NoSourceUnpackednessNoSourceStrictnessDecidedLazy)Par1)) | |
| typeRep (Arg a b)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Semigroup typeRep (Arg a b) =D1 (MetaData "Arg" "Data.Semigroup" "base"False) (C1 (MetaCons "Arg"PrefixIFalse) (S1 (MetaSel (Nothing ::MaybeSymbol)NoSourceUnpackednessNoSourceStrictnessDecidedLazy) (Rec0 a):*:S1 (MetaSel (Nothing ::MaybeSymbol)NoSourceUnpackednessNoSourceStrictnessDecidedLazy) (Rec0 b))) | |
Produced byHaddock version 2.20.0