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

Safe HaskellNone
LanguageHaskell98

Data.Semiring

Contents

Synopsis

Semiring typeclass

class Semiring a where Source #

The class of semirings (types with two binary operations and two respective identities). One can think of a semiring as two monoids of the same underlying type: A commutative monoid and an associative monoid. For any type R with a Num instance, the commutative monoid is (R, +, 0) and the associative monoid is (R, *, 1).

Instances should satisfy the following laws:

additive identity
x + zero = zero + x = x
additive associativity
x + (y + z) = (x + y) + z
additive commutativity
x + y = y + x
multiplicative identity
x * one = one * x = x
multiplicative associativity
x * (y * z) = (x * y) * z
left- and right-distributivity of * over +
x * (y + z) = (x * y) + (x * z)
(x + y) * z = (x * z) + (y * z)
annihilation
zero * x = x * zero = zero

Minimal complete definition

plus, zero, times, one

Methods

plus infixl 6 Source #

Arguments

:: a 
-> a 
-> a

Commutative Operation

zero Source #

Arguments

:: a

Commutative Unit

times infixl 7 Source #

Arguments

:: a 
-> a 
-> a

Associative Operation

one Source #

Arguments

:: a

Associative Unit

zero Source #

Arguments

:: Num a 
=> a

Commutative Unit

one Source #

Arguments

:: Num a 
=> a

Associative Unit

plus infixl 6 Source #

Arguments

:: Num a 
=> a 
-> a 
-> a

Commutative Operation

times infixl 7 Source #

Arguments

:: Num a 
=> a 
-> a 
-> a

Associative Operation

Instances

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

Methods

plus :: Int -> Int -> Int Source #

zero :: Int Source #

times :: Int -> Int -> Int Source #

one :: Int Source #

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

Methods

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

zero :: () Source #

times :: () -> () -> () Source #

one :: () 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

plus :: CCc -> CCc -> CCc Source #

zero :: CCc Source #

times :: CCc -> CCc -> CCc Source #

one :: CCc Source #

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

Methods

plus :: Fd -> Fd -> Fd Source #

zero :: Fd Source #

times :: Fd -> Fd -> Fd Source #

one :: Fd 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 WordPtr Source # 
Semiring IntPtr Source # 
Semiring IntSet Source # 
Semiring a => Semiring [a] Source # 

Methods

plus :: [a] -> [a] -> [a] Source #

zero :: [a] Source #

times :: [a] -> [a] -> [a] Source #

one :: [a] Source #

Semiring a => Semiring (Maybe a) Source # 

Methods

plus :: Maybe a -> Maybe a -> Maybe a Source #

zero :: Maybe a Source #

times :: Maybe a -> Maybe a -> Maybe a Source #

one :: Maybe a Source #

Integral a => Semiring (Ratio a) Source # 

Methods

plus :: Ratio a -> Ratio a -> Ratio a Source #

zero :: Ratio a Source #

times :: Ratio a -> Ratio a -> Ratio a Source #

one :: Ratio a Source #

Semiring a => Semiring (IO a) Source # 

Methods

plus :: IO a -> IO a -> IO a Source #

zero :: IO a Source #

times :: IO a -> IO a -> IO a Source #

one :: IO a Source #

Ring a => Semiring (Complex a) Source # 
HasResolution a => Semiring (Fixed a) Source # 

Methods

plus :: Fixed a -> Fixed a -> Fixed a Source #

zero :: Fixed a Source #

times :: Fixed a -> Fixed a -> Fixed a Source #

one :: Fixed a Source #

Semiring a => Semiring (Min a) Source # 

Methods

plus :: Min a -> Min a -> Min a Source #

zero :: Min a Source #

times :: Min a -> Min a -> Min a Source #

one :: Min a Source #

Semiring a => Semiring (Max a) Source # 

Methods

plus :: Max a -> Max a -> Max a Source #

zero :: Max a Source #

