semigroups-0.18.1: Anything that associates

Copyright(C) 2011-2015 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityprovisional
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell98

Data.Semigroup

Contents

Description

In mathematics, a semigroup is an algebraic structure consisting of a set together with an associative binary operation. A semigroup generalizes a monoid in that there might not exist an identity element. It also (originally) generalized a group (a monoid with all inverses) to a type where every element did not have to have an inverse, thus the name semigroup.

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

Synopsis

Documentation

class Semigroup a where Source

Minimal complete definition

Nothing

Methods

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

An associative operation.

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

If a is also a Monoid we further require

(<>) = mappend

sconcat :: NonEmpty a -> a Source

Reduce a non-empty list with <>

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

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

Repeat a value n times.

Given that this works on a Semigroup it is allowed to fail if you request 0 or fewer repetitions, and the default definition will do so.

By making this a member of the class, idempotent semigroups and monoids can upgrade this to execute in O(1) by picking stimes = stimesIdempotent or stimes = stimesIdempotentMonoid respectively.

Since: 0.17

Instances

Semigroup Ordering Source 
Semigroup () Source 

Methods

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

sconcat :: NonEmpty () -> () Source

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

Semigroup Void Source 
Semigroup All Source 

Methods

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

sconcat :: NonEmpty All -> All Source

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

Semigroup Any Source 

Methods

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

sconcat :: NonEmpty Any -> Any Source

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

Semigroup ByteString Source 
Semigroup ByteString Source 
Semigroup Builder Source 
Semigroup Builder Source 
Semigroup ShortByteString Source 
Semigroup IntSet Source 
Semigroup Builder Source 
Semigroup Text Source 
Semigroup Text Source 
Semigroup [a] Source 

Methods

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

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

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

Semigroup a => Semigroup (Identity a) Source 
Semigroup a => Semigroup (Dual a) Source 

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

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 (Sum a) Source 

Methods

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

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

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

Num a => Semigroup (Product a) Source 
Semigroup (First a) Source 

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 

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 (Maybe a) Source 

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 (IntMap v) Source 

Methods

(<>) :: IntMap v -> IntMap v -> IntMap v Source

sconcat :: NonEmpty (IntMap v) -> IntMap v Source

stimes :: Integral b => b -> IntMap v -> IntMap v Source

Ord a => Semigroup (Set a) Source 

Methods

(<>) :: Set a -> Set a -> Set a Source

sconcat :: NonEmpty (Set a) -> Set a Source

stimes :: Integral b => b -> Set a -> Set a Source

Semigroup (Seq a) Source 

Methods

(<>) :: Seq a -> Seq a -> Seq a Source

sconcat :: NonEmpty (Seq a) -> Seq a Source

stimes :: Integral b => b -> Seq a -> Seq a Source

(Hashable a, Eq a) => Semigroup (HashSet a) Source 
Semigroup (NonEmpty a) Source 
Semigroup a => Semigroup (Option a) Source 

Methods

(<>) :: Option a -> Option a -> Option a Source

sconcat :: NonEmpty (Option a) -> Option a Source

stimes :: Integral b => b -> Option a -> Option a Source

Monoid m => Semigroup (WrappedMonoid m) Source 
Semigroup (Last a) Source 

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 (First a) Source 

Methods

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

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

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

Ord a => Semigroup (Max a) Source 

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 

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 b => Semigroup (a -> b) Source 

Methods

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

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

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

Semigroup (Either a b) Source 

Methods

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

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

stimes :: Integral c => c -> Either a b -> Either a b Source

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

Methods

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

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

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

Semigroup a => Semigroup (Const a b) Source 

Methods

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

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

stimes :: Integral c => c -> Const a b -> Const a b Source

Semigroup (Proxy k s) Source 

Methods

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

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

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

Ord k => Semigroup (Map k v) Source 

Methods

(<>) :: Map k v -> Map k v -> Map k v Source

sconcat :: NonEmpty (Map k v) -> Map k v Source

stimes :: Integral b => b -> Map k v -> Map k v Source

(Hashable k, Eq k) => Semigroup (HashMap k a) Source 

Methods

(<>) :: HashMap k a -> HashMap k a -> HashMap k a Source

sconcat :: NonEmpty (HashMap k a) -> HashMap k a Source

stimes :: Integral b => b -> HashMap k a -> HashMap k a Source

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

Methods

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

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

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

Alternative f => Semigroup (Alt * f a) Source 

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 a => Semigroup (Tagged k s a) Source 

Methods

(<>) :: Tagged k s a -> Tagged k s a -> Tagged k s a Source

sconcat :: NonEmpty (Tagged k s a) -> Tagged k s a Source

