ghc-internal-9.1001.0: Basic libraries
Safe HaskellNone
LanguageHaskell2010

GHC.Internal.Data.Semigroup.Internal

Description

Auxiliary definitions for Semigroup

This module provides some newtype wrappers and helpers which are reexported from the Data.Semigroup module or imported directly by some other modules.

This module also provides internal definitions related to the Semigroup class some.

This module exists mostly to simplify or workaround import-graph issues.

@since base-4.11.0.0

Synopsis

Documentation

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

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.

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

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

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

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

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

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

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

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

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

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

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Generic (Dual a) Source # 
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) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Show a => Show (Dual a) Source #

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

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

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

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

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

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

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

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

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Semigroup All Source #

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

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

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

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

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Show All Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Eq All Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

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

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

Ord All Source #

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

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

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Semigroup Any Source #

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

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

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

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

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Show Any Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Eq Any Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

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

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

Ord Any Source #

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

@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
Applicative Sum Source #

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

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

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

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

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

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

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

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

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

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

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

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

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Show a => Show (Sum a) Source #

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

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

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

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

@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
Applicative Product Source #

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

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

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

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

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

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

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Num a => Semigroup (Product a) Source #

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

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

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Generic (Product a) Source # 
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) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Read a => Read (Product a) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Show a => Show (Product a) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Eq a => Eq (Product a) Source #

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

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

type Rep1 Product Source #

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

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

newtype Alt (f :: k -> Type) (a :: k) Source #

Monoid under <|>.

Alt l <> Alt r == Alt (l <|> r)

Examples

Expand
>>> Alt (Just 12) <> Alt (Just 24)
Alt {getAlt = Just 12}
>>> Alt Nothing <> Alt (Just 24)
Alt {getAlt = Just 24}

@since base-4.8.0.0

Constructors

Alt 

Fields

Instances

Instances details
Generic1 (Alt f :: k -> Type) Source # 
Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Associated Types

type Rep1 (Alt f :: k -> Type)

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

type Rep1 (Alt f :: k -> Type) = D1 ('MetaData "Alt" "GHC.Internal.Data.Semigroup.Internal" "ghc-internal" 'True) (C1 ('MetaCons "Alt" 'PrefixI 'True) (S1 ('MetaSel ('Just "getAlt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 f)))

Methods

from1 :: forall (a :: k). Alt f a -> Rep1 (Alt f) a Source #

to1 :: forall (a :: k). Rep1 (Alt f) a -> Alt f a Source #

Alternative f => Alternative (Alt f) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

empty :: Alt f a Source #

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

some :: Alt f a -> Alt f [a] Source #

many :: Alt f a -> Alt f [a] Source #

Applicative f => Applicative (Alt f) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

pure :: a -> Alt f a Source #

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

liftA2 :: (a -> b -> c) -> Alt f a -> Alt f b -> Alt f c Source #

(*>) :: Alt f a -> Alt f b -> Alt f b Source #

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

Functor f => Functor (Alt f) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

fmap :: (a -> b) -> Alt f a -> Alt f b Source #

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

Monad f => Monad (Alt f) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(>>=) :: Alt f a -> (a -> Alt f b) -> Alt f b Source #

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

return :: a -> Alt f a Source #

MonadPlus f => MonadPlus (Alt f) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

mzero :: Alt f a Source #

mplus :: Alt f a -> Alt f a -> Alt f a Source #

MonadFix f => MonadFix (Alt f) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Control.Monad.Fix

Methods

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

Foldable f => Foldable (Alt f) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Foldable

Methods

fold :: Monoid m => Alt f m -> m Source #

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

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

foldr :: (a -> b -> b) -> b -> Alt f a -> b Source #

foldr' :: (a -> b -> b) -> b -> Alt f a -> b Source #

foldl :: (b -> a -> b) -> b -> Alt f a -> b Source #

foldl' :: (b -> a -> b) -> b -> Alt f a -> b Source #

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

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

toList :: Alt f a -> [a] Source #

null :: Alt f a -> Bool Source #

length :: Alt f a -> Int Source #

elem :: Eq a => a -> Alt f a -> Bool Source #

maximum :: Ord a => Alt f a -> a Source #

minimum :: Ord a => Alt f a -> a Source #

sum :: Num a => Alt f a -> a Source #

product :: Num a => Alt f a -> a Source #

Traversable f => Traversable (Alt f) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

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

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

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

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

Alternative f => Monoid (Alt f a) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

mempty :: Alt f a Source #

mappend :: Alt f a -> Alt f a -> Alt f a Source #

mconcat :: [Alt f a] -> Alt f a Source #

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

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

(Data (f a), Data a, Typeable f) => Data (Alt f a) Source #

@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) -> Alt f a -> c (Alt f a) Source #

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

toConstr :: Alt f a -> Constr Source #

dataTypeOf :: Alt f a -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Enum (f a) => Enum (Alt f a) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

succ :: Alt f a -> Alt f a Source #

pred :: Alt f a -> Alt f a Source #

toEnum :: Int -> Alt f a Source #

fromEnum :: Alt f a -> Int Source #

enumFrom :: Alt f a -> [Alt f a] Source #

enumFromThen :: Alt f a -> Alt f a -> [Alt f a] Source #

enumFromTo :: Alt f a -> Alt f a -> [Alt f a] Source #

enumFromThenTo :: Alt f a -> Alt f a -> Alt f a -> [Alt f a] Source #

Generic (Alt f a) Source # 
Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Associated Types

type Rep (Alt f a)

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

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

Methods

from :: Alt f a -> Rep (Alt f a) x Source #

to :: Rep (Alt f a) x -> Alt f a Source #

Num (f a) => Num (Alt f a) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

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

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

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

negate :: Alt f a -> Alt f a Source #

abs :: Alt f a -> Alt f a Source #

signum :: Alt f a -> Alt f a Source #

fromInteger :: Integer -> Alt f a Source #

Read (f a) => Read (Alt f a) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Show (f a) => Show (Alt f a) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

showsPrec :: Int -> Alt f a -> ShowS Source #

show :: Alt f a -> String Source #

showList :: [Alt f a] -> ShowS Source #

Eq (f a) => Eq (Alt f a) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(==) :: Alt f a -> Alt f a -> Bool Source #

(/=) :: Alt f a -> Alt f a -> Bool Source #

Ord (f a) => Ord (Alt f a) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

compare :: Alt f a -> Alt f a -> Ordering Source #

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

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

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

(>=) :: Alt f a -> Alt f a -> Bool Source #

max :: Alt f a -> Alt f a -> Alt f a Source #

min :: Alt f a -> Alt f a -> Alt f a Source #

type Rep1 (Alt f :: k -> Type) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

type Rep1 (Alt f :: k -> Type) = D1 ('MetaData "Alt" "GHC.Internal.Data.Semigroup.Internal" "ghc-internal" 'True) (C1 ('MetaCons "Alt" 'PrefixI 'True) (S1 ('MetaSel ('Just "getAlt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 f)))
type Rep (Alt f a) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

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