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

Safe HaskellNone
LanguageHaskell98

Data.Semiring

Contents

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

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

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

Instances
Semiring Bool Source # 
Instance details

Defined in Data.Semiring

Semiring Double Source # 
Instance details

Defined in Data.Semiring

Semiring Float Source # 
Instance details

Defined in Data.Semiring

Semiring Int Source # 
Instance details

Defined in Data.Semiring

Methods

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

zero :: Int Source #

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

one :: Int Source #

Semiring Int8 Source # 
Instance details

Defined in Data.Semiring

Semiring Int16 Source # 
Instance details

Defined in Data.Semiring

Semiring Int32 Source # 
Instance details

Defined in Data.Semiring

Semiring Int64 Source # 
Instance details

Defined in Data.Semiring

Semiring Integer Source # 
Instance details

Defined in Data.Semiring

Semiring Natural Source # 
Instance details

Defined in Data.Semiring

Semiring Word Source # 
Instance details

Defined in Data.Semiring

Semiring Word8 Source # 
Instance details

Defined in Data.Semiring

Semiring Word16 Source # 
Instance details

Defined in Data.Semiring

Semiring Word32 Source # 
Instance details

Defined in Data.Semiring

Semiring Word64 Source # 
Instance details

Defined in Data.Semiring

Semiring () Source # 
Instance details

Defined in Data.Semiring

Methods

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

zero :: () Source #

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

one :: () Source #

Semiring CDev Source # 
Instance details

Defined in Data.Semiring

Semiring CIno Source # 
Instance details

Defined in Data.Semiring

Semiring CMode Source # 
Instance details

Defined in Data.Semiring

Semiring COff Source # 
Instance details

Defined in Data.Semiring

Semiring CPid Source # 
Instance details

Defined in Data.Semiring

Semiring CSsize Source # 
Instance details

Defined in Data.Semiring

Semiring CGid Source # 
Instance details

Defined in Data.Semiring

Semiring CNlink Source # 
Instance details

Defined in Data.Semiring

Semiring CUid Source # 
Instance details

Defined in Data.Semiring

Semiring CCc Source # 
Instance details

Defined in Data.Semiring

Methods

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

zero :: CCc Source #

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

one :: CCc Source #

Semiring CSpeed Source # 
Instance details

Defined in Data.Semiring

Semiring CTcflag Source # 
Instance details

Defined in Data.Semiring

Semiring CRLim Source # 
Instance details

Defined in Data.Semiring

Semiring Fd Source # 
Instance details

Defined in Data.Semiring

Methods

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

zero :: Fd Source #

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

one :: Fd Source #

Semiring CChar Source # 
Instance details

Defined in Data.Semiring

Semiring CSChar Source # 
Instance details

Defined in Data.Semiring

Semiring CUChar Source # 
Instance details

Defined in Data.Semiring

Semiring CShort Source # 
Instance details

Defined in Data.Semiring

Semiring CUShort Source # 
Instance details

Defined in Data.Semiring

Semiring CInt Source # 
Instance details

Defined in Data.Semiring

Semiring CUInt Source # 
Instance details

Defined in Data.Semiring

Semiring CLong Source # 
Instance details

Defined in Data.Semiring

Semiring CULong Source # 
Instance details

Defined in Data.Semiring

Semiring CLLong Source # 
Instance details

Defined in Data.Semiring

Semiring CULLong Source # 
Instance details

Defined in Data.Semiring

Semiring CFloat Source # 
Instance details

Defined in Data.Semiring

Semiring CDouble Source # 
Instance details

Defined in Data.Semiring

Semiring CPtrdiff Source # 
Instance details

Defined in Data.Semiring

Semiring CSize Source # 
Instance details

Defined in Data.Semiring

Semiring CWchar Source # 
Instance details

Defined in Data.Semiring

Semiring CSigAtomic Source # 
Instance details

Defined in Data.Semiring

Semiring CClock Source # 
Instance details

Defined in Data.Semiring

Semiring CTime Source # 
Instance details

Defined in Data.Semiring

Semiring CUSeconds Source # 
Instance details

Defined in Data.Semiring

