semiring-num-1.1.0.1: Basic semiring class and instances

Safe HaskellNone
LanguageHaskell2010

Data.Semiring.Infinite

Description

This module provides various "infinite" wrappers, which can provide a detectable infinity to an otherwise non-infinite type.

Synopsis

Documentation

class HasPositiveInfinity a where Source #

A class for semirings with a concept of "infinity". It's important that this isn't regarded as the same as "bounded": x <+> positiveInfinity should probably equal positiveInfinity.

Methods

positiveInfinity :: a Source #

A positive infinite value

positiveInfinity :: RealFloat a => a Source #

A positive infinite value

isPositiveInfinity :: a -> Bool Source #

Test if a value is positive infinity.

isPositiveInfinity :: RealFloat a => a -> Bool Source #

Test if a value is positive infinity.

class HasNegativeInfinity a where Source #

A class for semirings with a concept of "negative infinity". It's important that this isn't regarded as the same as "bounded": x <+> negativeInfinity should probably equal negativeInfinity.

Methods

negativeInfinity :: a Source #

A negative infinite value

negativeInfinity :: RealFloat a => a Source #

A negative infinite value

isNegativeInfinity :: a -> Bool Source #

Test if a value is negative infinity.

isNegativeInfinity :: RealFloat a => a -> Bool Source #

Test if a value is negative infinity.

data NegativeInfinite a Source #

Adds negative infinity to a type. Useful for expressing detectable infinity in types like Integer, etc.

Constructors

NegativeInfinity 
NegFinite !a 

Instances

Functor NegativeInfinite Source # 

Methods

fmap :: (a -> b) -> NegativeInfinite a -> NegativeInfinite b #

(<$) :: a -> NegativeInfinite b -> NegativeInfinite a #

Applicative NegativeInfinite Source # 
Foldable NegativeInfinite Source # 

Methods

fold :: Monoid m => NegativeInfinite m -> m #

foldMap :: Monoid m => (a -> m) -> NegativeInfinite a -> m #

foldr :: (a -> b -> b) -> b -> NegativeInfinite a -> b #

foldr' :: (a -> b -> b) -> b -> NegativeInfinite a -> b #

foldl :: (b -> a -> b) -> b -> NegativeInfinite a -> b #

foldl' :: (b -> a -> b) -> b -> NegativeInfinite a -> b #

foldr1 :: (a -> a -> a) -> NegativeInfinite a -> a #

foldl1 :: (a -> a -> a) -> NegativeInfinite a -> a #

toList :: NegativeInfinite a -> [a] #

null :: NegativeInfinite a -> Bool #

length :: NegativeInfinite a -> Int #

elem :: Eq a => a -> NegativeInfinite a -> Bool #

maximum :: Ord a => NegativeInfinite a -> a #

minimum :: Ord a => NegativeInfinite a -> a #

sum :: Num a => NegativeInfinite a -> a #

product :: Num a => NegativeInfinite a -> a #

Traversable NegativeInfinite Source # 

Methods

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

sequenceA :: Applicative f => NegativeInfinite (f a) -> f (NegativeInfinite a) #

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

sequence :: Monad m => NegativeInfinite (m a) -> m (NegativeInfinite a) #

Generic1 NegativeInfinite Source # 

Associated Types

type Rep1 (NegativeInfinite :: * -> *) :: * -> * #

Bounded a => Bounded (NegativeInfinite a) Source # 
(Enum a, Bounded a, Eq a) => Enum (NegativeInfinite a) Source # 
Eq a => Eq (NegativeInfinite a) Source # 
Num a => Num (NegativeInfinite a) Source # 
Ord a => Ord (NegativeInfinite a) Source # 
Read a => Read (NegativeInfinite a) Source # 
Show a => Show (NegativeInfinite a) Source # 
Generic (NegativeInfinite a) Source # 

Associated Types

type Rep (NegativeInfinite a) :: * -> * #

Monoid a => Monoid (NegativeInfinite a) Source # 
Storable a => Storable (NegativeInfinite a) Source # 
HasNegativeInfinity (NegativeInfinite a) Source # 
DetectableZero a => DetectableZero (NegativeInfinite a) Source # 
DetectableZero a => Semiring (NegativeInfinite a) Source #

Doesn't follow annihilateL or mulDistribR.

type Rep1 NegativeInfinite Source # 
type Rep1 NegativeInfinite = D1 (MetaData "NegativeInfinite" "Data.Semiring.Infinite" "semiring-num-1.1.0.1-3LgHbMC5oj7KROaTeTae0F" False) ((:+:) (C1 (MetaCons "NegativeInfinity" PrefixI False) U1) (C1 (MetaCons "NegFinite" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1)))
type Rep (NegativeInfinite a) Source # 
type Rep (NegativeInfinite a) = D1 (MetaData "NegativeInfinite" "Data.Semiring.Infinite" "semiring-num-1.1.0.1-3LgHbMC5oj7KROaTeTae0F" False) ((:+:) (C1 (MetaCons "NegativeInfinity" PrefixI False) U1) (C1 (MetaCons "NegFinite" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a))))