times :: Max a -> Max a -> Max a Source #

one :: Max a Source #

Semiring a => Semiring (Identity a) Source # 
Semiring a => Semiring (Dual a) Source # 

Methods

plus :: Dual a -> Dual a -> Dual a Source #

zero :: Dual a Source #

times :: Dual a -> Dual a -> Dual a Source #

one :: Dual a Source #

Monoid a => Semiring (Endo a) Source #

This is not a true semiring. Even if the underlying monoid is commutative, it is only a near semiring. It is, however, quite 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

plus :: Endo a -> Endo a -> Endo a Source #

zero :: Endo a Source #

times :: Endo a -> Endo a -> Endo a Source #

one :: Endo a Source #

Semiring a => Semiring (Sum a) Source # 

Methods

plus :: Sum a -> Sum a -> Sum a Source #

zero :: Sum a Source #

times :: Sum a -> Sum a -> Sum a Source #

one :: Sum a Source #

Semiring a => Semiring (Product a) Source # 
Semiring a => Semiring (Down a) Source # 

Methods

plus :: Down a -> Down a -> Down a Source #

zero :: Down a Source #

times :: Down a -> Down a -> Down a Source #

one :: Down a Source #

Semiring a => Semiring (IntMap a) Source # 

Methods

plus :: IntMap a -> IntMap a -> IntMap a Source #

zero :: IntMap a Source #

times :: IntMap a -> IntMap a -> IntMap a Source #

one :: IntMap a Source #

Semiring a => Semiring (Seq a) Source # 

Methods

plus :: Seq a -> Seq a -> Seq a Source #

zero :: Seq a Source #

times :: Seq a -> Seq a -> Seq a Source #

one :: Seq a Source #

(Ord a, Semiring a) => Semiring (Set a) Source # 

Methods

plus :: Set a -> Set a -> Set a Source #

zero :: Set a Source #

times :: Set a -> Set a -> Set a Source #

one :: Set a Source #

(Eq a, Hashable a, Semiring a) => Semiring (HashSet a) Source # 
(Unbox a, Semiring a) => Semiring (Vector a) Source # 

Methods

plus :: Vector a -> Vector a -> Vector a Source #

zero :: Vector a Source #

times :: Vector a -> Vector a -> Vector a Source #

one :: Vector a Source #

(Storable a, Semiring a) => Semiring (Vector a) Source # 

Methods

plus :: Vector a -> Vector a -> Vector a Source #

zero :: Vector a Source #

times :: Vector a -> Vector a -> Vector a Source #

one :: Vector a Source #

Semiring a => Semiring (Vector a) Source # 

Methods

plus :: Vector a -> Vector a -> Vector a Source #

zero :: Vector a Source #

times :: Vector a -> Vector a -> Vector a Source #

one :: Vector a Source #

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

Methods

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

zero :: a -> b Source #

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

one :: a -> b Source #

(Ord a, Semiring a, Semiring b) => Semiring (Map a b) Source # 

Methods

plus :: Map a b -> Map a b -> Map a b Source #

zero :: Map a b Source #

times :: Map a b -> Map a b -> Map a b Source #

one :: Map a b Source #

(Eq k, Hashable k, Semiring k, Semiring v) => Semiring (HashMap k v) Source # 

Methods

plus :: HashMap k v -> HashMap k v -> HashMap k v Source #

zero :: HashMap k v Source #

times :: HashMap k v -> HashMap k v -> HashMap k v Source #

one :: HashMap k v Source #

Semiring a => Semiring (Const * a b) Source # 

Methods

plus :: Const * a b -> Const * a b -> Const * a b Source #

zero :: Const * a b Source #

times :: Const * a b -> Const * a b -> Const * a b Source #

one :: Const * a b Source #

(Alternative f, Semiring a) => Semiring (Alt * f a) Source # 

Methods

plus :: Alt * f a -> Alt * f a -> Alt * f a Source #

zero :: Alt * f a Source #