stimes :: Integral b => b -> Tagged k s a -> Tagged k s a Source

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

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 e => e -> (a, b, c, d) -> (a, b, c, d) Source

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

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 f => f -> (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 O(1) rather than O(log n).

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

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

When mappend x x = x, this definition should be preferred, because it works in O(1) rather than 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

Implemented using stimes and mempty.

This is a suitable definition for an mtimes member of Monoid.

Since: 0.17

Semigroups

newtype Min a Source

Constructors

Min 

Fields

Instances

Monad Min Source 

Methods

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

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

return :: a -> Min a

fail :: String -> Min a

Functor Min Source 

Methods

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

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

MonadFix Min Source 

Methods

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

Applicative Min Source 

Methods

pure :: a -> Min a

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

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

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

Foldable Min Source 

Methods

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

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

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

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

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

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

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

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

toList :: Min a -> [a]

null :: Min a -> Bool

length :: Min a -> Int

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

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

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

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

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

Traversable Min Source 

Methods

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

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

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

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

Generic1 Min Source 

Associated Types

type Rep1 (Min :: * -> *) :: * -> *

Methods

from1 :: Min a -> Rep1 Min a

to1 :: Rep1 Min a -> Min a

Bounded a => Bounded (Min a) Source 

Methods

minBound :: Min a

maxBound :: Min a

Enum a => Enum (Min a) Source 

Methods

succ :: Min a -> Min a

pred :: Min a -> Min a

toEnum :: Int -> Min a

fromEnum :: Min a -> Int

enumFrom :: Min a -> [Min a]

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

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

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

Eq a => Eq (Min a) Source 

Methods

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

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

Data a => Data (Min a) Source 

Methods

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

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

toConstr :: Min a -> Constr

dataTypeOf :: Min a -> DataType

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

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

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

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

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

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

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

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

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

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

Num a => Num (Min a) Source 

Methods

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

(-) :: Min a -> Min a -> Min a

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

negate :: Min a -> Min a

abs :: Min a -> Min a

signum :: Min a -> Min a

fromInteger :: Integer -> Min a

Ord a => Ord (Min a) Source 

Methods

compare :: Min a -> Min a -> Ordering

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

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

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

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

max :: Min a -> Min a -> Min a

min :: Min a -> Min a -> Min a

Read a => Read (Min a) Source 
Show a => Show (Min a) Source 

Methods

showsPrec :: Int -> Min a -> ShowS

show :: Min a -> String

showList :: [Min a] -> ShowS

Generic (Min a) Source 

Associated Types

type Rep (Min a) :: * -> *

Methods

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

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

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

Methods

mempty :: Min a

mappend :: Min a -> Min a -> Min a

mconcat :: [Min a] -> Min a

NFData a => NFData (Min a) Source 

Methods

rnf :: Min a -> ()

Hashable a => Hashable (Min a) Source 

Methods

hashWithSalt :: Int -> Min a -> Int

hash :: Min a -> Int

Ord a => Semigroup (Min a) Source 

Methods

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

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

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

type Rep1 Min Source 
type Rep (Min a) Source 

newtype Max a Source

Constructors

Max 

Fields

Instances

Monad Max Source 

Methods

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

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

return :: a -> Max a

fail :: String -> Max a

Functor Max Source 

Methods

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

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

MonadFix Max Source 

Methods

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

Applicative Max Source 

Methods

pure :: a -> Max a

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

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

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

Foldable Max Source 

Methods

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

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

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

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

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

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

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

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

toList :: Max a -> [a]

null :: Max a -> Bool

length :: Max a -> Int

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

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

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

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

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

Traversable Max Source 

Methods

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

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

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

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

Generic1 Max Source 

Associated Types

type Rep1 (Max :: * -> *) :: * -> *

Methods

from1 :: Max a -> Rep1 Max a

to1 :: Rep1 Max a -> Max a

Bounded a => Bounded (Max a) Source 

Methods

minBound :: Max a

maxBound :: Max a

Enum a => Enum (Max a) Source 

Methods

succ :: Max a -> Max a

pred :: Max a -> Max a

toEnum :: Int -> Max a

fromEnum :: Max a -> Int

enumFrom :: Max a -> [Max a]

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

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

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

Eq a => Eq (Max a) Source 

Methods

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

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

Data a => Data (Max a) Source 

Methods

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

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

toConstr :: Max a -> Constr

dataTypeOf :: Max a -> DataType

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

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

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

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

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

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

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

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

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

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

Num a => Num (Max a) Source 

Methods

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

(-) :: Max a -> Max a -> Max a

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

negate :: Max a -> Max a

abs :: Max a -> Max a

signum :: Max a -> Max a

fromInteger :: Integer -> Max a

Ord a => Ord (Max a) Source 

Methods

compare :: Max a -> Max a -> Ordering

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

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

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

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

max :: Max a -> Max a -> Max a

min :: Max a -> Max a -> Max a

Read a => Read (Max a) Source 
Show a => Show (Max a) Source 

Methods

showsPrec :: Int -> Max a -> ShowS

show :: Max a -> String

showList :: [Max a] -> ShowS

Generic (Max a) Source 

Associated Types

type Rep (Max a) :: * -> *

Methods

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

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

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

Methods

mempty :: Max a

mappend :: Max a -> Max a -> Max a

mconcat :: [Max a] -> Max a

NFData a => NFData (Max a) Source 

Methods

rnf :: Max a -> ()

Hashable a => Hashable (Max a) Source 

Methods

hashWithSalt :: Int -> Max a -> Int

hash :: Max a -> Int

Ord a => Semigroup (Max a) Source 

Methods

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

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

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

type Rep1 Max Source 
type Rep (Max a) Source 

newtype First a Source

Use Option (First a) to get the behavior of First from Data.Monoid.

Constructors

First 

Fields

Instances

Monad First Source 

Methods

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

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

return :: a -> First a

fail :: String -> First a

Functor First Source 

Methods

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

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

MonadFix First Source 

Methods

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

Applicative First Source 

Methods

pure :: a -> First a

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

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

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

Foldable First Source 

Methods

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

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

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

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

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

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

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

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

toList :: First a -> [a]

null :: First a -> Bool

length :: First a -> Int

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

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

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

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

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

Traversable First Source 

Methods

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

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

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

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

Generic1 First Source 

Associated Types

type Rep1 (First :: * -> *) :: * -> *

Methods

from1 :: First a -> Rep1 First a

to1 :: Rep1 First a -> First a

Bounded a => Bounded (First a) Source 

Methods

minBound :: First a

maxBound :: First a

Enum a => Enum (First a) Source 

Methods

succ :: First a -> First a

pred :: First a -> First a

toEnum :: Int -> First a

fromEnum :: First a -> Int

enumFrom :: First a -> [First a]

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

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

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

Eq a => Eq (First a) Source 

Methods

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

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

Data a => Data (First a) Source 

Methods

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

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

toConstr :: First a -> Constr

dataTypeOf :: First a -> DataType

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (First a) Source 

Methods

compare :: First a -> First a -> Ordering

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

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

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

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

max :: First a -> First a -> First a

min :: First a -> First a -> First a

Read a => Read (First a) Source 
Show a => Show (First a) Source 

Methods

showsPrec :: Int -> First a -> ShowS

show :: First a -> String

showList :: [First a] -> ShowS

Generic (First a) Source 

Associated Types

type Rep (First a) :: * -> *

Methods

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

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

NFData a => NFData (First a) Source 

Methods

rnf :: First a -> ()

Hashable a => Hashable (First a) Source 

Methods

hashWithSalt :: Int -> First a -> Int

hash :: First a -> Int

Semigroup (First a) Source 

Methods

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

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

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

type Rep1 First Source 
type Rep (First a) Source 

newtype Last a Source

Use Option (Last a) to get the behavior of Last from Data.Monoid

Constructors

Last 

Fields

Instances

Monad Last Source 

Methods

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

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

return :: a -> Last a

fail :: String -> Last a

Functor Last Source 

Methods

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

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

MonadFix Last Source 

Methods

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

Applicative Last Source 

Methods

pure :: a -> Last a

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

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

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

Foldable Last Source 

Methods

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

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

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

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

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

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

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

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

toList :: Last a -> [a]

null :: Last a -> Bool

length :: Last a -> Int

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

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

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

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

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

Traversable Last Source 

Methods

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

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

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

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

Generic1 Last Source 

Associated Types

type Rep1 (Last :: * -> *) :: * -> *

Methods

from1 :: Last a -> Rep1 Last a

to1 :: Rep1 Last a -> Last a

Bounded a => Bounded (Last a) Source 

Methods

minBound :: Last a

maxBound :: Last a

Enum a => Enum (Last a) Source 

Methods

succ :: Last a -> Last a

pred :: Last a -> Last a

toEnum :: Int -> Last a

fromEnum :: Last a -> Int

enumFrom :: Last a -> [Last a]

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

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

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

Eq a => Eq (Last a) Source 

Methods

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

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

Data a => Data (Last a) Source 

Methods

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

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

toConstr :: Last a -> Constr

dataTypeOf :: Last a -> DataType

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (Last a) Source 

Methods

compare :: Last a -> Last a -> Ordering

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

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

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

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

max :: Last a -> Last a -> Last a

min :: Last a -> Last a -> Last a

Read a => Read (Last a) Source 
Show a => Show (Last a) Source 

Methods

showsPrec :: Int -> Last a -> ShowS

show :: Last a -> String

showList :: [Last a] -> ShowS

Generic (Last a) Source 

Associated Types

type Rep (Last a) :: * -> *

Methods

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

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

NFData a => NFData (Last a) Source 

Methods

rnf :: Last a -> ()

Hashable a => Hashable (Last a) Source 

Methods

hashWithSalt :: Int -> Last a -> Int

hash :: Last a -> Int

Semigroup (Last a) Source 

Methods

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

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

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

type Rep1 Last Source 
type Rep (Last a) Source 

newtype WrappedMonoid m Source

Provide a Semigroup for an arbitrary Monoid.

Constructors

WrapMonoid 

Fields

Instances

Generic1 WrappedMonoid Source 

Associated Types

type Rep1 (WrappedMonoid :: * -> *) :: * -> *

Bounded a => Bounded (WrappedMonoid a) Source 
Enum a => Enum (WrappedMonoid a) Source 
Eq m => Eq (WrappedMonoid m) Source 
Data m => Data (WrappedMonoid m) Source 

Methods

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

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

toConstr :: WrappedMonoid m -> Constr

dataTypeOf :: WrappedMonoid m -> DataType

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

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

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

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

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

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

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

gmapM :: Monad a => (forall d. Data d => d -> a d) -> WrappedMonoid m -> a (WrappedMonoid m)

gmapMp :: MonadPlus a => (forall d. Data d => d -> a d) -> WrappedMonoid m -> a (WrappedMonoid m)

gmapMo :: MonadPlus a => (forall d. Data d => d -> a d) -> WrappedMonoid m -> a (WrappedMonoid m)

Ord m => Ord (WrappedMonoid m) Source 
Read m => Read (WrappedMonoid m) Source 
Show m => Show (WrappedMonoid m) Source 
Generic (WrappedMonoid m) Source 

Associated Types

type Rep (WrappedMonoid m) :: * -> *

Monoid m => Monoid (WrappedMonoid m) Source 
NFData m => NFData (WrappedMonoid m) Source 

Methods

rnf :: WrappedMonoid m -> ()

Hashable a => Hashable (WrappedMonoid a) Source 
Monoid m => Semigroup (WrappedMonoid m) Source 
type Rep1 WrappedMonoid Source 
type Rep (WrappedMonoid m) Source 

Re-exported monoids from Data.Monoid

class Monoid a where

The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following laws:

  • mappend mempty x = x
  • mappend x mempty = x
  • mappend x (mappend y z) = mappend (mappend x y) z
  • mconcat = foldr mappend mempty

The method names refer to the monoid of lists under concatenation, but there are many other instances.

Some types can be viewed as a monoid in more than one way, e.g. both addition and multiplication on numbers. In such cases we often define newtypes and make those instances of Monoid, e.g. Sum and Product.

Minimal complete definition

mempty, mappend

Methods

mempty :: a

Identity of mappend

mappend :: a -> a -> a

An associative operation

mconcat :: [a] -> a

Fold a list using the monoid. For most types, the default definition for mconcat will be used, but the function is included in the class definition so that an optimized version can be provided for specific types.

Instances

Monoid Ordering 
Monoid () 

Methods

mempty :: ()

mappend :: () -> () -> ()

mconcat :: [()] -> ()

Monoid All 

Methods

mempty :: All

mappend :: All -> All -> All

mconcat :: [All] -> All

Monoid Any 

Methods

mempty :: Any

mappend :: Any -> Any -> Any

mconcat :: [Any] -> Any

Monoid ByteString 
Monoid ByteString 
Monoid Builder 
Monoid Builder 
Monoid ShortByteString 
Monoid IntSet 
Monoid Builder 
Monoid [a] 

Methods

mempty :: [a]

mappend :: [a] -> [a] -> [a]

mconcat :: [[a]] -> [a]

Ord a => Monoid (Max a) 

Methods

mempty :: Max a

mappend :: Max a -> Max a -> Max a

mconcat :: [Max a] -> Max a

Ord a => Monoid (Min a) 

Methods

mempty :: Min a

mappend :: Min a -> Min a -> Min a

mconcat :: [Min a] -> Min a

Monoid a => Monoid (Dual a) 

Methods

mempty :: Dual a

mappend :: Dual a -> Dual a -> Dual a

mconcat :: [Dual a] -> Dual a

Monoid (Endo a) 

Methods

mempty :: Endo a

mappend :: Endo a -> Endo a -> Endo a

mconcat :: [Endo a] -> Endo a

Num a => Monoid (Sum a) 

Methods

mempty :: Sum a

mappend :: Sum a -> Sum a -> Sum a

mconcat :: [Sum a] -> Sum a

Num a => Monoid (Product a) 

Methods

mempty :: Product a

mappend :: Product a -> Product a -> Product a

mconcat :: [Product a] -> Product a

Monoid (First a) 

Methods

mempty :: First a

mappend :: First a -> First a -> First a

mconcat :: [First a] -> First a

Monoid (Last a) 

Methods

mempty :: Last a

mappend :: Last a -> Last a -> Last a

mconcat :: [Last a] -> Last a

Monoid a => Monoid (Maybe a)

Lift a semigroup into Maybe forming a Monoid according to http://en.wikipedia.org/wiki/Monoid: "Any semigroup S may be turned into a monoid simply by adjoining an element e not in S and defining e*e = e and e*s = s = s*e for all s ∈ S." Since there is no "Semigroup" typeclass providing just mappend, we use Monoid instead.

Methods

mempty :: Maybe a

mappend :: Maybe a -> Maybe a -> Maybe a

mconcat :: [Maybe a] -> Maybe a

Monoid (IntMap a) 

Methods

mempty :: IntMap a

mappend :: IntMap a -> IntMap a -> IntMap a

mconcat :: [IntMap a] -> IntMap a

Ord a => Monoid (Set a) 

Methods

mempty :: Set a

mappend :: Set a -> Set a -> Set a

mconcat :: [Set a] -> Set a

Monoid (Seq a) 

Methods

mempty :: Seq a

mappend :: Seq a -> Seq a -> Seq a

mconcat :: [Seq a] -> Seq a

(Hashable a, Eq a) => Monoid (HashSet a) 

Methods

mempty :: HashSet a

mappend :: HashSet a -> HashSet a -> HashSet a

mconcat :: [HashSet a] -> HashSet a

Semigroup a => Monoid (Option a) 

Methods

mempty :: Option a

mappend :: Option a -> Option a -> Option a

mconcat :: [Option a] -> Option a

Monoid m => Monoid (WrappedMonoid m) 
(Ord a, Bounded a) => Monoid (Max a) 

Methods

mempty :: Max a

mappend :: Max a -> Max a -> Max a

mconcat :: [Max a] -> Max a

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

Methods

mempty :: Min a

mappend :: Min a -> Min a -> Min a

mconcat :: [Min a] -> Min a

Monoid b => Monoid (a -> b) 

Methods

mempty :: a -> b

mappend :: (a -> b) -> (a -> b) -> a -> b

mconcat :: [a -> b] -> a -> b

(Monoid a, Monoid b) => Monoid (a, b) 

Methods

mempty :: (a, b)

mappend :: (a, b) -> (a, b) -> (a, b)

mconcat :: [(a, b)] -> (a, b)

Monoid a => Monoid (Const a b) 

Methods

mempty :: Const a b

mappend :: Const a b -> Const a b -> Const a b

mconcat :: [Const a b] -> Const a b

Monoid (Proxy k s) 

Methods

mempty :: Proxy k s

mappend :: Proxy k s -> Proxy k s -> Proxy k s

mconcat :: [Proxy k s] -> Proxy k s

Ord k => Monoid (Map k v) 

Methods

mempty :: Map k v

mappend :: Map k v -> Map k v -> Map k v

mconcat :: [Map k v] -> Map k v

(Eq k, Hashable k) => Monoid (HashMap k v) 

Methods

mempty :: HashMap k v

mappend :: HashMap k v -> HashMap k v -> HashMap k v

mconcat :: [HashMap k v] -> HashMap k v

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

Methods

mempty :: (a, b, c)

mappend :: (a, b, c) -> (a, b, c) -> (a, b, c)

mconcat :: [(a, b, c)] -> (a, b, c)

Alternative f => Monoid (Alt * f a) 

Methods

mempty :: Alt * f a

mappend :: Alt * f a -> Alt * f a -> Alt * f a

mconcat :: [Alt * f a] -> Alt * f a

Monoid a => Monoid (Tagged k s a) 

Methods

mempty :: Tagged k s a

mappend :: Tagged k s a -> Tagged k s a -> Tagged k s a

mconcat :: [Tagged k s a] -> Tagged k s a

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

Methods

mempty :: (a, b, c, d)

mappend :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d)

