semiring-num-1.0.0.0: Basic semiring class and instances

LicenseMIT
Maintainermail@doisinkidney.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Data.Semiring

Contents

Description

 

Synopsis

Semiring classes

class Semiring a where Source #

A Semiring is like the the combination of two Monoids. The first is called <+>; it has the identity element zero, and it is commutative. The second is called <.>; it has identity element one, and it must distribute over <+>.

Laws

Normal Monoid laws

(a <+> b) <+> c = a <+> (b <+> c)
zero <+> a = a <+> zero = a
(a <.> b) <.> c = a <.> (b <.> c)
one <.> a = a <.> one = a

Commutativity of <+>

a <+> b = b <+> a

Distribution of <.> over <+>

a <.> (b <+> c) = (a <.> b) <+> (a <.> c)
(a <+> b) <.> c = (a <.> c) <+> (b <.> c)

Annihilation

zero <.> a = a <.> zero = zero

An ordered semiring follows the laws:

x <= y => x <+> z <= y <+> z
x <= y => x <+> z <= y <+> z
zero <= z && x <= y => x <.> z <= y <.> z && z <.> x <= z <.> y

Methods

zero :: a Source #

The identity of <+>.

one :: a Source #

The identity of <.>.

(<.>) :: a -> a -> a infixl 7 Source #

An associative binary operation, which distributes over <+>.

(<+>) :: a -> a -> a infixl 6 Source #

An associative, commutative binary operation.

zero :: Num a => a Source #

The identity of <+>.

one :: Num a => a Source #

The identity of <.>.

(<+>) :: Num a => a -> a -> a infixl 6 Source #

An associative, commutative binary operation.

(<.>) :: Num a => a -> a -> a infixl 7 Source #

An associative binary operation, which distributes over <+>.

Instances

Semiring Bool Source # 
Semiring Double Source # 
Semiring Float Source # 
Semiring Int Source # 

Methods

zero :: Int Source #

one :: Int Source #

(<.>) :: Int -> Int -> Int Source #

(<+>) :: Int -> Int -> Int Source #

Semiring Int8 Source # 
Semiring Int16 Source # 
Semiring Int32 Source # 
Semiring Int64 Source # 
Semiring Integer Source # 
Semiring Word Source # 
Semiring Word8 Source # 
Semiring Word16 Source # 
Semiring Word32 Source # 
Semiring Word64 Source # 
Semiring () Source # 

Methods

zero :: () Source #

one :: () Source #

(<.>) :: () -> () -> () Source #

(<+>) :: () -> () -> () Source #

Semiring Natural Source # 
Semiring CDev Source # 
Semiring CIno Source # 
Semiring CMode Source # 
Semiring COff Source # 
Semiring CPid Source # 
Semiring CSsize Source # 
Semiring CGid Source # 
Semiring CNlink Source # 
Semiring CUid Source # 
Semiring CCc Source # 

Methods

zero :: CCc Source #

one :: CCc Source #

(<.>) :: CCc -> CCc -> CCc Source #

(<+>) :: CCc -> CCc -> CCc Source #

Semiring CSpeed Source # 
Semiring CTcflag Source # 
Semiring CRLim Source # 
Semiring Fd Source # 

Methods

zero :: Fd Source #

one :: Fd Source #

(<.>) :: Fd -> Fd -> Fd Source #

(<+>) :: Fd -> Fd -> Fd Source #

Semiring WordPtr Source # 
Semiring IntPtr Source # 
Semiring CChar Source # 
Semiring CSChar Source # 
Semiring CUChar Source # 
Semiring CShort Source # 
Semiring CUShort Source # 
Semiring CInt Source # 
Semiring CUInt Source # 
Semiring CLong Source # 
Semiring CULong Source # 
Semiring CLLong Source # 
Semiring CULLong Source # 
Semiring CFloat Source # 
Semiring CDouble Source # 
Semiring CPtrdiff Source # 
Semiring CSize Source # 
Semiring CWchar Source # 
Semiring CSigAtomic Source # 
Semiring CClock Source # 
Semiring CTime Source # 
Semiring CUSeconds Source # 
Semiring CSUSeconds Source # 
Semiring CIntPtr Source # 
Semiring CUIntPtr Source # 
Semiring CIntMax Source # 
Semiring CUIntMax Source # 
Semiring All Source # 

Methods

zero :: All Source #

one :: All Source #

(<.>) :: All -> All -> All Source #

(<+>) :: All -> All -> All Source #

Semiring Any Source # 

Methods

zero :: Any Source #

one :: Any Source #

(<.>) :: Any -> Any -> Any Source #

(<+>) :: Any -> Any -> Any Source #

Semiring a => Semiring [a] Source #

A polynomial in x can be defined as a list of its coefficients, where the ith element is the coefficient of x^i. This is the semiring for such a list. Adapted from here.

Methods

zero :: [a] Source #

one :: [a] Source #

(<.>) :: [a] -> [a] -> [a] Source #

(<+>) :: [a] -> [a] -> [a] Source #

Integral a => Semiring (Ratio a) Source # 

Methods

zero :: Ratio a Source #

one :: Ratio a Source #

(<.>) :: Ratio a -> Ratio a -> Ratio a Source #

(<+>) :: Ratio a -> Ratio a -> Ratio a Source #

Semiring a => Semiring (Identity a) Source # 
HasResolution a => Semiring (Fixed a) Source # 

Methods

zero :: Fixed a Source #

one :: Fixed a Source #

(<.>) :: Fixed a -> Fixed a -> Fixed a Source #

(<+>) :: Fixed a -> Fixed a -> Fixed a Source #

RealFloat a => Semiring (Complex a) Source # 
Monoid a => Semiring (Endo a) Source #

This is not a true semiring. In particular, it requires the underlying monoid to be commutative, and even then, it is only a near semiring. It is, however, extremely useful. For instance, this type:

forall a. Endo (Endo a)

Is a valid encoding of church numerals, with addition and multiplication being their semiring variants.

Methods

zero :: Endo a Source #

one :: Endo a Source #

(<.>) :: Endo a -> Endo a -> Endo a Source #

(<+>) :: Endo a -> Endo a -> Endo a Source #

Semiring a => Semiring (Sum a) Source # 

Methods

zero :: Sum a Source #