Semiring CSUSeconds Source # 
Instance details

Defined in Data.Semiring

Semiring CIntPtr Source # 
Instance details

Defined in Data.Semiring

Semiring CUIntPtr Source # 
Instance details

Defined in Data.Semiring

Semiring CIntMax Source # 
Instance details

Defined in Data.Semiring

Semiring CUIntMax Source # 
Instance details

Defined in Data.Semiring

Semiring WordPtr Source # 
Instance details

Defined in Data.Semiring

Semiring IntPtr Source # 
Instance details

Defined in Data.Semiring

Semiring a => Semiring [a] Source #

The Semiring instance for '[a]' can be interpreted as treating each element of the list as coefficients to a polynomial in one variable.

Examples

Expand

poly1 = [1,2,3] :: [Int] poly2 = [ 2,1] :: [Int] poly1 * poly2 = [2,5,8,3] fromList [2,5,8,3]

Instance details

Defined in Data.Semiring

Methods

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

zero :: [a] Source #

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

one :: [a] Source #

Semiring a => Semiring (Maybe a) Source # 
Instance details

Defined in Data.Semiring

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 # 
Instance details

Defined in Data.Semiring

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 # 
Instance details

Defined in Data.Semiring

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 #

This instance can suffer due to floating point arithmetic.

Instance details

Defined in Data.Semiring

HasResolution a => Semiring (Fixed a) Source # 
Instance details

Defined in Data.Semiring

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 (Predicate a) Source # 
Instance details

Defined in Data.Semiring

Semiring a => Semiring (Equivalence a) Source # 
Instance details

Defined in Data.Semiring

Semiring a => Semiring (Identity a) Source # 
Instance details

Defined in Data.Semiring

Semiring a => Semiring (Dual a) Source # 
Instance details

Defined in Data.Semiring

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 #

Semiring a => Semiring (Down a) Source # 
Instance details

Defined in Data.Semiring

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 #

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

The multiplication laws are satisfied for any underlying Monoid, so we require a Monoid constraint instead of a Semiring constraint since times can use the context of either.

Instance details

Defined in Data.Semiring

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, Monoid a) => Semiring (HashSet a) Source #

The multiplication laws are satisfied for any underlying Monoid, so we require a Monoid constraint instead of a Semiring constraint since times can use the context of either.

Instance details

Defined in Data.Semiring

(Unbox a, Semiring a) => Semiring (Vector a) Source # 
Instance details

Defined in Data.Semiring

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 # 
Instance details

Defined in Data.Semiring

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 #

The Semiring instance for 'Vector a' can be interpreted as treating each element of the list as coefficients to a polynomial in one variable.

Examples

Expand

poly1 = Vector.fromList [1,2,3 :: Int] poly2 = Vector.fromList [ 2,1 :: Int] poly1 * poly2 fromList [2,5,8,3]

Instance details

Defined in Data.Semiring

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 #

(Coercible Int a, Monoid a) => Semiring (IntSetOf a) Source # 
Instance details

Defined in Data.Semiring

Num a => Semiring (WrappedNum a) Source # 
Instance details

Defined in Data.Semiring

Semiring a => Semiring (GenericSemiring a) Source # 
Instance details

Defined in Data.Semiring.Generic

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

Defined in Data.Semiring

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 #

(Semiring a, Semiring b) => Semiring (a, b) Source # 
Instance details

Defined in Data.Semiring.Generic

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 #

Semiring a => Semiring (Op a b) Source # 
Instance details

Defined in Data.Semiring

Methods

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

zero :: Op a b Source #

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

one :: Op a b Source #

Semiring (Proxy a) Source # 
Instance details

Defined in Data.Semiring

Methods

plus :: Proxy a -> Proxy a -> Proxy a Source #

zero :: Proxy a Source #

times :: Proxy a -> Proxy a -> Proxy a Source #

one :: Proxy a Source #

(Ord k, Monoid k, Semiring v) => Semiring (Map k v) Source #

The multiplication laws are satisfied for any underlying Monoid as the key type, so we require a Monoid constraint instead of a Semiring constraint since times can use the context of either.

