| Safe Haskell | None | 
|---|---|
| Language | Haskell98 | 
Data.Semiring
Description
A class for semirings (types with two binary operations, one commutative and one associative, and two respective identities), with various general-purpose instances.
Synopsis
- class Semiring a where
- (+) :: Semiring a => a -> a -> a
- (*) :: Semiring a => a -> a -> a
- (^) :: (Semiring a, Integral b) => a -> b -> a
- foldMapP :: (Foldable t, Semiring s) => (a -> s) -> t a -> s
- foldMapT :: (Foldable t, Semiring s) => (a -> s) -> t a -> s
- sum :: (Foldable t, Semiring a) => t a -> a
- product :: (Foldable t, Semiring a) => t a -> a
- sum' :: (Foldable t, Semiring a) => t a -> a
- product' :: (Foldable t, Semiring a) => t a -> a
- isZero :: (Eq a, Semiring a) => a -> Bool
- isOne :: (Eq a, Semiring a) => a -> Bool
- newtype Add a = Add {- getAdd :: a
 
- newtype Mul a = Mul {- getMul :: a
 
- newtype WrappedNum a = WrapNum {- unwrapNum :: a
 
- newtype Mod2 = Mod2 {}
- newtype IntSetOf a = IntSetOf {}
- newtype IntMapOf k v = IntMapOf {}
- class Semiring a => Ring a where- negate :: a -> a
 
- fromInteger :: Ring a => Integer -> a
- fromIntegral :: (Integral a, Ring b) => a -> b
- minus :: Ring a => a -> a -> a
- (-) :: Ring a => a -> a -> a
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, with the first being commutative.
 In the documentation, you will often see the first
 monoid being referred to as additive, and the second
 monoid being referred to as multiplicative, a typical
 convention when talking about semirings.
For any type R with a Num
 instance, the additive monoid is (R, +, 0)
 and the multiplicative monoid is (R, *, 1).
For Bool, the additive monoid is (Bool, ||, False)
 and the multiplicative monoid is (Bool, &&, True).
Instances should satisfy the following laws:
- additive left identity
- zero- +x = x
- additive right identity
- x- +- zero= x
- additive associativity
- x- +(y- +z) = (x- +y)- +z
- additive commutativity
- x- +y = y- +x
- multiplicative left identity
- one- *x = x
- multiplicative right identity
- x- *- one= x
- multiplicative associativity
- x- *(y- *z) = (x- *y)- *z
- left-distributivity of *over+
- x- *(y- +z) = (x- *y)- +(x- *z)
- right-distributivity of *over+
- (x- +y)- *z = (x- *z)- +(y- *z)
- annihilation
- zero- *x = x- *- zero=- zero
Minimal complete definition
plus, times, (zero, one | fromNatural)
Methods
Arguments
| :: a | |
| -> a | |
| -> a | Commutative Operation | 
Arguments
| :: a | Commutative Unit | 
Arguments
| :: a | |
| -> a | |
| -> a | Associative Operation | 
Arguments
| :: a | Associative Unit | 
Arguments
| :: Natural | |
| -> a | Homomorphism of additive semigroups | 
Instances
(^) :: (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 call error.
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.
Types
Instances
| Functor Add Source # | |
| Foldable Add Source # | |
| Defined in Data.Semiring Methods fold :: Monoid m => Add m -> m # foldMap :: Monoid m => (a -> m) -> Add a -> 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 # elem :: Eq a => a -> Add a -> Bool # maximum :: Ord a => Add a -> a # | |
| Traversable Add Source # | |
| Bounded a => Bounded (Add a) Source # | |
| Enum a => Enum (Add a) Source # | |
| Eq a => Eq (Add a) Source # | |
| Fractional a => Fractional (Add a) Source # | |
| Num a => Num (Add a) Source # | |
| Ord a => Ord (Add a) Source # | |
| Read a => Read (Add a) Source # | |
| Real a => Real (Add a) Source # | |
| Defined in Data.Semiring Methods toRational :: Add a -> Rational # | |
| RealFrac a => RealFrac (Add a) Source # | |
| Show a => Show (Add a) Source # | |
| Generic (Add a) Source # | |
| Semiring a => Semigroup (Add a) Source # | |
| Semiring a => Monoid (Add a) Source # | |
| Storable a => Storable (Add a) Source # | |
| Generic1 Add Source # | |
| type Rep (Add a) Source # | |
| Defined in Data.Semiring | |
| type Rep1 Add Source # | |
| Defined in Data.Semiring | |
Instances
| Functor Mul Source # | |
| Foldable Mul Source # | |
| Defined in Data.Semiring Methods fold :: Monoid m => Mul m -> m # foldMap :: Monoid m => (a -> m) -> Mul a -> 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 # elem :: Eq a => a -> Mul a -> Bool # maximum :: Ord a => Mul a -> a # | |
| Traversable Mul Source # | |
| Bounded a => Bounded (Mul a) Source # | |
| Enum a => Enum (Mul a) Source # | |
| Eq a => Eq (Mul a) Source # | |
| Fractional a => Fractional (Mul a) Source # | |
| Num a => Num (Mul a) Source # | |
| Ord a => Ord (Mul a) Source # | |
| Read a => Read (Mul a) Source # | |
| Real a => Real (Mul a) Source # | |
| Defined in Data.Semiring Methods toRational :: Mul a -> Rational # | |
| RealFrac a => RealFrac (Mul a) Source # | |
| Show a => Show (Mul a) Source # | |
| Generic (Mul a) Source # | |
| Semiring a => Semigroup (Mul a) Source # | |
| Semiring a => Monoid (Mul a) Source # | |
| Storable a => Storable (Mul a) Source # | |
| Generic1 Mul Source # | |
| type Rep (Mul a) Source # | |
| Defined in Data.Semiring | |
| type Rep1 Mul Source # | |
| Defined in Data.Semiring | |
newtype WrappedNum a Source #
Provide Semiring and Ring for an arbitrary Num. It is useful with GHC 8.6+'s DerivingVia extension.
Instances
Mod2 represents the integers mod 2.
It is useful in the computing of Zhegalkin polynomials.
Instances
| Bounded Mod2 Source # | |
| Enum Mod2 Source # | |
| Eq Mod2 Source # | |
| Ord Mod2 Source # | |
| Read Mod2 Source # | |
| Show Mod2 Source # | |
| Generic Mod2 Source # | |
| Ring Mod2 Source # | |
| Semiring Mod2 Source # | |
| Field Mod2 Source # | |
| Defined in Data.Euclidean | |
| Euclidean Mod2 Source # | |
| GcdDomain Mod2 Source # | |
| Star Mod2 Source # | |
| type Rep Mod2 Source # | |
| Defined in Data.Semiring | |
Wrapper to mimic Set (Sum Int),
 Set (Product Int), etc.,
 while having a more efficient underlying representation.
Instances
| Eq (IntSetOf a) Source # | |
| Ord (IntSetOf a) Source # | |
| Read (IntSetOf a) Source # | |
| Show (IntSetOf a) Source # | |
| Generic (IntSetOf a) Source # | |
| Semigroup (IntSetOf a) Source # | |
| Monoid (IntSetOf a) Source # | |
| (Coercible Int a, Monoid a) => Semiring (IntSetOf a) Source # | |
| Generic1 IntSetOf Source # | |
| type Rep (IntSetOf a) Source # | |
| Defined in Data.Semiring | |
| type Rep1 IntSetOf Source # | |
| Defined in Data.Semiring | |
Wrapper to mimic Map (Sum Int) v,
 Map (Product Int) v, etc.,
 while having a more efficient underlying representation.
Instances
| Generic1 (IntMapOf k :: Type -> Type) Source # | |
| Eq v => Eq (IntMapOf k v) Source # | |
| Ord v => Ord (IntMapOf k v) Source # | |
| Defined in Data.Semiring | |
| Read v => Read (IntMapOf k v) Source # | |
| Show v => Show (IntMapOf k v) Source # | |
| Generic (IntMapOf k v) Source # | |
| Semigroup (IntMapOf k v) Source # | |
| Monoid (IntMapOf k v) Source # | |
| (Coercible Int k, Monoid k, Semiring v) => Semiring (IntMapOf k v) Source # | |
| type Rep1 (IntMapOf k :: Type -> Type) Source # | |
| Defined in Data.Semiring | |
| type Rep (IntMapOf k v) Source # | |
| Defined in Data.Semiring | |
Ring typeclass
class Semiring a => Ring a where Source #
Instances
fromInteger :: Ring a => Integer -> a Source #
fromIntegral :: (Integral a, Ring b) => a -> b Source #
Convert from integral to ring.