one :: Sum a Source #

(<.>) :: Sum a -> Sum a -> Sum a Source #

(<+>) :: Sum a -> Sum a -> Sum a Source #

Semiring a => Semiring (Product a) Source # 
(Semiring a, Ord a, HasNegativeInfinity a) => Semiring (Max a) Source # 

Methods

zero :: Max a Source #

one :: Max a Source #

(<.>) :: Max a -> Max a -> Max a Source #

(<+>) :: Max a -> Max a -> Max a Source #

(Semiring a, Ord a, HasPositiveInfinity a) => Semiring (Min a) Source # 

Methods

zero :: Min a Source #

one :: Min a Source #

(<.>) :: Min a -> Min a -> Min a Source #

(<+>) :: Min a -> Min a -> Min a Source #

Semiring a => Semiring (Mul a) Source # 

Methods

zero :: Mul a Source #

one :: Mul a Source #

(<.>) :: Mul a -> Mul a -> Mul a Source #

(<+>) :: Mul a -> Mul a -> Mul a Source #

Semiring a => Semiring (Add a) Source # 

Methods

zero :: Add a Source #

one :: Add a Source #

(<.>) :: Add a -> Add a -> Add a Source #

(<+>) :: Add a -> Add a -> Add a Source #

Semiring (Free a) Source # 

Methods

zero :: Free a Source #

one :: Free a Source #

(<.>) :: Free a -> Free a -> Free a Source #

(<+>) :: Free a -> Free a -> Free a Source #

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

Not distributive.

DetectableZero a => Semiring (PositiveInfinite a) Source #

Only lawful when used with positive numbers.

DetectableZero a => Semiring (NegativeInfinite a) Source #

Doesn't follow annihilateL or mulDistribR.

Semiring a => Semiring (PosInt a) Source # 

Methods

zero :: PosInt a Source #

one :: PosInt a Source #

(<.>) :: PosInt a -> PosInt a -> PosInt a Source #

(<+>) :: PosInt a -> PosInt a -> PosInt a Source #

Semiring a => Semiring (PosFrac a) Source # 
(Floating a, HasPositiveInfinity a) => Semiring (Log a) Source # 

Methods

zero :: Log a Source #

one :: Log a Source #

(<.>) :: Log a -> Log a -> Log a Source #

(<+>) :: Log a -> Log a -> Log a Source #

(Ord a, Semiring a) => Semiring (Viterbi a) Source # 
(Ord a, Num a) => Semiring (Łukasiewicz a) Source # 
(Integral a, Semiring a) => Semiring (Division a) Source #

Only expects positive numbers

(Bounded a, Ord a) => Semiring (Bottleneck a) Source # 
Semiring b => Semiring (a -> b) Source #

The (->) instance is analogous to the one for Monoid.

Methods

zero :: a -> b Source #

one :: a -> b Source #

(<.>) :: (a -> b) -> (a -> b) -> a -> b Source #

(<+>) :: (a -> b) -> (a -> b) -> a -> b Source #

(Semiring a0, Semiring a1) => Semiring (a0, a1) Source # 

Methods

zero :: (a0, a1) Source #

one :: (a0, a1) Source #

(<.>) :: (a0, a1) -> (a0, a1) -> (a0, a1) Source #

(<+>) :: (a0, a1) -> (a0, a1) -> (a0, a1) Source #

(Semiring a0, Semiring a1, Semiring a2) => Semiring (a0, a1, a2) Source # 

Methods

zero :: (a0, a1, a2) Source #

one :: (a0, a1, a2) Source #

(<.>) :: (a0, a1, a2) -> (a0, a1, a2) -> (a0, a1, a2) Source #

(<+>) :: (a0, a1, a2) -> (a0, a1, a2) -> (a0, a1, a2) Source #

(Semiring a0, Semiring a1, Semiring a2, Semiring a3) => Semiring (a0, a1, a2, a3) Source # 

Methods

zero :: (a0, a1, a2, a3) Source #

one :: (a0, a1, a2, a3) Source #

(<.>) :: (a0, a1, a2, a3) -> (a0, a1, a2, a3) -> (a0, a1, a2, a3) Source #

(<+>) :: (a0, a1, a2, a3) -> (a0, a1, a2, a3) -> (a0, a1, a2, a3) Source #

(Semiring a0, Semiring a1, Semiring a2, Semiring a3, Semiring a4) => Semiring (a0, a1, a2, a3, a4) Source # 

Methods

zero :: (a0, a1, a2, a3, a4) Source #

one :: (a0, a1, a2, a3, a4) Source #

(<.>) :: (a0, a1, a2, a3, a4) -> (a0, a1, a2, a3, a4) -> (a0, a1, a2, a3, a4) Source #

(<+>) :: (a0, a1, a2, a3, a4) -> (a0, a1, a2, a3, a4) -> (a0, a1, a2, a3, a4) Source #

(Semiring a0, Semiring a1, Semiring a2, Semiring a3, Semiring a4, Semiring a5) => Semiring (a0, a1, a2, a3, a4, a5) Source # 

Methods

zero :: (a0, a1, a2, a3, a4, a5) Source #

one :: (a0, a1, a2, a3, a4, a5) Source #

(<.>) :: (a0, a1, a2, a3, a4, a5) -> (a0, a1, a2, a3, a4, a5) -> (a0, a1, a2, a3, a4, a5) Source #

(<+>) :: (a0, a1, a2, a3, a4, a5) -> (a0, a1, a2, a3, a4, a5) -> (a0, a1, a2, a3, a4, a5) Source #

(Semiring a0, Semiring a1, Semiring a2, Semiring a3, Semiring a4, Semiring a5, Semiring a6) => Semiring (a0, a1, a2, a3, a4, a5, a6) Source # 

Methods

zero :: (a0, a1, a2, a3, a4, a5, a6) Source #

one :: (a0, a1, a2, a3, a4, a5, a6) Source #

(<.>) :: (a0, a1, a2, a3, a4, a5, a6) -> (a0, a1, a2, a3, a4, a5, a6) -> (a0, a1, a2, a3, a4, a5, a6) Source #

(<+>) :: (a0, a1, a2, a3, a4, a5, a6) -> (a0, a1, a2, a3, a4, a5, a6) -> (a0, a1, a2, a3, a4, a5, a6) Source #