mconcat :: [(a, b, c, d)] -> (a, b, c, d)

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

Methods

mempty :: (a, b, c, d, e)

mappend :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e)

mconcat :: [(a, b, c, d, e)] -> (a, b, c, d, e)

newtype Dual a :: * -> *

The dual of a Monoid, obtained by swapping the arguments of mappend.

Constructors

Dual 

Fields

Instances

Generic1 Dual 

Associated Types

type Rep1 (Dual :: * -> *) :: * -> *

Methods

from1 :: Dual a -> Rep1 Dual a

to1 :: Rep1 Dual a -> Dual a

Bounded a => Bounded (Dual a) 

Methods

minBound :: Dual a

maxBound :: Dual a

Eq a => Eq (Dual a) 

Methods

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

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

Ord a => Ord (Dual a) 

Methods

compare :: Dual a -> Dual a -> Ordering

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

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

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

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

max :: Dual a -> Dual a -> Dual a

min :: Dual a -> Dual a -> Dual a

Read a => Read (Dual a) 
Show a => Show (Dual a) 

Methods

showsPrec :: Int -> Dual a -> ShowS

show :: Dual a -> String

showList :: [Dual a] -> ShowS

Generic (Dual a) 

Associated Types

type Rep (Dual a) :: * -> *

Methods

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

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

