semirings-0.3.1.2: two monoids as one, in holy haskimony

Safe HaskellNone
LanguageHaskell98

Data.Semiring.Tropical

Description

A tropical semiring is an extension of another totally ordered semiring with the operations of minimum or maximum as addition. The extended semiring is given positive or negative infinity as its zero element, so that the following hold:

plus Infinity y = y
plus x Infinity = x

i.e., In the max-plus tropical semiring (where plus is max), Infinity unifies with the typical interpretation of negative infinity, and thus it is the identity for the maximum, and in the min-plus tropical semiring (where plus is min), Infinity unifies with the typical interpretation of positive infinity, and thus it is the identity for the minimum.

Synopsis

Documentation

data Tropical (e :: Extrema) a Source #

The tropical semiring.

Tropical 'Minima a is equivalent to the semiring \( (a \cup \{+\infty\}, \oplus, \otimes) \), where \( x \oplus y = min\{x,y\}\) and \(x \otimes y = x + y\).

Tropical 'Maxima a is equivalent to the semiring \( (a \cup \{-\infty\}, \oplus, \otimes) \), where \( x \oplus y = max\{x,y\}\) and \(x \otimes y = x + y\).

In literature, the Semiring instance of the Tropical semiring lifts the underlying semiring's additive structure. One might ask why this lifting doesn't instead witness a Monoid, since we only lift zero and plus - the reason is that usually the additive structure of a semiring is monotonic, i.e. a + (min b c) == min (a + b) (a + c), but in general this is not true. For example, lifting Product Word into Tropical is lawful, but Product Int is not, lacking distributivity: (-1) * (min 0 1) /= min ((-1) * 0) ((-1) * 1). So, we deviate from literature and instead witness the lifting of a Monoid, so the user must take care to ensure that their implementation of mappend is monotonic.

Constructors

Infinity 
Tropical a 
Instances
Eq a => Eq (Tropical e a) Source # 
Instance details

Defined in Data.Semiring.Tropical

Methods

(==) :: Tropical e a -> Tropical e a -> Bool #

(/=) :: Tropical e a -> Tropical e a -> Bool #

(Typeable e, Data a) => Data (Tropical e a) Source # 
Instance details

Defined in Data.Semiring.Tropical

Methods

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

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

toConstr :: Tropical e a -> Constr #

dataTypeOf :: Tropical e a -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> Tropical e a -> Tropical e a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tropical e a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tropical e a -> r #

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

gmapQi :: Int -> (forall d. Data d => d -> u) -> Tropical e a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tropical e a -> m (Tropical e a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tropical e a -> m (Tropical e a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tropical e a -> m (Tropical e a) #

(Ord a, Extremum e) => Ord (Tropical e a) Source # 
Instance details

Defined in Data.Semiring.Tropical

Methods

compare :: Tropical e a -> Tropical e a -> Ordering #

(<) :: Tropical e a -> Tropical e a -> Bool #

(<=) :: Tropical e a -> Tropical e a -> Bool #

(>) :: Tropical e a -> Tropical e a -> Bool #

(>=) :: Tropical e a -> Tropical e a -> Bool #

max :: Tropical e a -> Tropical e a -> Tropical e a #

min :: Tropical e a -> Tropical e a -> Tropical e a #

Read a => Read (Tropical e a) Source # 
Instance details

Defined in Data.Semiring.Tropical

Show a => Show (Tropical e a) Source # 
Instance details

Defined in Data.Semiring.Tropical

Methods

showsPrec :: Int -> Tropical e a -> ShowS #

show :: Tropical e a -> String #

showList :: [Tropical e a] -> ShowS #

(Ord a, Monoid a, Extremum e) => Semiring (Tropical e a) Source # 
Instance details

Defined in Data.Semiring.Tropical

Methods

plus :: Tropical e a -> Tropical e a -> Tropical e a Source #

zero :: Tropical e a Source #

times :: Tropical e a -> Tropical e a -> Tropical e a Source #

one :: Tropical e a Source #

(Ord a, Monoid a, Extremum e) => Star (Tropical e a) Source # 
Instance details

Defined in Data.Semiring.Tropical

Methods

star :: Tropical e a -> Tropical e a Source #

aplus :: Tropical e a -> Tropical e a Source #

data Extrema Source #

A datatype to be used at the kind-level. Its only purpose is to decide the ordering for the tropical semiring in a type-safe way.

Constructors

Minima 
Maxima 

class Extremum (e :: Extrema) where Source #

The Extremum typeclass exists for us to match on the kind-level Extrema, so that we can recover which ordering to use in the Semiring instance for Tropical.

Methods

extremum :: EProxy e -> Extrema Source #

Instances
Extremum Minima Source # 
Instance details

Defined in Data.Semiring.Tropical

Extremum Maxima Source # 
Instance details

Defined in Data.Semiring.Tropical

data EProxy (e :: Extrema) Source #

On older GHCs, Proxy is not polykinded, so we provide our own proxy type for Extrema. This turns out not to be a problem, since Extremum is a closed typeclass.

Constructors

EProxy