Copyright | (c) 2016 Stephen Diehl (c) 2016-2018 Serokell (c) 2018-2023 Kowainik |
---|---|
License | MIT |
Maintainer | Kowainik <xrom.xkov@gmail.com> |
Stability | Stable |
Portability | Portable |
Safe Haskell | Safe |
Language | Haskell2010 |
Relude.Monoid
Contents
Description
Reexports functions to work with monoids plus adds extra useful functions.
Synopsis
- newtype Any = Any {}
- newtype Last a = Last {}
- newtype First a = First {}
- class Semigroup a => Monoid a where
- newtype Alt (f :: k -> Type) (a :: k) = Alt {
- getAlt :: f a
- newtype Product a = Product {
- getProduct :: a
- newtype Sum a = Sum {
- getSum :: a
- newtype All = All {}
- newtype Endo a = Endo {
- appEndo :: a -> a
- newtype Dual a = Dual {
- getDual :: a
- newtype Ap (f :: k -> Type) (a :: k) = Ap {
- getAp :: f a
- class Semigroup a where
- stimesIdempotent :: Integral b => b -> a -> a
- stimesIdempotentMonoid :: (Integral b, Monoid a) => b -> a -> a
- stimesMonoid :: (Integral b, Monoid a) => b -> a -> a
- data WrappedMonoid m
- cycle1 :: Semigroup m => m -> m
- mtimesDefault :: (Integral b, Monoid a) => b -> a -> a
- newtype Ap (f :: k -> Type) (a :: k) = Ap {
- getAp :: f a
- maybeToMonoid :: Monoid m => Maybe m -> m
- memptyIfFalse :: Monoid m => Bool -> m -> m
- memptyIfTrue :: Monoid m => Bool -> m -> m
Reexports
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
NFData Any | Since: deepseq-1.4.0.0 | ||||
Defined in Control.DeepSeq | |||||
Monoid Any | @since base-2.01 | ||||
Semigroup Any | @since base-4.9.0.0 | ||||
Data Any | @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 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Any # dataTypeOf :: Any -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Any) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Any) # gmapT :: (forall b. Data b => b -> b) -> Any -> Any # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Any -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Any -> r # gmapQ :: (forall d. Data d => d -> u) -> Any -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Any -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Any -> m Any # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Any -> m Any # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Any -> m Any # | |||||
Bounded Any | @since base-2.01 | ||||
Generic Any | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
Read Any | @since base-2.01 | ||||
Show Any | @since base-2.01 | ||||
Eq Any | @since base-2.01 | ||||
Ord Any | @since base-2.01 | ||||
type Rep Any | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal |
Maybe monoid returning the rightmost non-Nothing
value.
is isomorphic to Last
a
, and thus to
Dual
(First
a)Dual
(Alt
Maybe
a)
Data.Semigroup.
Last
. The former returns the last non-Nothing
,
so x <> Data.Monoid.Last Nothing = x
. The latter simply returns the last value,
thus x <> Data.Semigroup.Last Nothing = Data.Semigroup.Last Nothing
.
Examples
>>>
Last (Just "hello") <> Last Nothing <> Last (Just "world")
Last {getLast = Just "world"}
>>>
Last Nothing <> mempty
Last {getLast = Nothing}
Instances
MonadZip Last | Since: base-4.8.0.0 | ||||
NFData1 Last | Since: deepseq-1.4.3.0 | ||||
Defined in Control.DeepSeq | |||||
Applicative Last | @since base-4.8.0.0 | ||||
Functor Last | @since base-4.8.0.0 | ||||
Monad Last | @since base-4.8.0.0 | ||||
Foldable Last | @since base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Foldable Methods fold :: Monoid m => Last m -> m # foldMap :: Monoid m => (a -> m) -> Last a -> m # foldMap' :: Monoid m => (a -> m) -> Last a -> m # foldr :: (a -> b -> b) -> b -> Last a -> b # foldr' :: (a -> b -> b) -> b -> Last a -> b # foldl :: (b -> a -> b) -> b -> Last a -> b # foldl' :: (b -> a -> b) -> b -> Last a -> b # foldr1 :: (a -> a -> a) -> Last a -> a # foldl1 :: (a -> a -> a) -> Last a -> a # elem :: Eq a => a -> Last a -> Bool # maximum :: Ord a => Last a -> a # | |||||
Traversable Last | @since base-4.8.0.0 | ||||
Generic1 Last | |||||
Defined in GHC.Internal.Data.Monoid Associated Types
| |||||
NFData a => NFData (Last a) | Since: deepseq-1.4.0.0 | ||||
Defined in Control.DeepSeq | |||||
Monoid (Last a) | @since base-2.01 | ||||
Semigroup (Last a) | @since base-4.9.0.0 | ||||
Data a => Data (Last a) | @since base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Last a -> c (Last a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Last a) # toConstr :: Last a -> Constr # dataTypeOf :: Last a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Last a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Last a)) # gmapT :: (forall b. Data b => b -> b) -> Last a -> Last a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Last a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Last a -> r # gmapQ :: (forall d. Data d => d -> u) -> Last a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Last a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Last a -> m (Last a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Last a -> m (Last a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Last a -> m (Last a) # | |||||
Generic (Last a) | |||||
Defined in GHC.Internal.Data.Monoid Associated Types
| |||||
Read a => Read (Last a) | @since base-2.01 | ||||
Show a => Show (Last a) | @since base-2.01 | ||||
Eq a => Eq (Last a) | @since base-2.01 | ||||
Ord a => Ord (Last a) | @since base-2.01 | ||||
type Rep1 Last | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Monoid | |||||
type Rep (Last a) | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Monoid |
Maybe monoid returning the leftmost non-Nothing
value.
is isomorphic to First
a
, but precedes it
historically.Alt
Maybe
a
Beware that Data.Monoid.
First
is different from
Data.Semigroup.
First
. The former returns the first non-Nothing
,
so Data.Monoid.First Nothing <> x = x
. The latter simply returns the first value,
thus Data.Semigroup.First Nothing <> x = Data.Semigroup.First Nothing
.
Examples
>>>
First (Just "hello") <> First Nothing <> First (Just "world")
First {getFirst = Just "hello"}
>>>
First Nothing <> mempty
First {getFirst = Nothing}
Instances
MonadZip First | Since: base-4.8.0.0 | ||||
NFData1 First | Since: deepseq-1.4.3.0 | ||||
Defined in Control.DeepSeq | |||||
Applicative First | @since base-4.8.0.0 | ||||
Functor First | @since base-4.8.0.0 | ||||
Monad First | @since base-4.8.0.0 | ||||
Foldable First | @since base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Foldable Methods fold :: Monoid m => First m -> m # foldMap :: Monoid m => (a -> m) -> First a -> m # foldMap' :: Monoid m => (a -> m) -> First a -> m # foldr :: (a -> b -> b) -> b -> First a -> b # foldr' :: (a -> b -> b) -> b -> First a -> b # foldl :: (b -> a -> b) -> b -> First a -> b # foldl' :: (b -> a -> b) -> b -> First a -> b # foldr1 :: (a -> a -> a) -> First a -> a # foldl1 :: (a -> a -> a) -> First a -> a # elem :: Eq a => a -> First a -> Bool # maximum :: Ord a => First a -> a # minimum :: Ord a => First a -> a # | |||||
Traversable First | @since base-4.8.0.0 | ||||
Generic1 First | |||||
Defined in GHC.Internal.Data.Monoid Associated Types
| |||||
NFData a => NFData (First a) | Since: deepseq-1.4.0.0 | ||||
Defined in Control.DeepSeq | |||||
Monoid (First a) | @since base-2.01 | ||||
Semigroup (First a) | @since base-4.9.0.0 | ||||
Data a => Data (First a) | @since base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> First a -> c (First a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (First a) # toConstr :: First a -> Constr # dataTypeOf :: First a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (First a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (First a)) # gmapT :: (forall b. Data b => b -> b) -> First a -> First a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> First a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> First a -> r # gmapQ :: (forall d. Data d => d -> u) -> First a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> First a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> First a -> m (First a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> First a -> m (First a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> First a -> m (First a) # | |||||
Generic (First a) | |||||
Defined in GHC.Internal.Data.Monoid Associated Types
| |||||
Read a => Read (First a) | @since base-2.01 | ||||
Show a => Show (First a) | @since base-2.01 | ||||
Eq a => Eq (First a) | @since base-2.01 | ||||
Ord a => Ord (First a) | @since base-2.01 | ||||
Defined in GHC.Internal.Data.Monoid | |||||
type Rep1 First | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Monoid | |||||
type Rep (First a) | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Monoid |
class Semigroup a => Monoid a where #
The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following:
- Right identity
x
<>
mempty
= x- Left identity
mempty
<>
x = x- Associativity
x
(<>
(y<>
z) = (x<>
y)<>
zSemigroup
law)- Concatenation
mconcat
=foldr
(<>
)mempty
You can alternatively define mconcat
instead of mempty
, in which case the
laws are:
- Unit
mconcat
(pure
x) = x- Multiplication
mconcat
(join
xss) =mconcat
(fmap
mconcat
xss)- Subclass
mconcat
(toList
xs) =sconcat
xs
The method names refer to the monoid of lists under concatenation, but there are many other instances.
Some types can be viewed as a monoid in more than one way,
e.g. both addition and multiplication on numbers.
In such cases we often define newtype
s and make those instances
of Monoid
, e.g. Sum
and Product
.
NOTE: Semigroup
is a superclass of Monoid
since base-4.11.0.0.
Methods
Identity of mappend
Examples
>>>
"Hello world" <> mempty
"Hello world"
>>>
mempty <> [1, 2, 3]
[1,2,3]
An associative operation
NOTE: This method is redundant and has the default
implementation
since base-4.11.0.0.
Should it be implemented manually, since mappend
= (<>
)mappend
is a synonym for
(<>
), it is expected that the two functions are defined the same
way. In a future GHC release mappend
will be removed from Monoid
.
Fold a list using the monoid.
For most types, the default definition for mconcat
will be
used, but the function is included in the class definition so
that an optimized version can be provided for specific types.
>>>
mconcat ["Hello", " ", "Haskell", "!"]
"Hello Haskell!"
Instances
Monoid ByteArray | Since: base-4.17.0.0 |
Monoid Builder | |
Monoid ByteString | |
Defined in Data.ByteString.Internal.Type Methods mempty :: ByteString # mappend :: ByteString -> ByteString -> ByteString # mconcat :: [ByteString] -> ByteString # | |
Monoid ByteString | |
Defined in Data.ByteString.Lazy.Internal Methods mempty :: ByteString # mappend :: ByteString -> ByteString -> ByteString # mconcat :: [ByteString] -> ByteString # | |
Monoid ShortByteString | |
Defined in Data.ByteString.Short.Internal Methods mappend :: ShortByteString -> ShortByteString -> ShortByteString # mconcat :: [ShortByteString] -> ShortByteString # | |
Monoid IntSet | |
Monoid All | @since base-2.01 |
Monoid Any | @since base-2.01 |
Monoid Ordering | @since base-2.01 |
Monoid OsString | "String-Concatenation" for |
Monoid PosixString | |
Defined in System.OsString.Internal.Types Methods mempty :: PosixString # mappend :: PosixString -> PosixString -> PosixString # mconcat :: [PosixString] -> PosixString # | |
Monoid WindowsString | |
Defined in System.OsString.Internal.Types Methods mempty :: WindowsString # mappend :: WindowsString -> WindowsString -> WindowsString # mconcat :: [WindowsString] -> WindowsString # | |
Monoid Doc | |
Monoid Builder | |
Monoid StrictBuilder | |
Defined in Data.Text.Internal.StrictBuilder Methods mempty :: StrictBuilder # mappend :: StrictBuilder -> StrictBuilder -> StrictBuilder # mconcat :: [StrictBuilder] -> StrictBuilder # | |
Monoid () | @since base-2.01 |
Monoid (Comparison a) |
mempty :: Comparison a mempty = Comparison _ _ -> EQ |
Defined in Data.Functor.Contravariant Methods mempty :: Comparison a # mappend :: Comparison a -> Comparison a -> Comparison a # mconcat :: [Comparison a] -> Comparison a # | |
Monoid (Equivalence a) |
mempty :: Equivalence a mempty = Equivalence _ _ -> True |
Defined in Data.Functor.Contravariant Methods mempty :: Equivalence a # mappend :: Equivalence a -> Equivalence a -> Equivalence a # mconcat :: [Equivalence a] -> Equivalence a # | |
Monoid (Predicate a) |
mempty :: Predicate a mempty = _ -> True |
(Ord a, Bounded a) => Monoid (Max a) | Since: base-4.9.0.0 |
(Ord a, Bounded a) => Monoid (Min a) | Since: base-4.9.0.0 |
Monoid m => Monoid (WrappedMonoid m) | Since: base-4.9.0.0 |
Defined in Data.Semigroup Methods mempty :: WrappedMonoid m # mappend :: WrappedMonoid m -> WrappedMonoid m -> WrappedMonoid m # mconcat :: [WrappedMonoid m] -> WrappedMonoid m # | |
Monoid (IntMap a) | |
Monoid (Seq a) | |
Monoid (MergeSet a) | |
Ord a => Monoid (Set a) | |
Monoid a => Monoid (STM a) | @since base-4.17.0.0 |
Monoid a => Monoid (Identity a) | @since base-4.9.0.0 |
Monoid (First a) | @since base-2.01 |
Monoid (Last a) | @since base-2.01 |
Monoid a => Monoid (Down a) | @since base-4.11.0.0 |
Monoid a => Monoid (Dual a) | @since base-2.01 |
Monoid (Endo a) | @since base-2.01 |
Num a => Monoid (Product a) | @since base-2.01 |
Num a => Monoid (Sum a) | @since base-2.01 |
(Generic a, Monoid (Rep a ())) => Monoid (Generically a) | @since base-4.17.0.0 |
Defined in GHC.Internal.Generics Methods mempty :: Generically a # mappend :: Generically a -> Generically a -> Generically a # mconcat :: [Generically a] -> Generically a # | |
Monoid p => Monoid (Par1 p) | @since base-4.12.0.0 |
Monoid a => Monoid (IO a) | @since base-4.9.0.0 |
Monoid (Validity k) | |
(Hashable a, Eq a) => Monoid (HashSet a) | \(O(n+m)\) To obtain good performance, the smaller set must be presented as the first argument. Examples
|
Monoid (Doc a) | |
Monoid a => Monoid (Q a) | Since: template-haskell-2.17.0.0 |
Semigroup a => Monoid (Maybe a) | Lift a semigroup into Since 4.11.0: constraint on inner @since base-2.01 |
Monoid a => Monoid (Solo a) | @since base-4.15 |
Monoid [a] | @since base-2.01 |
Monoid a => Monoid (Op a b) |
mempty :: Op a b mempty = Op _ -> mempty |
Ord k => Monoid (Map k v) | |
Monoid (Proxy s) | @since base-4.7.0.0 |
Monoid (U1 p) | @since base-4.12.0.0 |
(Eq k, Hashable k) => Monoid (HashMap k v) | If a key occurs in both maps, the mapping from the first will be the mapping in the result. Examples
|
(Monoid a, Monoid b) => Monoid (a, b) | @since base-2.01 |
Monoid b => Monoid (a -> b) | @since base-2.01 |
Monoid a => Monoid (Const a b) | @since base-4.9.0.0 |
(Applicative f, Monoid a) => Monoid (Ap f a) | @since base-4.12.0.0 |
Alternative f => Monoid (Alt f a) | @since base-4.8.0.0 |
Monoid (f p) => Monoid (Rec1 f p) | @since base-4.12.0.0 |
Monoid a => Monoid (Constant a b) | |
(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) | @since base-2.01 |
(Monoid (f a), Monoid (g a)) => Monoid (Product f g a) | Since: base-4.16.0.0 |
(Monoid (f p), Monoid (g p)) => Monoid ((f :*: g) p) | @since base-4.12.0.0 |
Monoid c => Monoid (K1 i c p) | @since base-4.12.0.0 |
(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d) | @since base-2.01 |
Monoid (f (g a)) => Monoid (Compose f g a) | Since: base-4.16.0.0 |
Monoid (f (g p)) => Monoid ((f :.: g) p) | @since base-4.12.0.0 |
Monoid (f p) => Monoid (M1 i c f p) | @since base-4.12.0.0 |
(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e) | @since base-2.01 |
newtype Alt (f :: k -> Type) (a :: k) #
Monoid under <|>
.
Alt l <> Alt r == Alt (l <|> r)
Examples
>>>
Alt (Just 12) <> Alt (Just 24)
Alt {getAlt = Just 12}
>>>
Alt Nothing <> Alt (Just 24)
Alt {getAlt = Just 24}
@since base-4.8.0.0
Instances
Generic1 (Alt f :: k -> Type) | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
MonadZip f => MonadZip (Alt f) | Since: base-4.8.0.0 | ||||
Foldable1 f => Foldable1 (Alt f) | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 Methods fold1 :: Semigroup m => Alt f m -> m # foldMap1 :: Semigroup m => (a -> m) -> Alt f a -> m # foldMap1' :: Semigroup m => (a -> m) -> Alt f a -> m # toNonEmpty :: Alt f a -> NonEmpty a # maximum :: Ord a => Alt f a -> a # minimum :: Ord a => Alt f a -> a # foldrMap1 :: (a -> b) -> (a -> b -> b) -> Alt f a -> b # foldlMap1' :: (a -> b) -> (b -> a -> b) -> Alt f a -> b # foldlMap1 :: (a -> b) -> (b -> a -> b) -> Alt f a -> b # foldrMap1' :: (a -> b) -> (a -> b -> b) -> Alt f a -> b # | |||||
Contravariant f => Contravariant (Alt f) | |||||
Alternative f => Alternative (Alt f) | @since base-4.8.0.0 | ||||
Applicative f => Applicative (Alt f) | @since base-4.8.0.0 | ||||
Functor f => Functor (Alt f) | @since base-4.8.0.0 | ||||
Monad f => Monad (Alt f) | @since base-4.8.0.0 | ||||
MonadPlus f => MonadPlus (Alt f) | @since base-4.8.0.0 | ||||
Foldable f => Foldable (Alt f) | @since base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Foldable Methods fold :: Monoid m => Alt f m -> m # foldMap :: Monoid m => (a -> m) -> Alt f a -> m # foldMap' :: Monoid m => (a -> m) -> Alt f a -> m # foldr :: (a -> b -> b) -> b -> Alt f a -> b # foldr' :: (a -> b -> b) -> b -> Alt f a -> b # foldl :: (b -> a -> b) -> b -> Alt f a -> b # foldl' :: (b -> a -> b) -> b -> Alt f a -> b # foldr1 :: (a -> a -> a) -> Alt f a -> a # foldl1 :: (a -> a -> a) -> Alt f a -> a # elem :: Eq a => a -> Alt f a -> Bool # maximum :: Ord a => Alt f a -> a # minimum :: Ord a => Alt f a -> a # | |||||
Traversable f => Traversable (Alt f) | @since base-4.12.0.0 | ||||
Alternative f => Monoid (Alt f a) | @since base-4.8.0.0 | ||||
Alternative f => Semigroup (Alt f a) | @since base-4.9.0.0 | ||||
(Data (f a), Data a, Typeable f) => Data (Alt f a) | @since base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Alt f a -> c (Alt f a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Alt f a) # toConstr :: Alt f a -> Constr # dataTypeOf :: Alt f a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Alt f a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Alt f a)) # gmapT :: (forall b. Data b => b -> b) -> Alt f a -> Alt f a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Alt f a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Alt f a -> r # gmapQ :: (forall d. Data d => d -> u) -> Alt f a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Alt f a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Alt f a -> m (Alt f a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Alt f a -> m (Alt f a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Alt f a -> m (Alt f a) # | |||||
Enum (f a) => Enum (Alt f a) | @since base-4.8.0.0 | ||||
Generic (Alt f a) | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
Num (f a) => Num (Alt f a) | @since base-4.8.0.0 | ||||
Read (f a) => Read (Alt f a) | @since base-4.8.0.0 | ||||
Show (f a) => Show (Alt f a) | @since base-4.8.0.0 | ||||
Eq (f a) => Eq (Alt f a) | @since base-4.8.0.0 | ||||
Ord (f a) => Ord (Alt f a) | @since base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
type Rep1 (Alt f :: k -> Type) | @since base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
type Rep (Alt f a) | @since base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal |
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
MonadZip Product | Since: base-4.8.0.0 | ||||
Foldable1 Product | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 Methods fold1 :: Semigroup m => Product m -> m # foldMap1 :: Semigroup m => (a -> m) -> Product a -> m # foldMap1' :: Semigroup m => (a -> m) -> Product a -> m # toNonEmpty :: Product a -> NonEmpty a # maximum :: Ord a => Product a -> a # minimum :: Ord a => Product a -> a # foldrMap1 :: (a -> b) -> (a -> b -> b) -> Product a -> b # foldlMap1' :: (a -> b) -> (b -> a -> b) -> Product a -> b # foldlMap1 :: (a -> b) -> (b -> a -> b) -> Product a -> b # foldrMap1' :: (a -> b) -> (a -> b -> b) -> Product a -> b # | |||||
NFData1 Product | Since: deepseq-1.4.3.0 | ||||
Defined in Control.DeepSeq | |||||
Applicative Product | @since base-4.8.0.0 | ||||
Functor Product | @since base-4.8.0.0 | ||||
Monad Product | @since base-4.8.0.0 | ||||
Foldable Product | @since base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Foldable Methods fold :: Monoid m => Product m -> m # foldMap :: Monoid m => (a -> m) -> Product a -> m # foldMap' :: Monoid m => (a -> m) -> Product a -> m # foldr :: (a -> b -> b) -> b -> Product a -> b # foldr' :: (a -> b -> b) -> b -> Product a -> b # foldl :: (b -> a -> b) -> b -> Product a -> b # foldl' :: (b -> a -> b) -> b -> Product a -> b # foldr1 :: (a -> a -> a) -> Product a -> a # foldl1 :: (a -> a -> a) -> Product a -> a # elem :: Eq a => a -> Product a -> Bool # maximum :: Ord a => Product a -> a # minimum :: Ord a => Product a -> a # | |||||
Traversable Product | @since base-4.8.0.0 | ||||
Generic1 Product | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
NFData a => NFData (Product a) | Since: deepseq-1.4.0.0 | ||||
Defined in Control.DeepSeq | |||||
Num a => Monoid (Product a) | @since base-2.01 | ||||
Num a => Semigroup (Product a) | @since base-4.9.0.0 | ||||
Data a => Data (Product a) | @since base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Product a -> c (Product a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Product a) # toConstr :: Product a -> Constr # dataTypeOf :: Product a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Product a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Product a)) # gmapT :: (forall b. Data b => b -> b) -> Product a -> Product a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Product a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Product a -> r # gmapQ :: (forall d. Data d => d -> u) -> Product a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Product a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Product a -> m (Product a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Product a -> m (Product a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Product a -> m (Product a) # | |||||
Bounded a => Bounded (Product a) | @since base-2.01 | ||||
Generic (Product a) | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
Num a => Num (Product a) | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
Read a => Read (Product a) | @since base-2.01 | ||||
Show a => Show (Product a) | @since base-2.01 | ||||
Eq a => Eq (Product a) | @since base-2.01 | ||||
Ord a => Ord (Product a) | @since base-2.01 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
type Rep1 Product | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
type Rep (Product a) | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal |
Monoid under addition.
Sum a <> Sum b = Sum (a + b)
Examples
>>>
Sum 1 <> Sum 2 <> mempty
Sum {getSum = 3}
>>>
mconcat [ Sum n | n <- [3 .. 9]]
Sum {getSum = 42}
Instances
MonadZip Sum | Since: base-4.8.0.0 | ||||
Foldable1 Sum | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 Methods fold1 :: Semigroup m => Sum m -> m # foldMap1 :: Semigroup m => (a -> m) -> Sum a -> m # foldMap1' :: Semigroup m => (a -> m) -> Sum a -> m # toNonEmpty :: Sum a -> NonEmpty a # maximum :: Ord a => Sum a -> a # minimum :: Ord a => Sum a -> a # foldrMap1 :: (a -> b) -> (a -> b -> b) -> Sum a -> b # foldlMap1' :: (a -> b) -> (b -> a -> b) -> Sum a -> b # foldlMap1 :: (a -> b) -> (b -> a -> b) -> Sum a -> b # foldrMap1' :: (a -> b) -> (a -> b -> b) -> Sum a -> b # | |||||
NFData1 Sum | Since: deepseq-1.4.3.0 | ||||
Defined in Control.DeepSeq | |||||
Applicative Sum | @since base-4.8.0.0 | ||||
Functor Sum | @since base-4.8.0.0 | ||||
Monad Sum | @since base-4.8.0.0 | ||||
Foldable Sum | @since base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Foldable Methods fold :: Monoid m => Sum m -> m # foldMap :: Monoid m => (a -> m) -> Sum a -> m # foldMap' :: Monoid m => (a -> m) -> Sum a -> m # foldr :: (a -> b -> b) -> b -> Sum a -> b # foldr' :: (a -> b -> b) -> b -> Sum a -> b # foldl :: (b -> a -> b) -> b -> Sum a -> b # foldl' :: (b -> a -> b) -> b -> Sum a -> b # foldr1 :: (a -> a -> a) -> Sum a -> a # foldl1 :: (a -> a -> a) -> Sum a -> a # elem :: Eq a => a -> Sum a -> Bool # maximum :: Ord a => Sum a -> a # | |||||
Traversable Sum | @since base-4.8.0.0 | ||||
Generic1 Sum | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
NFData a => NFData (Sum a) | Since: deepseq-1.4.0.0 | ||||
Defined in Control.DeepSeq | |||||
Num a => Monoid (Sum a) | @since base-2.01 | ||||
Num a => Semigroup (Sum a) | @since base-4.9.0.0 | ||||
Data a => Data (Sum a) | @since base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Sum a -> c (Sum a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Sum a) # dataTypeOf :: Sum a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Sum a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Sum a)) # gmapT :: (forall b. Data b => b -> b) -> Sum a -> Sum a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sum a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sum a -> r # gmapQ :: (forall d. Data d => d -> u) -> Sum a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Sum a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Sum a -> m (Sum a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Sum a -> m (Sum a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Sum a -> m (Sum a) # | |||||
Bounded a => Bounded (Sum a) | @since base-2.01 | ||||
Generic (Sum a) | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
Num a => Num (Sum a) | @since base-4.7.0.0 | ||||
Read a => Read (Sum a) | @since base-2.01 | ||||
Show a => Show (Sum a) | @since base-2.01 | ||||
Eq a => Eq (Sum a) | @since base-2.01 | ||||
Ord a => Ord (Sum a) | @since base-2.01 | ||||
type Rep1 Sum | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
type Rep (Sum a) | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal |
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
NFData All | Since: deepseq-1.4.0.0 | ||||
Defined in Control.DeepSeq | |||||
Monoid All | @since base-2.01 | ||||
Semigroup All | @since base-4.9.0.0 | ||||
Data All | @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 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c All # dataTypeOf :: All -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c All) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c All) # gmapT :: (forall b. Data b => b -> b) -> All -> All # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> All -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> All -> r # gmapQ :: (forall d. Data d => d -> u) -> All -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> All -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> All -> m All # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> All -> m All # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> All -> m All # | |||||
Bounded All | @since base-2.01 | ||||
Generic All | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
Read All | @since base-2.01 | ||||
Show All | @since base-2.01 | ||||
Eq All | @since base-2.01 | ||||
Ord All | @since base-2.01 | ||||
type Rep All | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal |
The monoid of endomorphisms under composition.
Endo f <> Endo g == Endo (f . g)
Examples
>>>
let computation = Endo ("Hello, " ++) <> Endo (++ "!")
>>>
appEndo computation "Haskell"
"Hello, Haskell!"
>>>
let computation = Endo (*3) <> Endo (+1)
>>>
appEndo computation 1
6
Instances
Monoid (Endo a) | @since base-2.01 | ||||
Semigroup (Endo a) | @since base-4.9.0.0 | ||||
Generic (Endo a) | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
type Rep (Endo a) | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal |
The dual of a Monoid
, obtained by swapping the arguments of (<>)
.
Dual a <> Dual b == Dual (b <> a)
Examples
>>>
Dual "Hello" <> Dual "World"
Dual {getDual = "WorldHello"}
>>>
Dual (Dual "Hello") <> Dual (Dual "World")
Dual {getDual = Dual {getDual = "HelloWorld"}}
Instances
MonadZip Dual | Since: base-4.8.0.0 | ||||
Foldable1 Dual | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 Methods fold1 :: Semigroup m => Dual m -> m # foldMap1 :: Semigroup m => (a -> m) -> Dual a -> m # foldMap1' :: Semigroup m => (a -> m) -> Dual a -> m # toNonEmpty :: Dual a -> NonEmpty a # maximum :: Ord a => Dual a -> a # minimum :: Ord a => Dual a -> a # foldrMap1 :: (a -> b) -> (a -> b -> b) -> Dual a -> b # foldlMap1' :: (a -> b) -> (b -> a -> b) -> Dual a -> b # foldlMap1 :: (a -> b) -> (b -> a -> b) -> Dual a -> b # foldrMap1' :: (a -> b) -> (a -> b -> b) -> Dual a -> b # | |||||
NFData1 Dual | Since: deepseq-1.4.3.0 | ||||
Defined in Control.DeepSeq | |||||
Applicative Dual | @since base-4.8.0.0 | ||||
Functor Dual | @since base-4.8.0.0 | ||||
Monad Dual | @since base-4.8.0.0 | ||||
Foldable Dual | @since base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Foldable Methods fold :: Monoid m => Dual m -> m # foldMap :: Monoid m => (a -> m) -> Dual a -> m # foldMap' :: Monoid m => (a -> m) -> Dual a -> m # foldr :: (a -> b -> b) -> b -> Dual a -> b # foldr' :: (a -> b -> b) -> b -> Dual a -> b # foldl :: (b -> a -> b) -> b -> Dual a -> b # foldl' :: (b -> a -> b) -> b -> Dual a -> b # foldr1 :: (a -> a -> a) -> Dual a -> a # foldl1 :: (a -> a -> a) -> Dual a -> a # elem :: Eq a => a -> Dual a -> Bool # maximum :: Ord a => Dual a -> a # | |||||
Traversable Dual | @since base-4.8.0.0 | ||||
Generic1 Dual | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
NFData a => NFData (Dual a) | Since: deepseq-1.4.0.0 | ||||
Defined in Control.DeepSeq | |||||
Monoid a => Monoid (Dual a) | @since base-2.01 | ||||
Semigroup a => Semigroup (Dual a) | @since base-4.9.0.0 | ||||
Data a => Data (Dual a) | @since base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Dual a -> c (Dual a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Dual a) # toConstr :: Dual a -> Constr # dataTypeOf :: Dual a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Dual a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Dual a)) # gmapT :: (forall b. Data b => b -> b) -> Dual a -> Dual a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Dual a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Dual a -> r # gmapQ :: (forall d. Data d => d -> u) -> Dual a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Dual a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Dual a -> m (Dual a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Dual a -> m (Dual a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Dual a -> m (Dual a) # | |||||
Bounded a => Bounded (Dual a) | @since base-2.01 | ||||
Generic (Dual a) | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
Read a => Read (Dual a) | @since base-2.01 | ||||
Show a => Show (Dual a) | @since base-2.01 | ||||
Eq a => Eq (Dual a) | @since base-2.01 | ||||
Ord a => Ord (Dual a) | @since base-2.01 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
type Rep1 Dual | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
type Rep (Dual a) | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal |
newtype Ap (f :: k -> Type) (a :: k) #
This data type witnesses the lifting of a Monoid
into an
Applicative
pointwise.
Examples
>>>
Ap (Just [1, 2, 3]) <> Ap Nothing
Ap {getAp = Nothing}
>>>
Ap [Sum 10, Sum 20] <> Ap [Sum 1, Sum 2]
Ap {getAp = [Sum {getSum = 11},Sum {getSum = 12},Sum {getSum = 21},Sum {getSum = 22}]}
@since base-4.12.0.0
Instances
Generic1 (Ap f :: k -> Type) | |||||
Defined in GHC.Internal.Data.Monoid Associated Types
| |||||
Foldable1 f => Foldable1 (Ap f) | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 Methods fold1 :: Semigroup m => Ap f m -> m # foldMap1 :: Semigroup m => (a -> m) -> Ap f a -> m # foldMap1' :: Semigroup m => (a -> m) -> Ap f a -> m # toNonEmpty :: Ap f a -> NonEmpty a # maximum :: Ord a => Ap f a -> a # minimum :: Ord a => Ap f a -> a # foldrMap1 :: (a -> b) -> (a -> b -> b) -> Ap f a -> b # foldlMap1' :: (a -> b) -> (b -> a -> b) -> Ap f a -> b # foldlMap1 :: (a -> b) -> (b -> a -> b) -> Ap f a -> b # foldrMap1' :: (a -> b) -> (a -> b -> b) -> Ap f a -> b # | |||||
Alternative f => Alternative (Ap f) | @since base-4.12.0.0 | ||||
Applicative f => Applicative (Ap f) | @since base-4.12.0.0 | ||||
Functor f => Functor (Ap f) | @since base-4.12.0.0 | ||||
Monad f => Monad (Ap f) | @since base-4.12.0.0 | ||||
MonadPlus f => MonadPlus (Ap f) | @since base-4.12.0.0 | ||||
MonadFail f => MonadFail (Ap f) | @since base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Monoid | |||||
Foldable f => Foldable (Ap f) | @since base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Foldable Methods fold :: Monoid m => Ap f m -> m # foldMap :: Monoid m => (a -> m) -> Ap f a -> m # foldMap' :: Monoid m => (a -> m) -> Ap f a -> m # foldr :: (a -> b -> b) -> b -> Ap f a -> b # foldr' :: (a -> b -> b) -> b -> Ap f a -> b # foldl :: (b -> a -> b) -> b -> Ap f a -> b # foldl' :: (b -> a -> b) -> b -> Ap f a -> b # foldr1 :: (a -> a -> a) -> Ap f a -> a # foldl1 :: (a -> a -> a) -> Ap f a -> a # elem :: Eq a => a -> Ap f a -> Bool # maximum :: Ord a => Ap f a -> a # | |||||
Traversable f => Traversable (Ap f) | @since base-4.12.0.0 | ||||
(Applicative f, Monoid a) => Monoid (Ap f a) | @since base-4.12.0.0 | ||||
(Applicative f, Semigroup a) => Semigroup (Ap f a) | @since base-4.12.0.0 | ||||
(Data (f a), Data a, Typeable f) => Data (Ap f a) | @since base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ap f a -> c (Ap f a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Ap f a) # toConstr :: Ap f a -> Constr # dataTypeOf :: Ap f a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Ap f a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Ap f a)) # gmapT :: (forall b. Data b => b -> b) -> Ap f a -> Ap f a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ap f a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ap f a -> r # gmapQ :: (forall d. Data d => d -> u) -> Ap f a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Ap f a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ap f a -> m (Ap f a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ap f a -> m (Ap f a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ap f a -> m (Ap f a) # | |||||
(Applicative f, Bounded a) => Bounded (Ap f a) | @since base-4.12.0.0 | ||||
Enum (f a) => Enum (Ap f a) | @since base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Monoid | |||||
Generic (Ap f a) | |||||
Defined in GHC.Internal.Data.Monoid Associated Types
| |||||
(Applicative f, Num a) => Num (Ap f a) | Note that even if the underlying Commutativity:
Additive inverse:
Distributivity:
@since base-4.12.0.0 | ||||
Read (f a) => Read (Ap f a) | @since base-4.12.0.0 | ||||
Show (f a) => Show (Ap f a) | @since base-4.12.0.0 | ||||
Eq (f a) => Eq (Ap f a) | @since base-4.12.0.0 | ||||
Ord (f a) => Ord (Ap f a) | @since base-4.12.0.0 | ||||
type Rep1 (Ap f :: k -> Type) | @since base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Monoid | |||||
type Rep (Ap f a) | @since base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Monoid |
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 #
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!
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 #
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 \(\mathcal{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 | Since: base-4.17.0.0 |
Semigroup Builder | |
Semigroup ByteString | |
Defined in Data.ByteString.Internal.Type Methods (<>) :: ByteString -> ByteString -> ByteString # sconcat :: NonEmpty ByteString -> ByteString # stimes :: Integral b => b -> ByteString -> ByteString # | |
Semigroup ByteString | |
Defined in Data.ByteString.Lazy.Internal Methods (<>) :: ByteString -> ByteString -> ByteString # sconcat :: NonEmpty ByteString -> ByteString # stimes :: Integral b => b -> ByteString -> ByteString # | |
Semigroup ShortByteString | |
Defined in Data.ByteString.Short.Internal Methods (<>) :: ShortByteString -> ShortByteString -> ShortByteString # sconcat :: NonEmpty ShortByteString -> ShortByteString # stimes :: Integral b => b -> ShortByteString -> ShortByteString # | |
Semigroup IntSet | Since: containers-0.5.7 |
Semigroup Void | @since base-4.9.0.0 |
Semigroup All | @since base-4.9.0.0 |
Semigroup Any | @since base-4.9.0.0 |
Semigroup Ordering | @since base-4.9.0.0 |
Semigroup OsString | |
Semigroup PosixString | |
Defined in System.OsString.Internal.Types Methods (<>) :: PosixString -> PosixString -> PosixString # sconcat :: NonEmpty PosixString -> PosixString # stimes :: Integral b => b -> PosixString -> PosixString # | |
Semigroup WindowsString | |
Defined in System.OsString.Internal.Types Methods (<>) :: WindowsString -> WindowsString -> WindowsString # sconcat :: NonEmpty WindowsString -> WindowsString # stimes :: Integral b => b -> WindowsString -> WindowsString # | |
Semigroup Doc | |
Semigroup Builder | |
Semigroup StrictBuilder | Concatenation of |
Defined in Data.Text.Internal.StrictBuilder Methods (<>) :: StrictBuilder -> StrictBuilder -> StrictBuilder # sconcat :: NonEmpty StrictBuilder -> StrictBuilder # stimes :: Integral b => b -> StrictBuilder -> StrictBuilder # | |
Semigroup () | @since base-4.9.0.0 |
Semigroup (FromMaybe b) | |
Semigroup a => Semigroup (JoinWith a) | |
Semigroup (NonEmptyDList a) | |
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 Methods (<>) :: Comparison a -> Comparison a -> Comparison a # sconcat :: NonEmpty (Comparison a) -> Comparison a # stimes :: Integral b => b -> Comparison a -> Comparison a # | |
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 Methods (<>) :: Equivalence a -> Equivalence a -> Equivalence a # sconcat :: NonEmpty (Equivalence a) -> Equivalence a # stimes :: Integral b => b -> Equivalence a -> Equivalence a # | |
Semigroup (Predicate a) |
(<>) :: Predicate a -> Predicate a -> Predicate a Predicate pred <> Predicate pred' = Predicate a -> pred a && pred' a |
Semigroup (First a) | Since: base-4.9.0.0 |
Semigroup (Last 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 |
Monoid m => Semigroup (WrappedMonoid m) | Since: base-4.9.0.0 |
Defined in Data.Semigroup Methods (<>) :: WrappedMonoid m -> WrappedMonoid m -> WrappedMonoid m # sconcat :: NonEmpty (WrappedMonoid m) -> WrappedMonoid m # stimes :: Integral b => b -> WrappedMonoid m -> WrappedMonoid m # | |
Semigroup (IntMap a) | Since: containers-0.5.7 |
Semigroup (Seq a) | Since: containers-0.5.7 |
Ord a => Semigroup (Intersection a) | |
Defined in Data.Set.Internal Methods (<>) :: Intersection a -> Intersection a -> Intersection a # sconcat :: NonEmpty (Intersection a) -> Intersection a # stimes :: Integral b => b -> Intersection a -> Intersection a # | |
Semigroup (MergeSet a) | |
Ord a => Semigroup (Set a) | Since: containers-0.5.7 |
Semigroup (NonEmpty a) | @since base-4.9.0.0 |
Semigroup a => Semigroup (STM a) | @since base-4.17.0.0 |
Semigroup a => Semigroup (Identity a) | @since base-4.9.0.0 |
Semigroup (First a) | @since base-4.9.0.0 |
Semigroup (Last a) | @since base-4.9.0.0 |
Semigroup a => Semigroup (Down a) | @since base-4.11.0.0 |
Semigroup a => Semigroup (Dual a) | @since base-4.9.0.0 |
Semigroup (Endo a) | @since base-4.9.0.0 |
Num a => Semigroup (Product a) | @since base-4.9.0.0 |
Num a => Semigroup (Sum a) | @since base-4.9.0.0 |
(Generic a, Semigroup (Rep a ())) => Semigroup (Generically a) | @since base-4.17.0.0 |
Defined in GHC.Internal.Generics Methods (<>) :: Generically a -> Generically a -> Generically a # sconcat :: NonEmpty (Generically a) -> Generically a # stimes :: Integral b => b -> Generically a -> Generically a # | |
Semigroup p => Semigroup (Par1 p) | @since base-4.12.0.0 |
Semigroup a => Semigroup (IO a) | @since base-4.10.0.0 |
Semigroup (Validity k) | |
(Hashable a, Eq a) => Semigroup (HashSet a) | \(O(n+m)\) To obtain good performance, the smaller set must be presented as the first argument. Examples
|
Semigroup (Doc a) | |
Semigroup a => Semigroup (Q a) | Since: template-haskell-2.17.0.0 |
Semigroup a => Semigroup (Maybe a) | @since base-4.9.0.0 |
Semigroup a => Semigroup (Solo a) | @since base-4.15 |
Semigroup [a] | @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 |
Ord k => Semigroup (Map k v) | |
Semigroup (Either a b) | @since base-4.9.0.0 |
Semigroup (Proxy s) | @since base-4.9.0.0 |
Semigroup (U1 p) | @since base-4.12.0.0 |
Semigroup (V1 p) | @since base-4.12.0.0 |
(Eq k, Hashable k) => Semigroup (HashMap k v) | If a key occurs in both maps, the mapping from the first will be the mapping in the result. Examples
|
(Semigroup a, Semigroup b) => Semigroup (a, b) | @since base-4.9.0.0 |
Semigroup b => Semigroup (a -> b) | @since base-4.9.0.0 |
Semigroup a => Semigroup (Const a b) | @since base-4.9.0.0 |
(Applicative f, Semigroup a) => Semigroup (Ap f a) | @since base-4.12.0.0 |
Alternative f => Semigroup (Alt f a) | @since base-4.9.0.0 |
Semigroup (f p) => Semigroup (Rec1 f p) | @since base-4.12.0.0 |
Semigroup a => Semigroup (Constant a b) | |
(Semigroup a, Semigroup b, Semigroup c) => Semigroup (a, b, c) | @since base-4.9.0.0 |
(Semigroup (f a), Semigroup (g a)) => Semigroup (Product f g a) | Since: base-4.16.0.0 |
(Semigroup (f p), Semigroup (g p)) => Semigroup ((f :*: g) p) | @since base-4.12.0.0 |
Semigroup c => Semigroup (K1 i c 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 (g a)) => Semigroup (Compose f g a) | Since: base-4.16.0.0 |
Semigroup (f (g p)) => Semigroup ((f :.: g) p) | @since base-4.12.0.0 |
Semigroup (f p) => Semigroup (M1 i c f 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 |
stimesIdempotent :: Integral b => b -> a -> a #
stimesIdempotentMonoid :: (Integral b, Monoid a) => b -> a -> a #
stimesMonoid :: (Integral b, Monoid a) => b -> a -> a #
data WrappedMonoid m #
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.
Instances
mtimesDefault :: (Integral b, Monoid a) => b -> a -> a #
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"
newtype Ap (f :: k -> Type) (a :: k) #
This data type witnesses the lifting of a Monoid
into an
Applicative
pointwise.
Examples
>>>
Ap (Just [1, 2, 3]) <> Ap Nothing
Ap {getAp = Nothing}
>>>
Ap [Sum 10, Sum 20] <> Ap [Sum 1, Sum 2]
Ap {getAp = [Sum {getSum = 11},Sum {getSum = 12},Sum {getSum = 21},Sum {getSum = 22}]}
@since base-4.12.0.0
Instances
Generic1 (Ap f :: k -> Type) | |||||
Defined in GHC.Internal.Data.Monoid Associated Types
| |||||
Foldable1 f => Foldable1 (Ap f) | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 Methods fold1 :: Semigroup m => Ap f m -> m # foldMap1 :: Semigroup m => (a -> m) -> Ap f a -> m # foldMap1' :: Semigroup m => (a -> m) -> Ap f a -> m # toNonEmpty :: Ap f a -> NonEmpty a # maximum :: Ord a => Ap f a -> a # minimum :: Ord a => Ap f a -> a # foldrMap1 :: (a -> b) -> (a -> b -> b) -> Ap f a -> b # foldlMap1' :: (a -> b) -> (b -> a -> b) -> Ap f a -> b # foldlMap1 :: (a -> b) -> (b -> a -> b) -> Ap f a -> b # foldrMap1' :: (a -> b) -> (a -> b -> b) -> Ap f a -> b # | |||||
Alternative f => Alternative (Ap f) | @since base-4.12.0.0 | ||||
Applicative f => Applicative (Ap f) | @since base-4.12.0.0 | ||||
Functor f => Functor (Ap f) | @since base-4.12.0.0 | ||||
Monad f => Monad (Ap f) | @since base-4.12.0.0 | ||||
MonadPlus f => MonadPlus (Ap f) | @since base-4.12.0.0 | ||||
MonadFail f => MonadFail (Ap f) | @since base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Monoid | |||||
Foldable f => Foldable (Ap f) | @since base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Foldable Methods fold :: Monoid m => Ap f m -> m # foldMap :: Monoid m => (a -> m) -> Ap f a -> m # foldMap' :: Monoid m => (a -> m) -> Ap f a -> m # foldr :: (a -> b -> b) -> b -> Ap f a -> b # foldr' :: (a -> b -> b) -> b -> Ap f a -> b # foldl :: (b -> a -> b) -> b -> Ap f a -> b # foldl' :: (b -> a -> b) -> b -> Ap f a -> b # foldr1 :: (a -> a -> a) -> Ap f a -> a # foldl1 :: (a -> a -> a) -> Ap f a -> a # elem :: Eq a => a -> Ap f a -> Bool # maximum :: Ord a => Ap f a -> a # | |||||
Traversable f => Traversable (Ap f) | @since base-4.12.0.0 | ||||
(Applicative f, Monoid a) => Monoid (Ap f a) | @since base-4.12.0.0 | ||||
(Applicative f, Semigroup a) => Semigroup (Ap f a) | @since base-4.12.0.0 | ||||
(Data (f a), Data a, Typeable f) => Data (Ap f a) | @since base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ap f a -> c (Ap f a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Ap f a) # toConstr :: Ap f a -> Constr # dataTypeOf :: Ap f a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Ap f a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Ap f a)) # gmapT :: (forall b. Data b => b -> b) -> Ap f a -> Ap f a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ap f a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ap f a -> r # gmapQ :: (forall d. Data d => d -> u) -> Ap f a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Ap f a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ap f a -> m (Ap f a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ap f a -> m (Ap f a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ap f a -> m (Ap f a) # | |||||
(Applicative f, Bounded a) => Bounded (Ap f a) | @since base-4.12.0.0 | ||||
Enum (f a) => Enum (Ap f a) | @since base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Monoid | |||||
Generic (Ap f a) | |||||
Defined in GHC.Internal.Data.Monoid Associated Types
| |||||
(Applicative f, Num a) => Num (Ap f a) | Note that even if the underlying Commutativity:
Additive inverse:
Distributivity:
@since base-4.12.0.0 | ||||
Read (f a) => Read (Ap f a) | @since base-4.12.0.0 | ||||
Show (f a) => Show (Ap f a) | @since base-4.12.0.0 | ||||
Eq (f a) => Eq (Ap f a) | @since base-4.12.0.0 | ||||
Ord (f a) => Ord (Ap f a) | @since base-4.12.0.0 | ||||
type Rep1 (Ap f :: k -> Type) | @since base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Monoid | |||||
type Rep (Ap f a) | @since base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Monoid |
Combinators
maybeToMonoid :: Monoid m => Maybe m -> m Source #
memptyIfFalse :: Monoid m => Bool -> m -> m Source #