Monoid a => Monoid (Dual a) 

Methods

mempty :: Dual a

mappend :: Dual a -> Dual a -> Dual a

mconcat :: [Dual a] -> Dual a

NFData a => NFData (Dual a)

Since: 1.4.0.0

Methods

rnf :: Dual a -> ()

Semigroup a => Semigroup (Dual a) Source 

Methods

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

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

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

type Rep1 Dual = D1 D1Dual (C1 C1_0Dual (S1 S1_0_0Dual Par1)) 
type Rep (Dual a) = D1 D1Dual (C1 C1_0Dual (S1 S1_0_0Dual (Rec0 a))) 

newtype Endo a :: * -> *

The monoid of endomorphisms under composition.

Constructors

Endo 

Fields

Instances

Generic (Endo a) 

Associated Types

type Rep (Endo a) :: * -> *

Methods

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

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

Monoid (Endo a) 

Methods

mempty :: Endo a

mappend :: Endo a -> Endo a -> Endo a

mconcat :: [Endo a] -> Endo a

Semigroup (Endo a) Source 

Methods

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

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

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

type Rep (Endo a) = D1 D1Endo (C1 C1_0Endo (S1 S1_0_0Endo (Rec0 (a -> a)))) 

newtype All :: *

Boolean monoid under conjunction (&&).

