monoid-extras-0.6.2: Various extra monoid-related definitions and utilities
Copyright(c) 2012-2015 diagrams-core team (see LICENSE)
LicenseBSD-style (see LICENSE)
Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Monoid.Inf

Description

Make semigroups under min or max into monoids by adjoining an element corresponding to infinity (positive or negative, respectively). These types are similar to Maybe (Min a) and Maybe (Max a) respectively, except that the Ord instance matches the Monoid instance.

Synopsis

Documentation

data Inf p a Source #

Inf p a represents the type a extended with a new "infinite" value, which is treated as either positive or negative infinity depending on the type index p. This type exists mostly for its Ord, Semigroup, and Monoid instances.

Constructors

Infinity 
Finite a 

Instances

Instances details
Foldable (Inf p) Source # 
Instance details

Defined in Data.Monoid.Inf

Methods

fold :: Monoid m => Inf p m -> m #

foldMap :: Monoid m => (a -> m) -> Inf p a -> m #

foldMap' :: Monoid m => (a -> m) -> Inf p a -> m #

foldr :: (a -> b -> b) -> b -> Inf p a -> b #

foldr' :: (a -> b -> b) -> b -> Inf p a -> b #

foldl :: (b -> a -> b) -> b -> Inf p a -> b #

foldl' :: (b -> a -> b) -> b -> Inf p a -> b #

foldr1 :: (a -> a -> a) -> Inf p a -> a #

foldl1 :: (a -> a -> a) -> Inf p a -> a #

toList :: Inf p a -> [a] #

null :: Inf p a -> Bool #

length :: Inf p a -> Int #

elem :: Eq a => a -> Inf p a -> Bool #

maximum :: Ord a => Inf p a -> a #

minimum :: Ord a => Inf p a -> a #

sum :: Num a => Inf p a -> a #

product :: Num a => Inf p a -> a #

Traversable (Inf p) Source # 
Instance details

Defined in Data.Monoid.Inf

Methods

traverse :: Applicative f => (a -> f b) -> Inf p a -> f (Inf p b) #

sequenceA :: Applicative f => Inf p (f a) -> f (Inf p a) #

mapM :: Monad m => (a -> m b) -> Inf p a -> m (Inf p b) #

sequence :: Monad m => Inf p (m a) -> m (Inf p a) #

Applicative (Inf p) Source # 
Instance details

Defined in Data.Monoid.Inf

Methods

pure :: a -> Inf p a #

(<*>) :: Inf p (a -> b) -> Inf p a -> Inf p b #

liftA2 :: (a -> b -> c) -> Inf p a -> Inf p b -> Inf p c #

(*>) :: Inf p a -> Inf p b -> Inf p b #

(<*) :: Inf p a -> Inf p b -> Inf p a #

Functor (Inf p) Source # 
Instance details

Defined in Data.Monoid.Inf

Methods

fmap :: (a -> b) -> Inf p a -> Inf p b #

(<$) :: a -> Inf p b -> Inf p a #

Monad (Inf p) Source # 
Instance details

Defined in Data.Monoid.Inf

Methods

(>>=) :: Inf p a -> (a -> Inf p b) -> Inf p b #

(>>) :: Inf p a -> Inf p b -> Inf p b #

return :: a -> Inf p a #

Bounded a => Bounded (NegInf a) Source # 
Instance details

Defined in Data.Monoid.Inf

Methods

minBound :: NegInf a #

maxBound :: NegInf a #

Bounded a => Bounded (PosInf a) Source # 
Instance details

Defined in Data.Monoid.Inf

Methods

minBound :: PosInf a #

maxBound :: PosInf a #

(Data p, Data a) => Data (Inf p a) Source # 
Instance details

Defined in Data.Monoid.Inf

Methods

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

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

toConstr :: Inf p a -> Constr #

dataTypeOf :: Inf p a -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> Inf p a -> Inf p a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Inf p a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Inf p a -> r #

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

