| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell98 | 
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:
plusInfinityy = yplusxInfinity= 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.
Documentation
data Tropical (e :: Extrema) a Source #
The tropical semiring.
 is equivalent to the semiring
   \( (a \cup \{+\infty\}, \oplus, \otimes) \), where \( x \oplus y = min\{x,y\}\) and \(x \otimes y = x + y\).Tropical 'Minima a
 is equivalent to the semiring
   \( (a \cup \{-\infty\}, \oplus, \otimes) \), where \( x \oplus y = max\{x,y\}\) and \(x \otimes y = x + y\).Tropical 'Maxima a
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 , but in general this is not true.
 For example, lifting + (min b c) == min (a + b) (a + c)Product Word into Tropical is lawful,
 but Product Int is not, lacking distributivity: (-1) .
 So, we deviate from literature and instead
 witness the lifting of a * (min 0 1) /= min ((-1) * 0) ((-1) * 1)Monoid, so the user must take care to ensure
 that their implementation of mappend is monotonic.
Instances
| (Typeable e, Data a) => Data (Tropical e a) Source # | |
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 :: forall r r'. (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) #  | |
| Read a => Read (Tropical e a) Source # | |
| Show a => Show (Tropical e a) Source # | |
| Eq a => Eq (Tropical e a) Source # | |
| (Ord a, Extremum e) => Ord (Tropical e a) Source # | |
Defined in Data.Semiring.Tropical  | |
| (Ord a, Monoid a, Extremum e) => Semiring (Tropical e a) Source # | |
| (Ord a, Monoid a, Extremum e) => Star (Tropical e a) 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.