Constructors

All 

Fields

Instances

Bounded All 

Methods

minBound :: All

maxBound :: All

Eq All 

Methods

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

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

Ord All 

Methods

compare :: All -> All -> Ordering

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

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

(>) :: All -> All -> Bool

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

max :: All -> All -> All

min :: All -> All -> All

Read All 
Show All 

Methods

showsPrec :: Int -> All -> ShowS

show :: All -> String

showList :: [All] -> ShowS

Generic All 

Associated Types

type Rep All :: * -> *

Methods

from :: All -> Rep All x

to :: Rep All x -> All

Monoid All 

Methods

mempty :: All

mappend :: All -> All -> All

mconcat :: [All] -> All

NFData All

Since: 1.4.0.0

Methods

rnf :: All -> ()

Semigroup All Source 

Methods

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

sconcat :: NonEmpty All -> All Source

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

type Rep All = D1 D1All (C1 C1_0All (S1 S1_0_0All (Rec0 Bool))) 

newtype Any :: *

Boolean monoid under disjunction (||).

Constructors

Any 

Fields

Instances

Bounded Any 

Methods

minBound :: Any

maxBound :: Any

Eq Any 

Methods

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

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

Ord Any 

Methods

compare :: Any -> Any -> Ordering

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

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

(>) :: Any -> Any -> Bool

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