times :: Alt * f a -> Alt * f a -> Alt * f a Source #

one :: Alt * f a Source #

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

Infix shorthand for plus.

(*) :: Semiring a => a -> a -> a infixl 7 Source #

Infix shorthand for times.

(^) :: (Semiring a, Integral b) => a -> b -> a infixr 8 Source #

Raise a number to a non-negative integral power. If the power is negative, this will return zero.

foldMapP :: (Foldable t, Semiring s) => (a -> s) -> t a -> s Source #

Map each element of the structure to a semiring, and combine the results using plus.

foldMapT :: (Foldable t, Semiring s) => (a -> s) -> t a -> s Source #

Map each element of the structure to a semiring, and combine the results using times.

sum :: (Foldable t, Semiring a) => t a -> a Source #

The sum function computes the additive sum of the elements in a structure. This function is lazy. For a strict version, see sum'.

prod :: (Foldable t, Semiring a) => t a -> a Source #

The prod function computes the multiplicative sum of the elements in a structure. This function is lazy. for a strict version, see prod'.

sum' :: (Foldable t, Semiring a) => t a -> a Source #

The sum' function computes the additive sum of the elements in a structure. This function is strict. For a lazy version, see sum.

prod' :: (Foldable t, Semiring a) => t a -> a Source #

The prod' function computes the additive sum of the elements in a structure. This function is strict. For a lazy version, see prod.

Ring typeclass

class Semiring a => Ring a where Source #

The class of semirings with an additive inverse.

negate a + a = zero

Minimal complete definition

negate

Methods

negate :: a -> a Source #

negate :: Num a => a -> a Source #

Instances

Ring Bool Source # 

Methods

negate :: Bool -> Bool Source #

Ring Double Source # 

Methods

negate :: Double -> Double Source #

Ring Float Source # 

Methods

negate :: Float -> Float Source #

Ring Int Source # 

Methods

negate :: Int -> Int Source #

Ring Int8 Source # 

Methods

negate :: Int8 -> Int8 Source #

Ring Int16 Source # 

Methods

negate :: Int16 -> Int16 Source #

Ring Int32 Source # 

Methods

negate :: Int32 -> Int32 Source #

Ring Int64 Source # 

Methods

negate :: Int64 -> Int64 Source #

Ring Integer Source # 
Ring Natural Source # 
Ring Word Source # 

Methods

negate :: Word -> Word Source #

Ring Word8 Source # 

Methods

negate :: Word8 -> Word8 Source #

Ring Word16 Source # 

Methods

negate :: Word16 -> Word16 Source #

Ring Word32 Source # 

Methods

negate :: Word32 -> Word32 Source #

Ring Word64 Source # 

Methods

negate :: Word64 -> Word64 Source #

Ring () Source # 

Methods

negate :: () -> () Source #

Ring CDev Source # 

Methods

negate :: CDev -> CDev Source #

Ring CIno Source # 

Methods

negate :: CIno -> CIno Source #

Ring CMode Source # 

Methods

negate :: CMode -> CMode Source #

Ring COff Source # 

Methods

negate :: COff -> COff Source #

Ring CPid Source # 

Methods

negate :: CPid -> CPid Source #

Ring CSsize Source # 

Methods

negate :: CSsize -> CSsize Source #

Ring CGid Source # 

Methods

negate :: CGid -> CGid Source #

Ring CNlink Source # 

Methods

negate :: CNlink -> CNlink Source #

Ring CUid Source # 

Methods

negate :: CUid -> CUid Source #

Ring CCc Source # 

Methods

negate :: CCc -> CCc Source #

Ring CSpeed Source # 

Methods

negate :: CSpeed -> CSpeed Source #

Ring CTcflag Source # 
Ring CRLim Source # 

Methods

negate :: CRLim -> CRLim Source #

Ring Fd Source # 

Methods

negate :: Fd -> Fd Source #

Ring CChar Source # 

Methods

