| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Universum.Monoid
Description
This module reexports functions to work with monoids plus adds extra useful functions.
Synopsis
- newtype Any = Any {}
- newtype Sum a = Sum {
- getSum :: a
- newtype Product a = Product {
- getProduct :: a
- 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 All = All {}
- newtype Endo a = Endo {
- appEndo :: a -> a
- newtype Dual a = Dual {
- getDual :: a
- class Semigroup a where
- data WrappedMonoid m
- stimesIdempotent :: Integral b => b -> a -> a
- stimesIdempotentMonoid :: (Integral b, Monoid a) => b -> a -> a
- stimesMonoid :: (Integral b, Monoid a) => b -> a -> a
- cycle1 :: Semigroup m => m -> m
- mtimesDefault :: (Integral b, Monoid a) => b -> a -> a
- maybeToMonoid :: Monoid m => Maybe m -> m
Documentation
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
| Data Any | Since: base-4.8.0.0 |
Defined in 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 # | |
| Monoid Any | Since: base-2.1 |
| Semigroup Any | Since: base-4.9.0.0 |
| Bounded Any | Since: base-2.1 |
| Generic Any | |
| Read Any | Since: base-2.1 |
| Show Any | Since: base-2.1 |
| NFData Any | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
| Eq Any | Since: base-2.1 |
| Ord Any | Since: base-2.1 |
| Unbox Any | |
Defined in Data.Vector.Unboxed.Base | |
| Vector Vector Any | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s Any -> ST s (Vector Any) # basicUnsafeThaw :: Vector Any -> ST s (Mutable Vector s Any) # basicLength :: Vector Any -> Int # basicUnsafeSlice :: Int -> Int -> Vector Any -> Vector Any # basicUnsafeIndexM :: Vector Any -> Int -> Box Any # basicUnsafeCopy :: Mutable Vector s Any -> Vector Any -> ST s () # | |
| MVector MVector Any | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s Any -> Int # basicUnsafeSlice :: Int -> Int -> MVector s Any -> MVector s Any # basicOverlaps :: MVector s Any -> MVector s Any -> Bool # basicUnsafeNew :: Int -> ST s (MVector s Any) # basicInitialize :: MVector s Any -> ST s () # basicUnsafeReplicate :: Int -> Any -> ST s (MVector s Any) # basicUnsafeRead :: MVector s Any -> Int -> ST s Any # basicUnsafeWrite :: MVector s Any -> Int -> Any -> ST s () # basicClear :: MVector s Any -> ST s () # basicSet :: MVector s Any -> Any -> ST s () # basicUnsafeCopy :: MVector s Any -> MVector s Any -> ST s () # basicUnsafeMove :: MVector s Any -> MVector s Any -> ST s () # basicUnsafeGrow :: MVector s Any -> Int -> ST s (MVector s Any) # | |
| type Rep Any | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal | |
| newtype Vector Any | |
| newtype MVector s Any | |
Monoid under addition.
>>>getSum (Sum 1 <> Sum 2 <> mempty)3
Instances
| Foldable Sum | Since: base-4.8.0.0 |
Defined in 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 |
| Applicative Sum | Since: base-4.8.0.0 |
| Functor Sum | Since: base-4.8.0.0 |
| Monad Sum | Since: base-4.8.0.0 |
| NFData1 Sum | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
| Generic1 Sum | |
| Unbox a => Vector Vector (Sum a) | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s (Sum a) -> ST s (Vector (Sum a)) # basicUnsafeThaw :: Vector (Sum a) -> ST s (Mutable Vector s (Sum a)) # basicLength :: Vector (Sum a) -> Int # basicUnsafeSlice :: Int -> Int -> Vector (Sum a) -> Vector (Sum a) # basicUnsafeIndexM :: Vector (Sum a) -> Int -> Box (Sum a) # basicUnsafeCopy :: Mutable Vector s (Sum a) -> Vector (Sum a) -> ST s () # | |
| Unbox a => MVector MVector (Sum a) | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s (Sum a) -> Int # basicUnsafeSlice :: Int -> Int -> MVector s (Sum a) -> MVector s (Sum a) # basicOverlaps :: MVector s (Sum a) -> MVector s (Sum a) -> Bool # basicUnsafeNew :: Int -> ST s (MVector s (Sum a)) # basicInitialize :: MVector s (Sum a) -> ST s () # basicUnsafeReplicate :: Int -> Sum a -> ST s (MVector s (Sum a)) # basicUnsafeRead :: MVector s (Sum a) -> Int -> ST s (Sum a) # basicUnsafeWrite :: MVector s (Sum a) -> Int -> Sum a -> ST s () # basicClear :: MVector s (Sum a) -> ST s () # basicSet :: MVector s (Sum a) -> Sum a -> ST s () # basicUnsafeCopy :: MVector s (Sum a) -> MVector s (Sum a) -> ST s () # basicUnsafeMove :: MVector s (Sum a) -> MVector s (Sum a) -> ST s () # basicUnsafeGrow :: MVector s (Sum a) -> Int -> ST s (MVector s (Sum a)) # | |
| Data a => Data (Sum a) | Since: base-4.8.0.0 |
Defined in 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) # | |
| Num a => Monoid (Sum a) | Since: base-2.1 |
| Num a => Semigroup (Sum a) | Since: base-4.9.0.0 |
| Bounded a => Bounded (Sum a) | Since: base-2.1 |
| Generic (Sum a) | |
| Num a => Num (Sum a) | Since: base-4.7.0.0 |
| Read a => Read (Sum a) | Since: base-2.1 |
| Show a => Show (Sum a) | Since: base-2.1 |
| NFData a => NFData (Sum a) | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
| Eq a => Eq (Sum a) | Since: base-2.1 |
| Ord a => Ord (Sum a) | Since: base-2.1 |
| Prim a => Prim (Sum a) | Since: primitive-0.6.5.0 |
Defined in Data.Primitive.Types Methods sizeOfType# :: Proxy (Sum a) -> Int# # alignmentOfType# :: Proxy (Sum a) -> Int# # alignment# :: Sum a -> Int# # indexByteArray# :: ByteArray# -> Int# -> Sum a # readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Sum a #) # writeByteArray# :: MutableByteArray# s -> Int# -> Sum a -> State# s -> State# s # setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Sum a -> State# s -> State# s # indexOffAddr# :: Addr# -> Int# -> Sum a # readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Sum a #) # writeOffAddr# :: Addr# -> Int# -> Sum a -> State# s -> State# s # setOffAddr# :: Addr# -> Int# -> Int# -> Sum a -> State# s -> State# s # | |
| Container (Sum a) Source # | |
Defined in Universum.Container.Class Methods toList :: Sum a -> [Element (Sum a)] Source # null :: Sum a -> Bool Source # foldr :: (Element (Sum a) -> b -> b) -> b -> Sum a -> b Source # foldl :: (b -> Element (Sum a) -> b) -> b -> Sum a -> b Source # foldl' :: (b -> Element (Sum a) -> b) -> b -> Sum a -> b Source # length :: Sum a -> Int Source # elem :: Element (Sum a) -> Sum a -> Bool Source # foldMap :: Monoid m => (Element (Sum a) -> m) -> Sum a -> m Source # fold :: Sum a -> Element (Sum a) Source # foldr' :: (Element (Sum a) -> b -> b) -> b -> Sum a -> b Source # notElem :: Element (Sum a) -> Sum a -> Bool Source # all :: (Element (Sum a) -> Bool) -> Sum a -> Bool Source # any :: (Element (Sum a) -> Bool) -> Sum a -> Bool Source # find :: (Element (Sum a) -> Bool) -> Sum a -> Maybe (Element (Sum a)) Source # safeHead :: Sum a -> Maybe (Element (Sum a)) Source # safeMaximum :: Sum a -> Maybe (Element (Sum a)) Source # safeMinimum :: Sum a -> Maybe (Element (Sum a)) Source # safeFoldr1 :: (Element (Sum a) -> Element (Sum a) -> Element (Sum a)) -> Sum a -> Maybe (Element (Sum a)) Source # safeFoldl1 :: (Element (Sum a) -> Element (Sum a) -> Element (Sum a)) -> Sum a -> Maybe (Element (Sum a)) Source # | |
| Unbox a => Unbox (Sum a) | |
Defined in Data.Vector.Unboxed.Base | |
| type Rep1 Sum | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal | |
| newtype MVector s (Sum a) | |
Defined in Data.Vector.Unboxed.Base | |
| type Rep (Sum a) | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal | |
| type Element (Sum a) Source # | |
Defined in Universum.Container.Class | |
| newtype Vector (Sum a) | |
Defined in Data.Vector.Unboxed.Base | |
Monoid under multiplication.
>>>getProduct (Product 3 <> Product 4 <> mempty)12
Constructors
| Product | |
Fields
| |
Instances
Maybe monoid returning the rightmost non-Nothing value.
is isomorphic to Last a, and thus to
Dual (First a)Dual (Alt Maybe a)
>>>getLast (Last (Just "hello") <> Last Nothing <> Last (Just "world"))Just "world"
Beware that Data.Monoid.Last is different from
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.
Instances
| Foldable Last | Since: base-4.8.0.0 |
Defined in 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 |
| Applicative Last | Since: base-4.8.0.0 |
| Functor Last | Since: base-4.8.0.0 |
| Monad Last | Since: base-4.8.0.0 |
| NFData1 Last | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
| Generic1 Last | |
| Data a => Data (Last a) | Since: base-4.8.0.0 |
Defined in 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) # | |
| Monoid (Last a) | Since: base-2.1 |
| Semigroup (Last a) | Since: base-4.9.0.0 |
| Generic (Last a) | |
| Read a => Read (Last a) | Since: base-2.1 |
| Show a => Show (Last a) | Since: base-2.1 |
| NFData a => NFData (Last a) | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
| Eq a => Eq (Last a) | Since: base-2.1 |
| Ord a => Ord (Last a) | Since: base-2.1 |
| Container (Last a) Source # | |
Defined in Universum.Container.Class Methods toList :: Last a -> [Element (Last a)] Source # null :: Last a -> Bool Source # foldr :: (Element (Last a) -> b -> b) -> b -> Last a -> b Source # foldl :: (b -> Element (Last a) -> b) -> b -> Last a -> b Source # foldl' :: (b -> Element (Last a) -> b) -> b -> Last a -> b Source # length :: Last a -> Int Source # elem :: Element (Last a) -> Last a -> Bool Source # foldMap :: Monoid m => (Element (Last a) -> m) -> Last a -> m Source # fold :: Last a -> Element (Last a) Source # foldr' :: (Element (Last a) -> b -> b) -> b -> Last a -> b Source # notElem :: Element (Last a) -> Last a -> Bool Source # all :: (Element (Last a) -> Bool) -> Last a -> Bool Source # any :: (Element (Last a) -> Bool) -> Last a -> Bool Source # and :: Last a -> Bool Source # find :: (Element (Last a) -> Bool) -> Last a -> Maybe (Element (Last a)) Source # safeHead :: Last a -> Maybe (Element (Last a)) Source # safeMaximum :: Last a -> Maybe (Element (Last a)) Source # safeMinimum :: Last a -> Maybe (Element (Last a)) Source # safeFoldr1 :: (Element (Last a) -> Element (Last a) -> Element (Last a)) -> Last a -> Maybe (Element (Last a)) Source # safeFoldl1 :: (Element (Last a) -> Element (Last a) -> Element (Last a)) -> Last a -> Maybe (Element (Last a)) Source # | |
| type Rep1 Last | Since: base-4.7.0.0 |
Defined in Data.Monoid | |
| type Rep (Last a) | Since: base-4.7.0.0 |
Defined in Data.Monoid | |
| type Element (Last a) Source # | |
Defined in Universum.Container.Class | |
Maybe monoid returning the leftmost non-Nothing value.
is isomorphic to First a, but precedes it
historically.Alt Maybe a
>>>getFirst (First (Just "hello") <> First Nothing <> First (Just "world"))Just "hello"
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.
Instances
| Foldable First | Since: base-4.8.0.0 |
Defined in 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 |
| Applicative First | Since: base-4.8.0.0 |
| Functor First | Since: base-4.8.0.0 |
| Monad First | Since: base-4.8.0.0 |
| NFData1 First | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
| Generic1 First | |
| Data a => Data (First a) | Since: base-4.8.0.0 |
Defined in 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) # | |
| Monoid (First a) | Since: base-2.1 |
| Semigroup (First a) | Since: base-4.9.0.0 |
| Generic (First a) | |
| Read a => Read (First a) | Since: base-2.1 |
| Show a => Show (First a) | Since: base-2.1 |
| NFData a => NFData (First a) | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
| Eq a => Eq (First a) | Since: base-2.1 |
| Ord a => Ord (First a) | Since: base-2.1 |
| Container (First a) Source # | |
Defined in Universum.Container.Class Methods toList :: First a -> [Element (First a)] Source # null :: First a -> Bool Source # foldr :: (Element (First a) -> b -> b) -> b -> First a -> b Source # foldl :: (b -> Element (First a) -> b) -> b -> First a -> b Source # foldl' :: (b -> Element (First a) -> b) -> b -> First a -> b Source # length :: First a -> Int Source # elem :: Element (First a) -> First a -> Bool Source # foldMap :: Monoid m => (Element (First a) -> m) -> First a -> m Source # fold :: First a -> Element (First a) Source # foldr' :: (Element (First a) -> b -> b) -> b -> First a -> b Source # notElem :: Element (First a) -> First a -> Bool Source # all :: (Element (First a) -> Bool) -> First a -> Bool Source # any :: (Element (First a) -> Bool) -> First a -> Bool Source # and :: First a -> Bool Source # or :: First a -> Bool Source # find :: (Element (First a) -> Bool) -> First a -> Maybe (Element (First a)) Source # safeHead :: First a -> Maybe (Element (First a)) Source # safeMaximum :: First a -> Maybe (Element (First a)) Source # safeMinimum :: First a -> Maybe (Element (First a)) Source # safeFoldr1 :: (Element (First a) -> Element (First a) -> Element (First a)) -> First a -> Maybe (Element (First a)) Source # safeFoldl1 :: (Element (First a) -> Element (First a) -> Element (First a)) -> First a -> Maybe (Element (First a)) Source # | |
| type Rep1 First | Since: base-4.7.0.0 |
Defined in Data.Monoid | |
| type Rep (First a) | Since: base-4.7.0.0 |
Defined in Data.Monoid | |
| type Element (First a) Source # | |
Defined in Universum.Container.Class | |
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)<>zSemigrouplaw)- Concatenation
mconcat=foldr(<>)mempty
You can alternatively define mconcat instead of mempty, in which case the
laws are:
- Unit
mconcat(purex) = x- Multiplication
mconcat(joinxss) =mconcat(fmapmconcatxss)- Subclass
mconcat(toListxs) =sconcatxs
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 newtypes 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
>>>"Hello world" <> mempty"Hello world"
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 All | Since: base-2.1 |
| Monoid Any | Since: base-2.1 |
| 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 Ordering | Since: base-2.1 |
| 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 () | Since: base-2.1 |
| FiniteBits a => Monoid (And a) | This constraint is arguably too strong. However,
as some types (such as Since: base-4.16 |
| FiniteBits a => Monoid (Iff a) | This constraint is arguably
too strong. However, as some types (such as Since: base-4.16 |
| Bits a => Monoid (Ior a) | Since: base-4.16 |
| Bits a => Monoid (Xor a) | Since: base-4.16 |
| Monoid a => Monoid (Identity a) | Since: base-4.9.0.0 |
| Monoid (First a) | Since: base-2.1 |
| Monoid (Last a) | Since: base-2.1 |
| Monoid a => Monoid (Down a) | Since: base-4.11.0.0 |
| (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 a => Monoid (Dual a) | Since: base-2.1 |
| Monoid (Endo a) | Since: base-2.1 |
| Num a => Monoid (Product a) | Since: base-2.1 |
| Num a => Monoid (Sum a) | Since: base-2.1 |
| Monoid a => Monoid (STM a) | Since: base-4.17.0.0 |
| (Generic a, Monoid (Rep a ())) => Monoid (Generically a) | Since: base-4.17.0.0 |
Defined in GHC.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 (IntMap a) | |
| Monoid (Seq a) | |
| Monoid (MergeSet a) | |
| Ord a => Monoid (Set a) | |
| Monoid a => Monoid (IO a) | Since: base-4.9.0.0 |
| Monoid a => Monoid (May a) | |
| Monoid (Doc a) | |
| Monoid (Array a) | |
| Monoid (PrimArray a) | Since: primitive-0.6.4.0 |
| Monoid (SmallArray a) | |
Defined in Data.Primitive.SmallArray Methods mempty :: SmallArray a # mappend :: SmallArray a -> SmallArray a -> SmallArray a # mconcat :: [SmallArray a] -> SmallArray a # | |
| Monoid a => Monoid (Q a) | Since: template-haskell-2.17.0.0 |
| (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 (Vector a) | |
| Prim a => Monoid (Vector a) | |
| Storable a => Monoid (Vector a) | |
| Semigroup a => Monoid (Maybe a) | Lift a semigroup into Since 4.11.0: constraint on inner Since: base-2.1 |
| Monoid a => Monoid (a) | Since: base-4.15 |
| Monoid [a] | Since: base-2.1 |
| Monoid (Proxy s) | Since: base-4.7.0.0 |
| Monoid (U1 p) | Since: base-4.12.0.0 |
| Ord k => Monoid (Map k v) | |
| Applicative f => Monoid (Traversed a f) | |
| Monoid a => Monoid (Err e a) | |
| (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.1 |
| Monoid b => Monoid (a -> b) | Since: base-2.1 |
| 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 |
| (Monad m, Monoid r) => Monoid (Effect m r a) | |
| (Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) | Since: base-2.1 |
| (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.1 |
| 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.1 |
newtype Alt (f :: k -> Type) (a :: k) #
Monoid under <|>.
>>>getAlt (Alt (Just 12) <> Alt (Just 24))Just 12
>>>getAlt $ Alt Nothing <> Alt (Just 24)Just 24
Since: base-4.8.0.0
Instances
| Generic1 (Alt f :: k -> Type) | |
| Unbox (f a) => Vector Vector (Alt f a) | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s (Alt f a) -> ST s (Vector (Alt f a)) # basicUnsafeThaw :: Vector (Alt f a) -> ST s (Mutable Vector s (Alt f a)) # basicLength :: Vector (Alt f a) -> Int # basicUnsafeSlice :: Int -> Int -> Vector (Alt f a) -> Vector (Alt f a) # basicUnsafeIndexM :: Vector (Alt f a) -> Int -> Box (Alt f a) # basicUnsafeCopy :: Mutable Vector s (Alt f a) -> Vector (Alt f a) -> ST s () # | |
| Unbox (f a) => MVector MVector (Alt f a) | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s (Alt f a) -> Int # basicUnsafeSlice :: Int -> Int -> MVector s (Alt f a) -> MVector s (Alt f a) # basicOverlaps :: MVector s (Alt f a) -> MVector s (Alt f a) -> Bool # basicUnsafeNew :: Int -> ST s (MVector s (Alt f a)) # basicInitialize :: MVector s (Alt f a) -> ST s () # basicUnsafeReplicate :: Int -> Alt f a -> ST s (MVector s (Alt f a)) # basicUnsafeRead :: MVector s (Alt f a) -> Int -> ST s (Alt f a) # basicUnsafeWrite :: MVector s (Alt f a) -> Int -> Alt f a -> ST s () # basicClear :: MVector s (Alt f a) -> ST s () # basicSet :: MVector s (Alt f a) -> Alt f a -> ST s () # basicUnsafeCopy :: MVector s (Alt f a) -> MVector s (Alt f a) -> ST s () # basicUnsafeMove :: MVector s (Alt f a) -> MVector s (Alt f a) -> ST s () # basicUnsafeGrow :: MVector s (Alt f a) -> Int -> ST s (MVector s (Alt f a)) # | |
| Foldable f => Foldable (Alt f) | Since: base-4.12.0.0 |
Defined in 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 => 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 |
| (Data (f a), Data a, Typeable f) => Data (Alt f a) | Since: base-4.8.0.0 |
Defined in 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) # | |
| Alternative f => Monoid (Alt f a) | Since: base-4.8.0.0 |
| Alternative f => Semigroup (Alt f a) | Since: base-4.9.0.0 |
| Enum (f a) => Enum (Alt f a) | Since: base-4.8.0.0 |
| Generic (Alt f a) | |
| 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 Data.Semigroup.Internal | |
| Unbox (f a) => Unbox (Alt f a) | |
Defined in Data.Vector.Unboxed.Base | |
| type Rep1 (Alt f :: k -> Type) | Since: base-4.8.0.0 |
Defined in Data.Semigroup.Internal | |
| newtype MVector s (Alt f a) | |
Defined in Data.Vector.Unboxed.Base | |
| type Rep (Alt f a) | Since: base-4.8.0.0 |
Defined in Data.Semigroup.Internal | |
| newtype Vector (Alt f a) | |
Defined in Data.Vector.Unboxed.Base | |
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
| Data All | Since: base-4.8.0.0 |
Defined in 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 # | |
| Monoid All | Since: base-2.1 |
| Semigroup All | Since: base-4.9.0.0 |
| Bounded All | Since: base-2.1 |
| Generic All | |
| Read All | Since: base-2.1 |
| Show All | Since: base-2.1 |
| NFData All | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
| Eq All | Since: base-2.1 |
| Ord All | Since: base-2.1 |
| Unbox All | |
Defined in Data.Vector.Unboxed.Base | |
| Vector Vector All | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s All -> ST s (Vector All) # basicUnsafeThaw :: Vector All -> ST s (Mutable Vector s All) # basicLength :: Vector All -> Int # basicUnsafeSlice :: Int -> Int -> Vector All -> Vector All # basicUnsafeIndexM :: Vector All -> Int -> Box All # basicUnsafeCopy :: Mutable Vector s All -> Vector All -> ST s () # | |
| MVector MVector All | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s All -> Int # basicUnsafeSlice :: Int -> Int -> MVector s All -> MVector s All # basicOverlaps :: MVector s All -> MVector s All -> Bool # basicUnsafeNew :: Int -> ST s (MVector s All) # basicInitialize :: MVector s All -> ST s () # basicUnsafeReplicate :: Int -> All -> ST s (MVector s All) # basicUnsafeRead :: MVector s All -> Int -> ST s All # basicUnsafeWrite :: MVector s All -> Int -> All -> ST s () # basicClear :: MVector s All -> ST s () # basicSet :: MVector s All -> All -> ST s () # basicUnsafeCopy :: MVector s All -> MVector s All -> ST s () # basicUnsafeMove :: MVector s All -> MVector s All -> ST s () # basicUnsafeGrow :: MVector s All -> Int -> ST s (MVector s All) # | |
| type Rep All | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal | |
| newtype Vector All | |
| newtype MVector s All | |
The monoid of endomorphisms under composition.
>>>let computation = Endo ("Hello, " ++) <> Endo (++ "!")>>>appEndo computation "Haskell""Hello, Haskell!"
The dual of a Monoid, obtained by swapping the arguments of mappend.
>>>getDual (mappend (Dual "Hello") (Dual "World"))"WorldHello"
Instances
| Foldable Dual | Since: base-4.8.0.0 |
Defined in 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 |
| Applicative Dual | Since: base-4.8.0.0 |
| Functor Dual | Since: base-4.8.0.0 |
| Monad Dual | Since: base-4.8.0.0 |
| NFData1 Dual | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
| Generic1 Dual | |
| Unbox a => Vector Vector (Dual a) | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: Mutable Vector s (Dual a) -> ST s (Vector (Dual a)) # basicUnsafeThaw :: Vector (Dual a) -> ST s (Mutable Vector s (Dual a)) # basicLength :: Vector (Dual a) -> Int # basicUnsafeSlice :: Int -> Int -> Vector (Dual a) -> Vector (Dual a) # basicUnsafeIndexM :: Vector (Dual a) -> Int -> Box (Dual a) # basicUnsafeCopy :: Mutable Vector s (Dual a) -> Vector (Dual a) -> ST s () # | |
| Unbox a => MVector MVector (Dual a) | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s (Dual a) -> Int # basicUnsafeSlice :: Int -> Int -> MVector s (Dual a) -> MVector s (Dual a) # basicOverlaps :: MVector s (Dual a) -> MVector s (Dual a) -> Bool # basicUnsafeNew :: Int -> ST s (MVector s (Dual a)) # basicInitialize :: MVector s (Dual a) -> ST s () # basicUnsafeReplicate :: Int -> Dual a -> ST s (MVector s (Dual a)) # basicUnsafeRead :: MVector s (Dual a) -> Int -> ST s (Dual a) # basicUnsafeWrite :: MVector s (Dual a) -> Int -> Dual a -> ST s () # basicClear :: MVector s (Dual a) -> ST s () # basicSet :: MVector s (Dual a) -> Dual a -> ST s () # basicUnsafeCopy :: MVector s (Dual a) -> MVector s (Dual a) -> ST s () # basicUnsafeMove :: MVector s (Dual a) -> MVector s (Dual a) -> ST s () # basicUnsafeGrow :: MVector s (Dual a) -> Int -> ST s (MVector s (Dual a)) # | |
| Data a => Data (Dual a) | Since: base-4.8.0.0 |
Defined in 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) # | |
| Monoid a => Monoid (Dual a) | Since: base-2.1 |
| Semigroup a => Semigroup (Dual a) | Since: base-4.9.0.0 |
| Bounded a => Bounded (Dual a) | Since: base-2.1 |
| Generic (Dual a) | |
| Read a => Read (Dual a) | Since: base-2.1 |
| Show a => Show (Dual a) | Since: base-2.1 |
| NFData a => NFData (Dual a) | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
| Eq a => Eq (Dual a) | Since: base-2.1 |
| Ord a => Ord (Dual a) | Since: base-2.1 |
| Prim a => Prim (Dual a) | Since: primitive-0.6.5.0 |
Defined in Data.Primitive.Types Methods sizeOfType# :: Proxy (Dual a) -> Int# # alignmentOfType# :: Proxy (Dual a) -> Int# # alignment# :: Dual a -> Int# # indexByteArray# :: ByteArray# -> Int# -> Dual a # readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Dual a #) # writeByteArray# :: MutableByteArray# s -> Int# -> Dual a -> State# s -> State# s # setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Dual a -> State# s -> State# s # indexOffAddr# :: Addr# -> Int# -> Dual a # readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Dual a #) # writeOffAddr# :: Addr# -> Int# -> Dual a -> State# s -> State# s # setOffAddr# :: Addr# -> Int# -> Int# -> Dual a -> State# s -> State# s # | |
| Container (Dual a) Source # | |
Defined in Universum.Container.Class Methods toList :: Dual a -> [Element (Dual a)] Source # null :: Dual a -> Bool Source # foldr :: (Element (Dual a) -> b -> b) -> b -> Dual a -> b Source # foldl :: (b -> Element (Dual a) -> b) -> b -> Dual a -> b Source # foldl' :: (b -> Element (Dual a) -> b) -> b -> Dual a -> b Source # length :: Dual a -> Int Source # elem :: Element (Dual a) -> Dual a -> Bool Source # foldMap :: Monoid m => (Element (Dual a) -> m) -> Dual a -> m Source # fold :: Dual a -> Element (Dual a) Source # foldr' :: (Element (Dual a) -> b -> b) -> b -> Dual a -> b Source # notElem :: Element (Dual a) -> Dual a -> Bool Source # all :: (Element (Dual a) -> Bool) -> Dual a -> Bool Source # any :: (Element (Dual a) -> Bool) -> Dual a -> Bool Source # and :: Dual a -> Bool Source # find :: (Element (Dual a) -> Bool) -> Dual a -> Maybe (Element (Dual a)) Source # safeHead :: Dual a -> Maybe (Element (Dual a)) Source # safeMaximum :: Dual a -> Maybe (Element (Dual a)) Source # safeMinimum :: Dual a -> Maybe (Element (Dual a)) Source # safeFoldr1 :: (Element (Dual a) -> Element (Dual a) -> Element (Dual a)) -> Dual a -> Maybe (Element (Dual a)) Source # safeFoldl1 :: (Element (Dual a) -> Element (Dual a) -> Element (Dual a)) -> Dual a -> Maybe (Element (Dual a)) Source # | |
| Unbox a => Unbox (Dual a) | |
Defined in Data.Vector.Unboxed.Base | |
| type Rep1 Dual | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal | |
| newtype MVector s (Dual a) | |
Defined in Data.Vector.Unboxed.Base | |
| type Rep (Dual a) | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal | |
| type Element (Dual a) Source # | |
Defined in Universum.Container.Class | |
| newtype Vector (Dual a) | |
Defined in Data.Vector.Unboxed.Base | |
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.
>>>[1,2,3] <> [4,5,6][1,2,3,4,5,6]
Reduce a non-empty list with <>
The default definition should be sufficient, but this can be overridden for efficiency.
>>>import Data.List.NonEmpty (NonEmpty (..))>>>sconcat $ "Hello" :| [" ", "Haskell", "!"]"Hello Haskell!"
stimes :: Integral b => b -> a -> a #
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 stimesIdempotentstimes =
respectively.stimesIdempotentMonoid
>>>stimes 4 [1][1,1,1,1]
Instances
| Semigroup ByteArray | Since: base-4.17.0.0 |
| Semigroup All | Since: base-4.9.0.0 |
| Semigroup Any | Since: base-4.9.0.0 |
| Semigroup Void | Since: base-4.9.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 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 () | Since: base-4.9.0.0 |
| Bits a => Semigroup (And a) | Since: base-4.16 |
| FiniteBits a => Semigroup (Iff a) | This constraint is arguably
too strong. However, as some types (such as Since: base-4.16 |
| Bits a => Semigroup (Ior a) | Since: base-4.16 |
| Bits a => Semigroup (Xor a) | Since: base-4.16 |
| 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 (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 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 |
| Semigroup (NonEmpty a) | Since: base-4.9.0.0 |
| Semigroup a => Semigroup (STM a) | Since: base-4.17.0.0 |
| (Generic a, Semigroup (Rep a ())) => Semigroup (Generically a) | Since: base-4.17.0.0 |
Defined in GHC.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 (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 a => Semigroup (IO a) | Since: base-4.10.0.0 |
| Semigroup a => Semigroup (May a) | |
| Semigroup (Doc a) | |
| Semigroup (Array a) | Since: primitive-0.6.3.0 |
| Semigroup (PrimArray a) | Since: primitive-0.6.4.0 |
| Semigroup (SmallArray a) | Since: primitive-0.6.3.0 |
Defined in Data.Primitive.SmallArray Methods (<>) :: SmallArray a -> SmallArray a -> SmallArray a # sconcat :: NonEmpty (SmallArray a) -> SmallArray a # stimes :: Integral b => b -> SmallArray a -> SmallArray a # | |
| Semigroup a => Semigroup (Q a) | Since: template-haskell-2.17.0.0 |
| (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 (Vector a) | |
| Prim a => Semigroup (Vector a) | |
| Storable a => Semigroup (Vector a) | |
| Semigroup a => Semigroup (Maybe a) | Since: base-4.9.0.0 |
| Semigroup a => Semigroup (a) | Since: base-4.15 |
| Semigroup [a] | Since: base-4.9.0.0 |
| 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 |
| Ord k => Semigroup (Map k v) | |
| Applicative f => Semigroup (Traversed a f) | |
| Semigroup a => Semigroup (Err e a) | |
| (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 |
| (Monad m, Semigroup r) => Semigroup (Effect m r a) | |
| (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 |
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
stimesIdempotent :: Integral b => b -> a -> a #
stimesIdempotentMonoid :: (Integral b, Monoid a) => b -> a -> a #
stimesMonoid :: (Integral b, Monoid a) => b -> a -> a #
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, `stimes 0 a` for a Monoid 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.