Instance details

Defined in Data.Semiring

Methods

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

zero :: Map k v Source #

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

one :: Map k v Source #

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

The multiplication laws are satisfied for any underlying Monoid as the key type, so we require a Monoid constraint instead of a Semiring constraint since times can use the context of either.

Instance details

Defined in Data.Semiring

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 #

(Coercible Int k, Monoid k, Semiring v) => Semiring (IntMapOf k v) Source # 
Instance details

Defined in Data.Semiring

Methods

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

zero :: IntMapOf k v Source #

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

one :: IntMapOf k v Source #

(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 #

(Semiring a, Semiring b, Semiring c) => Semiring (a, b, c) Source # 
Instance details

Defined in Data.Semiring.Generic

Methods

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

zero :: (a, b, c) Source #

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

one :: (a, b, c) Source #

Semiring a => Semiring (Const a b) Source # 
Instance details

Defined in Data.Semiring

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 #

(Semiring a, Applicative f) => Semiring (Ap f a) Source # 
Instance details

Defined in Data.Semiring

Methods

plus :: Ap f a -> Ap f a -> Ap f a Source #

zero :: Ap f a Source #

times :: Ap f a -> Ap f a -> Ap f a Source #

one :: Ap f a Source #

(Semiring a, Semiring b, Semiring c, Semiring d) => Semiring (a, b, c, d) Source # 
Instance details

Defined in Data.Semiring.Generic

Methods

plus :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) Source #

zero :: (a, b, c, d) Source #

times :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) Source #

one :: (a, b, c, d) Source #

(Semiring a, Semiring b, Semiring c, Semiring d, Semiring e) => Semiring (a, b, c, d, e) Source # 
Instance details

Defined in Data.Semiring.Generic

Methods

plus :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) Source #

zero :: (a, b, c, d, e) Source #

times :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) Source #

one :: (a, b, c, d, e) Source #

(Semiring a, Semiring b, Semiring c, Semiring d, Semiring e, Semiring f) => Semiring (a, b, c, d, e, f) Source # 
Instance details

Defined in Data.Semiring.Generic

Methods

plus :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> (a, b, c, d, e, f) Source #

zero :: (a, b, c, d, e, f) Source #

times :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> (a, b, c, d, e, f) Source #

one :: (a, b, c, d, e, f) Source #

(Semiring a, Semiring b, Semiring c, Semiring d, Semiring e, Semiring f, Semiring g) => Semiring (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Data.Semiring.Generic

Methods

plus :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) Source #

zero :: (a, b, c, d, e, f, g) Source #

times :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) Source #

one :: (a, b, c, d, e, f, g) 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'.

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

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

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.

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

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

Types

newtype Add a Source #

Monoid under plus. Analogous to Sum, but uses the Semiring constraint rather than Num.

Constructors

Add 

Fields

Instances
Functor Add Source # 
Instance details

Defined in Data.Semiring

Methods

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

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

Foldable Add Source # 
Instance details

Defined in Data.Semiring

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 # 
Instance details

Defined in Data.Semiring

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) #

Bounded a => Bounded (Add a) Source # 
Instance details

Defined in Data.Semiring

Methods

minBound :: Add a #

maxBound :: Add a #

Enum a => Enum (Add a) Source # 
Instance details

Defined in Data.Semiring

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 # 
Instance details

Defined in Data.Semiring

Methods

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

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

Fractional a => Fractional (Add a) Source # 
Instance details

Defined in Data.Semiring

Methods

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

recip :: Add a -> Add a #

fromRational :: Rational -> Add a #

Num a => Num (Add a) Source # 
Instance details

Defined in Data.Semiring

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 # 
Instance details

Defined in Data.Semiring

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 # 
Instance details

Defined in Data.Semiring

Real a => Real (Add a) Source # 
Instance details

Defined in Data.Semiring

Methods

toRational :: Add a -> Rational #

RealFrac a => RealFrac (Add a) Source # 
Instance details

Defined in Data.Semiring

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 # 
Instance details

Defined in Data.Semiring

Methods

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

show :: Add a -> String #

showList :: [Add a] -> ShowS #