data PositiveInfinite a Source #

Adds positive infinity to a type. Useful for expressing detectable infinity in types like Integer, etc.

Constructors

PosFinite !a 
PositiveInfinity 

Instances

Functor PositiveInfinite Source # 

Methods

fmap :: (a -> b) -> PositiveInfinite a -> PositiveInfinite b #

(<$) :: a -> PositiveInfinite b -> PositiveInfinite a #

Applicative PositiveInfinite Source # 
Foldable PositiveInfinite Source # 

Methods

fold :: Monoid m => PositiveInfinite m -> m #

foldMap :: Monoid m => (a -> m) -> PositiveInfinite a -> m #

foldr :: (a -> b -> b) -> b -> PositiveInfinite a -> b #

foldr' :: (a -> b -> b) -> b -> PositiveInfinite a -> b #

foldl :: (b -> a -> b) -> b -> PositiveInfinite a -> b #

foldl' :: (b -> a -> b) -> b -> PositiveInfinite a -> b #

foldr1 :: (a -> a -> a) -> PositiveInfinite a -> a #

foldl1 :: (a -> a -> a) -> PositiveInfinite a -> a #

toList :: PositiveInfinite a -> [a] #

null :: PositiveInfinite a -> Bool #

length :: PositiveInfinite a -> Int #

elem :: Eq a => a -> PositiveInfinite a -> Bool #

maximum :: Ord a => PositiveInfinite a -> a #

minimum :: Ord a => PositiveInfinite a -> a #

sum :: Num a => PositiveInfinite a -> a #

product :: Num a => PositiveInfinite a -> a #

Traversable PositiveInfinite Source # 

Methods

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

sequenceA :: Applicative f => PositiveInfinite (f a) -> f (PositiveInfinite a) #

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

sequence :: Monad m => PositiveInfinite (m a) -> m (PositiveInfinite a) #

Generic1 PositiveInfinite Source # 

Associated Types

type Rep1 (PositiveInfinite :: * -> *) :: * -> * #

Bounded a => Bounded (PositiveInfinite a) Source # 
(Enum a, Bounded a, Eq a) => Enum (PositiveInfinite a) Source # 
Eq a => Eq (PositiveInfinite a) Source # 
Num a => Num (PositiveInfinite a) Source # 
Ord a => Ord (PositiveInfinite a) Source # 
Read a => Read (PositiveInfinite a) Source # 
Show a => Show (PositiveInfinite a) Source # 
Generic (PositiveInfinite a) Source # 

Associated Types

type Rep (PositiveInfinite a) :: * -> * #

Monoid a => Monoid (PositiveInfinite a) Source # 
Storable a => Storable (PositiveInfinite a) Source # 
HasPositiveInfinity (PositiveInfinite a) Source # 
DetectableZero a => DetectableZero (PositiveInfinite a) Source # 
DetectableZero a => StarSemiring (PositiveInfinite a) Source # 
DetectableZero a => Semiring (PositiveInfinite a) Source #

Only lawful when used with positive numbers.

type Rep1 PositiveInfinite Source # 
type Rep1 PositiveInfinite = D1 (MetaData "PositiveInfinite" "Data.Semiring.Infinite" "semiring-num-1.1.0.1-3LgHbMC5oj7KROaTeTae0F" False) ((:+:) (C1 (MetaCons "PosFinite" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1)) (C1 (MetaCons "PositiveInfinity" PrefixI False) U1))
type Rep (PositiveInfinite a) Source # 
type Rep (PositiveInfinite a) = D1 (MetaData "PositiveInfinite" "Data.Semiring.Infinite" "semiring-num-1.1.0.1-3LgHbMC5oj7KROaTeTae0F" False) ((:+:) (C1 (MetaCons "PosFinite" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a))) (C1 (MetaCons "PositiveInfinity" PrefixI False) U1))

data Infinite a Source #

Adds positive and negative infinity to a type. Useful for expressing detectable infinity in types like Integer, etc.

Constructors

Negative 
Finite !a 
Positive 

Instances

Functor Infinite Source # 

Methods

fmap :: (a -> b) -> Infinite a -> Infinite b #

(<$) :: a -> Infinite b -> Infinite a #

Applicative Infinite Source # 

Methods

pure :: a -> Infinite a #

(<*>) :: Infinite (a -> b) -> Infinite a -> Infinite b #

(*>) :: Infinite a -> Infinite b -> Infinite b #

(<*) :: Infinite a -> Infinite b -> Infinite a #