(Semiring a0, Semiring a1, Semiring a2, Semiring a3, Semiring a4, Semiring a5, Semiring a6, Semiring a7) => Semiring (a0, a1, a2, a3, a4, a5, a6, a7) Source # 

Methods

zero :: (a0, a1, a2, a3, a4, a5, a6, a7) Source #

one :: (a0, a1, a2, a3, a4, a5, a6, a7) Source #

(<.>) :: (a0, a1, a2, a3, a4, a5, a6, a7) -> (a0, a1, a2, a3, a4, a5, a6, a7) -> (a0, a1, a2, a3, a4, a5, a6, a7) Source #

(<+>) :: (a0, a1, a2, a3, a4, a5, a6, a7) -> (a0, a1, a2, a3, a4, a5, a6, a7) -> (a0, a1, a2, a3, a4, a5, a6, a7) Source #

(Semiring a0, Semiring a1, Semiring a2, Semiring a3, Semiring a4, Semiring a5, Semiring a6, Semiring a7, Semiring a8) => Semiring (a0, a1, a2, a3, a4, a5, a6, a7, a8) Source # 

Methods

zero :: (a0, a1, a2, a3, a4, a5, a6, a7, a8) Source #

one :: (a0, a1, a2, a3, a4, a5, a6, a7, a8) Source #

(<.>) :: (a0, a1, a2, a3, a4, a5, a6, a7, a8) -> (a0, a1, a2, a3, a4, a5, a6, a7, a8) -> (a0, a1, a2, a3, a4, a5, a6, a7, a8) Source #

(<+>) :: (a0, a1, a2, a3, a4, a5, a6, a7, a8) -> (a0, a1, a2, a3, a4, a5, a6, a7, a8) -> (a0, a1, a2, a3, a4, a5, a6, a7, a8) Source #

class Semiring a => StarSemiring a where Source #

A Star semiring adds one operation, star to a Semiring, such that it follows the law:

star x = one <+> x <.> star x = one <+> star x <.> x

For the semiring of types, this is equivalent to a list. When looking at the Applicative and Alternative classes as (near-) semirings, this is equivalent to the many operation.

Another operation, plus, can be defined in relation to star:

plus x = x <.> star x

This should be recognizable as a non-empty list on types, or the some operation in Alternative.

Minimal complete definition

star | plus

Methods

star :: a -> a Source #

plus :: a -> a Source #

Instances

StarSemiring Bool Source # 

Methods

star :: Bool -> Bool Source #

plus :: Bool -> Bool Source #

StarSemiring () Source # 

Methods

star :: () -> () Source #

plus :: () -> () Source #

StarSemiring All Source # 

Methods

star :: All -> All Source #

plus :: All -> All Source #

StarSemiring Any Source # 

Methods

star :: Any -> Any Source #

plus :: Any -> Any Source #

(Monoid a, Eq a) => StarSemiring (Endo a) Source # 

Methods

star :: Endo a -> Endo a Source #

plus :: Endo a -> Endo a Source #

(Semiring a, Ord a, HasPositiveInfinity a, HasNegativeInfinity a) => StarSemiring (Max a) Source # 

Methods

star :: Max a -> Max a Source #

plus :: Max a -> Max a Source #

(Semiring a, Ord a, HasPositiveInfinity a, HasNegativeInfinity a) => StarSemiring (Min a) Source # 

Methods

star :: Min a -> Min a Source #

plus :: Min a -> Min a Source #

StarSemiring a => StarSemiring (Mul a) Source # 

Methods

star :: Mul a -> Mul a Source #

plus :: Mul a -> Mul a Source #

StarSemiring a => StarSemiring (Add a) Source # 

Methods

star :: Add a -> Add a Source #

plus :: Add a -> Add a Source #

DetectableZero a => StarSemiring (PositiveInfinite a) Source # 
(Eq a, Semiring a, HasPositiveInfinity a) => StarSemiring (PosInt a) Source # 

Methods

star :: PosInt a -> PosInt a Source #

plus :: PosInt a -> PosInt a Source #

(Ord a, Fractional a, Semiring a, HasPositiveInfinity a) => StarSemiring (PosFrac a) Source # 

Methods

star :: PosFrac a -> PosFrac a Source #

plus :: PosFrac a -> PosFrac a Source #

StarSemiring b => StarSemiring (a -> b) Source # 

Methods

star :: (a -> b) -> a -> b Source #

plus :: (a -> b) -> a -> b Source #

(StarSemiring a0, StarSemiring a1) => StarSemiring (a0, a1) Source # 

Methods

star :: (a0, a1) -> (a0, a1) Source #

plus :: (a0, a1) -> (a0, a1) Source #

(StarSemiring a0, StarSemiring a1, StarSemiring a2) => StarSemiring (a0, a1, a2) Source # 

Methods

star :: (a0, a1, a2) -> (a0, a1, a2) Source #

plus :: (a0, a1, a2) -> (a0, a1, a2) Source #

(StarSemiring a0, StarSemiring a1, StarSemiring a2, StarSemiring a3) => StarSemiring (a0, a1, a2, a3) Source # 

Methods

star :: (a0, a1, a2, a3) -> (a0, a1, a2, a3) Source #

plus :: (a0, a1, a2, a3) -> (a0, a1, a2, a3) Source #

(StarSemiring a0, StarSemiring a1, StarSemiring a2, StarSemiring a3, StarSemiring a4) => StarSemiring (a0, a1, a2, a3, a4) Source # 

Methods

star :: (a0, a1, a2, a3, a4) -> (a0, a1, a2, a3, a4) Source #

plus :: (a0, a1, a2, a3, a4) -> (a0, a1, a2, a3, a4) Source #

(StarSemiring a0, StarSemiring a1, StarSemiring a2, StarSemiring a3, StarSemiring a4, StarSemiring a5) => StarSemiring (a0, a1, a2, a3, a4, a5) Source # 

Methods

star :: (a0, a1, a2, a3, a4, a5) -> (a0, a1, a2, a3, a4, a5) Source #

plus :: (a0, a1, a2, a3, a4, a5) -> (a0, a1, a2, a3, a4, a5) Source #

