| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Papa.Base.Export.Data.Semigroup
- class Semigroup a where
- stimesMonoid :: (Integral b, Monoid a) => b -> a -> a
- stimesIdempotent :: Integral b => b -> a -> a
- stimesIdempotentMonoid :: (Integral b, Monoid a) => b -> a -> a
- mtimesDefault :: (Integral b, Monoid a) => b -> a -> a
- data Min a :: * -> *
- data Max a :: * -> *
- data First a :: * -> *
- data Last a :: * -> *
- data WrappedMonoid m :: * -> *
- data Dual a :: * -> *
- data Endo a :: * -> *
- data All :: *
- data Any :: *
- data Sum a :: * -> *
- data Product a :: * -> *
- data Option a :: * -> *
- option :: b -> (a -> b) -> Option a -> b
- diff :: Semigroup m => m -> Endo m
- cycle1 :: Semigroup m => m -> m
- data WrappedMonoid m :: * -> *
- data Arg a b :: * -> * -> * = Arg a b
- type ArgMin a b = Min (Arg a b)
- type ArgMax a b = Max (Arg a b)
Documentation
The class of semigroups (types with an associative binary operation).
Since: 4.9.0.0
Methods
(<>) :: a -> a -> a infixr 6 #
An associative operation.
(a<>b)<>c = a<>(b<>c)
If a is also a Monoid we further require
(<>) =mappend
Reduce a non-empty list with <>
The default definition should be sufficient, but this can be overridden for efficiency.
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 O(1) by picking
stimes = stimesIdempotent or stimes = stimesIdempotentMonoid
respectively.
Instances
| Semigroup Ordering | Since: 4.9.0.0 |
| Semigroup () | Since: 4.9.0.0 |
| Semigroup Void | Since: 4.9.0.0 |
| Semigroup Event | Since: 4.10.0.0 |
| Semigroup Lifetime | Since: 4.10.0.0 |
| Semigroup All | Since: 4.9.0.0 |
| Semigroup Any | Since: 4.9.0.0 |
| Semigroup [a] | Since: 4.9.0.0 |
| Semigroup a => Semigroup (Maybe a) | Since: 4.9.0.0 |
| Semigroup a => Semigroup (IO a) | Since: 4.10.0.0 |
| Ord a => Semigroup (Min a) | Since: 4.9.0.0 |
| Ord a => Semigroup (Max a) | Since: 4.9.0.0 |
| Semigroup (First a) | Since: 4.9.0.0 |
| Semigroup (Last a) | Since: 4.9.0.0 |
| Monoid m => Semigroup (WrappedMonoid m) | Since: 4.9.0.0 |
| Semigroup a => Semigroup (Option a) | Since: 4.9.0.0 |
| Semigroup (NonEmpty a) | Since: 4.9.0.0 |
| Semigroup a => Semigroup (Identity a) | Since: 4.9.0.0 |
| Semigroup a => Semigroup (Dual a) | Since: 4.9.0.0 |
| Semigroup (Endo a) | Since: 4.9.0.0 |
| Num a => Semigroup (Sum a) | Since: 4.9.0.0 |
| Num a => Semigroup (Product a) | Since: 4.9.0.0 |
| Semigroup (First a) | Since: 4.9.0.0 |
| Semigroup (Last a) | Since: 4.9.0.0 |
| Semigroup b => Semigroup (a -> b) | Since: 4.9.0.0 |
| Semigroup (Either a b) | Since: 4.9.0.0 |
| (Semigroup a, Semigroup b) => Semigroup (a, b) | Since: 4.9.0.0 |
| Semigroup (Proxy k s) | Since: 4.9.0.0 |
| (Semigroup a, Semigroup b, Semigroup c) => Semigroup (a, b, c) | Since: 4.9.0.0 |
| Semigroup a => Semigroup (Const k a b) | Since: 4.9.0.0 |
| Alternative f => Semigroup (Alt * f a) | Since: 4.9.0.0 |
| (Semigroup a, Semigroup b, Semigroup c, Semigroup d) => Semigroup (a, b, c, d) | Since: 4.9.0.0 |
| (Semigroup a, Semigroup b, Semigroup c, Semigroup d, Semigroup e) => Semigroup (a, b, c, d, e) | Since: 4.9.0.0 |
stimesMonoid :: (Integral b, Monoid a) => b -> a -> a #
stimesIdempotent :: Integral b => b -> a -> a #
stimesIdempotentMonoid :: (Integral b, Monoid a) => b -> a -> a #
mtimesDefault :: (Integral b, Monoid a) => b -> a -> a #
Instances
| Monad Min | Since: 4.9.0.0 |
| Functor Min | Since: 4.9.0.0 |
| MonadFix Min | Since: 4.9.0.0 |
| Applicative Min | Since: 4.9.0.0 |
| Foldable Min | Since: 4.9.0.0 |
| Traversable Min | Since: 4.9.0.0 |
| Bounded a => Bounded (Min a) | |
| Enum a => Enum (Min a) | Since: 4.9.0.0 |
| Eq a => Eq (Min a) | |
| Data a => Data (Min a) | |
| Num a => Num (Min a) | Since: 4.9.0.0 |
| Ord a => Ord (Min a) | |
| Read a => Read (Min a) | |
| Show a => Show (Min a) | |
| Generic (Min a) | |
| Ord a => Semigroup (Min a) | Since: 4.9.0.0 |
| (Ord a, Bounded a) => Monoid (Min a) | Since: 4.9.0.0 |
| Generic1 * Min | |
| type Rep (Min a) | |
| type Rep1 * Min | |
Instances
| Monad Max | Since: 4.9.0.0 |
| Functor Max | Since: 4.9.0.0 |
| MonadFix Max | Since: 4.9.0.0 |
| Applicative Max | Since: 4.9.0.0 |
| Foldable Max | Since: 4.9.0.0 |
| Traversable Max | Since: 4.9.0.0 |
| Bounded a => Bounded (Max a) | |
| Enum a => Enum (Max a) | Since: 4.9.0.0 |
| Eq a => Eq (Max a) | |
| Data a => Data (Max a) | |
| Num a => Num (Max a) | Since: 4.9.0.0 |
| Ord a => Ord (Max a) | |
| Read a => Read (Max a) | |
| Show a => Show (Max a) | |
| Generic (Max a) | |
| Ord a => Semigroup (Max a) | Since: 4.9.0.0 |
| (Ord a, Bounded a) => Monoid (Max a) | Since: 4.9.0.0 |
| Generic1 * Max | |
| type Rep (Max a) | |
| type Rep1 * Max | |
Use to get the behavior of
Option (First a)First from Data.Monoid.
Instances
| Monad First | Since: 4.9.0.0 |
| Functor First | Since: 4.9.0.0 |
| MonadFix First | Since: 4.9.0.0 |
| Applicative First | Since: 4.9.0.0 |
| Foldable First | Since: 4.9.0.0 |
| Traversable First | Since: 4.9.0.0 |
| Bounded a => Bounded (First a) | |
| Enum a => Enum (First a) | Since: 4.9.0.0 |
| Eq a => Eq (First a) | |
| Data a => Data (First a) | |
| Ord a => Ord (First a) | |
| Read a => Read (First a) | |
| Show a => Show (First a) | |
| Generic (First a) | |
| Semigroup (First a) | Since: 4.9.0.0 |
| Generic1 * First | |
| type Rep (First a) | |
| type Rep1 * First | |
Use to get the behavior of
Option (Last a)Last from Data.Monoid
Instances
| Monad Last | Since: 4.9.0.0 |
| Functor Last | Since: 4.9.0.0 |
| MonadFix Last | Since: 4.9.0.0 |
| Applicative Last | Since: 4.9.0.0 |
| Foldable Last | Since: 4.9.0.0 |
| Traversable Last | Since: 4.9.0.0 |
| Bounded a => Bounded (Last a) | |
| Enum a => Enum (Last a) | Since: 4.9.0.0 |
| Eq a => Eq (Last a) | |
| Data a => Data (Last a) | |
| Ord a => Ord (Last a) | |
| Read a => Read (Last a) | |
| Show a => Show (Last a) | |
| Generic (Last a) | |
| Semigroup (Last a) | Since: 4.9.0.0 |
| Generic1 * Last | |
| type Rep (Last a) | |
| type Rep1 * Last | |
data WrappedMonoid m :: * -> * #
Provide a Semigroup for an arbitrary Monoid.
Instances
| Bounded m => Bounded (WrappedMonoid m) | |
| Enum a => Enum (WrappedMonoid a) | Since: 4.9.0.0 |
| Eq m => Eq (WrappedMonoid m) | |
| Data m => Data (WrappedMonoid m) | |
| Ord m => Ord (WrappedMonoid m) | |
| Read m => Read (WrappedMonoid m) | |
| Show m => Show (WrappedMonoid m) | |
| Generic (WrappedMonoid m) | |
| Monoid m => Semigroup (WrappedMonoid m) | Since: 4.9.0.0 |
| Monoid m => Monoid (WrappedMonoid m) | Since: 4.9.0.0 |
| Generic1 * WrappedMonoid | |
| type Rep (WrappedMonoid m) | |
| type Rep1 * WrappedMonoid | |
Instances
| Monad Dual | Since: 4.8.0.0 |
| Functor Dual | Since: 4.8.0.0 |
| Applicative Dual | Since: 4.8.0.0 |
| Foldable Dual | Since: 4.8.0.0 |
| Traversable Dual | Since: 4.8.0.0 |
| Bounded a => Bounded (Dual a) | |
| Eq a => Eq (Dual a) | |
| Ord a => Ord (Dual a) | |
| Read a => Read (Dual a) | |
| Show a => Show (Dual a) | |
| Generic (Dual a) | |
| Semigroup a => Semigroup (Dual a) | Since: 4.9.0.0 |
| Monoid a => Monoid (Dual a) | Since: 2.1 |
| Generic1 * Dual | |
| type Rep (Dual a) | |
| type Rep1 * Dual | |
The monoid of endomorphisms under composition.
Boolean monoid under conjunction (&&).
Boolean monoid under disjunction (||).
Monoid under addition.
Instances
| Monad Sum | Since: 4.8.0.0 |
| Functor Sum | Since: 4.8.0.0 |
| Applicative Sum | Since: 4.8.0.0 |
| Foldable Sum | Since: 4.8.0.0 |
| Traversable Sum | Since: 4.8.0.0 |
| Bounded a => Bounded (Sum a) | |
| Eq a => Eq (Sum a) | |
| Num a => Num (Sum a) | |
| Ord a => Ord (Sum a) | |
| Read a => Read (Sum a) | |
| Show a => Show (Sum a) | |
| Generic (Sum a) | |
| Num a => Semigroup (Sum a) | Since: 4.9.0.0 |
| Num a => Monoid (Sum a) | Since: 2.1 |
| Generic1 * Sum | |
| type Rep (Sum a) | |
| type Rep1 * Sum | |
Monoid under multiplication.
Instances
| Monad Product | Since: 4.8.0.0 |
| Functor Product | Since: 4.8.0.0 |
| Applicative Product | Since: 4.8.0.0 |
| Foldable Product | Since: 4.8.0.0 |
| Traversable Product | Since: 4.8.0.0 |
| Bounded a => Bounded (Product a) | |
| Eq a => Eq (Product a) | |
| Num a => Num (Product a) | |
| Ord a => Ord (Product a) | |
| Read a => Read (Product a) | |
| Show a => Show (Product a) | |
| Generic (Product a) | |
| Num a => Semigroup (Product a) | Since: 4.9.0.0 |
| Num a => Monoid (Product a) | Since: 2.1 |
| Generic1 * Product | |
| type Rep (Product a) | |
| type Rep1 * Product | |
Option is effectively Maybe with a better instance of
Monoid, built off of an underlying Semigroup instead of an
underlying Monoid.
Ideally, this type would not exist at all and we would just fix the
Monoid instance of Maybe
Instances
| Monad Option | Since: 4.9.0.0 |
| Functor Option | Since: 4.9.0.0 |
| MonadFix Option | Since: 4.9.0.0 |
| Applicative Option | Since: 4.9.0.0 |
| Foldable Option | Since: 4.9.0.0 |
| Traversable Option | Since: 4.9.0.0 |
| Alternative Option | Since: 4.9.0.0 |
| MonadPlus Option | Since: 4.9.0.0 |
| Eq a => Eq (Option a) | |
| Data a => Data (Option a) | |
| Ord a => Ord (Option a) | |
| Read a => Read (Option a) | |
| Show a => Show (Option a) | |
| Generic (Option a) | |
| Semigroup a => Semigroup (Option a) | Since: 4.9.0.0 |
| Semigroup a => Monoid (Option a) | Since: 4.9.0.0 |
| Generic1 * Option | |
| type Rep (Option a) | |
| type Rep1 * Option | |
data WrappedMonoid m :: * -> * #
Provide a Semigroup for an arbitrary Monoid.
Instances
| Bounded m => Bounded (WrappedMonoid m) | |
| Enum a => Enum (WrappedMonoid a) | Since: 4.9.0.0 |
| Eq m => Eq (WrappedMonoid m) | |
| Data m => Data (WrappedMonoid m) | |
| Ord m => Ord (WrappedMonoid m) | |
| Read m => Read (WrappedMonoid m) | |
| Show m => Show (WrappedMonoid m) | |
| Generic (WrappedMonoid m) | |
| Monoid m => Semigroup (WrappedMonoid m) | Since: 4.9.0.0 |
| Monoid m => Monoid (WrappedMonoid m) | Since: 4.9.0.0 |
| Generic1 * WrappedMonoid | |
| type Rep (WrappedMonoid m) | |
| type Rep1 * WrappedMonoid | |
Arg isn't itself a Semigroup in its own right, but it can be
placed inside Min and Max to compute an arg min or arg max.
Constructors
| Arg a b |
Instances
| Bitraversable Arg | Since: 4.10.0.0 |
| Bifoldable Arg | Since: 4.10.0.0 |
| Bifunctor Arg | Since: 4.9.0.0 |
| Functor (Arg a) | Since: 4.9.0.0 |
| Foldable (Arg a) | Since: 4.9.0.0 |
| Traversable (Arg a) | Since: 4.9.0.0 |
| Generic1 * (Arg a) | |
| Eq a => Eq (Arg a b) | Since: 4.9.0.0 |
| (Data b, Data a) => Data (Arg a b) | |
| Ord a => Ord (Arg a b) | Since: 4.9.0.0 |
| (Read b, Read a) => Read (Arg a b) | |
| (Show b, Show a) => Show (Arg a b) | |
| Generic (Arg a b) | |
| type Rep1 * (Arg a) | |
| type Rep (Arg a b) | |