max :: Any -> Any -> Any

min :: Any -> Any -> Any

Read Any 
Show Any 

Methods

showsPrec :: Int -> Any -> ShowS

show :: Any -> String

showList :: [Any] -> ShowS

Generic Any 

Associated Types

type Rep Any :: * -> *

Methods

from :: Any -> Rep Any x

to :: Rep Any x -> Any

Monoid Any 

Methods

mempty :: Any

mappend :: Any -> Any -> Any

mconcat :: [Any] -> Any

NFData Any

Since: 1.4.0.0

Methods

rnf :: Any -> ()

Semigroup Any Source 

Methods

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

sconcat :: NonEmpty Any -> Any Source

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

type Rep Any = D1 D1Any (C1 C1_0Any (S1 S1_0_0Any (Rec0 Bool))) 

newtype Sum a :: * -> *

Monoid under addition.

Constructors

Sum 

Fields

Instances

Generic1 Sum 

Associated Types

type Rep1 (Sum :: * -> *) :: * -> *

Methods

from1 :: Sum a -> Rep1 Sum a

to1 :: Rep1 Sum a -> Sum a

Bounded a => Bounded (Sum a) 

Methods

minBound :: Sum a

maxBound :: Sum a

Eq a => Eq (Sum a) 

Methods

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

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

Num a => Num (Sum a) 

Methods

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

(-) :: Sum a -> Sum a -> Sum a

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

negate :: Sum a -> Sum a

abs :: Sum a -> Sum a

signum :: Sum a -> Sum a

fromInteger :: Integer -> Sum a

Ord a => Ord (Sum a) 

Methods

compare :: Sum a -> Sum a -> Ordering

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

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

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

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

max :: Sum a -> Sum a -> Sum a

min :: Sum a -> Sum a -> Sum a

Read a => Read (Sum a) 
Show a => Show (Sum a) 

Methods

showsPrec :: Int -> Sum a -> ShowS

show :: Sum a -> String

showList :: [Sum a] -> ShowS

Generic (Sum a) 

Associated Types

type Rep (Sum a) :: * -> *

Methods

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

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

Num a => Monoid (Sum a) 

Methods

mempty :: Sum a

mappend :: Sum a -> Sum a -> Sum a

mconcat :: [Sum a] -> Sum a

NFData a => NFData (Sum a)

Since: 1.4.0.0

Methods

rnf :: Sum a -> ()

Num a => Semigroup (Sum a) Source 

Methods

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

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

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

type Rep1 Sum = D1 D1Sum (C1 C1_0Sum (S1 S1_0_0Sum Par1)) 
type Rep (Sum a) = D1 D1Sum (C1 C1_0Sum (S1 S1_0_0Sum (Rec0 a))) 

newtype Product a :: * -> *

Monoid under multiplication.

Constructors

Product 

Fields

Instances

Generic1 Product 

Associated Types

type Rep1 (Product :: * -> *) :: * -> *

Methods

from1 :: Product a -> Rep1 Product a

to1 :: Rep1 Product a -> Product a

Bounded a => Bounded (Product a) 
Eq a => Eq (Product a) 

Methods

(==) :: Product a -> Product a -> Bool

(/=) :: Product a -> Product a -> Bool

Num a => Num (Product a) 

Methods

(+) :: Product a -> Product a -> Product a

(-) :: Product a -> Product a -> Product a

(*) :: Product a -> Product a -> Product a

negate :: Product a -> Product a

abs :: Product a -> Product a

signum :: Product a -> Product a

fromInteger :: Integer -> Product a

Ord a => Ord (Product a) 

Methods

compare :: Product a -> Product a -> Ordering

(<) :: Product a -> Product a -> Bool

(<=) :: Product a -> Product a -> Bool

(>) :: Product a -> Product a -> Bool

(>=) :: Product a -> Product a -> Bool

max :: Product a -> Product a -> Product a

min :: Product a -> Product a -> Product a

Read a => Read (Product a) 
Show a => Show (Product a) 

Methods

showsPrec :: Int -> Product a -> ShowS