(StarSemiring a0, StarSemiring a1, StarSemiring a2, StarSemiring a3, StarSemiring a4, StarSemiring a5, StarSemiring a6) => StarSemiring (a0, a1, a2, a3, a4, a5, a6) Source # 

Methods

star :: (a0, a1, a2, a3, a4, a5, a6) -> (a0, a1, a2, a3, a4, a5, a6) Source #

plus :: (a0, a1, a2, a3, a4, a5, a6) -> (a0, a1, a2, a3, a4, a5, a6) Source #

(StarSemiring a0, StarSemiring a1, StarSemiring a2, StarSemiring a3, StarSemiring a4, StarSemiring a5, StarSemiring a6, StarSemiring a7) => StarSemiring (a0, a1, a2, a3, a4, a5, a6, a7) Source # 

Methods

star :: (a0, a1, a2, a3, a4, a5, a6, a7) -> (a0, a1, a2, a3, a4, a5, a6, a7) Source #

plus :: (a0, a1, a2, a3, a4, a5, a6, a7) -> (a0, a1, a2, a3, a4, a5, a6, a7) Source #

(StarSemiring a0, StarSemiring a1, StarSemiring a2, StarSemiring a3, StarSemiring a4, StarSemiring a5, StarSemiring a6, StarSemiring a7, StarSemiring a8) => StarSemiring (a0, a1, a2, a3, a4, a5, a6, a7, a8) Source # 

Methods

star :: (a0, a1, a2, a3, a4, a5, a6, a7, a8) -> (a0, a1, a2, a3, a4, a5, a6, a7, a8) Source #

plus :: (a0, a1, a2, a3, a4, a5, a6, a7, a8) -> (a0, a1, a2, a3, a4, a5, a6, a7, a8) Source #

Helper classes

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.

class Semiring a => DetectableZero a where Source #

Useful for operations where zeroes may need to be discarded: for instance in sparse matrix calculations.

Methods

isZero :: a -> Bool Source #

True if x is zero.

isZero :: Eq a => a -> Bool Source #

True if x is zero.

Instances

DetectableZero Bool Source # 

Methods

isZero :: Bool -> Bool Source #

DetectableZero Double Source # 

Methods

isZero :: Double -> Bool Source #

DetectableZero Float Source # 

Methods

isZero :: Float -> Bool Source #

DetectableZero Int Source # 

Methods

isZero :: Int -> Bool Source #

DetectableZero Int8 Source # 

Methods

isZero :: Int8 -> Bool Source #

DetectableZero Int16 Source # 

Methods

isZero :: Int16 -> Bool Source #

DetectableZero Int32 Source # 

Methods

isZero :: Int32 -> Bool Source #

DetectableZero Int64 Source # 

Methods

isZero :: Int64 -> Bool Source #

DetectableZero Integer Source # 

Methods

isZero :: Integer -> Bool Source #

DetectableZero Word Source # 

Methods

isZero :: Word -> Bool Source #

DetectableZero Word8 Source # 

Methods

isZero :: Word8 -> Bool Source #

DetectableZero Word16 Source # 

Methods

isZero :: Word16 -> Bool Source #

DetectableZero Word32 Source # 

Methods

isZero :: Word32 -> Bool Source #

DetectableZero Word64 Source # 

Methods

isZero :: Word64 -> Bool Source #

DetectableZero () Source # 

Methods

isZero :: () -> Bool Source #

DetectableZero Natural Source # 

Methods

isZero :: Natural -> Bool Source #

DetectableZero CDev Source # 

Methods

isZero :: CDev -> Bool Source #

DetectableZero CIno Source # 

Methods

isZero :: CIno -> Bool Source #

DetectableZero CMode Source # 

Methods

isZero :: CMode -> Bool Source #

DetectableZero COff Source # 

Methods

isZero :: COff -> Bool Source #

DetectableZero CPid Source # 

Methods

isZero :: CPid -> Bool Source #

DetectableZero CSsize Source # 

Methods

isZero :: CSsize -> Bool Source #

DetectableZero CGid Source # 

Methods

isZero :: CGid -> Bool Source #

DetectableZero CNlink Source # 

Methods

isZero :: CNlink -> Bool Source #

DetectableZero CUid Source # 

Methods

isZero :: CUid -> Bool Source #

DetectableZero CCc Source # 

Methods

isZero :: CCc -> Bool Source #

DetectableZero CSpeed Source # 

Methods

isZero :: CSpeed -> Bool Source #

DetectableZero CTcflag Source # 

Methods

isZero :: CTcflag -> Bool Source #

DetectableZero CRLim Source # 

Methods

isZero :: CRLim -> Bool Source #

DetectableZero Fd Source # 

Methods

isZero :: Fd -> Bool Source #

DetectableZero WordPtr Source # 

Methods

isZero :: WordPtr -> Bool Source #

DetectableZero IntPtr Source # 

Methods

isZero :: IntPtr -> Bool Source #

DetectableZero CChar Source # 

Methods

isZero :: CChar -> Bool Source #

DetectableZero CSChar Source # 

Methods

isZero :: CSChar -> Bool Source #

DetectableZero CUChar Source # 

Methods

isZero :: CUChar -> Bool Source #

DetectableZero CShort Source # 

Methods

isZero :: CShort -> Bool Source #

DetectableZero CUShort Source # 

Methods

isZero :: CUShort -> Bool Source #

DetectableZero CInt Source # 

Methods

isZero :: CInt -> Bool Source #

DetectableZero CUInt Source # 

Methods

isZero :: CUInt -> Bool Source #

DetectableZero CLong Source # 

Methods

isZero :: CLong -> Bool Source #

DetectableZero CULong Source # 

Methods

isZero :: CULong -> Bool Source #

DetectableZero CLLong Source # 

Methods

isZero :: CLLong -> Bool Source #

DetectableZero CULLong Source # 

Methods

isZero :: CULLong -> Bool Source #

DetectableZero CFloat Source # 

Methods

isZero :: CFloat -> Bool Source #

DetectableZero CDouble Source # 

Methods

isZero :: CDouble -> Bool Source #

DetectableZero CPtrdiff Source # 

Methods

isZero :: CPtrdiff -> Bool Source #

DetectableZero CSize Source # 

Methods

isZero :: CSize -> Bool Source #