negate :: CChar -> CChar Source #

Ring CSChar Source # 

Methods

negate :: CSChar -> CSChar Source #

Ring CUChar Source # 

Methods

negate :: CUChar -> CUChar Source #

Ring CShort Source # 

Methods

negate :: CShort -> CShort Source #

Ring CUShort Source # 
Ring CInt Source # 

Methods

negate :: CInt -> CInt Source #

Ring CUInt Source # 

Methods

negate :: CUInt -> CUInt Source #

Ring CLong Source # 

Methods

negate :: CLong -> CLong Source #

Ring CULong Source # 

Methods

negate :: CULong -> CULong Source #

Ring CLLong Source # 

Methods

negate :: CLLong -> CLLong Source #

Ring CULLong Source # 
Ring CFloat Source # 

Methods

negate :: CFloat -> CFloat Source #

Ring CDouble Source # 
Ring CPtrdiff Source # 
Ring CSize Source # 

Methods

negate :: CSize -> CSize Source #

Ring CWchar Source # 

Methods

negate :: CWchar -> CWchar Source #

Ring CSigAtomic Source # 
Ring CClock Source # 

Methods

negate :: CClock -> CClock Source #

Ring CTime Source # 

Methods

negate :: CTime -> CTime Source #

Ring CUSeconds Source # 
Ring CSUSeconds Source # 
Ring CIntPtr Source # 
Ring CUIntPtr Source # 
Ring CIntMax Source # 
Ring CUIntMax Source # 
Ring WordPtr Source # 
Ring IntPtr Source # 

Methods

negate :: IntPtr -> IntPtr Source #

Ring a => Ring [a] Source # 

Methods

negate :: [a] -> [a] Source #

Ring a => Ring (Maybe a) Source # 

Methods

negate :: Maybe a -> Maybe a Source #

Integral a => Ring (Ratio a) Source # 

Methods

negate :: Ratio a -> Ratio a Source #

Ring a => Ring (IO a) Source # 

Methods

negate :: IO a -> IO a Source #

Ring a => Ring (Complex a) Source # 

Methods

negate :: Complex a -> Complex a Source #

HasResolution a => Ring (Fixed a) Source # 

Methods

negate :: Fixed a -> Fixed a Source #

Ring a => Ring (Min a) Source # 

Methods

negate :: Min a -> Min a Source #

Ring a => Ring (Max a) Source # 

Methods

negate :: Max a -> Max a Source #

Ring a => Ring (Identity a) Source # 

Methods

negate :: Identity a -> Identity a Source #

Ring a => Ring (Dual a) Source # 

Methods

negate :: Dual a -> Dual a Source #

(Monoid a, Ring a) => Ring (Endo a) Source # 

Methods

negate :: Endo a -> Endo a Source #

Ring a => Ring (Sum a) Source # 

Methods

negate :: Sum a -> Sum a Source #

Ring a => Ring (Product a) Source # 

Methods

negate :: Product a -> Product a Source #

Ring a => Ring (Down a) Source # 

Methods

negate :: Down a -> Down a Source #

(Unbox a, Ring a) => Ring (Vector a) Source # 

Methods

negate :: Vector a -> Vector a Source #

(Storable a, Ring a) => Ring (Vector a) Source # 

Methods

negate :: Vector a -> Vector a Source #

Ring a => Ring (Vector a) Source # 

Methods

negate :: Vector a -> Vector a Source #

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

Methods

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

Ring a => Ring (Const * a b) Source # 

Methods

negate :: Const * a b -> Const * a b Source #

(Alternative f, Ring a) => Ring (Alt * f a) Source # 

Methods

negate :: Alt * f a -> Alt * f a Source #

(-) :: Ring a => a -> a -> a infixl 6 Source #

Infix shorthand for minus.

minus :: Ring a => a -> a -> a infixl 6 Source #

Substract two Ring values. For any type R with a Num instance, this is the same as Prelude's -.

x minus y = x + negate y