gmapQi :: Int -> (forall d. Data d => d -> u) -> Inf p a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Inf p a -> m (Inf p a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Inf p a -> m (Inf p a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Inf p a -> m (Inf p a) #

Ord a => Monoid (Inf Neg a) Source #

An ordered type extended with negative infinity is a monoid under max, with negative infinity as the identity element.

Instance details

Defined in Data.Monoid.Inf

Methods

mempty :: Inf Neg a #

mappend :: Inf Neg a -> Inf Neg a -> Inf Neg a #

mconcat :: [Inf Neg a] -> Inf Neg a #

Ord a => Monoid (Inf Pos a) Source #

An ordered type extended with positive infinity is a monoid under min, with positive infinity as the identity element.

Instance details

Defined in Data.Monoid.Inf

Methods

mempty :: Inf Pos a #

mappend :: Inf Pos a -> Inf Pos a -> Inf Pos a #

mconcat :: [Inf Pos a] -> Inf Pos a #

Ord a => Semigroup (Inf Neg a) Source #

An ordered type extended with negative infinity is a semigroup under max.

Instance details

Defined in Data.Monoid.Inf

Methods

(<>) :: Inf Neg a -> Inf Neg a -> Inf Neg a #

sconcat :: NonEmpty (Inf Neg a) -> Inf Neg a #

stimes :: Integral b => b -> Inf Neg a -> Inf Neg a #

Ord a => Semigroup (Inf Pos a) Source #

An ordered type extended with positive infinity is a semigroup under min.

Instance details

Defined in Data.Monoid.Inf

Methods

(<>) :: Inf Pos a -> Inf Pos a -> Inf Pos a #

sconcat :: NonEmpty (Inf Pos a) -> Inf Pos a #

stimes :: Integral b => b -> Inf Pos a -> Inf Pos a #

Read a => Read (Inf p a) Source # 
Instance details

Defined in Data.Monoid.Inf

Methods

readsPrec :: Int -> ReadS (Inf p a) #

readList :: ReadS [Inf p a] #

readPrec :: ReadPrec (Inf p a) #

readListPrec :: ReadPrec [Inf p a] #

Show a => Show (Inf p a) Source # 
Instance details

Defined in Data.Monoid.Inf

Methods

showsPrec :: Int -> Inf p a -> ShowS #

show :: Inf p a -> String #

showList :: [Inf p a] -> ShowS #

Eq a => Eq (Inf p a) Source # 
Instance details

Defined in Data.Monoid.Inf

Methods

(==) :: Inf p a -> Inf p a -> Bool #

(/=) :: Inf p a -> Inf p a -> Bool #

Ord a => Ord (Inf Neg a) Source #

Negative infinity is less than any finite value.

Instance details

Defined in Data.Monoid.Inf

Methods

compare :: Inf Neg a -> Inf Neg a -> Ordering #

(<) :: Inf Neg a -> Inf Neg a -> Bool #

(<=) :: Inf Neg a -> Inf Neg a -> Bool #

(>) :: Inf Neg a -> Inf Neg a -> Bool #

(>=) :: Inf Neg a -> Inf Neg a -> Bool #

max :: Inf Neg a -> Inf Neg a -> Inf Neg a #

min :: Inf Neg a -> Inf Neg a -> Inf Neg a #

Ord a => Ord (Inf Pos a) Source #

Positive infinity is greater than any finite value.

Instance details

Defined in Data.Monoid.Inf

Methods

compare :: Inf Pos a -> Inf Pos a -> Ordering #

(<) :: Inf Pos a -> Inf Pos a -> Bool #

(<=) :: Inf Pos a -> Inf Pos a -> Bool #

(>) :: Inf Pos a -> Inf Pos a -> Bool #

(>=) :: Inf Pos a -> Inf Pos a -> Bool #

max :: Inf Pos a -> Inf Pos a -> Inf Pos a #

min :: Inf Pos a -> Inf Pos a -> Inf Pos a #

data Pos Source #

Type index indicating positive infinity.

Instances

Instances details
Bounded a => Bounded (PosInf a) Source # 
Instance details

Defined in Data.Monoid.Inf

Methods

minBound :: PosInf a #

maxBound :: PosInf a #

Ord a => Monoid (Inf Pos a) Source #

An ordered type extended with positive infinity is a monoid under min, with positive infinity as the identity element.

Instance details

Defined in Data.Monoid.Inf

Methods

mempty :: Inf Pos a #

mappend :: Inf Pos a -> Inf Pos a -> Inf Pos a #

mconcat :: [Inf Pos a] -> Inf Pos a #

Ord a => Semigroup (Inf Pos a) Source #

An ordered type extended with positive infinity is a semigroup under min.

Instance details

Defined in Data.Monoid.Inf

Methods

(<>) :: Inf Pos a -> Inf Pos a -> Inf Pos a #

sconcat :: NonEmpty (Inf Pos a) -> Inf Pos a #

stimes :: Integral b => b -> Inf Pos a -> Inf Pos a #

Ord a => Ord (Inf Pos a) Source #

Positive infinity is greater than any finite value.

Instance details

Defined in Data.Monoid.Inf

Methods

compare :: Inf Pos a -> Inf Pos a -> Ordering #

(<) :: Inf Pos a -> Inf Pos a -> Bool #

(<=) :: Inf Pos a -> Inf Pos a -> Bool #

(>) :: Inf Pos a -> Inf Pos a -> Bool #

(>=) :: Inf Pos a -> Inf Pos a -> Bool #

max :: Inf Pos a -> Inf Pos a -> Inf Pos a #

min :: Inf Pos a -> Inf Pos a -> Inf Pos a #

data Neg Source #

Type index indicating negative infinity.

Instances

Instances details
Bounded a => Bounded (NegInf a) Source # 
Instance details

Defined in Data.Monoid.Inf

Methods

minBound :: NegInf a #

maxBound :: NegInf a #

Ord a => Monoid (Inf Neg a) Source #

An ordered type extended with negative infinity is a monoid under max, with negative infinity as the identity element.

Instance details

Defined in Data.Monoid.Inf

Methods

mempty :: Inf Neg a #

mappend :: Inf Neg a -> Inf Neg a -> Inf Neg a #

mconcat :: [Inf Neg a] -> Inf Neg a #

Ord a => Semigroup (Inf Neg a) Source #

An ordered type extended with negative infinity is a semigroup under max.

Instance details

Defined in Data.Monoid.Inf

Methods

(<>) :: Inf Neg a -> Inf Neg a -> Inf Neg a #

sconcat :: NonEmpty (Inf Neg a) -> Inf Neg a #

stimes :: Integral b => b -> Inf Neg a -> Inf Neg a #

Ord a => Ord (Inf Neg a) Source #

Negative infinity is less than any finite value.

Instance details

Defined in Data.Monoid.Inf

Methods

compare :: Inf Neg a -> Inf Neg a -> Ordering #

(<) :: Inf Neg a -> Inf Neg a -> Bool #

(<=) :: Inf Neg a -> Inf Neg a -> Bool #

(>) :: Inf Neg a -> Inf Neg a -> Bool #

(>=) :: Inf Neg a -> Inf Neg a -> Bool #

max :: Inf Neg a -> Inf Neg a -> Inf Neg a #

min :: Inf Neg a -> Inf Neg a -> Inf Neg a #

type PosInf a = Inf Pos a Source #

The type a extended with positive infinity.

type NegInf a = Inf Neg a Source #

The type a extended with negative infinity.

minimum :: Ord a => [a] -> PosInf a Source #

Find the minimum of a list of values. Returns positive infinity iff the list is empty.

maximum :: Ord a => [a] -> NegInf a Source #

Find the maximum of a list of values. Returns negative infinity iff the list is empty.

Type-restricted constructors

posInfty :: PosInf a Source #

Positive infinity.

negInfty :: NegInf a Source #

Negative infinity.

posFinite :: a -> PosInf a Source #

Embed a finite value into the space of such values extended with positive infinity.

negFinite :: a -> NegInf a Source #

Embed a finite value into the space of such values extended with negative infinity.