show :: Product a -> String

showList :: [Product a] -> ShowS

Generic (Product a) 

Associated Types

type Rep (Product a) :: * -> *

Methods

from :: Product a -> Rep (Product a) x

to :: Rep (Product a) x -> Product a

Num a => Monoid (Product a) 

Methods

mempty :: Product a

mappend :: Product a -> Product a -> Product a

mconcat :: [Product a] -> Product a

NFData a => NFData (Product a)

Since: 1.4.0.0

Methods

rnf :: Product a -> ()

Num a => Semigroup (Product a) Source 
type Rep1 Product = D1 D1Product (C1 C1_0Product (S1 S1_0_0Product Par1)) 
type Rep (Product a) = D1 D1Product (C1 C1_0Product (S1 S1_0_0Product (Rec0 a))) 

A better monoid for Maybe

newtype Option a Source

Option is effectively Maybe with a better instance of Monoid, built off of an underlying Semigroup instead of an underlying Monoid.

Ideally, this type would not exist at all and we would just fix the Monoid instance of Maybe

Constructors

Option 

Fields

Instances

Monad Option Source 

Methods

(>>=) :: Option a -> (a -> Option b) -> Option b

(>>) :: Option a -> Option b -> Option b

return :: a -> Option a

fail :: String -> Option a

Functor Option Source 

Methods

fmap :: (a -> b) -> Option a -> Option b

(<$) :: a -> Option b -> Option a

MonadFix Option Source 

Methods

mfix :: (a -> Option a) -> Option a

Applicative Option Source 

Methods

pure :: a -> Option a

(<*>) :: Option (a -> b) -> Option a -> Option b

(*>) :: Option a -> Option b -> Option b

(<*) :: Option a -> Option b -> Option a

Foldable Option Source 

Methods

fold :: Monoid m => Option m -> m

foldMap :: Monoid m => (a -> m) -> Option a -> m

foldr :: (a -> b -> b) -> b -> Option a -> b

foldr' :: (a -> b -> b) -> b -> Option a -> b

foldl :: (b -> a -> b) -> b -> Option a -> b

foldl' :: (b -> a -> b) -> b -> Option a -> b

foldr1 :: (a -> a -> a) -> Option a -> a

foldl1 :: (a -> a -> a) -> Option a -> a

toList :: Option a -> [a]

null :: Option a -> Bool

length :: Option a -> Int

elem :: Eq a => a -> Option a -> Bool

maximum :: Ord a => Option a -> a

minimum :: Ord a => Option a -> a

sum :: Num a => Option a -> a

product :: Num a => Option a -> a

Traversable Option Source 

Methods

traverse :: Applicative f => (a -> f b) -> Option a -> f (Option b)

sequenceA :: Applicative f => Option (f a) -> f (Option a)

mapM :: Monad m => (a -> m b) -> Option a -> m (Option b)

sequence :: Monad m => Option (m a) -> m (Option a)

Generic1 Option Source 

Associated Types

type Rep1 (Option :: * -> *) :: * -> *

Methods

from1 :: Option a -> Rep1 Option a

to1 :: Rep1 Option a -> Option a

Alternative Option Source 

Methods

empty :: Option a

(<|>) :: Option a -> Option a -> Option a

some :: Option a -> Option [a]

many :: Option a -> Option [a]

MonadPlus Option Source 

Methods

mzero :: Option a

mplus :: Option a -> Option a -> Option a

Eq a => Eq (Option a) Source 

Methods

(==) :: Option a -> Option a -> Bool

(/=) :: Option a -> Option a -> Bool

Data a => Data (Option a) Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Option a -> c (Option a)

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Option a)

toConstr :: Option a -> Constr

dataTypeOf :: Option a -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Option a))

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Option a))

gmapT :: (forall b. Data b => b -> b) -> Option a -> Option a

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Option a -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Option a -> r

gmapQ :: (forall d. Data d => d -> u) -> Option a -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Option a -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Option a -> m (Option a)

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Option a -> m (Option a)

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Option a -> m (Option a)

Ord a => Ord (Option a) Source 

Methods

compare :: Option a -> Option a -> Ordering

(<) :: Option a -> Option a -> Bool

(<=) :: Option a -> Option a -> Bool

(>) :: Option a -> Option a -> Bool

(>=) :: Option a -> Option a -> Bool

max :: Option a -> Option a -> Option a

min :: Option a -> Option a -> Option a

Read a => Read (Option a) Source 
Show a => Show (Option a) Source 

Methods

showsPrec :: Int -> Option a -> ShowS

show :: Option a -> String

showList :: [Option a] -> ShowS

Generic (Option a) Source 

Associated Types

type Rep (Option a) :: * -> *

Methods

from :: Option a -> Rep (Option a) x

to :: Rep (Option a) x -> Option a

Semigroup a => Monoid (Option a) Source 

Methods

mempty :: Option a

mappend :: Option a -> Option a -> Option a

mconcat :: [Option a] -> Option a

NFData a => NFData (Option a) Source 

Methods

rnf :: Option a -> ()

Hashable a => Hashable (Option a) Source 

Methods

hashWithSalt :: Int -> Option a -> Int

