{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module Data.Monoid.Inf
( Inf(..)
, Pos, Neg
, PosInf, NegInf
, minimum, maximum
, posInfty, negInfty
, posFinite, negFinite
) where
import Control.Applicative (Applicative(..), liftA2)
import Data.Data
import Data.Semigroup
import Prelude hiding (maximum, minimum)
import qualified Prelude as P
import Data.Foldable (Foldable)
import Data.Traversable (Traversable)
data Pos
data Neg
data Inf p a = Infinity | Finite a
deriving (Typeable (Inf p a)
DataType
Constr
Typeable (Inf p a)
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Inf p a -> c (Inf p a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Inf p a))
-> (Inf p a -> Constr)
-> (Inf p a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Inf p a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Inf p a)))
-> ((forall b. Data b => b -> b) -> Inf p a -> Inf p a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Inf p a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Inf p a -> r)
-> (forall u. (forall d. Data d => d -> u) -> Inf p a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Inf p a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Inf p a -> m (Inf p a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Inf p a -> m (Inf p a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Inf p a -> m (Inf p a))
-> Data (Inf p a)
Inf p a -> DataType
Inf p a -> Constr
(forall b. Data b => b -> b) -> Inf p a -> Inf p a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Inf p a -> c (Inf p a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Inf p a)
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Inf p a))
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Inf p a -> u
forall u. (forall d. Data d => d -> u) -> Inf p a -> [u]
forall p a. (Data p, Data a) => Typeable (Inf p a)
forall p a. (Data p, Data a) => Inf p a -> DataType
forall p a. (Data p, Data a) => Inf p a -> Constr
forall p a.
(Data p, Data a) =>
(forall b. Data b => b -> b) -> Inf p a -> Inf p a
forall p a u.
(Data p, Data a) =>
Int -> (forall d. Data d => d -> u) -> Inf p a -> u
forall p a u.
(Data p, Data a) =>
(forall d. Data d => d -> u) -> Inf p a -> [u]
forall p a r r'.
(Data p, Data a) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Inf p a -> r
forall p a r r'.
(Data p, Data a) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Inf p a -> r
forall p a (m :: * -> *).
(Data p, Data a, Monad m) =>
(forall d. Data d => d -> m d) -> Inf p a -> m (Inf p a)
forall p a (m :: * -> *).
(Data p, Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Inf p a -> m (Inf p a)
forall p a (c :: * -> *).
(Data p, Data a) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Inf p a)
forall p a (c :: * -> *).
(Data p, Data a) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Inf p a -> c (Inf p a)
forall p a (t :: * -> *) (c :: * -> *).
(Data p, Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Inf p a))
forall p a (t :: * -> * -> *) (c :: * -> *).
(Data p, Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Inf p a))
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Inf p a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Inf p a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Inf p a -> m (Inf p a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Inf p a -> m (Inf p a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Inf p a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Inf p a -> c (Inf p a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Inf p a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Inf p a))
$cFinite :: Constr
$cInfinity :: Constr
$tInf :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Inf p a -> m (Inf p a)
$cgmapMo :: forall p a (m :: * -> *).
(Data p, Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Inf p a -> m (Inf p a)
gmapMp :: (forall d. Data d => d -> m d) -> Inf p a -> m (Inf p a)
$cgmapMp :: forall p a (m :: * -> *).
(Data p, Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Inf p a -> m (Inf p a)
gmapM :: (forall d. Data d => d -> m d) -> Inf p a -> m (Inf p a)
$cgmapM :: forall p a (m :: * -> *).
(Data p, Data a, Monad m) =>
(forall d. Data d => d -> m d) -> Inf p a -> m (Inf p a)
gmapQi :: Int -> (forall d. Data d => d -> u) -> Inf p a -> u
$cgmapQi :: forall p a u.
(Data p, Data a) =>
Int -> (forall d. Data d => d -> u) -> Inf p a -> u
gmapQ :: (forall d. Data d => d -> u) -> Inf p a -> [u]
$cgmapQ :: forall p a u.
(Data p, Data a) =>
(forall d. Data d => d -> u) -> Inf p a -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Inf p a -> r
$cgmapQr :: forall p a r r'.
(Data p, Data a) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Inf p a -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Inf p a -> r
$cgmapQl :: forall p a r r'.
(Data p, Data a) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Inf p a -> r
gmapT :: (forall b. Data b => b -> b) -> Inf p a -> Inf p a
$cgmapT :: forall p a.
(Data p, Data a) =>
(forall b. Data b => b -> b) -> Inf p a -> Inf p a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Inf p a))
$cdataCast2 :: forall p a (t :: * -> * -> *) (c :: * -> *).
(Data p, Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Inf p a))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (Inf p a))
$cdataCast1 :: forall p a (t :: * -> *) (c :: * -> *).
(Data p, Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Inf p a))
dataTypeOf :: Inf p a -> DataType
$cdataTypeOf :: forall p a. (Data p, Data a) => Inf p a -> DataType
toConstr :: Inf p a -> Constr
$ctoConstr :: forall p a. (Data p, Data a) => Inf p a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Inf p a)
$cgunfold :: forall p a (c :: * -> *).
(Data p, Data a) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Inf p a)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Inf p a -> c (Inf p a)
$cgfoldl :: forall p a (c :: * -> *).
(Data p, Data a) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Inf p a -> c (Inf p a)
$cp1Data :: forall p a. (Data p, Data a) => Typeable (Inf p a)
Data, Typeable, Int -> Inf p a -> ShowS
[Inf p a] -> ShowS
Inf p a -> String
(Int -> Inf p a -> ShowS)
-> (Inf p a -> String) -> ([Inf p a] -> ShowS) -> Show (Inf p a)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall p a. Show a => Int -> Inf p a -> ShowS
forall p a. Show a => [Inf p a] -> ShowS
forall p a. Show a => Inf p a -> String
showList :: [Inf p a] -> ShowS
$cshowList :: forall p a. Show a => [Inf p a] -> ShowS
show :: Inf p a -> String
$cshow :: forall p a. Show a => Inf p a -> String
showsPrec :: Int -> Inf p a -> ShowS
$cshowsPrec :: forall p a. Show a => Int -> Inf p a -> ShowS
Show, ReadPrec [Inf p a]
ReadPrec (Inf p a)
Int -> ReadS (Inf p a)
ReadS [Inf p a]
(Int -> ReadS (Inf p a))
-> ReadS [Inf p a]
-> ReadPrec (Inf p a)
-> ReadPrec [Inf p a]
-> Read (Inf p a)
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
forall p a. Read a => ReadPrec [Inf p a]
forall p a. Read a => ReadPrec (Inf p a)
forall p a. Read a => Int -> ReadS (Inf p a)
forall p a. Read a => ReadS [Inf p a]
readListPrec :: ReadPrec [Inf p a]
$creadListPrec :: forall p a. Read a => ReadPrec [Inf p a]
readPrec :: ReadPrec (Inf p a)
$creadPrec :: forall p a. Read a => ReadPrec (Inf p a)
readList :: ReadS [Inf p a]
$creadList :: forall p a. Read a => ReadS [Inf p a]
readsPrec :: Int -> ReadS (Inf p a)
$creadsPrec :: forall p a. Read a => Int -> ReadS (Inf p a)
Read, Inf p a -> Inf p a -> Bool
(Inf p a -> Inf p a -> Bool)
-> (Inf p a -> Inf p a -> Bool) -> Eq (Inf p a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall p a. Eq a => Inf p a -> Inf p a -> Bool
/= :: Inf p a -> Inf p a -> Bool
$c/= :: forall p a. Eq a => Inf p a -> Inf p a -> Bool
== :: Inf p a -> Inf p a -> Bool
$c== :: forall p a. Eq a => Inf p a -> Inf p a -> Bool
Eq, a -> Inf p b -> Inf p a
(a -> b) -> Inf p a -> Inf p b
(forall a b. (a -> b) -> Inf p a -> Inf p b)
-> (forall a b. a -> Inf p b -> Inf p a) -> Functor (Inf p)
forall a b. a -> Inf p b -> Inf p a
forall a b. (a -> b) -> Inf p a -> Inf p b
forall p a b. a -> Inf p b -> Inf p a
forall p a b. (a -> b) -> Inf p a -> Inf p b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Inf p b -> Inf p a
$c<$ :: forall p a b. a -> Inf p b -> Inf p a
fmap :: (a -> b) -> Inf p a -> Inf p b
$cfmap :: forall p a b. (a -> b) -> Inf p a -> Inf p b
Functor, Inf p a -> Bool
(a -> m) -> Inf p a -> m
(a -> b -> b) -> b -> Inf p a -> b
(forall m. Monoid m => Inf p m -> m)
-> (forall m a. Monoid m => (a -> m) -> Inf p a -> m)
-> (forall m a. Monoid m => (a -> m) -> Inf p a -> m)
-> (forall a b. (a -> b -> b) -> b -> Inf p a -> b)
-> (forall a b. (a -> b -> b) -> b -> Inf p a -> b)
-> (forall b a. (b -> a -> b) -> b -> Inf p a -> b)
-> (forall b a. (b -> a -> b) -> b -> Inf p a -> b)
-> (forall a. (a -> a -> a) -> Inf p a -> a)
-> (forall a. (a -> a -> a) -> Inf p a -> a)
-> (forall a. Inf p a -> [a])
-> (forall a. Inf p a -> Bool)
-> (forall a. Inf p a -> Int)
-> (forall a. Eq a => a -> Inf p a -> Bool)
-> (forall a. Ord a => Inf p a -> a)
-> (forall a. Ord a => Inf p a -> a)
-> (forall a. Num a => Inf p a -> a)
-> (forall a. Num a => Inf p a -> a)
-> Foldable (Inf p)
forall a. Eq a => a -> Inf p a -> Bool
forall a. Num a => Inf p a -> a
forall a. Ord a => Inf p a -> a
forall m. Monoid m => Inf p m -> m
forall a. Inf p a -> Bool
forall a. Inf p a -> Int
forall a. Inf p a -> [a]
forall a. (a -> a -> a) -> Inf p a -> a
forall p a. Eq a => a -> Inf p a -> Bool
forall p a. Num a => Inf p a -> a
forall p a. Ord a => Inf p a -> a
forall m a. Monoid m => (a -> m) -> Inf p a -> m
forall p m. Monoid m => Inf p m -> m
forall p a. Inf p a -> Bool
forall p a. Inf p a -> Int
forall p a. Inf p a -> [a]
forall b a. (b -> a -> b) -> b -> Inf p a -> b
forall a b. (a -> b -> b) -> b -> Inf p a -> b
forall p a. (a -> a -> a) -> Inf p a -> a
forall p m a. Monoid m => (a -> m) -> Inf p a -> m
forall p b a. (b -> a -> b) -> b -> Inf p a -> b
forall p a b. (a -> b -> b) -> b -> Inf p a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: Inf p a -> a
$cproduct :: forall p a. Num a => Inf p a -> a
sum :: Inf p a -> a
$csum :: forall p a. Num a => Inf p a -> a
minimum :: Inf p a -> a
$cminimum :: forall p a. Ord a => Inf p a -> a
maximum :: Inf p a -> a
$cmaximum :: forall p a. Ord a => Inf p a -> a
elem :: a -> Inf p a -> Bool
$celem :: forall p a. Eq a => a -> Inf p a -> Bool
length :: Inf p a -> Int
$clength :: forall p a. Inf p a -> Int
null :: Inf p a -> Bool
$cnull :: forall p a. Inf p a -> Bool
toList :: Inf p a -> [a]
$ctoList :: forall p a. Inf p a -> [a]
foldl1 :: (a -> a -> a) -> Inf p a -> a
$cfoldl1 :: forall p a. (a -> a -> a) -> Inf p a -> a
foldr1 :: (a -> a -> a) -> Inf p a -> a
$cfoldr1 :: forall p a. (a -> a -> a) -> Inf p a -> a
foldl' :: (b -> a -> b) -> b -> Inf p a -> b
$cfoldl' :: forall p b a. (b -> a -> b) -> b -> Inf p a -> b
foldl :: (b -> a -> b) -> b -> Inf p a -> b
$cfoldl :: forall p b a. (b -> a -> b) -> b -> Inf p a -> b
foldr' :: (a -> b -> b) -> b -> Inf p a -> b
$cfoldr' :: forall p a b. (a -> b -> b) -> b -> Inf p a -> b
foldr :: (a -> b -> b) -> b -> Inf p a -> b
$cfoldr :: forall p a b. (a -> b -> b) -> b -> Inf p a -> b
foldMap' :: (a -> m) -> Inf p a -> m
$cfoldMap' :: forall p m a. Monoid m => (a -> m) -> Inf p a -> m
foldMap :: (a -> m) -> Inf p a -> m
$cfoldMap :: forall p m a. Monoid m => (a -> m) -> Inf p a -> m
fold :: Inf p m -> m
$cfold :: forall p m. Monoid m => Inf p m -> m
Foldable,
Functor (Inf p)
Foldable (Inf p)
Functor (Inf p)
-> Foldable (Inf p)
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Inf p a -> f (Inf p b))
-> (forall (f :: * -> *) a.
Applicative f =>
Inf p (f a) -> f (Inf p a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Inf p a -> m (Inf p b))
-> (forall (m :: * -> *) a. Monad m => Inf p (m a) -> m (Inf p a))
-> Traversable (Inf p)
(a -> f b) -> Inf p a -> f (Inf p b)
forall p. Functor (Inf p)
forall p. Foldable (Inf p)
forall p (m :: * -> *) a. Monad m => Inf p (m a) -> m (Inf p a)
forall p (f :: * -> *) a.
Applicative f =>
Inf p (f a) -> f (Inf p a)
forall p (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Inf p a -> m (Inf p b)
forall p (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Inf p a -> f (Inf p b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => Inf p (m a) -> m (Inf p a)
forall (f :: * -> *) a. Applicative f => Inf p (f a) -> f (Inf p a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Inf p a -> m (Inf p b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Inf p a -> f (Inf p b)
sequence :: Inf p (m a) -> m (Inf p a)
$csequence :: forall p (m :: * -> *) a. Monad m => Inf p (m a) -> m (Inf p a)
mapM :: (a -> m b) -> Inf p a -> m (Inf p b)
$cmapM :: forall p (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Inf p a -> m (Inf p b)
sequenceA :: Inf p (f a) -> f (Inf p a)
$csequenceA :: forall p (f :: * -> *) a.
Applicative f =>
Inf p (f a) -> f (Inf p a)
traverse :: (a -> f b) -> Inf p a -> f (Inf p b)
$ctraverse :: forall p (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Inf p a -> f (Inf p b)
$cp2Traversable :: forall p. Foldable (Inf p)
$cp1Traversable :: forall p. Functor (Inf p)
Traversable)
type PosInf a = Inf Pos a
type NegInf a = Inf Neg a
instance Ord a => Ord (Inf Pos a) where
compare :: Inf Pos a -> Inf Pos a -> Ordering
compare Inf Pos a
Infinity Inf Pos a
Infinity = Ordering
EQ
compare Inf Pos a
Infinity Finite{} = Ordering
GT
compare Finite{} Inf Pos a
Infinity = Ordering
LT
compare (Finite a
a) (Finite a
b) = a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare a
a a
b
instance Ord a => Ord (Inf Neg a) where
compare :: Inf Neg a -> Inf Neg a -> Ordering
compare Inf Neg a
Infinity Inf Neg a
Infinity = Ordering
EQ
compare Inf Neg a
Infinity Finite{} = Ordering
LT
compare Finite{} Inf Neg a
Infinity = Ordering
GT
compare (Finite a
a) (Finite a
b) = a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare a
a a
b
instance Ord a => Semigroup (Inf Pos a) where
<> :: Inf Pos a -> Inf Pos a -> Inf Pos a
(<>) = Inf Pos a -> Inf Pos a -> Inf Pos a
forall a. Ord a => a -> a -> a
min
instance Ord a => Semigroup (Inf Neg a) where
<> :: Inf Neg a -> Inf Neg a -> Inf Neg a
(<>) = Inf Neg a -> Inf Neg a -> Inf Neg a
forall a. Ord a => a -> a -> a
max
instance Ord a => Monoid (Inf Pos a) where
mempty :: Inf Pos a
mempty = Inf Pos a
forall p a. Inf p a
Infinity
mappend :: Inf Pos a -> Inf Pos a -> Inf Pos a
mappend = Inf Pos a -> Inf Pos a -> Inf Pos a
forall a. Semigroup a => a -> a -> a
(<>)
instance Ord a => Monoid (Inf Neg a) where
mempty :: Inf Neg a
mempty = Inf Neg a
forall p a. Inf p a
Infinity
mappend :: Inf Neg a -> Inf Neg a -> Inf Neg a
mappend = Inf Neg a -> Inf Neg a -> Inf Neg a
forall a. Semigroup a => a -> a -> a
(<>)
instance Applicative (Inf p) where
pure :: a -> Inf p a
pure = a -> Inf p a
forall p a. a -> Inf p a
Finite
Inf p (a -> b)
Infinity <*> :: Inf p (a -> b) -> Inf p a -> Inf p b
<*> Inf p a
_ = Inf p b
forall p a. Inf p a
Infinity
Inf p (a -> b)
_ <*> Inf p a
Infinity = Inf p b
forall p a. Inf p a
Infinity
Finite a -> b
f <*> Finite a
x = b -> Inf p b
forall p a. a -> Inf p a
Finite (b -> Inf p b) -> b -> Inf p b
forall a b. (a -> b) -> a -> b
$ a -> b
f a
x
instance Monad (Inf p) where
Inf p a
Infinity >>= :: Inf p a -> (a -> Inf p b) -> Inf p b
>>= a -> Inf p b
_ = Inf p b
forall p a. Inf p a
Infinity
Finite a
x >>= a -> Inf p b
f = a -> Inf p b
f a
x
return :: a -> Inf p a
return = a -> Inf p a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
instance Bounded a => Bounded (NegInf a) where
minBound :: NegInf a
minBound = NegInf a
forall p a. Inf p a
Infinity
maxBound :: NegInf a
maxBound = a -> NegInf a
forall p a. a -> Inf p a
Finite a
forall a. Bounded a => a
maxBound
instance Bounded a => Bounded (PosInf a) where
minBound :: PosInf a
minBound = a -> PosInf a
forall p a. a -> Inf p a
Finite a
forall a. Bounded a => a
minBound
maxBound :: PosInf a
maxBound = PosInf a
forall p a. Inf p a
Infinity
minimum :: Ord a => [a] -> PosInf a
minimum :: [a] -> PosInf a
minimum [a]
xs = [PosInf a] -> PosInf a
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
P.minimum (PosInf a
forall p a. Inf p a
Infinity PosInf a -> [PosInf a] -> [PosInf a]
forall a. a -> [a] -> [a]
: (a -> PosInf a) -> [a] -> [PosInf a]
forall a b. (a -> b) -> [a] -> [b]
map a -> PosInf a
forall p a. a -> Inf p a
Finite [a]
xs)
maximum :: Ord a => [a] -> NegInf a
maximum :: [a] -> NegInf a
maximum [a]
xs = [NegInf a] -> NegInf a
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
P.maximum (NegInf a
forall p a. Inf p a
Infinity NegInf a -> [NegInf a] -> [NegInf a]
forall a. a -> [a] -> [a]
: (a -> NegInf a) -> [a] -> [NegInf a]
forall a b. (a -> b) -> [a] -> [b]
map a -> NegInf a
forall p a. a -> Inf p a
Finite [a]
xs)
posInfty :: PosInf a
negInfty :: NegInf a
posFinite :: a -> PosInf a
negFinite :: a -> NegInf a
posInfty :: PosInf a
posInfty = PosInf a
forall p a. Inf p a
Infinity
negInfty :: NegInf a
negInfty = NegInf a
forall p a. Inf p a
Infinity
posFinite :: a -> PosInf a
posFinite = a -> PosInf a
forall p a. a -> Inf p a
Finite
negFinite :: a -> NegInf a
negFinite = a -> NegInf a
forall p a. a -> Inf p a
Finite