Safe Haskell | None |
---|---|
Language | Haskell2010 |
Compatibility layer for Data.Semigroup
Synopsis
- class Semigroup a where
- (<>) :: a -> a -> a
- class Semigroup a => Monoid a where
- newtype All = All {}
- newtype Any = Any {}
- newtype First' a = First' {
- getFirst' :: a
- newtype Last' a = Last' {
- getLast' :: a
- newtype Option' a = Option' {
- getOption' :: Maybe a
- gmappend :: (Generic a, GSemigroup (Rep a)) => a -> a -> a
- gmempty :: (Generic a, GMonoid (Rep a)) => a
Documentation
class Semigroup a where Source #
The class of semigroups (types with an associative binary operation).
Instances should satisfy the following:
Since: base-4.9.0.0
Instances
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
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
>>>
"Hello world" <> mempty
"Hello world"
mappend :: a -> a -> a Source #
An associative operation
NOTE: This method is redundant and has the default
implementation
since base-4.11.0.0.
Should it be implemented manually, since mappend
= (<>
)mappend
is a synonym for
(<>
), it is expected that the two functions are defined the same
way. In a future GHC release mappend
will be removed from Monoid
.
Fold a list using the monoid.
For most types, the default definition for mconcat
will be
used, but the function is included in the class definition so
that an optimized version can be provided for specific types.
>>>
mconcat ["Hello", " ", "Haskell", "!"]
"Hello Haskell!"
Instances
Boolean monoid under conjunction (&&
).
>>>
getAll (All True <> mempty <> All False)
False
>>>
getAll (mconcat (map (\x -> All (even x)) [2,4,6,7,8]))
False
Instances
Bounded All | Since: base-2.1 |
Eq All | Since: base-2.1 |
Data All | Since: base-4.8.0.0 |
Defined in 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 # | |
Ord All | Since: base-2.1 |
Read All | Since: base-2.1 |
Show All | Since: base-2.1 |
Generic All | Since: base-4.7.0.0 |
Semigroup All | Since: base-4.9.0.0 |
Monoid All | Since: base-2.1 |
Binary All | Since: binary-0.8.4.0 |
NFData All | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
type Rep All | |
Defined in Data.Semigroup.Internal |
Boolean monoid under disjunction (||
).
>>>
getAny (Any True <> mempty <> Any False)
True
>>>
getAny (mconcat (map (\x -> Any (even x)) [2,4,6,7,8]))
True
Instances
Bounded Any | Since: base-2.1 |
Eq Any | Since: base-2.1 |
Data Any | Since: base-4.8.0.0 |
Defined in 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 # | |
Ord Any | Since: base-2.1 |
Read Any | Since: base-2.1 |
Show Any | Since: base-2.1 |
Generic Any | Since: base-4.7.0.0 |
Semigroup Any | Since: base-4.9.0.0 |
Monoid Any | Since: base-2.1 |
Binary Any | Since: binary-0.8.4.0 |
NFData Any | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
type Rep Any | |
Defined in Data.Semigroup.Internal |
A copy of First
.
A copy of Last
.
Instances
Functor Last' # | |
Eq a => Eq (Last' a) # | |
Ord a => Ord (Last' a) # | |
Defined in Distribution.Compat.Semigroup | |
Read a => Read (Last' a) # | |
Show a => Show (Last' a) # | |
Generic (Last' a) # | |
Semigroup (Last' a) # | |
Binary a => Binary (Last' a) # | |
Structured a => Structured (Last' a) # | |
Defined in Distribution.Compat.Semigroup | |
type Rep (Last' a) # | |
Defined in Distribution.Compat.Semigroup |
A wrapper around Maybe
, providing the Semigroup
and Monoid
instances
implemented for Maybe
since base-4.11
.
Option' | |
|
Instances
Functor Option' # | |
Eq a => Eq (Option' a) # | |
Ord a => Ord (Option' a) # | |
Defined in Distribution.Compat.Semigroup | |
Read a => Read (Option' a) # | |
Show a => Show (Option' a) # | |
Generic (Option' a) # | |
Semigroup a => Semigroup (Option' a) # | |
Semigroup a => Monoid (Option' a) # | |
Binary a => Binary (Option' a) # | |
Structured a => Structured (Option' a) # | |
Defined in Distribution.Compat.Semigroup | |
type Rep (Option' a) # | |
Defined in Distribution.Compat.Semigroup |