Foldable Infinite Source # 

Methods

fold :: Monoid m => Infinite m -> m #

foldMap :: Monoid m => (a -> m) -> Infinite a -> m #

foldr :: (a -> b -> b) -> b -> Infinite a -> b #

foldr' :: (a -> b -> b) -> b -> Infinite a -> b #

foldl :: (b -> a -> b) -> b -> Infinite a -> b #

foldl' :: (b -> a -> b) -> b -> Infinite a -> b #

foldr1 :: (a -> a -> a) -> Infinite a -> a #

foldl1 :: (a -> a -> a) -> Infinite a -> a #

toList :: Infinite a -> [a] #

null :: Infinite a -> Bool #

length :: Infinite a -> Int #

elem :: Eq a => a -> Infinite a -> Bool #

maximum :: Ord a => Infinite a -> a #

minimum :: Ord a => Infinite a -> a #

sum :: Num a => Infinite a -> a #

product :: Num a => Infinite a -> a #

Traversable Infinite Source # 

Methods

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

sequenceA :: Applicative f => Infinite (f a) -> f (Infinite a) #

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

sequence :: Monad m => Infinite (m a) -> m (Infinite a) #

Generic1 Infinite Source # 

Associated Types

type Rep1 (Infinite :: * -> *) :: * -> * #

Methods

from1 :: Infinite a -> Rep1 Infinite a #

to1 :: Rep1 Infinite a -> Infinite a #

Bounded (Infinite a) Source # 
(Enum a, Bounded a, Eq a) => Enum (Infinite a) Source # 
Eq a => Eq (Infinite a) Source # 

Methods

(==) :: Infinite a -> Infinite a -> Bool #

(/=) :: Infinite a -> Infinite a -> Bool #

Num a => Num (Infinite a) Source # 
Ord a => Ord (Infinite a) Source # 

Methods

compare :: Infinite a -> Infinite a -> Ordering #

(<) :: Infinite a -> Infinite a -> Bool #

(<=) :: Infinite a -> Infinite a -> Bool #

(>) :: Infinite a -> Infinite a -> Bool #

(>=) :: Infinite a -> Infinite a -> Bool #

max :: Infinite a -> Infinite a -> Infinite a #

min :: Infinite a -> Infinite a -> Infinite a #

Read a => Read (Infinite a) Source # 
Show a => Show (Infinite a) Source # 

Methods

showsPrec :: Int -> Infinite a -> ShowS #

show :: Infinite a -> String #

showList :: [Infinite a] -> ShowS #

Generic (Infinite a) Source # 

Associated Types

type Rep (Infinite a) :: * -> * #

Methods

from :: Infinite a -> Rep (Infinite a) x #

to :: Rep (Infinite a) x -> Infinite a #

Monoid a => Monoid (Infinite a) Source # 

Methods

mempty :: Infinite a #

mappend :: Infinite a -> Infinite a -> Infinite a #

mconcat :: [Infinite a] -> Infinite a #

Storable a => Storable (Infinite a) Source # 

Methods

sizeOf :: Infinite a -> Int #

alignment :: Infinite a -> Int #

peekElemOff :: Ptr (Infinite a) -> Int -> IO (Infinite a) #

pokeElemOff :: Ptr (Infinite a) -> Int -> Infinite a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Infinite a) #

pokeByteOff :: Ptr b -> Int -> Infinite a -> IO () #

peek :: Ptr (Infinite a) -> IO (Infinite a) #

poke :: Ptr (Infinite a) -> Infinite a -> IO () #

HasNegativeInfinity (Infinite a) Source # 
HasPositiveInfinity (Infinite a) Source # 
(DetectableZero a, Ord a) => DetectableZero (Infinite a) Source # 

Methods

isZero :: Infinite a -> Bool Source #

(DetectableZero a, Ord a) => Semiring (Infinite a) Source #

Not distributive.

type Rep1 Infinite Source # 
type Rep1 Infinite = D1 (MetaData "Infinite" "Data.Semiring.Infinite" "semiring-num-1.1.0.1-3LgHbMC5oj7KROaTeTae0F" False) ((:+:) (C1 (MetaCons "Negative" PrefixI False) U1) ((:+:) (C1 (MetaCons "Finite" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1)) (C1 (MetaCons "Positive" PrefixI False) U1)))
type Rep (Infinite a) Source # 
type Rep (Infinite a) = D1 (MetaData "Infinite" "Data.Semiring.Infinite" "semiring-num-1.1.0.1-3LgHbMC5oj7KROaTeTae0F" False) ((:+:) (C1 (MetaCons "Negative" PrefixI False) U1) ((:+:) (C1 (MetaCons "Finite" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a))) (C1 (MetaCons "Positive" PrefixI False) U1)))