DetectableZero CWchar Source # 

Methods

isZero :: CWchar -> Bool Source #

DetectableZero CSigAtomic Source # 
DetectableZero CClock Source # 

Methods

isZero :: CClock -> Bool Source #

DetectableZero CTime Source # 

Methods

isZero :: CTime -> Bool Source #

DetectableZero CUSeconds Source # 
DetectableZero CSUSeconds Source # 
DetectableZero CIntPtr Source # 

Methods

isZero :: CIntPtr -> Bool Source #

DetectableZero CUIntPtr Source # 

Methods

isZero :: CUIntPtr -> Bool Source #

DetectableZero CIntMax Source # 

Methods

isZero :: CIntMax -> Bool Source #

DetectableZero CUIntMax Source # 

Methods

isZero :: CUIntMax -> Bool Source #

DetectableZero All Source # 

Methods

isZero :: All -> Bool Source #

DetectableZero Any Source # 

Methods

isZero :: Any -> Bool Source #

Semiring a => DetectableZero [a] Source # 

Methods

isZero :: [a] -> Bool Source #

Integral a => DetectableZero (Ratio a) Source # 

Methods

isZero :: Ratio a -> Bool Source #

DetectableZero a => DetectableZero (Identity a) Source # 

Methods

isZero :: Identity a -> Bool Source #

HasResolution a => DetectableZero (Fixed a) Source # 

Methods

isZero :: Fixed a -> Bool Source #

RealFloat a => DetectableZero (Complex a) Source # 

Methods

isZero :: Complex a -> Bool Source #

(Enum a, Bounded a, Eq a, Monoid a) => DetectableZero (Endo a) Source # 

Methods

isZero :: Endo a -> Bool Source #

DetectableZero a => DetectableZero (Sum a) Source # 

Methods

isZero :: Sum a -> Bool Source #

DetectableZero a => DetectableZero (Product a) Source # 

Methods

isZero :: Product a -> Bool Source #

(Semiring a, Ord a, HasNegativeInfinity a) => DetectableZero (Max a) Source # 

Methods

isZero :: Max a -> Bool Source #

(Semiring a, Ord a, HasPositiveInfinity a) => DetectableZero (Min a) Source # 

Methods

isZero :: Min a -> Bool Source #

DetectableZero a => DetectableZero (Mul a) Source # 

Methods

isZero :: Mul a -> Bool Source #

DetectableZero a => DetectableZero (Add a) Source # 

Methods

isZero :: Add a -> Bool Source #

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

Methods

isZero :: Infinite a -> Bool Source #

DetectableZero a => DetectableZero (PositiveInfinite a) Source # 
DetectableZero a => DetectableZero (NegativeInfinite a) Source # 
(Eq a, Semiring a) => DetectableZero (PosInt a) Source # 

Methods

isZero :: PosInt a -> Bool Source #

(Eq a, Semiring a) => DetectableZero (PosFrac a) Source # 

Methods

isZero :: PosFrac a -> Bool Source #

(Floating a, HasPositiveInfinity a) => DetectableZero (Log a) Source # 

Methods

isZero :: Log a -> Bool Source #

(Ord a, DetectableZero a) => DetectableZero (Viterbi a) Source # 

Methods

isZero :: Viterbi a -> Bool Source #

(Ord a, Num a) => DetectableZero (Łukasiewicz a) Source # 
(Integral a, DetectableZero a) => DetectableZero (Division a) Source # 

Methods

isZero :: Division a -> Bool Source #

(Bounded a, Ord a) => DetectableZero (Bottleneck a) Source # 

Methods

isZero :: Bottleneck a -> Bool Source #

(DetectableZero a0, DetectableZero a1) => DetectableZero (a0, a1) Source # 

Methods

isZero :: (a0, a1) -> Bool Source #

(DetectableZero a0, DetectableZero a1, DetectableZero a2) => DetectableZero (a0, a1, a2) Source # 

Methods

isZero :: (a0, a1, a2) -> Bool Source #

(DetectableZero a0, DetectableZero a1, DetectableZero a2, DetectableZero a3) => DetectableZero (a0, a1, a2, a3) Source # 

Methods

isZero :: (a0, a1, a2, a3) -> Bool Source #

(DetectableZero a0, DetectableZero a1, DetectableZero a2, DetectableZero a3, DetectableZero a4) => DetectableZero (a0, a1, a2, a3, a4) Source # 

Methods

isZero :: (a0, a1, a2, a3, a4) -> Bool Source #

(DetectableZero a0, DetectableZero a1, DetectableZero a2, DetectableZero a3, DetectableZero a4, DetectableZero a5) => DetectableZero (a0, a1, a2, a3, a4, a5) Source # 

Methods

isZero :: (a0, a1, a2, a3, a4, a5) -> Bool Source #

(DetectableZero a0, DetectableZero a1, DetectableZero a2, DetectableZero a3, DetectableZero a4, DetectableZero a5, DetectableZero a6) => DetectableZero (a0, a1, a2, a3, a4, a5, a6) Source # 

Methods

isZero :: (a0, a1, a2, a3, a4, a5, a6) -> Bool Source #

(DetectableZero a0, DetectableZero a1, DetectableZero a2, DetectableZero a3, DetectableZero a4, DetectableZero a5, DetectableZero a6, DetectableZero a7) => DetectableZero (a0, a1, a2, a3, a4, a5, a6, a7) Source # 

Methods

isZero :: (a0, a1, a2, a3, a4, a5, a6, a7) -> Bool Source #

(DetectableZero a0, DetectableZero a1, DetectableZero a2, DetectableZero a3, DetectableZero a4, DetectableZero a5, DetectableZero a6, DetectableZero a7, DetectableZero a8) => DetectableZero (a0, a1, a2, a3, a4, a5, a6, a7, a8) Source # 

Methods

isZero :: (a0, a1, a2, a3, a4, a5, a6, a7, a8) -> Bool Source #

Monoidal wrappers

newtype Add a Source #

Monoid under <+>. Analogous to Sum, but uses the Semiring constraint, rather than Num.

Constructors

Add 

Fields

Instances

Functor Add Source # 

Methods

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

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

Foldable Add Source # 

Methods

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

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

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

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

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

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

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

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

toList :: Add a -> [a] #

null :: Add a -> Bool #

