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 |
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
- newtype Option a = Option {}
- option :: b -> (a -> b) -> Option a -> b
- 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:
Since: base-4.9.0.0
(<>) :: a -> a -> a infixr 6 Source #
An associative operation.
>>>
[1,2,3] <> [4,5,6]
[1,2,3,4,5,6]
sconcat :: NonEmpty a -> a Source #
Reduce a non-empty list with <>
The default definition should be sufficient, but this can be overridden for efficiency.
>>>
import Data.List.NonEmpty
>>>
sconcat $ "Hello" :| [" ", "Haskell", "!"]
"Hello Haskell!"
stimes :: Integral b => b -> a -> a Source #
Repeat a value n
times.
Given that this works on a Semigroup
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 in \(\mathcal{O}(1)\) by
picking stimes =
or stimesIdempotent
stimes =
respectively.stimesIdempotentMonoid
>>>
stimes 4 [1]
[1,1,1,1]
Instances
Semigroup Ordering # | Since: base-4.9.0.0 |
Semigroup () # | Since: base-4.9.0.0 |
Semigroup Any # | Since: base-4.9.0.0 |
Semigroup All # | Since: base-4.9.0.0 |
Semigroup Lifetime # | Since: base-4.10.0.0 |
Semigroup Event # | Since: base-4.10.0.0 |
Semigroup Void # | Since: base-4.9.0.0 |
Semigroup [a] # | Since: base-4.9.0.0 |
Semigroup a => Semigroup (Maybe a) # | Since: base-4.9.0.0 |
Semigroup a => Semigroup (IO a) # | Since: base-4.10.0.0 |
Semigroup p => Semigroup (Par1 p) # | Since: base-4.12.0.0 |
Semigroup (NonEmpty a) # | Since: base-4.9.0.0 |
Semigroup a => Semigroup (Down a) # | Since: base-4.11.0.0 |
Num a => Semigroup (Product a) # | Since: base-4.9.0.0 |
Num a => Semigroup (Sum a) # | Since: base-4.9.0.0 |
Semigroup (Endo a) # | Since: base-4.9.0.0 |
Semigroup a => Semigroup (Dual a) # | Since: base-4.9.0.0 |
Semigroup (Last a) # | Since: base-4.9.0.0 |
Semigroup (First a) # | Since: base-4.9.0.0 |
Semigroup a => Semigroup (Identity a) # | Since: base-4.9.0.0 |
Semigroup a => Semigroup (Option a) # | Since: base-4.9.0.0 |
Monoid m => Semigroup (WrappedMonoid m) # | Since: base-4.9.0.0 |
Defined in Data.Semigroup (<>) :: WrappedMonoid m -> WrappedMonoid m -> WrappedMonoid m Source # sconcat :: NonEmpty (WrappedMonoid m) -> WrappedMonoid m Source # stimes :: Integral b => b -> WrappedMonoid m -> WrappedMonoid m Source # | |
Semigroup (Last a) # | Since: base-4.9.0.0 |
Semigroup (First a) # | Since: base-4.9.0.0 |
Ord a => Semigroup (Max a) # | Since: base-4.9.0.0 |
Ord a => Semigroup (Min a) # | Since: base-4.9.0.0 |
Semigroup (Equivalence a) # |
(<>) :: Equivalence a -> Equivalence a -> Equivalence a Equivalence equiv <> Equivalence equiv' = Equivalence a b -> equiv a b && equiv a b |
Defined in Data.Functor.Contravariant (<>) :: Equivalence a -> Equivalence a -> Equivalence a Source # sconcat :: NonEmpty (Equivalence a) -> Equivalence a Source # stimes :: Integral b => b -> Equivalence a -> Equivalence a Source # | |
Semigroup (Comparison a) # |
(<>) :: Comparison a -> Comparison a -> Comparison a Comparison cmp <> Comparison cmp' = Comparison a a' -> cmp a a' <> cmp a a' |
Defined in Data.Functor.Contravariant (<>) :: Comparison a -> Comparison a -> Comparison a Source # sconcat :: NonEmpty (Comparison a) -> Comparison a Source # stimes :: Integral b => b -> Comparison a -> Comparison a Source # | |
Semigroup (Predicate a) # |
(<>) :: Predicate a -> Predicate a -> Predicate a Predicate pred <> Predicate pred' = Predicate a -> pred a && pred' a |
Semigroup b => Semigroup (a -> b) # | Since: base-4.9.0.0 |
Semigroup (Either a b) # | Since: base-4.9.0.0 |
Semigroup (V1 p) # | Since: base-4.12.0.0 |
Semigroup (U1 p) # | Since: base-4.12.0.0 |
(Semigroup a, Semigroup b) => Semigroup (a, b) # | Since: base-4.9.0.0 |
Semigroup a => Semigroup (ST s a) # | Since: base-4.11.0.0 |
Semigroup (Proxy s) # | Since: base-4.9.0.0 |
Semigroup a => Semigroup (Op a b) # |
(<>) :: Op a b -> Op a b -> Op a b Op f <> Op g = Op a -> f a <> g a |
Semigroup (f p) => Semigroup (Rec1 f p) # | Since: base-4.12.0.0 |
(Semigroup a, Semigroup b, Semigroup c) => Semigroup (a, b, c) # | Since: base-4.9.0.0 |
Alternative f => Semigroup (Alt f a) # | Since: base-4.9.0.0 |
(Applicative f, Semigroup a) => Semigroup (Ap f a) # | Since: base-4.12.0.0 |
Semigroup a => Semigroup (Const a b) # | Since: base-4.9.0.0 |
Semigroup c => Semigroup (K1 i c p) # | Since: base-4.12.0.0 |
(Semigroup (f p), Semigroup (g p)) => Semigroup ((f :*: g) p) # | Since: base-4.12.0.0 |
(Semigroup a, Semigroup b, Semigroup c, Semigroup d) => Semigroup (a, b, c, d) # | Since: base-4.9.0.0 |
Semigroup (f p) => Semigroup (M1 i c f p) # | Since: base-4.12.0.0 |
Semigroup (f (g p)) => Semigroup ((f :.: g) p) # | Since: base-4.12.0.0 |
(Semigroup a, Semigroup b, Semigroup c, Semigroup d, Semigroup e) => Semigroup (a, b, c, d, e) # | 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 #
Semigroups
Instances
Monad Min # | Since: base-4.9.0.0 |
Functor Min # | Since: base-4.9.0.0 |
MonadFix Min # | Since: base-4.9.0.0 |
Applicative Min # | Since: base-4.9.0.0 |
Foldable Min # | Since: base-4.9.0.0 |
Defined in Data.Semigroup 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 # | Since: base-4.9.0.0 |
Bounded a => Bounded (Min a) # | Since: base-4.9.0.0 |
Enum a => Enum (Min a) # | Since: base-4.9.0.0 |
Defined in Data.Semigroup 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 # | |
Eq a => Eq (Min a) # | Since: base-4.9.0.0 |
Data a => Data (Min a) # | Since: base-4.9.0.0 |
Defined in Data.Semigroup 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 # | |
Num a => Num (Min a) # | Since: base-4.9.0.0 |
Ord a => Ord (Min a) # | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
Read a => Read (Min a) # | Since: base-4.9.0.0 |
Show a => Show (Min a) # | Since: base-4.9.0.0 |
Generic (Min a) # | |
Ord a => Semigroup (Min a) # | Since: base-4.9.0.0 |
(Ord a, Bounded a) => Monoid (Min a) # | Since: base-4.9.0.0 |
Generic1 Min # | |
type Rep (Min a) # | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
type Rep1 Min # | Since: base-4.9.0.0 |
Defined in Data.Semigroup |
Instances
Monad Max # | Since: base-4.9.0.0 |
Functor Max # | Since: base-4.9.0.0 |
MonadFix Max # | Since: base-4.9.0.0 |
Applicative Max # | Since: base-4.9.0.0 |
Foldable Max # | Since: base-4.9.0.0 |
Defined in Data.Semigroup 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 # | Since: base-4.9.0.0 |
Bounded a => Bounded (Max a) # | Since: base-4.9.0.0 |
Enum a => Enum (Max a) # | Since: base-4.9.0.0 |
Defined in Data.Semigroup 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 # | |
Eq a => Eq (Max a) # | Since: base-4.9.0.0 |
Data a => Data (Max a) # | Since: base-4.9.0.0 |
Defined in Data.Semigroup 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 # | |
Num a => Num (Max a) # | Since: base-4.9.0.0 |
Ord a => Ord (Max a) # | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
Read a => Read (Max a) # | Since: base-4.9.0.0 |
Show a => Show (Max a) # | Since: base-4.9.0.0 |
Generic (Max a) # | |
Ord a => Semigroup (Max a) # | Since: base-4.9.0.0 |
(Ord a, Bounded a) => Monoid (Max a) # | Since: base-4.9.0.0 |
Generic1 Max # | |
type Rep (Max a) # | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
type Rep1 Max # | Since: base-4.9.0.0 |
Defined in Data.Semigroup |
Instances
Monad First # | Since: base-4.9.0.0 |
Functor First # | Since: base-4.9.0.0 |
MonadFix First # | Since: base-4.9.0.0 |
Applicative First # | Since: base-4.9.0.0 |
Foldable First # | Since: base-4.9.0.0 |
Defined in Data.Semigroup 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.9.0.0 |
Bounded a => Bounded (First a) # | Since: base-4.9.0.0 |
Enum a => Enum (First a) # | Since: base-4.9.0.0 |
Defined in Data.Semigroup 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 # | |
Eq a => Eq (First a) # | Since: base-4.9.0.0 |
Data a => Data (First a) # | Since: base-4.9.0.0 |
Defined in Data.Semigroup 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 # | |
Ord a => Ord (First a) # | Since: base-4.9.0.0 |
Read a => Read (First a) # | Since: base-4.9.0.0 |
Show a => Show (First a) # | Since: base-4.9.0.0 |
Generic (First a) # | |
Semigroup (First a) # | Since: base-4.9.0.0 |
Generic1 First # | |
type Rep (First a) # | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
type Rep1 First # | Since: base-4.9.0.0 |
Defined in Data.Semigroup |
Instances
Monad Last # | Since: base-4.9.0.0 |
Functor Last # | Since: base-4.9.0.0 |
MonadFix Last # | Since: base-4.9.0.0 |
Applicative Last # | Since: base-4.9.0.0 |
Foldable Last # | Since: base-4.9.0.0 |
Defined in Data.Semigroup 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.9.0.0 |
Bounded a => Bounded (Last a) # | Since: base-4.9.0.0 |
Enum a => Enum (Last a) # | Since: base-4.9.0.0 |
Defined in Data.Semigroup 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 # | |
Eq a => Eq (Last a) # | Since: base-4.9.0.0 |
Data a => Data (Last a) # | Since: base-4.9.0.0 |
Defined in Data.Semigroup 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 # | |
Ord a => Ord (Last a) # | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
Read a => Read (Last a) # | Since: base-4.9.0.0 |
Show a => Show (Last a) # | Since: base-4.9.0.0 |
Generic (Last a) # | |
Semigroup (Last a) # | Since: base-4.9.0.0 |
Generic1 Last # | |
type Rep (Last a) # | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
type Rep1 Last # | 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.
WrapMonoid | |
|
Instances
Re-exported monoids from Data.Monoid
The dual of a Monoid
, obtained by swapping the arguments of mappend
.
>>>
getDual (mappend (Dual "Hello") (Dual "World"))
"WorldHello"
Instances
Monad Dual # | Since: base-4.8.0.0 |
Functor Dual # | Since: base-4.8.0.0 |
MonadFix Dual # | Since: base-4.8.0.0 |
Applicative Dual # | Since: base-4.8.0.0 |
Foldable Dual # | Since: base-4.8.0.0 |
Defined in 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 |
MonadZip Dual # | Since: base-4.8.0.0 |
Bounded a => Bounded (Dual a) # | Since: base-2.1 |
Eq a => Eq (Dual a) # | Since: base-2.1 |
Data a => Data (Dual a) # | 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) -> 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 # | |
Ord a => Ord (Dual a) # | Since: base-2.1 |
Defined in Data.Semigroup.Internal | |
Read a => Read (Dual a) # | Since: base-2.1 |
Show a => Show (Dual a) # | Since: base-2.1 |
Generic (Dual a) # | |
Semigroup a => Semigroup (Dual a) # | Since: base-4.9.0.0 |
Monoid a => Monoid (Dual a) # | Since: base-2.1 |
Generic1 Dual # | |
type Rep (Dual a) # | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal | |
type Rep1 Dual # | Since: base-4.7.0.0 |
Defined in Data.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
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 # | |
Semigroup All # | Since: base-4.9.0.0 |
Monoid All # | Since: base-2.1 |
type Rep All # | Since: base-4.7.0.0 |
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 # | |
Semigroup Any # | Since: base-4.9.0.0 |
Monoid Any # | Since: base-2.1 |
type Rep Any # | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal |
Monoid under addition.
>>>
getSum (Sum 1 <> Sum 2 <> mempty)
3
Instances
Monad Sum # | Since: base-4.8.0.0 |
Functor Sum # | Since: base-4.8.0.0 |
MonadFix Sum # | Since: base-4.8.0.0 |
Applicative Sum # | Since: base-4.8.0.0 |
Foldable Sum # | Since: base-4.8.0.0 |
Defined in 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 |
MonadZip Sum # | Since: base-4.8.0.0 |
Bounded a => Bounded (Sum a) # | Since: base-2.1 |
Eq a => Eq (Sum a) # | Since: base-2.1 |
Data a => Data (Sum a) # | 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) -> 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 # | |
Num a => Num (Sum a) # | Since: base-4.7.0.0 |
Ord a => Ord (Sum a) # | Since: base-2.1 |
Defined in Data.Semigroup.Internal | |
Read a => Read (Sum a) # | Since: base-2.1 |
Show a => Show (Sum a) # | Since: base-2.1 |
Generic (Sum a) # | |
Num a => Semigroup (Sum a) # | Since: base-4.9.0.0 |
Num a => Monoid (Sum a) # | Since: base-2.1 |
Generic1 Sum # | |
type Rep (Sum a) # | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal | |
type Rep1 Sum # | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal |
Monoid under multiplication.
>>>
getProduct (Product 3 <> Product 4 <> mempty)
12
Product | |
|
Instances
Monad Product # | Since: base-4.8.0.0 |
Functor Product # | Since: base-4.8.0.0 |
MonadFix Product # | Since: base-4.8.0.0 |
Applicative Product # | Since: base-4.8.0.0 |
Defined in Data.Semigroup.Internal | |
Foldable Product # | Since: base-4.8.0.0 |
Defined in 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 Data.Traversable | |
MonadZip Product # | Since: base-4.8.0.0 |
Bounded a => Bounded (Product a) # | Since: base-2.1 |
Eq a => Eq (Product a) # | Since: base-2.1 |
Data a => Data (Product a) # | 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) -> 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 # | |
Num a => Num (Product a) # | Since: base-4.7.0.0 |
Defined in 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 # | |
Ord a => Ord (Product a) # | Since: base-2.1 |
Defined in Data.Semigroup.Internal | |
Read a => Read (Product a) # | Since: base-2.1 |
Show a => Show (Product a) # | Since: base-2.1 |
Generic (Product a) # | |
Num a => Semigroup (Product a) # | Since: base-4.9.0.0 |
Num a => Monoid (Product a) # | Since: base-2.1 |
Generic1 Product # | |
type Rep (Product a) # | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal | |
type Rep1 Product # | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal |
A better monoid for Maybe
Deprecated: will be removed in GHC 9.2; use Maybe
instead.
Option
is effectively Maybe
with a better instance of
Monoid
, built off of an underlying Semigroup
instead of an
underlying Monoid
.
Ideally, this type would not exist at all and we would just fix the
Monoid
instance of Maybe
.
In GHC 8.4 and higher, the Monoid
instance for Maybe
has been
corrected to lift a Semigroup
instance instead of a Monoid
instance. Consequently, this type is no longer useful.
Instances
Monad Option # | Since: base-4.9.0.0 |
Functor Option # | Since: base-4.9.0.0 |
MonadFix Option # | Since: base-4.9.0.0 |
Applicative Option # | Since: base-4.9.0.0 |
Foldable Option # | Since: base-4.9.0.0 |
Defined in Data.Semigroup fold :: Monoid m => Option m -> m Source # foldMap :: Monoid m => (a -> m) -> Option a -> m Source # foldMap' :: Monoid m => (a -> m) -> Option a -> m Source # foldr :: (a -> b -> b) -> b -> Option a -> b Source # foldr' :: (a -> b -> b) -> b -> Option a -> b Source # foldl :: (b -> a -> b) -> b -> Option a -> b Source # foldl' :: (b -> a -> b) -> b -> Option a -> b Source # foldr1 :: (a -> a -> a) -> Option a -> a Source # foldl1 :: (a -> a -> a) -> Option a -> a Source # toList :: Option a -> [a] Source # null :: Option a -> Bool Source # length :: Option a -> Int Source # elem :: Eq a => a -> Option a -> Bool Source # maximum :: Ord a => Option a -> a Source # minimum :: Ord a => Option a -> a Source # | |
Traversable Option # | Since: base-4.9.0.0 |
MonadPlus Option # | Since: base-4.9.0.0 |
Alternative Option # | Since: base-4.9.0.0 |
Eq a => Eq (Option a) # | Since: base-4.9.0.0 |
Data a => Data (Option a) # | Since: base-4.9.0.0 |
Defined in Data.Semigroup 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 -> Constr Source # dataTypeOf :: Option a -> DataType Source # 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 a Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Option a -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Option a -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Option a -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Option a -> u Source # 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) # | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
Read a => Read (Option a) # | Since: base-4.9.0.0 |
Show a => Show (Option a) # | Since: base-4.9.0.0 |
Generic (Option a) # | |
Semigroup a => Semigroup (Option a) # | Since: base-4.9.0.0 |
Semigroup a => Monoid (Option a) # | Since: base-4.9.0.0 |
Generic1 Option # | |
type Rep (Option a) # | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
type Rep1 Option # | Since: base-4.9.0.0 |
Defined in Data.Semigroup |
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
.
Example:
>>>
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.
>>>
minimum [ Arg (x * x) x | x <- [-10 .. 10] ]
Arg 0 0
Instances
Bifunctor Arg # | Since: base-4.9.0.0 |
Bifoldable Arg # | Since: base-4.10.0.0 |
Bitraversable Arg # | Since: base-4.10.0.0 |
Defined in Data.Semigroup bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Arg a b -> f (Arg c d) Source # | |
Functor (Arg a) # | Since: base-4.9.0.0 |
Foldable (Arg a) # | Since: base-4.9.0.0 |
Defined in Data.Semigroup 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) # | Since: base-4.9.0.0 |
Generic1 (Arg a :: Type -> Type) # | |
Eq a => Eq (Arg a b) # | Since: base-4.9.0.0 |
(Data a, Data b) => Data (Arg a b) # | Since: base-4.9.0.0 |
Defined in Data.Semigroup 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 # | |
Ord a => Ord (Arg a b) # | Since: base-4.9.0.0 |
(Read a, Read b) => Read (Arg a b) # | Since: base-4.9.0.0 |
(Show a, Show b) => Show (Arg a b) # | Since: base-4.9.0.0 |
Generic (Arg a b) # | |
type Rep1 (Arg a :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Semigroup type Rep1 (Arg a :: Type -> Type) = D1 ('MetaData "Arg" "Data.Semigroup" "base" '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) # | Since: base-4.9.0.0 |
Defined in Data.Semigroup type Rep (Arg a b) = D1 ('MetaData "Arg" "Data.Semigroup" "base" '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))) |