base-4.20.0.0: Core data structures and operations
Copyright(C) 2011-2015 Edward Kmett
LicenseBSD-style (see the file LICENSE)
Maintainerlibraries@haskell.org
Stabilityprovisional
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Semigroup

Description

A type a is a Semigroup if it provides an associative function (<>) that lets you combine any two values of type a into one. Where being associative means that the following must always hold:

(a <> b) <> c == a <> (b <> c)

Examples

Expand

The Min Semigroup instance for Int is defined to always pick the smaller number:

>>> Min 1 <> Min 2 <> Min 3 <> Min 4 :: Min Int
Min {getMin = 1}

If we need to combine multiple values we can use the sconcat function to do so. We need to ensure however that we have at least one value to operate on, since otherwise our result would be undefined. It is for this reason that sconcat uses Data.List.NonEmpty.NonEmpty - a list that can never be empty:

>>> (1 :| [])
1 :| []               -- equivalent to [1] but guaranteed to be non-empty.
>>> (1 :| [2, 3, 4])
1 :| [2,3,4]          -- equivalent to [1,2,3,4] but guaranteed to be non-empty.

Equipped with this guaranteed to be non-empty data structure, we can combine values using sconcat and a Semigroup of our choosing. We can try the Min and Max instances of Int which pick the smallest, or largest number respectively:

>>> sconcat (1 :| [2, 3, 4]) :: Min Int
Min {getMin = 1}
>>> sconcat (1 :| [2, 3, 4]) :: Max Int
Max {getMax = 4}

String concatenation is another example of a Semigroup instance:

>>> "foo" <> "bar"
"foobar"

A Semigroup is a generalization of a Monoid. Yet unlike the Semigroup, the Monoid requires the presence of a neutral element (mempty) in addition to the associative operator. The requirement for a neutral element prevents many types from being a full Monoid, like Data.List.NonEmpty.NonEmpty.

Note that the use of (<>) in this module conflicts with an operator with the same name that is being exported by Data.Monoid. However, this package re-exports (most of) the contents of Data.Monoid, so to use semigroups and monoids in the same package just

import Data.Semigroup

Since: base-4.9.0.0

Synopsis

Documentation

class Semigroup a where Source #

The class of semigroups (types with an associative binary operation).

Instances should satisfy the following:

Associativity
x <> (y <> z) = (x <> y) <> z

You can alternatively define sconcat instead of (<>), in which case the laws are:

Unit
sconcat (pure x) = x
Multiplication
sconcat (join xss) = sconcat (fmap sconcat xss)

@since base-4.9.0.0

Minimal complete definition

(<>) | sconcat

Methods

(<>) :: a -> a -> a infixr 6 Source #

An associative operation.

Examples