length :: Add a -> Int #

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

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

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

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

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

Traversable Add Source # 

Methods

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

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

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

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

Generic1 Add Source # 

Associated Types

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

Methods

from1 :: Add a -> Rep1 Add a #

to1 :: Rep1 Add a -> Add a #

Bounded a => Bounded (Add a) Source # 

Methods

minBound :: Add a #

maxBound :: Add a #

Enum a => Enum (Add a) Source # 

Methods

succ :: Add a -> Add a #

pred :: Add a -> Add a #

toEnum :: Int -> Add a #

fromEnum :: Add a -> Int #

enumFrom :: Add a -> [Add a] #

enumFromThen :: Add a -> Add a -> [Add a] #

enumFromTo :: Add a -> Add a -> [Add a] #

enumFromThenTo :: Add a -> Add a -> Add a -> [Add a] #

Eq a => Eq (Add a) Source # 

Methods

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

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

Fractional a => Fractional (Add a) Source # 

Methods

(/) :: Add a -> Add a -> Add a #

recip :: Add a -> Add a #

fromRational :: Rational -> Add a #

Num a => Num (Add a) Source # 

Methods

(+) :: Add a -> Add a -> Add a #

(-) :: Add a -> Add a -> Add a #

(*) :: Add a -> Add a -> Add a #

negate :: Add a -> Add a #

abs :: Add a -> Add a #

signum :: Add a -> Add a #

fromInteger :: Integer -> Add a #

Ord a => Ord (Add a) Source # 

Methods

compare :: Add a -> Add a -> Ordering #

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

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

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

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

max :: Add a -> Add a -> Add a #

min :: Add a -> Add a -> Add a #

Read a => Read (Add a) Source # 
Real a => Real (Add a) Source # 

Methods

toRational :: Add a -> Rational #

RealFrac a => RealFrac (Add a) Source # 

Methods

properFraction :: Integral b => Add a -> (b, Add a) #

truncate :: Integral b => Add a -> b #

round :: Integral b => Add a -> b #

ceiling :: Integral b => Add a -> b #

floor :: Integral b => Add a -> b #

Show a => Show (Add a) Source # 

Methods

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

show :: Add a -> String #

showList :: [Add a] -> ShowS #

Generic (Add a) Source # 

Associated Types

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

Methods

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

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

Semiring a => Semigroup (Add a) Source # 

Methods

(<>) :: Add a -> Add a -> Add a #

sconcat :: NonEmpty (Add a) -> Add a #

stimes :: Integral b => b -> Add a -> Add a #

Semiring a => Monoid (Add a) Source # 

Methods

mempty :: Add a #

mappend :: Add a -> Add a -> Add a #

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

Storable a => Storable (Add a) Source # 

Methods

sizeOf :: Add a -> Int #

alignment :: Add a -> Int #

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

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

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

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

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

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

DetectableZero a => DetectableZero (Add a) Source # 

Methods

isZero :: Add a -> Bool Source #

StarSemiring a => StarSemiring (Add a) Source # 

Methods

star :: Add a -> Add a Source #

plus :: Add a -> Add a Source #

Semiring a => Semiring (Add a) Source # 

Methods

zero :: Add a Source #

one :: Add a Source #

(<.>) :: Add a -> Add a -> Add a Source #

(<+>) :: Add a -> Add a -> Add a Source #