hash :: Option a -> Int

Semigroup a => Semigroup (Option a) Source 

Methods

(<>) :: Option a -> Option a -> Option a Source

sconcat :: NonEmpty (Option a) -> Option a Source

stimes :: Integral b => b -> Option a -> Option a Source

type Rep1 Option Source 
type Rep (Option a) Source 

option :: b -> (a -> b) -> Option a -> b Source

Fold an Option case-wise, just like maybe.

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.

cycle1 :: Semigroup m => m -> m Source

A generalization of cycle to an arbitrary Semigroup. May fail to terminate for some values in some semigroups.

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.

Constructors

Arg a b 

Instances

Bifunctor Arg Source 

Methods

bimap :: (a -> b) -> (c -> d) -> Arg a c -> Arg b d

first :: (a -> b) -> Arg a c -> Arg b c

second :: (b -> c) -> Arg a b -> Arg a c

Functor (Arg a) Source 

Methods

fmap :: (b -> c) -> Arg a b -> Arg a c

(<$) :: b -> Arg a c -> Arg a b

Foldable (Arg a) Source 

Methods

fold :: Monoid m => Arg a m -> m

foldMap :: Monoid m => (b -> m) -> Arg a b -> m

foldr :: (b -> c -> c) -> c -> Arg a b -> c

foldr' :: (b -> c -> c) -> c -> Arg a b -> c

foldl :: (b -> c -> b) -> b -> Arg a c -> b

foldl' :: (b -> c -> b) -> b -> Arg a c -> b

foldr1 :: (b -> b -> b) -> Arg a b -> b

foldl1 :: (b -> b -> b) -> Arg a b -> b

toList :: Arg a b -> [b]

null :: Arg a b -> Bool

length :: Arg a b -> Int

elem :: Eq b => b -> Arg a b -> Bool

maximum :: Ord b => Arg a b -> b

minimum :: Ord b => Arg a b -> b

sum :: Num b => Arg a b -> b

product :: Num b => Arg a b -> b

Traversable (Arg a) Source 

Methods

traverse :: Applicative f => (b -> f c) -> Arg a b -> f (Arg a c)

sequenceA :: Applicative f => Arg a (f b) -> f (Arg a b)

mapM :: Monad m => (b -> m c) -> Arg a b -> m (Arg a c)

sequence :: Monad m => Arg a (m b) -> m (Arg a b)

Generic1 (Arg a) Source 

Associated Types

type Rep1 (Arg a :: * -> *) :: * -> *

Methods

from1 :: Arg a b -> Rep1 (Arg a) b

to1 :: Rep1 (Arg a) b -> Arg a b

Eq a => Eq (Arg a b) Source 

Methods

(==) :: Arg a b -> Arg a b -> Bool

(/=) :: Arg a b -> Arg a b -> Bool

(Data a, Data b) => Data (Arg a b) Source 

Methods

gfoldl :: (forall d e. Data d => c (d -> e) -> d -> c e) -> (forall g. g -> c g) -> Arg a b -> c (Arg a b)

gunfold :: (forall d r. Data d => c (d -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Arg a b)

toConstr :: Arg a b -> Constr

dataTypeOf :: Arg a b -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Arg a b))

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Arg a b))

gmapT :: (forall c. Data c => c -> c) -> Arg a b -> Arg a b

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Arg a b -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Arg a b -> r

gmapQ :: (forall d. Data d => d -> u) -> Arg a b -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Arg a b -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Arg a b -> m (Arg a b)

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Arg a b -> m (Arg a b)

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Arg a b -> m (Arg a b)

Ord a => Ord (Arg a b) Source 

Methods

compare :: Arg a b -> Arg a b -> Ordering

(<) :: Arg a b -> Arg a b -> Bool

(<=) :: Arg a b -> Arg a b -> Bool

(>) :: Arg a b -> Arg a b -> Bool

(>=) :: Arg a b -> Arg a b -> Bool

max :: Arg a b -> Arg a b -> Arg a b

min :: Arg a b -> Arg a b -> Arg a b

(Read a, Read b) => Read (Arg a b) Source 

Methods

readsPrec :: Int -> ReadS (Arg a b)

readList :: ReadS [Arg a b]

readPrec :: ReadPrec (Arg a b)

readListPrec :: ReadPrec [Arg a b]

(Show a, Show b) => Show (Arg a b) Source 

Methods

showsPrec :: Int -> Arg a b -> ShowS

show :: Arg a b -> String

showList :: [Arg a b] -> ShowS

Generic (Arg a b) Source 

Associated Types

type Rep (Arg a b) :: * -> *

Methods

from :: Arg a b -> Rep (Arg a b) x

to :: Rep (Arg a b) x -> Arg a b

(NFData a, NFData b) => NFData (Arg a b) Source 

Methods

rnf :: Arg a b -> ()

(Hashable a, Hashable b) => Hashable (Arg a b) Source 

Methods

hashWithSalt :: Int -> Arg a b -> Int

hash :: Arg a b -> Int

type Rep1 (Arg a) Source 
type Rep (Arg a b) Source 

type ArgMin a b = Min (Arg a b) Source

type ArgMax a b = Max (Arg a b) Source