Expand
>>> [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!

sconcat :: NonEmpty a -> a Source #

Reduce a non-empty list with <>

The default definition should be sufficient, but this can be overridden for efficiency.

Examples

Expand

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 Source #

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 = stimesIdempotent or stimes = stimesIdempotentMonoid respectively.

Examples

Expand
>>> stimes 4 [1]
[1,1,1,1]
>>> stimes 5 (putStr "hi!")
hi!hi!hi!hi!hi!
>>> stimes 3 (Right ":)")
Right ":)"

Instances

Instances details
Semigroup ByteArray Source #

Since: base-4.17.0.0

Instance details

Defined in Data.Array.Byte

Semigroup Void

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Semigroup All

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(<>) :: All -> All -> All Source #

sconcat :: NonEmpty All -> All Source #

stimes :: Integral b => b -> All -> All Source #

Semigroup Any

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(<>) :: Any -> Any -> Any Source #

sconcat :: NonEmpty Any -> Any Source #

stimes :: Integral b => b -> Any -> Any Source #

Semigroup Event

@since base-4.10.0.0

Instance details

Defined in GHC.Internal.Event.Internal.Types

Semigroup EventLifetime

@since base-4.11.0.0

Instance details

Defined in GHC.Internal.Event.Internal.Types

Methods

(<>) :: EventLifetime -> EventLifetime -> EventLifetime Source #

sconcat :: NonEmpty EventLifetime -> EventLifetime Source #

stimes :: Integral b => b -> EventLifetime -> EventLifetime Source #

Semigroup Lifetime

@since base-4.10.0.0

Instance details

Defined in GHC.Internal.Event.Internal.Types

Semigroup ExceptionContext 
Instance details

Defined in GHC.Internal.Exception.Context

Semigroup Ordering

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Semigroup ()

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

(<>) :: () -> () -> () Source #

sconcat :: NonEmpty () -> () Source #

stimes :: Integral b => b -> () -> () Source #

Semigroup (Comparison a) Source #

(<>) on comparisons combines results with (<>) @Ordering. Without newtypes this equals liftA2 (liftA2 (<>)).

(<>) :: Comparison a -> Comparison a -> Comparison a
Comparison cmp <> Comparison cmp' = Comparison a a' ->
  cmp a a' <> cmp a a'
Instance details

Defined in Data.Functor.Contravariant

Semigroup (Equivalence a) Source #

(<>) on equivalences uses logical conjunction (&&) on the results. Without newtypes this equals liftA2 (liftA2 (&&)).

(<>) :: Equivalence a -> Equivalence a -> Equivalence a
Equivalence equiv <> Equivalence equiv' = Equivalence a b ->
  equiv a b && equiv' a b
Instance details

Defined in Data.Functor.Contravariant

Semigroup (Predicate a) Source #

(<>) on predicates uses logical conjunction (&&) on the results. Without newtypes this equals liftA2 (&&).

(<>) :: Predicate a -> Predicate a -> Predicate a
Predicate pred <> Predicate pred' = Predicate a ->
  pred a && pred' a
Instance details

Defined in Data.Functor.Contravariant

Semigroup (First a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

(<>) :: First a -> First a -> First a Source #

sconcat :: NonEmpty (First a) -> First a Source #

stimes :: Integral b => b -> First a -> First a Source #

Semigroup (Last a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

(<>) :: Last a -> Last a -> Last a Source #

sconcat :: NonEmpty (Last a) -> Last a Source #

stimes :: Integral b => b -> Last a -> Last a Source #

Ord a => Semigroup (Max a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

(<>) :: Max a -> Max a -> Max a Source #

sconcat :: NonEmpty (Max a) -> Max a Source #

stimes :: Integral b => b -> Max a -> Max a Source #

Ord a => Semigroup (Min a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

(<>) :: Min a -> Min a -> Min a Source #

sconcat :: NonEmpty (Min a) -> Min a Source #

stimes :: Integral b => b -> Min a -> Min a Source #

Monoid m => Semigroup (WrappedMonoid m) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Semigroup (NonEmpty a)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Semigroup a => Semigroup (STM a)

@since base-4.17.0.0

Instance details

Defined in GHC.Internal.Conc.Sync

Methods

(<>) :: STM a -> STM a -> STM a Source #

sconcat :: NonEmpty (STM a) -> STM a Source #

stimes :: Integral b => b -> STM a -> STM a Source #

Bits a => Semigroup (And a)

@since base-4.16

Instance details

Defined in GHC.Internal.Data.Bits

Methods

(<>) :: And a -> And a -> And a Source #

sconcat :: NonEmpty (And a) -> And a Source #

stimes :: Integral b => b -> And a -> And a Source #

FiniteBits a => Semigroup (Iff a)

This constraint is arguably too strong. However, as some types (such as Natural) have undefined complement, this is the only safe choice.

@since base-4.16

Instance details

Defined in GHC.Internal.Data.Bits

Methods

(<>) :: Iff a -> Iff a -> Iff a Source #

sconcat :: NonEmpty (Iff a) -> Iff a Source #

stimes :: Integral b => b -> Iff a -> Iff a Source #

Bits a => Semigroup (Ior a)

@since base-4.16

Instance details

Defined in GHC.Internal.Data.Bits

Methods

(<>) :: Ior a -> Ior a -> Ior a Source #

sconcat :: NonEmpty (Ior a) -> Ior a Source #

stimes :: Integral b => b -> Ior a -> Ior a Source #

Bits a => Semigroup (Xor a)

@since base-4.16

Instance details

Defined in GHC.Internal.Data.Bits

Methods

(<>) :: Xor a -> Xor a -> Xor a Source #

sconcat :: NonEmpty (Xor a) -> Xor a Source #

stimes :: Integral b => b -> Xor a -> Xor a Source #

Semigroup a => Semigroup (Identity a)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Identity

Ord a => Semigroup (Max a)

@since base-4.11.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Utils

Methods

(<>) :: Max a -> Max a -> Max a Source #

sconcat :: NonEmpty (Max a) -> Max a Source #

stimes :: Integral b => b -> Max a -> Max a Source #

Ord a => Semigroup (Min a)

@since base-4.11.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Utils

Methods

(<>) :: Min a -> Min a -> Min a Source #

sconcat :: NonEmpty (Min a) -> Min a Source #

stimes :: Integral b => b -> Min a -> Min a Source #

Semigroup (First a)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

(<>) :: First a -> First a -> First a Source #

sconcat :: NonEmpty (First a) -> First a Source #

stimes :: Integral b => b -> First a -> First a Source #

Semigroup (Last a)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

(<>) :: Last a -> Last a -> Last a Source #

sconcat :: NonEmpty (Last a) -> Last a Source #

stimes :: Integral b => b -> Last a -> Last a Source #

Semigroup a => Semigroup (Down a)

@since base-4.11.0.0

Instance details

Defined in GHC.Internal.Data.Ord

Methods

(<>) :: Down a -> Down a -> Down a Source #

sconcat :: NonEmpty (Down a) -> Down a Source #

stimes :: Integral b => b -> Down a -> Down a Source #

Semigroup a => Semigroup (Dual a)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(<>) :: Dual a -> Dual a -> Dual a Source #

sconcat :: NonEmpty (Dual a) -> Dual a Source #

stimes :: Integral b => b -> Dual a -> Dual a Source #

Semigroup (Endo a)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(<>) :: Endo a -> Endo a -> Endo a Source #

sconcat :: NonEmpty (Endo a) -> Endo a Source #

stimes :: Integral b => b -> Endo a -> Endo a Source #

Num a => Semigroup (Product a)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(<>) :: Product a -> Product a -> Product a Source #

sconcat :: NonEmpty (Product a) -> Product a Source #

stimes :: Integral b => b -> Product a -> Product a Source #

Num a => Semigroup (Sum a)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(<>) :: Sum a -> Sum a -> Sum a Source #

sconcat :: NonEmpty (Sum a) -> Sum a Source #

stimes :: Integral b => b -> Sum a -> Sum a Source #

(Generic a, Semigroup (Rep a ())) => Semigroup (Generically a)

@since base-4.17.0.0

Instance details

Defined in GHC.Internal.Generics

Semigroup p => Semigroup (Par1 p)

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(<>) :: Par1 p -> Par1 p -> Par1 p Source #

sconcat :: NonEmpty (Par1 p) -> Par1 p Source #

stimes :: Integral b => b -> Par1 p -> Par1 p Source #

Semigroup a => Semigroup (IO a)

@since base-4.10.0.0

Instance details

Defined in GHC.Internal.Base

Methods

(<>) :: IO a -> IO a -> IO a Source #

sconcat :: NonEmpty (IO a) -> IO a Source #

stimes :: Integral b => b -> IO a -> IO a Source #

Semigroup a => Semigroup (Maybe a)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

(<>) :: Maybe a -> Maybe a -> Maybe a Source #

sconcat :: NonEmpty (Maybe a) -> Maybe a Source #

stimes :: Integral b => b -> Maybe a -> Maybe a Source #

Semigroup a => Semigroup (Solo a)

@since base-4.15

Instance details

Defined in GHC.Internal.Base

Methods

(<>) :: Solo a -> Solo a -> Solo a Source #

sconcat :: NonEmpty (Solo a) -> Solo a Source #

stimes :: Integral b => b -> Solo a -> Solo a Source #

Semigroup [a]

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

(<>) :: [a] -> [a] -> [a] Source #

sconcat :: NonEmpty [a] -> [a] Source #

stimes :: Integral b => b -> [a] -> [a] Source #

Semigroup a => Semigroup (Op a b) Source #

(<>) @(Op a b) without newtypes is (<>) @(b->a) = liftA2 (<>). This lifts the Semigroup operation (<>) over the output of a.

(<>) :: Op a b -> Op a b -> Op a b
Op f <> Op g = Op a -> f a <> g a
Instance details

Defined in Data.Functor.Contravariant

Methods

(<>) :: Op a b -> Op a b -> Op a b Source #

sconcat :: NonEmpty (Op a b) -> Op a b Source #

stimes :: Integral b0 => b0 -> Op a b -> Op a b Source #

Semigroup (Either a b)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Either

Methods

(<>) :: Either a b -> Either a b -> Either a b Source #

sconcat :: NonEmpty (Either a b) -> Either a b Source #

stimes :: Integral b0 => b0 -> Either a b -> Either a b Source #

Semigroup (Proxy s)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

(<>) :: Proxy s -> Proxy s -> Proxy s Source #

sconcat :: NonEmpty (Proxy s) -> Proxy s Source #

stimes :: Integral b => b -> Proxy s -> Proxy s Source #

Semigroup (U1 p)

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(<>) :: U1 p -> U1 p -> U1 p Source #

sconcat :: NonEmpty (U1 p) -> U1 p Source #

stimes :: Integral b => b -> U1 p -> U1 p Source #

Semigroup (V1 p)

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(<>) :: V1 p -> V1 p -> V1 p Source #

sconcat :: NonEmpty (V1 p) -> V1 p Source #

stimes :: Integral b => b -> V1 p -> V1 p Source #

Semigroup a => Semigroup (ST s a)

@since base-4.11.0.0

Instance details

Defined in GHC.Internal.ST

Methods

(<>) :: ST s a -> ST s a -> ST s a Source #

sconcat :: NonEmpty (ST s a) -> ST s a Source #

stimes :: Integral b => b -> ST s a -> ST s a Source #

(Semigroup a, Semigroup b) => Semigroup (a, b)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

(<>) :: (a, b) -> (a, b) -> (a, b) Source #

sconcat :: NonEmpty (a, b) -> (a, b) Source #

stimes :: Integral b0 => b0 -> (a, b) -> (a, b) Source #

Semigroup b => Semigroup (a -> b)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

(<>) :: (a -> b) -> (a -> b) -> a -> b Source #

sconcat :: NonEmpty (a -> b) -> a -> b Source #

stimes :: Integral b0 => b0 -> (a -> b) -> a -> b Source #

Semigroup a => Semigroup (Const a b)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Const

Methods

(<>) :: Const a b -> Const a b -> Const a b Source #

sconcat :: NonEmpty (Const a b) -> Const a b Source #

stimes :: Integral b0 => b0 -> Const a b -> Const a b Source #

(Applicative f, Semigroup a) => Semigroup (Ap f a)

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

(<>) :: Ap f a -> Ap f a -> Ap f a Source #

sconcat :: NonEmpty (Ap f a) -> Ap f a Source #

stimes :: Integral b => b -> Ap f a -> Ap f a Source #

Alternative f => Semigroup (Alt f a)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(<>) :: Alt f a -> Alt f a -> Alt f a Source #

sconcat :: NonEmpty (Alt f a) -> Alt f a Source #

stimes :: Integral b => b -> Alt f a -> Alt f a Source #

Semigroup (f p) => Semigroup (Rec1 f p)

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(<>) :: Rec1 f p -> Rec1 f p -> Rec1 f p Source #

sconcat :: NonEmpty (Rec1 f p) -> Rec1 f p Source #

stimes :: Integral b => b -> Rec1 f p -> Rec1 f p Source #

(Semigroup a, Semigroup b, Semigroup c) => Semigroup (a, b, c)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

(<>) :: (a, b, c) -> (a, b, c) -> (a, b, c) Source #

sconcat :: NonEmpty (a, b, c) -> (a, b, c) Source #

stimes :: Integral b0 => b0 -> (a, b, c) -> (a, b, c) Source #

(Semigroup (f a), Semigroup (g a)) => Semigroup (Product f g a) Source #

Since: base-4.16.0.0

Instance details

Defined in Data.Functor.Product

Methods

(<>) :: Product f g a -> Product f g a -> Product f g a Source #

sconcat :: NonEmpty (Product f g a) -> Product f g a Source #

stimes :: Integral b => b -> Product f g a -> Product f g a Source #

(Semigroup (f p), Semigroup (g p)) => Semigroup ((f :*: g) p)

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(<>) :: (f :*: g) p -> (f :*: g) p -> (f :*: g) p Source #

sconcat :: NonEmpty ((f :*: g) p) -> (f :*: g) p Source #

stimes :: Integral b => b -> (f :*: g) p -> (f :*: g) p Source #

Semigroup c => Semigroup (K1 i c p)

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(<>) :: K1 i c p -> K1 i c p -> K1 i c p Source #

sconcat :: NonEmpty (K1 i c p) -> K1 i c p Source #

stimes :: Integral b => b -> K1 i c p -> K1 i c p Source #

(Semigroup a, Semigroup b, Semigroup c, Semigroup d) => Semigroup (a, b, c, d)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

(<>) :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) Source #

sconcat :: NonEmpty (a, b, c, d) -> (a, b, c, d) Source #

stimes :: Integral b0 => b0 -> (a, b, c, d) -> (a, b, c, d) Source #

Semigroup (f (g a)) => Semigroup (Compose f g a) Source #

Since: base-4.16.0.0

Instance details

Defined in Data.Functor.Compose

Methods

(<>) :: Compose f g a -> Compose f g a -> Compose f g a Source #

sconcat :: NonEmpty (Compose f g a) -> Compose f g a Source #

stimes :: Integral b => b -> Compose f g a -> Compose f g a Source #

Semigroup (f (g p)) => Semigroup ((f :.: g) p)

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(<>) :: (f :.: g) p -> (f :.: g) p -> (f :.: g) p Source #

sconcat :: NonEmpty ((f :.: g) p) -> (f :.: g) p Source #

stimes :: Integral b => b -> (f :.: g) p -> (f :.: g) p Source #

Semigroup (f p) => Semigroup (M1 i c f p)

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(<>) :: M1 i c f p -> M1 i c f p -> M1 i c f p Source #

sconcat :: NonEmpty (M1 i c f p) -> M1 i c f p Source #

stimes :: Integral b => b -> M1 i c f p -> M1 i c f p Source #

(Semigroup a, Semigroup b, Semigroup c, Semigroup d, Semigroup e) => Semigroup (a, b, c, d, e)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

(<>) :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) Source #

sconcat :: NonEmpty (a, b, c, d, e) -> (a, b, c, d, e) Source #

stimes :: Integral b0 => b0 -> (a, b, c, d, e) -> (a, b, c, d, e) Source #

stimesMonoid :: (Integral b, Monoid a) => b -> a -> a Source #

This is a valid definition of stimes for a Monoid.

Unlike the default definition of stimes, it is defined for 0 and so it should be preferred where possible.

stimesIdempotent :: Integral b => b -> a -> a Source #

This is a valid definition of stimes for an idempotent Semigroup.

When x <> x = x, this definition should be preferred, because it works in \(\mathcal{O}(1)\) rather than \(\mathcal{O}(\log n)\).

stimesIdempotentMonoid :: (Integral b, Monoid a) => b -> a -> a Source #

This is a valid definition of stimes for an idempotent Monoid.

When x <> x = x, this definition should be preferred, because it works in \(\mathcal{O}(1)\) rather than \(\mathcal{O}(\log n)\)

mtimesDefault :: (Integral b, Monoid a) => b -> a -> a Source #

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.

Examples

Expand
>>> mtimesDefault 0 "bark"
[]
>>> mtimesDefault 3 "meow"
"meowmeowmeow"

Semigroups

newtype Min a Source #

The Min Monoid and Semigroup always choose the smaller element as by the Ord instance and min of the contained type.

Examples

Expand
>>> Min 42 <> Min 3
Min 3
>>> sconcat $ Min 1 :| [ Min n | n <- [2 .. 100]]
Min {getMin = 1}

Constructors

Min 

Fields

Instances

Instances details
Foldable1 Min Source #

Since: base-4.18.0.0

Instance details

Defined in Data.Foldable1

Methods

fold1 :: Semigroup m => Min m -> m Source #

foldMap1 :: Semigroup m => (a -> m) -> Min a -> m Source #

foldMap1' :: Semigroup m => (a -> m) -> Min a -> m Source #

toNonEmpty :: Min a -> NonEmpty a Source #

maximum :: Ord a => Min a -> a Source #

minimum :: Ord a => Min a -> a Source #

head :: Min a -> a Source #

last :: Min a -> a Source #

foldrMap1 :: (a -> b) -> (a -> b -> b) -> Min a -> b Source #

foldlMap1' :: (a -> b) -> (b -> a -> b) -> Min a -> b Source #

foldlMap1 :: (a -> b) -> (b -> a -> b) -> Min a -> b Source #

foldrMap1' :: (a -> b) -> (a -> b -> b) -> Min a -> b Source #

Applicative Min Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

pure :: a -> Min a Source #

(<*>) :: Min (a -> b) -> Min a -> Min b Source #

liftA2 :: (a -> b -> c) -> Min a -> Min b -> Min c Source #

(*>) :: Min a -> Min b -> Min b Source #

(<*) :: Min a -> Min b -> Min a Source #

Functor Min Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

fmap :: (a -> b) -> Min a -> Min b Source #

(<$) :: a -> Min b -> Min a Source #

Monad Min Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

(>>=) :: Min a -> (a -> Min b) -> Min b Source #

(>>) :: Min a -> Min b -> Min b Source #

return :: a -> Min a Source #

MonadFix Min Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

mfix :: (a -> Min a) -> Min a Source #

Foldable Min Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

fold :: Monoid m => Min m -> m Source #

foldMap :: Monoid m => (a -> m) -> Min a -> m Source #

foldMap' :: Monoid m => (a -> m) -> Min a -> m Source #

foldr :: (a -> b -> b) -> b -> Min a -> b Source #

foldr' :: (a -> b -> b) -> b -> Min a -> b Source #

foldl :: (b -> a -> b) -> b -> Min a -> b Source #

foldl' :: (b -> a -> b) -> b -> Min a -> b Source #

foldr1 :: (a -> a -> a) -> Min a -> a Source #

foldl1 :: (a -> a -> a) -> Min a -> a Source #

toList :: Min a -> [a] Source #

null :: Min a -> Bool Source #

length :: Min a -> Int Source #

elem :: Eq a => a -> Min a -> Bool Source #

maximum :: Ord a => Min a -> a Source #

minimum :: Ord a => Min a -> a Source #

sum :: Num a => Min a -> a Source #

product :: Num a => Min a -> a Source #

Traversable Min Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

traverse :: Applicative f => (a -> f b) -> Min a -> f (Min b) Source #

sequenceA :: Applicative f => Min (f a) -> f (Min a) Source #

mapM :: Monad m => (a -> m b) -> Min a -> m (Min b) Source #

sequence :: Monad m => Min (m a) -> m (Min a) Source #

Generic1 Min Source # 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep1 Min

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep1 Min = D1 ('MetaData "Min" "Data.Semigroup" "base" 'True) (C1 ('MetaCons "Min" 'PrefixI 'True) (S1 ('MetaSel ('Just "getMin") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))

Methods

from1 :: Min a -> Rep1 Min a Source #

to1 :: Rep1 Min a -> Min a Source #

(Ord a, Bounded a) => Monoid (Min a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

mempty :: Min a Source #

mappend :: Min a -> Min a -> Min a Source #

mconcat :: [Min a] -> Min a Source #

Ord a => Semigroup (Min a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

(<>) :: Min a -> Min a -> Min a Source #

sconcat :: NonEmpty (Min a) -> Min a Source #

stimes :: Integral b => b -> Min a -> Min a Source #

Data a => Data (Min a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Min a -> c (Min a) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Min a) Source #

toConstr :: Min a -> Constr Source #

dataTypeOf :: Min a -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Min a)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Min a)) Source #

gmapT :: (forall b. Data b => b -> b) -> Min a -> Min a Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Min a -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Min a -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Min a -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Min a -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Min a -> m (Min a) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Min a -> m (Min a) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Min a -> m (Min a) Source #

Bounded a => Bounded (Min a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Enum a => Enum (Min a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

succ :: Min a -> Min a Source #

pred :: Min a -> Min a Source #

toEnum :: Int -> Min a Source #

fromEnum :: Min a -> Int Source #

enumFrom :: Min a -> [Min a] Source #

enumFromThen :: Min a -> Min a -> [Min a] Source #

enumFromTo :: Min a -> Min a -> [Min a] Source #

enumFromThenTo :: Min a -> Min a -> Min a -> [Min a] Source #

Generic (Min a) Source # 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Min a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep (Min a) = D1 ('MetaData "Min" "Data.Semigroup" "base" 'True) (C1 ('MetaCons "Min" 'PrefixI 'True) (S1 ('MetaSel ('Just "getMin") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Methods

from :: Min a -> Rep (Min a) x Source #

to :: Rep (Min a) x -> Min a Source #

Num a => Num (Min a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

(+) :: Min a -> Min a -> Min a Source #

(-) :: Min a -> Min a -> Min a Source #

(*) :: Min a -> Min a -> Min a Source #

negate :: Min a -> Min a Source #

abs :: Min a -> Min a Source #

signum :: Min a -> Min a Source #

fromInteger :: Integer -> Min a Source #

Read a => Read (Min a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Show a => Show (Min a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

showsPrec :: Int -> Min a -> ShowS Source #

show :: Min a -> String Source #

showList :: [Min a] -> ShowS Source #

Eq a => Eq (Min a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

(==) :: Min a -> Min a -> Bool Source #

(/=) :: Min a -> Min a -> Bool Source #

Ord a => Ord (Min a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

compare :: Min a -> Min a -> Ordering Source #

(<) :: Min a -> Min a -> Bool Source #

(<=) :: Min a -> Min a -> Bool Source #

(>) :: Min a -> Min a -> Bool Source #

(>=) :: Min a -> Min a -> Bool Source #

max :: Min a -> Min a -> Min a Source #

min :: Min a -> Min a -> Min a Source #

type Rep1 Min Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep1 Min = D1 ('MetaData "Min" "Data.Semigroup" "base" 'True) (C1 ('MetaCons "Min" 'PrefixI 'True) (S1 ('MetaSel ('Just "getMin") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep (Min a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep (Min a) = D1 ('MetaData "Min" "Data.Semigroup" "base" 'True) (C1 ('MetaCons "Min" 'PrefixI 'True) (S1 ('MetaSel ('Just "getMin") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

newtype Max a Source #

The Max Monoid and Semigroup always choose the bigger element as by the Ord instance and max of the contained type.

Examples

Expand
>>> Max 42 <> Max 3
Max 42
>>> sconcat $ Max 1 :| [ Max n | n <- [2 .. 100]]
Max {getMax = 100}

Constructors

Max 

Fields

Instances

Instances details
Foldable1 Max Source #

Since: base-4.18.0.0

Instance details

Defined in Data.Foldable1

Methods

fold1 :: Semigroup m => Max m -> m Source #

foldMap1 :: Semigroup m => (a -> m) -> Max a -> m Source #

foldMap1' :: Semigroup m => (a -> m) -> Max a -> m Source #

toNonEmpty :: Max a -> NonEmpty a Source #

maximum :: Ord a => Max a -> a Source #

minimum :: Ord a => Max a -> a Source #

head :: Max a -> a Source #

last :: Max a -> a Source #

foldrMap1 :: (a -> b) -> (a -> b -> b) -> Max a -> b Source #

foldlMap1' :: (a -> b) -> (b -> a -> b) -> Max a -> b Source #

foldlMap1 :: (a -> b) -> (b -> a -> b) -> Max a -> b Source #

foldrMap1' :: (a -> b) -> (a -> b -> b) -> Max a -> b Source #

Applicative Max Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

pure :: a -> Max a Source #

(<*>) :: Max (a -> b) -> Max a -> Max b Source #

liftA2 :: (a -> b -> c) -> Max a -> Max b -> Max c Source #

(*>) :: Max a -> Max b -> Max b Source #

(<*) :: Max a -> Max b -> Max a Source #

Functor Max Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

fmap :: (a -> b) -> Max a -> Max b Source #

(<$) :: a -> Max b -> Max a Source #

Monad Max Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

(>>=) :: Max a -> (a -> Max b) -> Max b Source #

(>>) :: Max a -> Max b -> Max b Source #

return :: a -> Max a Source #

MonadFix Max Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

mfix :: (a -> Max a) -> Max a Source #

Foldable Max Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

fold :: Monoid m => Max m -> m Source #

foldMap :: Monoid m => (a -> m) -> Max a -> m Source #

foldMap' :: Monoid m => (a -> m) -> Max a -> m Source #

foldr :: (a -> b -> b) -> b -> Max a -> b Source #

foldr' :: (a -> b -> b) -> b -> Max a -> b Source #

foldl :: (b -> a -> b) -> b -> Max a -> b Source #

foldl' :: (b -> a -> b) -> b -> Max a -> b Source #

foldr1 :: (a -> a -> a) -> Max a -> a Source #

foldl1 :: (a -> a -> a) -> Max a -> a Source #

toList :: Max a -> [a] Source #

null :: Max a -> Bool Source #

length :: Max a -> Int Source #

elem :: Eq a => a -> Max a -> Bool Source #

maximum :: Ord a => Max a -> a Source #

minimum :: Ord a => Max a -> a Source #

sum :: Num a => Max a -> a Source #

product :: Num a => Max a -> a Source #

Traversable Max Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

traverse :: Applicative f => (a -> f b) -> Max a -> f (Max b) Source #

sequenceA :: Applicative f => Max (f a) -> f (Max a) Source #

mapM :: Monad m => (a -> m b) -> Max a -> m (Max b) Source #

sequence :: Monad m => Max (m a) -> m (Max a) Source #

Generic1 Max Source # 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep1 Max

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep1 Max = D1 ('MetaData "Max" "Data.Semigroup" "base" 'True) (C1 ('MetaCons "Max" 'PrefixI 'True) (S1 ('MetaSel ('Just "getMax") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))

Methods

from1 :: Max a -> Rep1 Max a Source #

to1 :: Rep1 Max a -> Max a Source #

(Ord a, Bounded a) => Monoid (Max a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

mempty :: Max a Source #

mappend :: Max a -> Max a -> Max a Source #

mconcat :: [Max a] -> Max a Source #

Ord a => Semigroup (Max a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

(<>) :: Max a -> Max a -> Max a Source #

sconcat :: NonEmpty (Max a) -> Max a Source #

stimes :: Integral b => b -> Max a -> Max a Source #

Data a => Data (Max a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Max a -> c (Max a) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Max a) Source #

toConstr :: Max a -> Constr Source #

dataTypeOf :: Max a -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Max a)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Max a)) Source #

gmapT :: (forall b. Data b => b -> b) -> Max a -> Max a Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Max a -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Max a -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Max a -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Max a -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Max a -> m (Max a) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Max a -> m (Max a) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Max a -> m (Max a) Source #

Bounded a => Bounded (Max a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Enum a => Enum (Max a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

succ :: Max a -> Max a Source #

pred :: Max a -> Max a Source #

toEnum :: Int -> Max a Source #

fromEnum :: Max a -> Int Source #

enumFrom :: Max a -> [Max a] Source #

enumFromThen :: Max a -> Max a -> [Max a] Source #

enumFromTo :: Max a -> Max a -> [Max a] Source #

enumFromThenTo :: Max a -> Max a -> Max a -> [Max a] Source #

Generic (Max a) Source # 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Max a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep (Max a) = D1 ('MetaData "Max" "Data.Semigroup" "base" 'True) (C1 ('MetaCons "Max" 'PrefixI 'True) (S1 ('MetaSel ('Just "getMax") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Methods

from :: Max a -> Rep (Max a) x Source #

to :: Rep (Max a) x -> Max a Source #

Num a => Num (Max a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

(+) :: Max a -> Max a -> Max a Source #

(-) :: Max a -> Max a -> Max a Source #

(*) :: Max a -> Max a -> Max a Source #

negate :: Max a -> Max a Source #

abs :: Max a -> Max a Source #

signum :: Max a -> Max a Source #

fromInteger :: Integer -> Max a Source #

Read a => Read (Max a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Show a => Show (Max a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

showsPrec :: Int -> Max a -> ShowS Source #

show :: Max a -> String Source #

showList :: [Max a] -> ShowS Source #

Eq a => Eq (Max a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

(==) :: Max a -> Max a -> Bool Source #

(/=) :: Max a -> Max a -> Bool Source #

Ord a => Ord (Max a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

compare :: Max a -> Max a -> Ordering Source #

(<) :: Max a -> Max a -> Bool Source #

(<=) :: Max a -> Max a -> Bool Source #

(>) :: Max a -> Max a -> Bool Source #

(>=) :: Max a -> Max a -> Bool Source #

max :: Max a -> Max a -> Max a Source #

min :: Max a -> Max a -> Max a Source #

type Rep1 Max Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep1 Max = D1 ('MetaData "Max" "Data.Semigroup" "base" 'True) (C1 ('MetaCons "Max" 'PrefixI 'True) (S1 ('MetaSel ('Just "getMax") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep (Max a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep (Max a) = D1 ('MetaData "Max" "Data.Semigroup" "base" 'True) (C1 ('MetaCons "Max" 'PrefixI 'True) (S1 ('MetaSel ('Just "getMax") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

newtype First a Source #

Beware that Data.Semigroup.First is different from Data.Monoid.First. The former simply returns the first value, so Data.Semigroup.First Nothing <> x = Data.Semigroup.First Nothing. The latter returns the first non-Nothing, thus Data.Monoid.First Nothing <> x = x.

Examples

Expand
>>> First 0 <> First 10
First 0
>>> sconcat $ First 1 :| [ First n | n <- [2 ..] ]
First 1

Constructors

First 

Fields

Instances

Instances details
Foldable1 First Source #

Since: base-4.18.0.0

Instance details

Defined in Data.Foldable1

Methods

fold1 :: Semigroup m => First m -> m Source #

foldMap1 :: Semigroup m => (a -> m) -> First a -> m Source #

foldMap1' :: Semigroup m => (a -> m) -> First a -> m Source #

toNonEmpty :: First a -> NonEmpty a Source #

maximum :: Ord a => First a -> a Source #

minimum :: Ord a => First a -> a Source #

head :: First a -> a Source #

last :: First a -> a Source #

foldrMap1 :: (a -> b) -> (a -> b -> b) -> First a -> b Source #

foldlMap1' :: (a -> b) -> (b -> a -> b) -> First a -> b Source #

foldlMap1 :: (a -> b) -> (b -> a -> b) -> First a -> b Source #

foldrMap1' :: (a -> b) -> (a -> b -> b) -> First a -> b Source #

Applicative First Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

pure :: a -> First a Source #

(<*>) :: First (a -> b) -> First a -> First b Source #

liftA2 :: (a -> b -> c) -> First a -> First b -> First c Source #

(*>) :: First a -> First b -> First b Source #

(<*) :: First a -> First b -> First a Source #

Functor First Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

fmap :: (a -> b) -> First a -> First b Source #

(<$) :: a -> First b -> First a Source #

Monad First Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

(>>=) :: First a -> (a -> First b) -> First b Source #

(>>) :: First a -> First b -> First b Source #

return :: a -> First a Source #

MonadFix First Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

mfix :: (a -> First a) -> First a Source #

Foldable First Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

fold :: Monoid m => First m -> m Source #

foldMap :: Monoid m => (a -> m) -> First a -> m Source #

foldMap' :: Monoid m => (a -> m) -> First a -> m Source #

foldr :: (a -> b -> b) -> b -> First a -> b Source #

foldr' :: (a -> b -> b) -> b -> First a -> b Source #

foldl :: (b -> a -> b) -> b -> First a -> b Source #

foldl' :: (b -> a -> b) -> b -> First a -> b Source #

foldr1 :: (a -> a -> a) -> First a -> a Source #

foldl1 :: (a -> a -> a) -> First a -> a Source #

toList :: First a -> [a] Source #

null :: First a -> Bool Source #

length :: First a -> Int Source #

elem :: Eq a => a -> First a -> Bool Source #

maximum :: Ord a => First a -> a Source #

minimum :: Ord a => First a -> a Source #

sum :: Num a => First a -> a Source #

product :: Num a => First a -> a Source #

Traversable First Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

traverse :: Applicative f => (a -> f b) -> First a -> f (First b) Source #

sequenceA :: Applicative f => First (f a) -> f (First a) Source #

mapM :: Monad m => (a -> m b) -> First a -> m (First b) Source #

sequence :: Monad m => First (m a) -> m (First a) Source #

Generic1 First Source # 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep1 First

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep1 First = D1 ('MetaData "First" "Data.Semigroup" "base" 'True) (C1 ('MetaCons "First" 'PrefixI 'True) (S1 ('MetaSel ('Just "getFirst") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))

Methods

from1 :: First a -> Rep1 First a Source #

to1 :: Rep1 First a -> First a Source #

Semigroup (First a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

(<>) :: First a -> First a -> First a Source #

sconcat :: NonEmpty (First a) -> First a Source #

stimes :: Integral b => b -> First a -> First a Source #

Data a => Data (First a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> First a -> c (First a) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (First a) Source #

toConstr :: First a -> Constr Source #

dataTypeOf :: First a -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (First a)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (First a)) Source #

gmapT :: (forall b. Data b => b -> b) -> First a -> First a Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> First a -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> First a -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> First a -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> First a -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> First a -> m (First a) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> First a -> m (First a) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> First a -> m (First a) Source #

Bounded a => Bounded (First a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Enum a => Enum (First a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

succ :: First a -> First a Source #

pred :: First a -> First a Source #

toEnum :: Int -> First a Source #

fromEnum :: First a -> Int Source #

enumFrom :: First a -> [First a] Source #

enumFromThen :: First a -> First a -> [First a] Source #

enumFromTo :: First a -> First a -> [First a] Source #

enumFromThenTo :: First a -> First a -> First a -> [First a] Source #

Generic (First a) Source # 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (First a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep (First a) = D1 ('MetaData "First" "Data.Semigroup" "base" 'True) (C1 ('MetaCons "First" 'PrefixI 'True) (S1 ('MetaSel ('Just "getFirst") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Methods

from :: First a -> Rep (First a) x Source #

to :: Rep (First a) x -> First a Source #

Read a => Read (First a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Show a => Show (First a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Eq a => Eq (First a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

(==) :: First a -> First a -> Bool Source #

(/=) :: First a -> First a -> Bool Source #

Ord a => Ord (First a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

compare :: First a -> First a -> Ordering Source #

(<) :: First a -> First a -> Bool Source #

(<=) :: First a -> First a -> Bool Source #

(>) :: First a -> First a -> Bool Source #

(>=) :: First a -> First a -> Bool Source #

max :: First a -> First a -> First a Source #

min :: First a -> First a -> First a Source #

type Rep1 First Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep1 First = D1 ('MetaData "First" "Data.Semigroup" "base" 'True) (C1 ('MetaCons "First" 'PrefixI 'True) (S1 ('MetaSel ('Just "getFirst") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep (First a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep (First a) = D1 ('MetaData "First" "Data.Semigroup" "base" 'True) (C1 ('MetaCons "First" 'PrefixI 'True) (S1 ('MetaSel ('Just "getFirst") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

newtype Last a Source #

Beware that Data.Semigroup.Last is different from Data.Monoid.Last. The former simply returns the last value, so x <> Data.Semigroup.Last Nothing = Data.Semigroup.Last Nothing. The latter returns the last non-Nothing, thus x <> Data.Monoid.Last Nothing = x.

Examples

Expand
>>> Last 0 <> Last 10
Last {getLast = 10}
>>> sconcat $ Last 1 :| [ Last n | n <- [2..]]
Last {getLast = * hangs forever *

Constructors

Last 

Fields

Instances

Instances details
Foldable1 Last Source #

Since: base-4.18.0.0

Instance details

Defined in Data.Foldable1

Methods

fold1 :: Semigroup m => Last m -> m Source #

foldMap1 :: Semigroup m => (a -> m) -> Last a -> m Source #

foldMap1' :: Semigroup m => (a -> m) -> Last a -> m Source #

toNonEmpty :: Last a -> NonEmpty a Source #

maximum :: Ord a => Last a -> a Source #

minimum :: Ord a => Last a -> a Source #

head :: Last a -> a Source #

last :: Last a -> a Source #

foldrMap1 :: (a -> b) -> (a -> b -> b) -> Last a -> b Source #

foldlMap1' :: (a -> b) -> (b -> a -> b) -> Last a -> b Source #

foldlMap1 :: (a -> b) -> (b -> a -> b) -> Last a -> b Source #

foldrMap1' :: (a -> b) -> (a -> b -> b) -> Last a -> b Source #

Applicative Last Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

pure :: a -> Last a Source #

(<*>) :: Last (a -> b) -> Last a -> Last b Source #

liftA2 :: (a -> b -> c) -> Last a -> Last b -> Last c Source #

(*>) :: Last a -> Last b -> Last b Source #

(<*) :: Last a -> Last b -> Last a Source #

Functor Last Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

fmap :: (a -> b) -> Last a -> Last b Source #

(<$) :: a -> Last b -> Last a Source #

Monad Last Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

(>>=) :: Last a -> (a -> Last b) -> Last b Source #

(>>) :: Last a -> Last b -> Last b Source #

return :: a -> Last a Source #

MonadFix Last Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

mfix :: (a -> Last a) -> Last a Source #

Foldable Last Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

fold :: Monoid m => Last m -> m Source #

foldMap :: Monoid m => (a -> m) -> Last a -> m Source #

foldMap' :: Monoid m => (a -> m) -> Last a -> m Source #

foldr :: (a -> b -> b) -> b -> Last a -> b Source #

foldr' :: (a -> b -> b) -> b -> Last a -> b Source #

foldl :: (b -> a -> b) -> b -> Last a -> b Source #

foldl' :: (b -> a -> b) -> b -> Last a -> b Source #

foldr1 :: (a -> a -> a) -> Last a -> a Source #

foldl1 :: (a -> a -> a) -> Last a -> a Source #

toList :: Last a -> [a] Source #

null :: Last a -> Bool Source #

length :: Last a -> Int Source #

elem :: Eq a => a -> Last a -> Bool Source #

maximum :: Ord a => Last a -> a Source #

minimum :: Ord a => Last a -> a Source #

sum :: Num a => Last a -> a Source #

product :: Num a => Last a -> a Source #

Traversable Last Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

traverse :: Applicative f => (a -> f b) -> Last a -> f (Last b) Source #

sequenceA :: Applicative f => Last (f a) -> f (Last a) Source #

mapM :: Monad m => (a -> m b) -> Last a -> m (Last b) Source #

sequence :: Monad m => Last (m a) -> m (Last a) Source #

Generic1 Last Source # 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep1 Last

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep1 Last = D1 ('MetaData "Last" "Data.Semigroup" "base" 'True) (C1 ('MetaCons "Last" 'PrefixI 'True) (S1 ('MetaSel ('Just "getLast") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))

Methods

from1 :: Last a -> Rep1 Last a Source #

to1 :: Rep1 Last a -> Last a Source #

Semigroup (Last a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

(<>) :: Last a -> Last a -> Last a Source #

sconcat :: NonEmpty (Last a) -> Last a Source #

stimes :: Integral b => b -> Last a -> Last a Source #

Data a => Data (Last a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Last a -> c (Last a) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Last a) Source #

toConstr :: Last a -> Constr Source #

dataTypeOf :: Last a -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Last a)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Last a)) Source #

gmapT :: (forall b. Data b => b -> b) -> Last a -> Last a Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Last a -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Last a -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Last a -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Last a -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Last a -> m (Last a) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Last a -> m (Last a) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Last a -> m (Last a) Source #

Bounded a => Bounded (Last a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Enum a => Enum (Last a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

succ :: Last a -> Last a Source #

pred :: Last a -> Last a Source #

toEnum :: Int -> Last a Source #

fromEnum :: Last a -> Int Source #

enumFrom :: Last a -> [Last a] Source #

enumFromThen :: Last a -> Last a -> [Last a] Source #

enumFromTo :: Last a -> Last a -> [Last a] Source #

enumFromThenTo :: Last a -> Last a -> Last a -> [Last a] Source #

Generic (Last a) Source # 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Last a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep (Last a) = D1 ('MetaData "Last" "Data.Semigroup" "base" 'True) (C1 ('MetaCons "Last" 'PrefixI 'True) (S1 ('MetaSel ('Just "getLast") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Methods

from :: Last a -> Rep (Last a) x Source #

to :: Rep (Last a) x -> Last a Source #

Read a => Read (Last a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Show a => Show (Last a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

showsPrec :: Int -> Last a -> ShowS Source #

show :: Last a -> String Source #

showList :: [Last a] -> ShowS Source #

Eq a => Eq (Last a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

(==) :: Last a -> Last a -> Bool Source #

(/=) :: Last a -> Last a -> Bool Source #

Ord a => Ord (Last a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

compare :: Last a -> Last a -> Ordering Source #

(<) :: Last a -> Last a -> Bool Source #

(<=) :: Last a -> Last a -> Bool Source #

(>) :: Last a -> Last a -> Bool Source #

(>=) :: Last a -> Last a -> Bool Source #

max :: Last a -> Last a -> Last a Source #

min :: Last a -> Last a -> Last a Source #

type Rep1 Last Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep1 Last = D1 ('MetaData "Last" "Data.Semigroup" "base" 'True) (C1 ('MetaCons "Last" 'PrefixI 'True) (S1 ('MetaSel ('Just "getLast") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep (Last a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep (Last a) = D1 ('MetaData "Last" "Data.Semigroup" "base" 'True) (C1 ('MetaCons "Last" 'PrefixI 'True) (S1 ('MetaSel ('Just "getLast") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

newtype WrappedMonoid m Source #

Provide a Semigroup for an arbitrary Monoid.

NOTE: This is not needed anymore since Semigroup became a superclass of Monoid in base-4.11 and this newtype be deprecated at some point in the future.

Constructors

WrapMonoid 

Fields

Instances

Instances details
Generic1 WrappedMonoid Source # 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep1 WrappedMonoid

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep1 WrappedMonoid = D1 ('MetaData "WrappedMonoid" "Data.Semigroup" "base" 'True) (C1 ('MetaCons "WrapMonoid" 'PrefixI 'True) (S1 ('MetaSel ('Just "unwrapMonoid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
Monoid m => Monoid (WrappedMonoid m) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Monoid m => Semigroup (WrappedMonoid m) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Data m => Data (WrappedMonoid m) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WrappedMonoid m -> c (WrappedMonoid m) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WrappedMonoid m) Source #

toConstr :: WrappedMonoid m -> Constr Source #

dataTypeOf :: WrappedMonoid m -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WrappedMonoid m)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WrappedMonoid m)) Source #

gmapT :: (forall b. Data b => b -> b) -> WrappedMonoid m -> WrappedMonoid m Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WrappedMonoid m -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WrappedMonoid m -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> WrappedMonoid m -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WrappedMonoid m -> u Source #

gmapM :: Monad m0 => (forall d. Data d => d -> m0 d) -> WrappedMonoid m -> m0 (WrappedMonoid m) Source #

gmapMp :: MonadPlus m0 => (forall d. Data d => d -> m0 d) -> WrappedMonoid m -> m0 (WrappedMonoid m) Source #

gmapMo :: MonadPlus m0 => (forall d. Data d => d -> m0 d) -> WrappedMonoid m -> m0 (WrappedMonoid m) Source #

Bounded m => Bounded (WrappedMonoid m) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Enum a => Enum (WrappedMonoid a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Generic (WrappedMonoid m) Source # 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (WrappedMonoid m)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep (WrappedMonoid m) = D1 ('MetaData "WrappedMonoid" "Data.Semigroup" "base" 'True) (C1 ('MetaCons "WrapMonoid" 'PrefixI 'True) (S1 ('MetaSel ('Just "unwrapMonoid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 m)))
Read m => Read (WrappedMonoid m) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Show m => Show (WrappedMonoid m) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Eq m => Eq (WrappedMonoid m) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Ord m => Ord (WrappedMonoid m) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep1 WrappedMonoid Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep1 WrappedMonoid = D1 ('MetaData "WrappedMonoid" "Data.Semigroup" "base" 'True) (C1 ('MetaCons "WrapMonoid" 'PrefixI 'True) (S1 ('MetaSel ('Just "unwrapMonoid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep (WrappedMonoid m) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep (WrappedMonoid m) = D1 ('MetaData "WrappedMonoid" "Data.Semigroup" "base" 'True) (C1 ('MetaCons "WrapMonoid" 'PrefixI 'True) (S1 ('MetaSel ('Just "unwrapMonoid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 m)))

Re-exported monoids from GHC.Internal.Data.Monoid

newtype Dual a Source #

The dual of a Monoid, obtained by swapping the arguments of (<>).

Dual a <> Dual b == Dual (b <> a)

Examples

Expand
>>> Dual "Hello" <> Dual "World"
Dual {getDual = "WorldHello"}
>>> Dual (Dual "Hello") <> Dual (Dual "World")
Dual {getDual = Dual {getDual = "HelloWorld"}}

Constructors

Dual 

Fields

Instances

Instances details
MonadZip Dual Source #

Since: base-4.8.0.0

Instance details

Defined in Control.Monad.Zip

Methods

mzip :: Dual a -> Dual b -> Dual (a, b) Source #

mzipWith :: (a -> b -> c) -> Dual a -> Dual b -> Dual c Source #

munzip :: Dual (a, b) -> (Dual a, Dual b) Source #

Foldable1 Dual Source #

Since: base-4.18.0.0

Instance details

Defined in Data.Foldable1

Methods

fold1 :: Semigroup m => Dual m -> m Source #

foldMap1 :: Semigroup m => (a -> m) -> Dual a -> m Source #

foldMap1' :: Semigroup m => (a -> m) -> Dual a -> m Source #

toNonEmpty :: Dual a -> NonEmpty a Source #

maximum :: Ord a => Dual a -> a Source #

minimum :: Ord a => Dual a -> a Source #

head :: Dual a -> a Source #

last :: Dual a -> a Source #

foldrMap1 :: (a -> b) -> (a -> b -> b) -> Dual a -> b Source #

foldlMap1' :: (a -> b) -> (b -> a -> b) -> Dual a -> b Source #

foldlMap1 :: (a -> b) -> (b -> a -> b) -> Dual a -> b Source #

foldrMap1' :: (a -> b) -> (a -> b -> b) -> Dual a -> b Source #

Applicative Dual

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

pure :: a -> Dual a Source #

(<*>) :: Dual (a -> b) -> Dual a -> Dual b Source #

liftA2 :: (a -> b -> c) -> Dual a -> Dual b -> Dual c Source #

(*>) :: Dual a -> Dual b -> Dual b Source #

(<*) :: Dual a -> Dual b -> Dual a Source #

Functor Dual

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

fmap :: (a -> b) -> Dual a -> Dual b Source #

(<$) :: a -> Dual b -> Dual a Source #

Monad Dual

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(>>=) :: Dual a -> (a -> Dual b) -> Dual b Source #

(>>) :: Dual a -> Dual b -> Dual b Source #

return :: a -> Dual a Source #

MonadFix Dual

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Control.Monad.Fix

Methods

mfix :: (a -> Dual a) -> Dual a Source #

Foldable Dual

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Foldable

Methods

fold :: Monoid m => Dual m -> m Source #

foldMap :: Monoid m => (a -> m) -> Dual a -> m Source #

foldMap' :: Monoid m => (a -> m) -> Dual a -> m Source #

foldr :: (a -> b -> b) -> b -> Dual a -> b Source #

foldr' :: (a -> b -> b) -> b -> Dual a -> b Source #

foldl :: (b -> a -> b) -> b -> Dual a -> b Source #

foldl' :: (b -> a -> b) -> b -> Dual a -> b Source #

foldr1 :: (a -> a -> a) -> Dual a -> a Source #

foldl1 :: (a -> a -> a) -> Dual a -> a Source #

toList :: Dual a -> [a] Source #

null :: Dual a -> Bool Source #

length :: Dual a -> Int Source #

elem :: Eq a => a -> Dual a -> Bool Source #

maximum :: Ord a => Dual a -> a Source #

minimum :: Ord a => Dual a -> a Source #

sum :: Num a => Dual a -> a Source #

product :: Num a => Dual a -> a Source #

Traversable Dual

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Dual a -> f (Dual b) Source #

sequenceA :: Applicative f => Dual (f a) -> f (Dual a) Source #

mapM :: Monad m => (a -> m b) -> Dual a -> m (Dual b) Source #

sequence :: Monad m => Dual (m a) -> m (Dual a) Source #

Generic1 Dual 
Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Associated Types

type Rep1 Dual

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

type Rep1 Dual = D1 ('MetaData "Dual" "GHC.Internal.Data.Semigroup.Internal" "ghc-internal" 'True) (C1 ('MetaCons "Dual" 'PrefixI 'True) (S1 ('MetaSel ('Just "getDual") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))

Methods

from1 :: Dual a -> Rep1 Dual a Source #

to1 :: Rep1 Dual a -> Dual a Source #

Monoid a => Monoid (Dual a)

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

mempty :: Dual a Source #

mappend :: Dual a -> Dual a -> Dual a Source #

mconcat :: [Dual a] -> Dual a Source #

Semigroup a => Semigroup (Dual a)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(<>) :: Dual a -> Dual a -> Dual a Source #

sconcat :: NonEmpty (Dual a) -> Dual a Source #

stimes :: Integral b => b -> Dual a -> Dual a Source #

Data a => Data (Dual a)

@since base-4.8.0.0

Instance details

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) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Dual a) Source #

toConstr :: Dual a -> Constr Source #

dataTypeOf :: Dual a -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Dual a)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Dual a)) Source #

gmapT :: (forall b. Data b => b -> b) -> Dual a -> Dual a Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Dual a -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Dual a -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Dual a -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Dual a -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Dual a -> m (Dual a) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Dual a -> m (Dual a) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Dual a -> m (Dual a) Source #

Bounded a => Bounded (Dual a)

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Generic (Dual a) 
Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Associated Types

type Rep (Dual a)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

type Rep (Dual a) = D1 ('MetaData "Dual" "GHC.Internal.Data.Semigroup.Internal" "ghc-internal" 'True) (C1 ('MetaCons "Dual" 'PrefixI 'True) (S1 ('MetaSel ('Just "getDual") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Methods

from :: Dual a -> Rep (Dual a) x Source #

to :: Rep (Dual a) x -> Dual a Source #

Read a => Read (Dual a)

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Show a => Show (Dual a)

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

showsPrec :: Int -> Dual a -> ShowS Source #

show :: Dual a -> String Source #

showList :: [Dual a] -> ShowS Source #

Eq a => Eq (Dual a)

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(==) :: Dual a -> Dual a -> Bool Source #

(/=) :: Dual a -> Dual a -> Bool Source #

Ord a => Ord (Dual a)

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

compare :: Dual a -> Dual a -> Ordering Source #

(<) :: Dual a -> Dual a -> Bool Source #

(<=) :: Dual a -> Dual a -> Bool Source #

(>) :: Dual a -> Dual a -> Bool Source #

(>=) :: Dual a -> Dual a -> Bool Source #

max :: Dual a -> Dual a -> Dual a Source #

min :: Dual a -> Dual a -> Dual a Source #

type Rep1 Dual

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

type Rep1 Dual = D1 ('MetaData "Dual" "GHC.Internal.Data.Semigroup.Internal" "ghc-internal" 'True) (C1 ('MetaCons "Dual" 'PrefixI 'True) (S1 ('MetaSel ('Just "getDual") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep (Dual a)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

type Rep (Dual a) = D1 ('MetaData "Dual" "GHC.Internal.Data.Semigroup.Internal" "ghc-internal" 'True) (C1 ('MetaCons "Dual" 'PrefixI 'True) (S1 ('MetaSel ('Just "getDual") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

newtype Endo a Source #

The monoid of endomorphisms under composition.

Endo f <> Endo g == Endo (f . g)

Examples

Expand
>>> let computation = Endo ("Hello, " ++) <> Endo (++ "!")
>>> appEndo computation "Haskell"
"Hello, Haskell!"
>>> let computation = Endo (*3) <> Endo (+1)
>>> appEndo computation 1
6

Constructors

Endo 

Fields

Instances

Instances details
Monoid (Endo a)

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

mempty :: Endo a Source #

mappend :: Endo a -> Endo a -> Endo a Source #

mconcat :: [Endo a] -> Endo a Source #

Semigroup (Endo a)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(<>) :: Endo a -> Endo a -> Endo a Source #

sconcat :: NonEmpty (Endo a) -> Endo a Source #

stimes :: Integral b => b -> Endo a -> Endo a Source #

Generic (Endo a) 
Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Associated Types

type Rep (Endo a)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

type Rep (Endo a) = D1 ('MetaData "Endo" "GHC.Internal.Data.Semigroup.Internal" "ghc-internal" 'True) (C1 ('MetaCons "Endo" 'PrefixI 'True) (S1 ('MetaSel ('Just "appEndo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (a -> a))))

Methods

from :: Endo a -> Rep (Endo a) x Source #

to :: Rep (Endo a) x -> Endo a Source #

type Rep (Endo a)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

type Rep (Endo a) = D1 ('MetaData "Endo" "GHC.Internal.Data.Semigroup.Internal" "ghc-internal" 'True) (C1 ('MetaCons "Endo" 'PrefixI 'True) (S1 ('MetaSel ('Just "appEndo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (a -> a))))

newtype All Source #

Boolean monoid under conjunction (&&).

All x <> All y = All (x && y)

Examples

Expand
>>> 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}

Constructors

All 

Fields

Instances

Instances details
Monoid All

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Semigroup All

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(<>) :: All -> All -> All Source #

sconcat :: NonEmpty All -> All Source #

stimes :: Integral b => b -> All -> All Source #

Data All

@since base-4.8.0.0

Instance details

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 Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c All Source #

toConstr :: All -> Constr Source #

dataTypeOf :: All -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c All) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c All) Source #

gmapT :: (forall b. Data b => b -> b) -> All -> All Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> All -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> All -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> All -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> All -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> All -> m All Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> All -> m All Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> All -> m All Source #

Bounded All

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Generic All 
Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Associated Types

type Rep All

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

type Rep All = D1 ('MetaData "All" "GHC.Internal.Data.Semigroup.Internal" "ghc-internal" 'True) (C1 ('MetaCons "All" 'PrefixI 'True) (S1 ('MetaSel ('Just "getAll") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))

Methods

from :: All -> Rep All x Source #

to :: Rep All x -> All Source #

Read All

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Show All

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Eq All

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(==) :: All -> All -> Bool Source #

(/=) :: All -> All -> Bool Source #

Ord All

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

compare :: All -> All -> Ordering Source #

(<) :: All -> All -> Bool Source #

(<=) :: All -> All -> Bool Source #

(>) :: All -> All -> Bool Source #

(>=) :: All -> All -> Bool Source #

max :: All -> All -> All Source #

min :: All -> All -> All Source #

type Rep All

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

type Rep All = D1 ('MetaData "All" "GHC.Internal.Data.Semigroup.Internal" "ghc-internal" 'True) (C1 ('MetaCons "All" 'PrefixI 'True) (S1 ('MetaSel ('Just "getAll") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))

newtype Any Source #

Boolean monoid under disjunction (||).

Any x <> Any y = Any (x || y)

Examples

Expand
>>> 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}

Constructors

Any 

Fields

Instances

Instances details
Monoid Any

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Semigroup Any

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(<>) :: Any -> Any -> Any Source #

sconcat :: NonEmpty Any -> Any Source #

stimes :: Integral b => b -> Any -> Any Source #

Data Any

@since base-4.8.0.0

Instance details

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 Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Any Source #

toConstr :: Any -> Constr Source #

dataTypeOf :: Any -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Any) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Any) Source #

gmapT :: (forall b. Data b => b -> b) -> Any -> Any Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Any -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Any -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Any -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Any -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Any -> m Any Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Any -> m Any Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Any -> m Any Source #

Bounded Any

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Generic Any 
Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Associated Types

type Rep Any

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

type Rep Any = D1 ('MetaData "Any" "GHC.Internal.Data.Semigroup.Internal" "ghc-internal" 'True) (C1 ('MetaCons "Any" 'PrefixI 'True) (S1 ('MetaSel ('Just "getAny") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))

Methods

from :: Any -> Rep Any x Source #

to :: Rep Any x -> Any Source #

Read Any

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Show Any

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Eq Any

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(==) :: Any -> Any -> Bool Source #

(/=) :: Any -> Any -> Bool Source #

Ord Any

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

compare :: Any -> Any -> Ordering Source #

(<) :: Any -> Any -> Bool Source #

(<=) :: Any -> Any -> Bool Source #

(>) :: Any -> Any -> Bool Source #

(>=) :: Any -> Any -> Bool Source #

max :: Any -> Any -> Any Source #

min :: Any -> Any -> Any Source #

type Rep Any

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

type Rep Any = D1 ('MetaData "Any" "GHC.Internal.Data.Semigroup.Internal" "ghc-internal" 'True) (C1 ('MetaCons "Any" 'PrefixI 'True) (S1 ('MetaSel ('Just "getAny") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))

newtype Sum a Source #

Monoid under addition.

Sum a <> Sum b = Sum (a + b)

Examples

Expand
>>> Sum 1 <> Sum 2 <> mempty
Sum {getSum = 3}
>>> mconcat [ Sum n | n <- [3 .. 9]]
Sum {getSum = 42}

Constructors

Sum 

Fields

Instances

Instances details
MonadZip Sum Source #

Since: base-4.8.0.0

Instance details

Defined in Control.Monad.Zip

Methods

mzip :: Sum a -> Sum b -> Sum (a, b) Source #

mzipWith :: (a -> b -> c) -> Sum a -> Sum b -> Sum c Source #

munzip :: Sum (a, b) -> (Sum a, Sum b) Source #

Foldable1 Sum Source #

Since: base-4.18.0.0

Instance details

Defined in Data.Foldable1

Methods

fold1 :: Semigroup m => Sum m -> m Source #

foldMap1 :: Semigroup m => (a -> m) -> Sum a -> m Source #

foldMap1' :: Semigroup m => (a -> m) -> Sum a -> m Source #

toNonEmpty :: Sum a -> NonEmpty a Source #

maximum :: Ord a => Sum a -> a Source #

minimum :: Ord a => Sum a -> a Source #

head :: Sum a -> a Source #

last :: Sum a -> a Source #

foldrMap1 :: (a -> b) -> (a -> b -> b) -> Sum a -> b Source #

foldlMap1' :: (a -> b) -> (b -> a -> b) -> Sum a -> b Source #

foldlMap1 :: (a -> b) -> (b -> a -> b) -> Sum a -> b Source #

foldrMap1' :: (a -> b) -> (a -> b -> b) -> Sum a -> b Source #

Applicative Sum

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

pure :: a -> Sum a Source #

(<*>) :: Sum (a -> b) -> Sum a -> Sum b Source #

liftA2 :: (a -> b -> c) -> Sum a -> Sum b -> Sum c Source #

(*>) :: Sum a -> Sum b -> Sum b Source #

(<*) :: Sum a -> Sum b -> Sum a Source #

Functor Sum

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

fmap :: (a -> b) -> Sum a -> Sum b Source #

(<$) :: a -> Sum b -> Sum a Source #

Monad Sum

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(>>=) :: Sum a -> (a -> Sum b) -> Sum b Source #

(>>) :: Sum a -> Sum b -> Sum b Source #

return :: a -> Sum a Source #

MonadFix Sum

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Control.Monad.Fix

Methods

mfix :: (a -> Sum a) -> Sum a Source #

Foldable Sum

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Foldable

Methods

fold :: Monoid m => Sum m -> m Source #

foldMap :: Monoid m => (a -> m) -> Sum a -> m Source #

foldMap' :: Monoid m => (a -> m) -> Sum a -> m Source #

foldr :: (a -> b -> b) -> b -> Sum a -> b Source #

foldr' :: (a -> b -> b) -> b -> Sum a -> b Source #

foldl :: (b -> a -> b) -> b -> Sum a -> b Source #

foldl' :: (b -> a -> b) -> b -> Sum a -> b Source #

foldr1 :: (a -> a -> a) -> Sum a -> a Source #

foldl1 :: (a -> a -> a) -> Sum a -> a Source #

toList :: Sum a -> [a] Source #

null :: Sum a -> Bool Source #

length :: Sum a -> Int Source #

elem :: Eq a => a -> Sum a -> Bool Source #

maximum :: Ord a => Sum a -> a Source #

minimum :: Ord a => Sum a -> a Source #

sum :: Num a => Sum a -> a Source #

product :: Num a => Sum a -> a Source #

Traversable Sum

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Sum a -> f (Sum b) Source #

sequenceA :: Applicative f => Sum (f a) -> f (Sum a) Source #

mapM :: Monad m => (a -> m b) -> Sum a -> m (Sum b) Source #

sequence :: Monad m => Sum (m a) -> m (Sum a) Source #

Generic1 Sum 
Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Associated Types

type Rep1 Sum

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

type Rep1 Sum = D1 ('MetaData "Sum" "GHC.Internal.Data.Semigroup.Internal" "ghc-internal" 'True) (C1 ('MetaCons "Sum" 'PrefixI 'True) (S1 ('MetaSel ('Just "getSum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))

Methods

from1 :: Sum a -> Rep1 Sum a Source #

to1 :: Rep1 Sum a -> Sum a Source #

Num a => Monoid (Sum a)

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

mempty :: Sum a Source #

mappend :: Sum a -> Sum a -> Sum a Source #

mconcat :: [Sum a] -> Sum a Source #

Num a => Semigroup (Sum a)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(<>) :: Sum a -> Sum a -> Sum a Source #

sconcat :: NonEmpty (Sum a) -> Sum a Source #

stimes :: Integral b => b -> Sum a -> Sum a Source #

Data a => Data (Sum a)

@since base-4.8.0.0

Instance details

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) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Sum a) Source #

toConstr :: Sum a -> Constr Source #

dataTypeOf :: Sum a -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Sum a)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Sum a)) Source #

gmapT :: (forall b. Data b => b -> b) -> Sum a -> Sum a Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sum a -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sum a -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Sum a -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Sum a -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Sum a -> m (Sum a) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Sum a -> m (Sum a) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Sum a -> m (Sum a) Source #

Bounded a => Bounded (Sum a)

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Generic (Sum a) 
Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Associated Types

type Rep (Sum a)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

type Rep (Sum a) = D1 ('MetaData "Sum" "GHC.Internal.Data.Semigroup.Internal" "ghc-internal" 'True) (C1 ('MetaCons "Sum" 'PrefixI 'True) (S1 ('MetaSel ('Just "getSum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Methods

from :: Sum a -> Rep (Sum a) x Source #

to :: Rep (Sum a) x -> Sum a Source #

Num a => Num (Sum a)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(+) :: Sum a -> Sum a -> Sum a Source #

(-) :: Sum a -> Sum a -> Sum a Source #

(*) :: Sum a -> Sum a -> Sum a Source #

negate :: Sum a -> Sum a Source #

abs :: Sum a -> Sum a Source #

signum :: Sum a -> Sum a Source #

fromInteger :: Integer -> Sum a Source #

Read a => Read (Sum a)

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Show a => Show (Sum a)

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

showsPrec :: Int -> Sum a -> ShowS Source #

show :: Sum a -> String Source #

showList :: [Sum a] -> ShowS Source #

Eq a => Eq (Sum a)

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(==) :: Sum a -> Sum a -> Bool Source #

(/=) :: Sum a -> Sum a -> Bool Source #

Ord a => Ord (Sum a)

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

compare :: Sum a -> Sum a -> Ordering Source #

(<) :: Sum a -> Sum a -> Bool Source #

(<=) :: Sum a -> Sum a -> Bool Source #

(>) :: Sum a -> Sum a -> Bool Source #

(>=) :: Sum a -> Sum a -> Bool Source #

max :: Sum a -> Sum a -> Sum a Source #

min :: Sum a -> Sum a -> Sum a Source #

type Rep1 Sum

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

type Rep1 Sum = D1 ('MetaData "Sum" "GHC.Internal.Data.Semigroup.Internal" "ghc-internal" 'True) (C1 ('MetaCons "Sum" 'PrefixI 'True) (S1 ('MetaSel ('Just "getSum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep (Sum a)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

type Rep (Sum a) = D1 ('MetaData "Sum" "GHC.Internal.Data.Semigroup.Internal" "ghc-internal" 'True) (C1 ('MetaCons "Sum" 'PrefixI 'True) (S1 ('MetaSel ('Just "getSum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

newtype Product a Source #

Monoid under multiplication.

Product x <> Product y == Product (x * y)

Examples

Expand
>>> Product 3 <> Product 4 <> mempty
Product {getProduct = 12}
>>> mconcat [ Product n | n <- [2 .. 10]]
Product {getProduct = 3628800}

Constructors

Product 

Fields

Instances

Instances details
MonadZip Product Source #

Since: base-4.8.0.0

Instance details

Defined in Control.Monad.Zip

Methods

mzip :: Product a -> Product b -> Product (a, b) Source #

mzipWith :: (a -> b -> c) -> Product a -> Product b -> Product c Source #

munzip :: Product (a, b) -> (Product a, Product b) Source #

Foldable1 Product Source #

Since: base-4.18.0.0

Instance details

Defined in Data.Foldable1

Methods

fold1 :: Semigroup m => Product m -> m Source #

foldMap1 :: Semigroup m => (a -> m) -> Product a -> m Source #

foldMap1' :: Semigroup m => (a -> m) -> Product a -> m Source #

toNonEmpty :: Product a -> NonEmpty a Source #

maximum :: Ord a => Product a -> a Source #

minimum :: Ord a => Product a -> a Source #

head :: Product a -> a Source #

last :: Product a -> a Source #

foldrMap1 :: (a -> b) -> (a -> b -> b) -> Product a -> b Source #

foldlMap1' :: (a -> b) -> (b -> a -> b) -> Product a -> b Source #

foldlMap1 :: (a -> b) -> (b -> a -> b) -> Product a -> b Source #

foldrMap1' :: (a -> b) -> (a -> b -> b) -> Product a -> b Source #

Applicative Product

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

pure :: a -> Product a Source #

(<*>) :: Product (a -> b) -> Product a -> Product b Source #

liftA2 :: (a -> b -> c) -> Product a -> Product b -> Product c Source #

(*>) :: Product a -> Product b -> Product b Source #

(<*) :: Product a -> Product b -> Product a Source #

Functor Product

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

fmap :: (a -> b) -> Product a -> Product b Source #

(<$) :: a -> Product b -> Product a Source #

Monad Product

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(>>=) :: Product a -> (a -> Product b) -> Product b Source #

(>>) :: Product a -> Product b -> Product b Source #

return :: a -> Product a Source #

MonadFix Product

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Control.Monad.Fix

Methods

mfix :: (a -> Product a) -> Product a Source #

Foldable Product

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Foldable

Methods

fold :: Monoid m => Product m -> m Source #

foldMap :: Monoid m => (a -> m) -> Product a -> m Source #

foldMap' :: Monoid m => (a -> m) -> Product a -> m Source #

foldr :: (a -> b -> b) -> b -> Product a -> b Source #

foldr' :: (a -> b -> b) -> b -> Product a -> b Source #

foldl :: (b -> a -> b) -> b -> Product a -> b Source #

foldl' :: (b -> a -> b) -> b -> Product a -> b Source #

foldr1 :: (a -> a -> a) -> Product a -> a Source #

foldl1 :: (a -> a -> a) -> Product a -> a Source #

toList :: Product a -> [a] Source #

null :: Product a -> Bool Source #

length :: Product a -> Int Source #

elem :: Eq a => a -> Product a -> Bool Source #

maximum :: Ord a => Product a -> a Source #

minimum :: Ord a => Product a -> a Source #

sum :: Num a => Product a -> a Source #

product :: Num a => Product a -> a Source #

Traversable Product

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Product a -> f (Product b) Source #

sequenceA :: Applicative f => Product (f a) -> f (Product a) Source #

mapM :: Monad m => (a -> m b) -> Product a -> m (Product b) Source #

sequence :: Monad m => Product (m a) -> m (Product a) Source #

Generic1 Product 
Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Associated Types

type Rep1 Product

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

type Rep1 Product = D1 ('MetaData "Product" "GHC.Internal.Data.Semigroup.Internal" "ghc-internal" 'True) (C1 ('MetaCons "Product" 'PrefixI 'True) (S1 ('MetaSel ('Just "getProduct") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
Num a => Monoid (Product a)

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Num a => Semigroup (Product a)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(<>) :: Product a -> Product a -> Product a Source #

sconcat :: NonEmpty (Product a) -> Product a Source #

stimes :: Integral b => b -> Product a -> Product a Source #

Data a => Data (Product a)

@since base-4.8.0.0

Instance details

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) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Product a) Source #

toConstr :: Product a -> Constr Source #

dataTypeOf :: Product a -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Product a)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Product a)) Source #

gmapT :: (forall b. Data b => b -> b) -> Product a -> Product a Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Product a -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Product a -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Product a -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Product a -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Product a -> m (Product a) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Product a -> m (Product a) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Product a -> m (Product a) Source #

Bounded a => Bounded (Product a)

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Generic (Product a) 
Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Associated Types

type Rep (Product a)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

type Rep (Product a) = D1 ('MetaData "Product" "GHC.Internal.Data.Semigroup.Internal" "ghc-internal" 'True) (C1 ('MetaCons "Product" 'PrefixI 'True) (S1 ('MetaSel ('Just "getProduct") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Methods

from :: Product a -> Rep (Product a) x Source #

to :: Rep (Product a) x -> Product a Source #

Num a => Num (Product a)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Read a => Read (Product a)

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Show a => Show (Product a)

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Eq a => Eq (Product a)

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(==) :: Product a -> Product a -> Bool Source #

(/=) :: Product a -> Product a -> Bool Source #

Ord a => Ord (Product a)

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

type Rep1 Product

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

type Rep1 Product = D1 ('MetaData "Product" "GHC.Internal.Data.Semigroup.Internal" "ghc-internal" 'True) (C1 ('MetaCons "Product" 'PrefixI 'True) (S1 ('MetaSel ('Just "getProduct") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep (Product a)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

type Rep (Product a) = D1 ('MetaData "Product" "GHC.Internal.Data.Semigroup.Internal" "ghc-internal" 'True) (C1 ('MetaCons "Product" 'PrefixI 'True) (S1 ('MetaSel ('Just "getProduct") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Difference lists of a semigroup

diff :: Semigroup m => m -> Endo m Source #

This lets you use a difference list of a Semigroup as a Monoid.

Examples

Expand
let hello = diff "Hello, "
>>> appEndo hello "World!"
"Hello, World!"
>>> appEndo (hello <> mempty) "World!"
"Hello, World!"
>>> appEndo (mempty <> hello) "World!"
"Hello, World!"
let world = diff "World"
let excl = diff "!"
>>> appEndo (hello <> (world <> excl)) mempty
"Hello, World!"
>>> appEndo ((hello <> world) <> excl) mempty
"Hello, World!"

cycle1 :: Semigroup m => m -> m Source #

A generalization of cycle to an arbitrary Semigroup. May fail to terminate for some values in some semigroups.

Examples

Expand
>>> take 10 $ cycle1 [1, 2, 3]
[1,2,3,1,2,3,1,2,3,1]
>>> cycle1 (Right 1)
Right 1
>>> cycle1 (Left 1)
* hangs forever *

ArgMin, ArgMax

data Arg a b Source #

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.

Examples

Expand
>>> minimum [ Arg (x * x) x | x <- [-10 .. 10] ]
Arg 0 0
>>> maximum [ Arg (-0.2*x^2 + 1.5*x + 1) x | x <- [-10 .. 10] ]
Arg 3.8 4.0
>>> minimum [ Arg (-0.2*x^2 + 1.5*x + 1) x | x <- [-10 .. 10] ]
Arg (-34.0) (-10.0)

Constructors

Arg 

Fields

  • a

    The argument used for comparisons in Eq and Ord.

  • b

    The "value" exposed via the Functor, Foldable etc. instances.

Instances

Instances details
Bifoldable Arg Source #

Since: base-4.10.0.0

Instance details

Defined in Data.Semigroup

Methods

bifold :: Monoid m => Arg m m -> m Source #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Arg a b -> m Source #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Arg a b -> c Source #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Arg a b -> c Source #

Bifoldable1 Arg Source # 
Instance details

Defined in Data.Bifoldable1

Methods

bifold1 :: Semigroup m => Arg m m -> m Source #

bifoldMap1 :: Semigroup m => (a -> m) -> (b -> m) -> Arg a b -> m Source #

Bifunctor Arg Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

bimap :: (a -> b) -> (c -> d) -> Arg a c -> Arg b d Source #

first :: (a -> b) -> Arg a c -> Arg b c Source #

second :: (b -> c) -> Arg a b -> Arg a c Source #

Bitraversable Arg Source #

Since: base-4.10.0.0

Instance details

Defined in Data.Semigroup

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Arg a b -> f (Arg c d) Source #

Generic1 (Arg a :: Type -> Type) Source # 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep1 (Arg a :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

from1 :: Arg a a0 -> Rep1 (Arg a) a0 Source #

to1 :: Rep1 (Arg a) a0 -> Arg a a0 Source #

Functor (Arg a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

fmap :: (a0 -> b) -> Arg a a0 -> Arg a b Source #

(<$) :: a0 -> Arg a b -> Arg a a0 Source #

Foldable (Arg a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

fold :: Monoid m => Arg a m -> m Source #

foldMap :: Monoid m => (a0 -> m) -> Arg a a0 -> m Source #

foldMap' :: Monoid m => (a0 -> m) -> Arg a a0 -> m Source #

foldr :: (a0 -> b -> b) -> b -> Arg a a0 -> b Source #

foldr' :: (a0 -> b -> b) -> b -> Arg a a0 -> b Source #

foldl :: (b -> a0 -> b) -> b -> Arg a a0 -> b Source #

foldl' :: (b -> a0 -> b) -> b -> Arg a a0 -> b Source #

foldr1 :: (a0 -> a0 -> a0) -> Arg a a0 -> a0 Source #

foldl1 :: (a0 -> a0 -> a0) -> Arg a a0 -> a0 Source #

toList :: Arg a a0 -> [a0] Source #

null :: Arg a a0 -> Bool Source #

length :: Arg a a0 -> Int Source #

elem :: Eq a0 => a0 -> Arg a a0 -> Bool Source #

maximum :: Ord a0 => Arg a a0 -> a0 Source #

minimum :: Ord a0 => Arg a a0 -> a0 Source #

sum :: Num a0 => Arg a a0 -> a0 Source #

product :: Num a0 => Arg a a0 -> a0 Source #

Traversable (Arg a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

traverse :: Applicative f => (a0 -> f b) -> Arg a a0 -> f (Arg a b) Source #

sequenceA :: Applicative f => Arg a (f a0) -> f (Arg a a0) Source #

mapM :: Monad m => (a0 -> m b) -> Arg a a0 -> m (Arg a b) Source #

sequence :: Monad m => Arg a (m a0) -> m (Arg a a0) Source #

(Data a, Data b) => Data (Arg a b) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Arg a b -> c (Arg a b) Source #

gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Arg a b) Source #

toConstr :: Arg a b -> Constr Source #

dataTypeOf :: Arg a b -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Arg a b)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Arg a b)) Source #

gmapT :: (forall b0. Data b0 => b0 -> b0) -> Arg a b -> Arg a b Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Arg a b -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Arg a b -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Arg a b -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Arg a b -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Arg a b -> m (Arg a b) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Arg a b -> m (Arg a b) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Arg a b -> m (Arg a b) Source #

Generic (Arg a b) Source # 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Arg a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

from :: Arg a b -> Rep (Arg a b) x Source #

to :: Rep (Arg a b) x -> Arg a b Source #

(Read a, Read b) => Read (Arg a b) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

(Show a, Show b) => Show (Arg a b) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

showsPrec :: Int -> Arg a b -> ShowS Source #

show :: Arg a b -> String Source #

showList :: [Arg a b] -> ShowS Source #

Eq a => Eq (Arg a b) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

(==) :: Arg a b -> Arg a b -> Bool Source #

(/=) :: Arg a b -> Arg a b -> Bool Source #

Ord a => Ord (Arg a b) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

compare :: Arg a b -> Arg a b -> Ordering Source #

(<) :: Arg a b -> Arg a b -> Bool Source #

(<=) :: Arg a b -> Arg a b -> Bool Source #

(>) :: Arg a b -> Arg a b -> Bool Source #

(>=) :: Arg a b -> Arg a b -> Bool Source #

max :: Arg a b -> Arg a b -> Arg a b Source #

min :: Arg a b -> Arg a b -> Arg a b Source #

type Rep1 (Arg a :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep (Arg a b) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type ArgMin a b = Min (Arg a b) Source #

Examples

Expand
>>> Min (Arg 0 ()) <> Min (Arg 1 ())
Min {getMin = Arg 0 ()}
>>> minimum [ Arg (length name) name | name <- ["violencia", "lea", "pixie"]]
Arg 3 "lea"

type ArgMax a b = Max (Arg a b) Source #

Examples

Expand
>>> Max (Arg 0 ()) <> Max (Arg 1 ())
Max {getMax = Arg 1 ()}
>>> maximum [ Arg (length name) name | name <- ["violencia", "lea", "pixie"]]
Arg 9 "violencia"