type Rep1 Add Source # 
type Rep1 Add = D1 (MetaData "Add" "Data.Semiring" "semiring-num-1.0.0.0-7OBAfS7Gua052Mg3sLOjjr" True) (C1 (MetaCons "Add" PrefixI True) (S1 (MetaSel (Just Symbol "getAdd") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))
type Rep (Add a) Source # 
type Rep (Add a) = D1 (MetaData "Add" "Data.Semiring" "semiring-num-1.0.0.0-7OBAfS7Gua052Mg3sLOjjr" True) (C1 (MetaCons "Add" PrefixI True) (S1 (MetaSel (Just Symbol "getAdd") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype Mul a Source #

Monoid under <.>. Analogous to Product, but uses the Semiring constraint, rather than Num.

Constructors

Mul 

Fields

Instances

Functor Mul Source # 

Methods

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

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

Foldable Mul Source # 

Methods

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

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

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

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

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

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

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

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

toList :: Mul a -> [a] #

null :: Mul a -> Bool #

length :: Mul a -> Int #

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

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

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

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

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

Traversable Mul Source # 

Methods

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

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

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

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

Generic1 Mul Source # 

Associated Types

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

Methods

from1 :: Mul a -> Rep1 Mul a #

to1 :: Rep1 Mul a -> Mul a #

Bounded a => Bounded (Mul a) Source # 

Methods

minBound :: Mul a #

maxBound :: Mul a #

Enum a => Enum (Mul a) Source # 

Methods

succ :: Mul a -> Mul a #

pred :: Mul a -> Mul a #

toEnum :: Int -> Mul a #

fromEnum :: Mul a -> Int #

enumFrom :: Mul a -> [Mul a] #

enumFromThen :: Mul a -> Mul a -> [Mul a] #

enumFromTo :: Mul a -> Mul a -> [Mul a] #

enumFromThenTo :: Mul a -> Mul a -> Mul a -> [Mul a] #

Eq a => Eq (Mul a) Source # 

Methods

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

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

Fractional a => Fractional (Mul a) Source # 

Methods

(/) :: Mul a -> Mul a -> Mul a #

recip :: Mul a -> Mul a #

fromRational :: Rational -> Mul a #

Num a => Num (Mul a) Source # 

Methods

(+) :: Mul a -> Mul a -> Mul a #

(-) :: Mul a -> Mul a -> Mul a #

(*) :: Mul a -> Mul a -> Mul a #

negate :: Mul a -> Mul a #

abs :: Mul a -> Mul a #

signum :: Mul a -> Mul a #

fromInteger :: Integer -> Mul a #

Ord a => Ord (Mul a) Source # 

Methods

compare :: Mul a -> Mul a -> Ordering #

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

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

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

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

max :: Mul a -> Mul a -> Mul a #

min :: Mul a -> Mul a -> Mul a #

Read a => Read (Mul a) Source # 
Real a => Real (Mul a) Source # 

Methods

toRational :: Mul a -> Rational #

RealFrac a => RealFrac (Mul a) Source # 

Methods

properFraction :: Integral b => Mul a -> (b, Mul a) #

truncate :: Integral b => Mul a -> b #

round :: Integral b => Mul a -> b #

ceiling :: Integral b => Mul a -> b #

floor :: Integral b => Mul a -> b #

Show a => Show (Mul a) Source # 

Methods

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

show :: Mul a -> String #

showList :: [Mul a] -> ShowS #

Generic (Mul a) Source # 

Associated Types

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

Methods

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

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

Semiring a => Semigroup (Mul a) Source # 

Methods

(<>) :: Mul a -> Mul a -> Mul a #

sconcat :: NonEmpty (Mul a) -> Mul a #

stimes :: Integral b => b -> Mul a -> Mul a #

Semiring a => Monoid (Mul a) Source # 

Methods

mempty :: Mul a #

mappend :: Mul a -> Mul a -> Mul a #

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

Storable a => Storable (Mul a) Source # 

Methods

sizeOf :: Mul a -> Int #

alignment :: Mul a -> Int #

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

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

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

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

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

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

DetectableZero a => DetectableZero (Mul a) Source # 

Methods

isZero :: Mul a -> Bool Source #

StarSemiring a => StarSemiring (Mul a) Source # 

Methods

star :: Mul a -> Mul a Source #

plus :: Mul a -> Mul a Source #

Semiring a => Semiring (Mul a) Source # 

Methods

zero :: Mul a Source #

one :: Mul a Source #

(<.>) :: Mul a -> Mul a -> Mul a Source #

(<+>) :: Mul a -> Mul a -> Mul a Source #

type Rep1 Mul Source # 
type Rep1 Mul = D1 (MetaData "Mul" "Data.Semiring" "semiring-num-1.0.0.0-7OBAfS7Gua052Mg3sLOjjr" True) (C1 (MetaCons "Mul" PrefixI True) (S1 (MetaSel (Just Symbol "getMul") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))
type Rep (Mul a) Source # 
type Rep (Mul a) = D1 (MetaData "Mul" "Data.Semiring" "semiring-num-1.0.0.0-7OBAfS7Gua052Mg3sLOjjr" True) (C1 (MetaCons "Mul" PrefixI True) (S1 (MetaSel (Just Symbol "getMul") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

add :: (Foldable f, Semiring a) => f a -> a Source #

Takes the sum of the elements of a Foldable. Analogous to sum on numbers, or or on Bools.

>>> add [1..5]
15
>>> add [False, False]
False
>>> add [False, True]
True
>>> add [True, undefined]
True

mul :: (Foldable f, Semiring a) => f a -> a Source #

Takes the product of the elements of a Foldable. Analogous to product on numbers, or and on Bools.

>>> mul [1..5]
120
>>> mul [True, True]
True
>>> mul [True, False]
False
>>> mul [False, undefined]
False

Ordering wrappers

newtype Max a Source #

The "Arctic" or max-plus semiring. It is a semiring where:

<+>  = max
zero = -∞
<.>  = <+>
one  = zero

Note that we can't use Max from Semigroup because annihilation needs to hold:

-∞ <+> x = x <+> -∞ = -∞

Taking -∞ to be minBound would break the above law. Using Nothing to represent it follows the law.

Constructors

Max 

Fields

Instances

Functor Max Source # 

Methods

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

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

Foldable Max Source # 

Methods

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

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

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

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

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

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

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

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

toList :: Max a -> [a] #

null :: Max a -> Bool #

length :: Max a -> Int #

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

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

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

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

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

Traversable Max Source # 

Methods

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

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

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

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

Generic1 Max Source # 

Associated Types

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

Methods

from1 :: Max a -> Rep1 Max a #

to1 :: Rep1 Max a -> Max a #

Bounded a => Bounded (Max a) Source # 

Methods

minBound :: Max a #

maxBound :: Max a #

Enum a => Enum (Max a) Source # 

Methods

succ :: Max a -> Max a #

pred :: Max a -> Max a #

toEnum :: Int -> Max a #

fromEnum :: Max a -> Int #

enumFrom :: Max a -> [Max a] #

enumFromThen :: Max a -> Max a -> [Max a] #

enumFromTo :: Max a -> Max a -> [Max a] #

enumFromThenTo :: Max a -> Max a -> Max a -> [Max a] #

Eq a => Eq (Max a) Source # 

Methods

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

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

Fractional a => Fractional (Max a) Source # 

Methods

(/) :: Max a -> Max a -> Max a #

recip :: Max a -> Max a #

fromRational :: Rational -> Max a #

Num a => Num (Max a) Source # 

Methods

(+) :: Max a -> Max a -> Max a #

(-) :: Max a -> Max a -> Max a #

(*) :: Max a -> Max a -> Max a #

negate :: Max a -> Max a #

abs :: Max a -> Max a #

signum :: Max a -> Max a #

fromInteger :: Integer -> Max a #

Ord a => Ord (Max a) Source # 

Methods

compare :: Max a -> Max a -> Ordering #

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

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

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

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

max :: Max a -> Max a -> Max a #

min :: Max a -> Max a -> Max a #

Read a => Read (Max a) Source # 
Real a => Real (Max a) Source # 

Methods

toRational :: Max a -> Rational #

RealFrac a => RealFrac (Max a) Source # 

Methods

properFraction :: Integral b => Max a -> (b, Max a) #

truncate :: Integral b => Max a -> b #

round :: Integral b => Max a -> b #

ceiling :: Integral b => Max a -> b #

floor :: Integral b => Max a -> b #

Show a => Show (Max a) Source # 

Methods

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

show :: Max a -> String #

showList :: [Max a] -> ShowS #

Generic (Max a) Source # 

Associated Types

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

Methods

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

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

Ord a => Semigroup (Max a) Source # 

Methods

(<>) :: Max a -> Max a -> Max a #

sconcat :: NonEmpty (Max a) -> Max a #

stimes :: Integral b => b -> Max a -> Max a #

(Ord a, HasNegativeInfinity a) => Monoid (Max a) Source #
>>> (getMax . foldMap Max) [1..10]
10.0

Methods

mempty :: Max a #

mappend :: Max a -> Max a -> Max a #

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

Storable a => Storable (Max a) Source # 

Methods

sizeOf :: Max a -> Int #

alignment :: Max a -> Int #

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

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

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

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

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

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

(Semiring a, Ord a, HasNegativeInfinity a) => DetectableZero (Max a) Source # 

Methods

isZero :: Max a -> Bool Source #

(Semiring a, Ord a, HasPositiveInfinity a, HasNegativeInfinity a) => StarSemiring (Max a) Source # 

Methods

star :: Max a -> Max a Source #

plus :: Max a -> Max a Source #

(Semiring a, Ord a, HasNegativeInfinity a) => Semiring (Max a) Source # 

Methods

zero :: Max a Source #

one :: Max a Source #

(<.>) :: Max a -> Max a -> Max a Source #

(<+>) :: Max a -> Max a -> Max a Source #

type Rep1 Max Source # 
type Rep1 Max = D1 (MetaData "Max" "Data.Semiring" "semiring-num-1.0.0.0-7OBAfS7Gua052Mg3sLOjjr" True) (C1 (MetaCons "Max" PrefixI True) (S1 (MetaSel (Just Symbol "getMax") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))
type Rep (Max a) Source # 
type Rep (Max a) = D1 (MetaData "Max" "Data.Semiring" "semiring-num-1.0.0.0-7OBAfS7Gua052Mg3sLOjjr" True) (C1 (MetaCons "Max" PrefixI True) (S1 (MetaSel (Just Symbol "getMax") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype Min a Source #

The "Tropical" or min-plus semiring. It is a semiring where:

<+>  = min
zero = ∞
<.>  = <+>
one  = zero

Note that we can't use Min from Semigroup because annihilation needs to hold:

<+> x = x <+> ∞ = ∞

Taking ∞ to be maxBound would break the above law. Using Nothing to represent it follows the law.

Constructors

Min 

Fields

Instances

Functor Min Source # 

Methods

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

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

Foldable Min Source # 

Methods

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

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

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

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

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

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

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

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

toList :: Min a -> [a] #

null :: Min a -> Bool #

length :: Min a -> Int #

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

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

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

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

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

Traversable Min Source # 

Methods

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

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

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

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

Generic1 Min Source # 

Associated Types

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

Methods

from1 :: Min a -> Rep1 Min a #

to1 :: Rep1 Min a -> Min a #

Bounded a => Bounded (Min a) Source # 

Methods

minBound :: Min a #

maxBound :: Min a #

Enum a => Enum (Min a) Source # 

Methods

succ :: Min a -> Min a #

pred :: Min a -> Min a #

toEnum :: Int -> Min a #

fromEnum :: Min a -> Int #

enumFrom :: Min a -> [Min a] #

enumFromThen :: Min a -> Min a -> [Min a] #

enumFromTo :: Min a -> Min a -> [Min a] #

enumFromThenTo :: Min a -> Min a -> Min a -> [Min a] #

Eq a => Eq (Min a) Source # 

Methods

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

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

Fractional a => Fractional (Min a) Source # 

Methods

(/) :: Min a -> Min a -> Min a #

recip :: Min a -> Min a #

fromRational :: Rational -> Min a #

Num a => Num (Min a) Source # 

Methods

(+) :: Min a -> Min a -> Min a #

(-) :: Min a -> Min a -> Min a #

(*) :: Min a -> Min a -> Min a #

negate :: Min a -> Min a #

abs :: Min a -> Min a #

signum :: Min a -> Min a #

fromInteger :: Integer -> Min a #

Ord a => Ord (Min a) Source # 

Methods

compare :: Min a -> Min a -> Ordering #

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

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

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

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

max :: Min a -> Min a -> Min a #

min :: Min a -> Min a -> Min a #

Read a => Read (Min a) Source # 
Real a => Real (Min a) Source # 

Methods

toRational :: Min a -> Rational #

RealFrac a => RealFrac (Min a) Source # 

Methods

properFraction :: Integral b => Min a -> (b, Min a) #

truncate :: Integral b => Min a -> b #

round :: Integral b => Min a -> b #

ceiling :: Integral b => Min a -> b #

floor :: Integral b => Min a -> b #

Show a => Show (Min a) Source # 

Methods

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

show :: Min a -> String #

showList :: [Min a] -> ShowS #

Generic (Min a) Source # 

Associated Types

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

Methods

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

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

Ord a => Semigroup (Min a) Source # 

Methods

(<>) :: Min a -> Min a -> Min a #

sconcat :: NonEmpty (Min a) -> Min a #

stimes :: Integral b => b -> Min a -> Min a #

(Ord a, HasPositiveInfinity a) => Monoid (Min a) Source #
>>> (getMin . foldMap Min) [1..10]
1.0

Methods

mempty :: Min a #

mappend :: Min a -> Min a -> Min a #

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

Storable a => Storable (Min a) Source # 

Methods

sizeOf :: Min a -> Int #

alignment :: Min a -> Int #

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

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

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

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

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

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

(Semiring a, Ord a, HasPositiveInfinity a) => DetectableZero (Min a) Source # 

Methods

isZero :: Min a -> Bool Source #

(Semiring a, Ord a, HasPositiveInfinity a, HasNegativeInfinity a) => StarSemiring (Min a) Source # 

Methods

star :: Min a -> Min a Source #

plus :: Min a -> Min a Source #

(Semiring a, Ord a, HasPositiveInfinity a) => Semiring (Min a) Source # 

Methods

zero :: Min a Source #

one :: Min a Source #

(<.>) :: Min a -> Min a -> Min a Source #

(<+>) :: Min a -> Min a -> Min a Source #

type Rep1 Min Source # 
type Rep1 Min = D1 (MetaData "Min" "Data.Semiring" "semiring-num-1.0.0.0-7OBAfS7Gua052Mg3sLOjjr" True) (C1 (MetaCons "Min" PrefixI True) (S1 (MetaSel (Just Symbol "getMin") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))
type Rep (Min a) Source # 
type Rep (Min a) = D1 (MetaData "Min" "Data.Semiring" "semiring-num-1.0.0.0-7OBAfS7Gua052Mg3sLOjjr" True) (C1 (MetaCons "Min" PrefixI True) (S1 (MetaSel (Just Symbol "getMin") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))