Copyright | (c) 2012-2015 diagrams-core team (see LICENSE) |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | diagrams-discuss@googlegroups.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Documentation
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.
Instances
Foldable (Inf p) Source # | |
Defined in Data.Monoid.Inf 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 # elem :: Eq a => a -> Inf p a -> Bool # maximum :: Ord a => Inf p a -> a # minimum :: Ord a => Inf p a -> a # | |
Traversable (Inf p) Source # | |
Applicative (Inf p) Source # | |
Functor (Inf p) Source # | |
Monad (Inf p) Source # | |
Bounded a => Bounded (NegInf a) Source # | |
Bounded a => Bounded (PosInf a) Source # | |
(Data p, Data a) => Data (Inf p a) Source # | |
Defined in Data.Monoid.Inf 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
|
Ord a => Monoid (Inf Pos a) Source # | An ordered type extended with positive infinity is a monoid under
|
Ord a => Semigroup (Inf Neg a) Source # | An ordered type extended with negative infinity is a semigroup
under |
Ord a => Semigroup (Inf Pos a) Source # | An ordered type extended with positive infinity is a semigroup
under |
Read a => Read (Inf p a) Source # | |
Show a => Show (Inf p a) Source # | |
Eq a => Eq (Inf p a) Source # | |
Ord a => Ord (Inf Neg a) Source # | Negative infinity is less than any finite value. |
Defined in Data.Monoid.Inf | |
Ord a => Ord (Inf Pos a) Source # | Positive infinity is greater than any finite value. |
Defined in Data.Monoid.Inf |
Type index indicating positive infinity.
Instances
Bounded a => Bounded (PosInf a) Source # | |
Ord a => Monoid (Inf Pos a) Source # | An ordered type extended with positive infinity is a monoid under
|
Ord a => Semigroup (Inf Pos a) Source # | An ordered type extended with positive infinity is a semigroup
under |
Ord a => Ord (Inf Pos a) Source # | Positive infinity is greater than any finite value. |
Defined in Data.Monoid.Inf |
Type index indicating negative infinity.
Instances
Bounded a => Bounded (NegInf a) Source # | |
Ord a => Monoid (Inf Neg a) Source # | An ordered type extended with negative infinity is a monoid under
|
Ord a => Semigroup (Inf Neg a) Source # | An ordered type extended with negative infinity is a semigroup
under |
Ord a => Ord (Inf Neg a) Source # | Negative infinity is less than any finite value. |
Defined in Data.Monoid.Inf |
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.