Generic (Add a) Source # 
Instance details

Defined in Data.Semiring

Associated Types

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

Methods

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

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

Semiring a => Semigroup (Add a) Source # 
Instance details

Defined in Data.Semiring

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 # 
Instance details

Defined in Data.Semiring

Methods

mempty :: Add a #

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

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

Storable a => Storable (Add a) Source # 
Instance details

Defined in Data.Semiring

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 () #

Generic1 Add Source # 
Instance details

Defined in Data.Semiring

Associated Types

type Rep1 Add :: k -> Type #

Methods

from1 :: Add a -> Rep1 Add a #

to1 :: Rep1 Add a -> Add a #

type Rep (Add a) Source # 
Instance details

Defined in Data.Semiring

type Rep (Add a) = D1 (MetaData "Add" "Data.Semiring" "semirings-0.3.1.2-6JsgtI1LNjC2TpBZyMwt2E" True) (C1 (MetaCons "Add" PrefixI True) (S1 (MetaSel (Just "getAdd") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 Add Source # 
Instance details

Defined in Data.Semiring

type Rep1 Add = D1 (MetaData "Add" "Data.Semiring" "semirings-0.3.1.2-6JsgtI1LNjC2TpBZyMwt2E" True) (C1 (MetaCons "Add" PrefixI True) (S1 (MetaSel (Just "getAdd") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))

newtype Mul a Source #

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

Constructors

Mul 

Fields

Instances
Functor Mul Source # 
Instance details

Defined in Data.Semiring

Methods

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

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

Foldable Mul Source # 
Instance details

Defined in Data.Semiring

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 # 
Instance details

Defined in Data.Semiring

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) #

Bounded a => Bounded (Mul a) Source # 
Instance details

Defined in Data.Semiring

Methods

minBound :: Mul a #

maxBound :: Mul a #

Enum a => Enum (Mul a) Source # 
Instance details

Defined in Data.Semiring

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 # 
Instance details

Defined in Data.Semiring

Methods

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

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

Fractional a => Fractional (Mul a) Source # 
Instance details

Defined in Data.Semiring

Methods

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

recip :: Mul a -> Mul a #

fromRational :: Rational -> Mul a #

Num a => Num (Mul a) Source # 
Instance details

Defined in Data.Semiring

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 # 
Instance details

Defined in Data.Semiring

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 # 
Instance details

Defined in Data.Semiring

Real a => Real (Mul a) Source # 
Instance details

Defined in Data.Semiring

Methods

toRational :: Mul a -> Rational #

RealFrac a => RealFrac (Mul a) Source # 
Instance details

Defined in Data.Semiring

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 # 
Instance details

Defined in Data.Semiring

Methods

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

show :: Mul a -> String #

showList :: [Mul a] -> ShowS #

Generic (Mul a) Source # 
Instance details

Defined in Data.Semiring

Associated Types

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

Methods

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

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

Semiring a => Semigroup (Mul a) Source # 
Instance details

Defined in Data.Semiring

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 # 
Instance details

Defined in Data.Semiring

Methods

mempty :: Mul a #

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

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

Storable a => Storable (Mul a) Source # 
Instance details

Defined in Data.Semiring

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 () #

Generic1 Mul Source # 
Instance details

Defined in Data.Semiring

Associated Types

type Rep1 Mul :: k -> Type #

Methods

from1 :: Mul a -> Rep1 Mul a #

to1 :: Rep1 Mul a -> Mul a #

type Rep (Mul a) Source # 
Instance details

Defined in Data.Semiring

type Rep (Mul a) = D1 (MetaData "Mul" "Data.Semiring" "semirings-0.3.1.2-6JsgtI1LNjC2TpBZyMwt2E" True) (C1 (MetaCons "Mul" PrefixI True) (S1 (MetaSel (Just "getMul") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 Mul Source # 
Instance details

Defined in Data.Semiring

type Rep1 Mul = D1 (MetaData "Mul" "Data.Semiring" "semirings-0.3.1.2-6JsgtI1LNjC2TpBZyMwt2E" True) (C1 (MetaCons "Mul" PrefixI True) (S1 (MetaSel (Just "getMul") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))

newtype WrappedNum a Source #

Provide Semiring and Ring for an arbitrary Num. It is useful with GHC 8.6+'s DerivingVia extension.

Constructors

WrapNum 

Fields

Instances
Functor WrappedNum Source # 
Instance details

Defined in Data.Semiring

Methods

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

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

Foldable WrappedNum Source # 
Instance details

Defined in Data.Semiring

Methods

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

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

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

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

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

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

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

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

toList :: WrappedNum a -> [a] #

null :: WrappedNum a -> Bool #

length :: WrappedNum a -> Int #

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

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

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

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

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

Traversable WrappedNum Source # 
Instance details

Defined in Data.Semiring

Methods

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

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

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

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

Bounded a => Bounded (WrappedNum a) Source # 
Instance details

Defined in Data.Semiring

Enum a => Enum (WrappedNum a) Source # 
Instance details

Defined in Data.Semiring

Eq a => Eq (WrappedNum a) Source # 
Instance details

Defined in Data.Semiring

Methods

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

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

Fractional a => Fractional (WrappedNum a) Source # 
Instance details

Defined in Data.Semiring

Num a => Num (WrappedNum a) Source # 
Instance details

Defined in Data.Semiring

Ord a => Ord (WrappedNum a) Source # 
Instance details

Defined in Data.Semiring

Read a => Read (WrappedNum a) Source # 
Instance details

Defined in Data.Semiring

Real a => Real (WrappedNum a) Source # 
Instance details

Defined in Data.Semiring

RealFrac a => RealFrac (WrappedNum a) Source # 
Instance details

Defined in Data.Semiring

Methods

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

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

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

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

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

Show a => Show (WrappedNum a) Source # 
Instance details

Defined in Data.Semiring

Generic (WrappedNum a) Source # 
Instance details

Defined in Data.Semiring

Associated Types

type Rep (WrappedNum a) :: Type -> Type #

Methods

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

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

Storable a => Storable (WrappedNum a) Source # 
Instance details

Defined in Data.Semiring

Methods

sizeOf :: WrappedNum a -> Int #

alignment :: WrappedNum a -> Int #

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

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

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

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

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

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

Num a => Ring (WrappedNum a) Source # 
Instance details

Defined in Data.Semiring

Num a => Semiring (WrappedNum a) Source # 
Instance details

Defined in Data.Semiring

Generic1 WrappedNum Source # 
Instance details

Defined in Data.Semiring

Associated Types

type Rep1 WrappedNum :: k -> Type #

type Rep (WrappedNum a) Source # 
Instance details

Defined in Data.Semiring

type Rep (WrappedNum a) = D1 (MetaData "WrappedNum" "Data.Semiring" "semirings-0.3.1.2-6JsgtI1LNjC2TpBZyMwt2E" True) (C1 (MetaCons "WrapNum" PrefixI True) (S1 (MetaSel (Just "unwrapNum") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 WrappedNum Source # 
Instance details

Defined in Data.Semiring

type Rep1 WrappedNum = D1 (MetaData "WrappedNum" "Data.Semiring" "semirings-0.3.1.2-6JsgtI1LNjC2TpBZyMwt2E" True) (C1 (MetaCons "WrapNum" PrefixI True) (S1 (MetaSel (Just "unwrapNum") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))

newtype IntSetOf a Source #

Wrapper to mimic Set (Sum Int), Set (Product Int), etc., while having a more efficient underlying representation.

Constructors

IntSetOf 

Fields

Instances
Eq (IntSetOf a) Source # 
Instance details

Defined in Data.Semiring

Methods

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

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

Ord (IntSetOf a) Source # 
Instance details

Defined in Data.Semiring

Methods

compare :: IntSetOf a -> IntSetOf a -> Ordering #

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

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

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

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

max :: IntSetOf a -> IntSetOf a -> IntSetOf a #

min :: IntSetOf a -> IntSetOf a -> IntSetOf a #

Read (IntSetOf a) Source # 
Instance details

Defined in Data.Semiring

Show (IntSetOf a) Source # 
Instance details

Defined in Data.Semiring

Methods

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

show :: IntSetOf a -> String #

showList :: [IntSetOf a] -> ShowS #

Generic (IntSetOf a) Source # 
Instance details

Defined in Data.Semiring

Associated Types

type Rep (IntSetOf a) :: Type -> Type #

Methods

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

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

Semigroup (IntSetOf a) Source # 
Instance details

Defined in Data.Semiring

Methods

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

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

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

Monoid (IntSetOf a) Source # 
Instance details

Defined in Data.Semiring

Methods

mempty :: IntSetOf a #

mappend :: IntSetOf a -> IntSetOf a -> IntSetOf a #

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

(Coercible Int a, Monoid a) => Semiring (IntSetOf a) Source # 
Instance details

Defined in Data.Semiring

Generic1 IntSetOf Source # 
Instance details

Defined in Data.Semiring

Associated Types

type Rep1 IntSetOf :: k -> Type #

Methods

from1 :: IntSetOf a -> Rep1 IntSetOf a #

to1 :: Rep1 IntSetOf a -> IntSetOf a #

type Rep (IntSetOf a) Source # 
Instance details

Defined in Data.Semiring

type Rep (IntSetOf a) = D1 (MetaData "IntSetOf" "Data.Semiring" "semirings-0.3.1.2-6JsgtI1LNjC2TpBZyMwt2E" True) (C1 (MetaCons "IntSetOf" PrefixI True) (S1 (MetaSel (Just "getIntSet") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IntSet)))
type Rep1 IntSetOf Source # 
Instance details

Defined in Data.Semiring

type Rep1 IntSetOf = D1 (MetaData "IntSetOf" "Data.Semiring" "semirings-0.3.1.2-6JsgtI1LNjC2TpBZyMwt2E" True) (C1 (MetaCons "IntSetOf" PrefixI True) (S1 (MetaSel (Just "getIntSet") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IntSet)))

newtype IntMapOf k v Source #

Wrapper to mimic Map (Sum Int) v, Map (Product Int) v, etc., while having a more efficient underlying representation.

Constructors

IntMapOf 

Fields

Instances
Generic1 (IntMapOf k :: Type -> Type) Source # 
Instance details

Defined in Data.Semiring

Associated Types

type Rep1 (IntMapOf k) :: k -> Type #

Methods

from1 :: IntMapOf k a -> Rep1 (IntMapOf k) a #

to1 :: Rep1 (IntMapOf k) a -> IntMapOf k a #

Eq v => Eq (IntMapOf k v) Source # 
Instance details

Defined in Data.Semiring

Methods

(==) :: IntMapOf k v -> IntMapOf k v -> Bool #

(/=) :: IntMapOf k v -> IntMapOf k v -> Bool #

Ord v => Ord (IntMapOf k v) Source # 
Instance details

Defined in Data.Semiring

Methods

compare :: IntMapOf k v -> IntMapOf k v -> Ordering #

(<) :: IntMapOf k v -> IntMapOf k v -> Bool #

(<=) :: IntMapOf k v -> IntMapOf k v -> Bool #

(>) :: IntMapOf k v -> IntMapOf k v -> Bool #

(>=) :: IntMapOf k v -> IntMapOf k v -> Bool #

max :: IntMapOf k v -> IntMapOf k v -> IntMapOf k v #

min :: IntMapOf k v -> IntMapOf k v -> IntMapOf k v #

Read v => Read (IntMapOf k v) Source # 
Instance details

Defined in Data.Semiring

Show v => Show (IntMapOf k v) Source # 
Instance details

Defined in Data.Semiring

Methods

showsPrec :: Int -> IntMapOf k v -> ShowS #

show :: IntMapOf k v -> String #

showList :: [IntMapOf k v] -> ShowS #

Generic (IntMapOf k v) Source # 
Instance details

Defined in Data.Semiring

Associated Types

type Rep (IntMapOf k v) :: Type -> Type #

Methods

from :: IntMapOf k v -> Rep (IntMapOf k v) x #

to :: Rep (IntMapOf k v) x -> IntMapOf k v #

Semigroup (IntMapOf k v) Source # 
Instance details

Defined in Data.Semiring

Methods

(<>) :: IntMapOf k v -> IntMapOf k v -> IntMapOf k v #

sconcat :: NonEmpty (IntMapOf k v) -> IntMapOf k v #

stimes :: Integral b => b -> IntMapOf k v -> IntMapOf k v #

Monoid (IntMapOf k v) Source # 
Instance details

Defined in Data.Semiring

Methods

mempty :: IntMapOf k v #

mappend :: IntMapOf k v -> IntMapOf k v -> IntMapOf k v #

mconcat :: [IntMapOf k v] -> IntMapOf k v #

(Coercible Int k, Monoid k, Semiring v) => Semiring (IntMapOf k v) Source # 
Instance details

Defined in Data.Semiring

Methods

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

zero :: IntMapOf k v Source #

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

one :: IntMapOf k v Source #

type Rep1 (IntMapOf k :: Type -> Type) Source # 
Instance details

Defined in Data.Semiring

type Rep1 (IntMapOf k :: Type -> Type) = D1 (MetaData "IntMapOf" "Data.Semiring" "semirings-0.3.1.2-6JsgtI1LNjC2TpBZyMwt2E" True) (C1 (MetaCons "IntMapOf" PrefixI True) (S1 (MetaSel (Just "getIntMap") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 IntMap)))
type Rep (IntMapOf k v) Source # 
Instance details

Defined in Data.Semiring

type Rep (IntMapOf k v) = D1 (MetaData "IntMapOf" "Data.Semiring" "semirings-0.3.1.2-6JsgtI1LNjC2TpBZyMwt2E" True) (C1 (MetaCons "IntMapOf" PrefixI True) (S1 (MetaSel (Just "getIntMap") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (IntMap v))))

Ring typeclass

class Semiring a => Ring a where Source #

The class of semirings with an additive inverse.

negate a + a = zero

Methods

negate :: a -> a Source #

Instances
Ring Bool Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: Bool -> Bool Source #

Ring Double Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: Double -> Double Source #

Ring Float Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: Float -> Float Source #

Ring Int Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: Int -> Int Source #

Ring Int8 Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: Int8 -> Int8 Source #

Ring Int16 Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: Int16 -> Int16 Source #

Ring Int32 Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: Int32 -> Int32 Source #

Ring Int64 Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: Int64 -> Int64 Source #

Ring Integer Source # 
Instance details

Defined in Data.Semiring

Ring Natural Source # 
Instance details

Defined in Data.Semiring

Ring Word Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: Word -> Word Source #

Ring Word8 Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: Word8 -> Word8 Source #

Ring Word16 Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: Word16 -> Word16 Source #

Ring Word32 Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: Word32 -> Word32 Source #

Ring Word64 Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: Word64 -> Word64 Source #

Ring () Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: () -> () Source #

Ring CDev Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: CDev -> CDev Source #

Ring CIno Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: CIno -> CIno Source #

Ring CMode Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: CMode -> CMode Source #

Ring COff Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: COff -> COff Source #

Ring CPid Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: CPid -> CPid Source #

Ring CSsize Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: CSsize -> CSsize Source #

Ring CGid Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: CGid -> CGid Source #

Ring CNlink Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: CNlink -> CNlink Source #

Ring CUid Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: CUid -> CUid Source #

Ring CCc Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: CCc -> CCc Source #

Ring CSpeed Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: CSpeed -> CSpeed Source #

Ring CTcflag Source # 
Instance details

Defined in Data.Semiring

Ring CRLim Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: CRLim -> CRLim Source #

Ring Fd Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: Fd -> Fd Source #

Ring CChar Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: CChar -> CChar Source #

Ring CSChar Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: CSChar -> CSChar Source #

Ring CUChar Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: CUChar -> CUChar Source #

Ring CShort Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: CShort -> CShort Source #

Ring CUShort Source # 
Instance details

Defined in Data.Semiring

Ring CInt Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: CInt -> CInt Source #

Ring CUInt Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: CUInt -> CUInt Source #

Ring CLong Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: CLong -> CLong Source #

Ring CULong Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: CULong -> CULong Source #

Ring CLLong Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: CLLong -> CLLong Source #

Ring CULLong Source # 
Instance details

Defined in Data.Semiring

Ring CFloat Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: CFloat -> CFloat Source #

Ring CDouble Source # 
Instance details

Defined in Data.Semiring

Ring CPtrdiff Source # 
Instance details

Defined in Data.Semiring

Ring CSize Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: CSize -> CSize Source #

Ring CWchar Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: CWchar -> CWchar Source #

Ring CSigAtomic Source # 
Instance details

Defined in Data.Semiring

Ring CClock Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: CClock -> CClock Source #

Ring CTime Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: CTime -> CTime Source #

Ring CUSeconds Source # 
Instance details

Defined in Data.Semiring

Ring CSUSeconds Source # 
Instance details

Defined in Data.Semiring

Ring CIntPtr Source # 
Instance details

Defined in Data.Semiring

Ring CUIntPtr Source # 
Instance details

Defined in Data.Semiring

Ring CIntMax Source # 
Instance details

Defined in Data.Semiring

Ring CUIntMax Source # 
Instance details

Defined in Data.Semiring

Ring WordPtr Source # 
Instance details

Defined in Data.Semiring

Ring IntPtr Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: IntPtr -> IntPtr Source #

Ring a => Ring [a] Source # 
Instance details

Defined in Data.Semiring

Methods

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

Ring a => Ring (Maybe a) Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: Maybe a -> Maybe a Source #

Integral a => Ring (Ratio a) Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: Ratio a -> Ratio a Source #

Ring a => Ring (IO a) Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: IO a -> IO a Source #

Ring a => Ring (Complex a) Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: Complex a -> Complex a Source #

HasResolution a => Ring (Fixed a) Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: Fixed a -> Fixed a Source #

Ring (Predicate a) Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: Predicate a -> Predicate a Source #

Ring a => Ring (Equivalence a) Source # 
Instance details

Defined in Data.Semiring

Ring a => Ring (Identity a) Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: Identity a -> Identity a Source #

Ring a => Ring (Dual a) Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: Dual a -> Dual a Source #

Ring a => Ring (Down a) Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: Down a -> Down a Source #

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

Defined in Data.Semiring

Methods

negate :: Vector a -> Vector a Source #

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

Defined in Data.Semiring

Methods

negate :: Vector a -> Vector a Source #

Ring a => Ring (Vector a) Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: Vector a -> Vector a Source #

Num a => Ring (WrappedNum a) Source # 
Instance details

Defined in Data.Semiring

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

Defined in Data.Semiring

Methods

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

(Ring a, Ring b) => Ring (a, b) Source # 
Instance details

Defined in Data.Semiring.Generic

Methods

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

Ring a => Ring (Op a b) Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: Op a b -> Op a b Source #

(Ring a, Ring b, Ring c) => Ring (a, b, c) Source # 
Instance details

Defined in Data.Semiring.Generic

Methods

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

Ring a => Ring (Const a b) Source # 
Instance details

Defined in Data.Semiring

Methods

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

(Ring a, Applicative f) => Ring (Ap f a) Source # 
Instance details

Defined in Data.Semiring

Methods

negate :: Ap f a -> Ap f a Source #

(Ring a, Ring b, Ring c, Ring d) => Ring (a, b, c, d) Source # 
Instance details

Defined in Data.Semiring.Generic

Methods

negate :: (a, b, c, d) -> (a, b, c, d) Source #

(Ring a, Ring b, Ring c, Ring d, Ring e) => Ring (a, b, c, d, e) Source # 
Instance details

Defined in Data.Semiring.Generic

Methods

negate :: (a, b, c, d, e) -> (a, b, c, d, e) Source #

(Ring a, Ring b, Ring c, Ring d, Ring e, Ring f) => Ring (a, b, c, d, e, f) Source # 
Instance details

Defined in Data.Semiring.Generic

Methods

negate :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) Source #

(Ring a, Ring b, Ring c, Ring d, Ring e, Ring f, Ring g) => Ring (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Data.Semiring.Generic

Methods

negate :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) Source #

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

Infix shorthand for minus.

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

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

x minus y = x + negate y