rings-0.0.1: basic algebra

Safe HaskellSafe
LanguageHaskell2010

Data.Semiring

Synopsis

Documentation

class Semigroup r => Semiring r where Source #

Right pre-semirings and (non-unital and unital) right semirings.

A right pre-semiring (sometimes referred to as a bisemigroup) is a type R endowed with two associative binary (i.e. semigroup) operations: (<>) and (><), along with a right-distributivity property connecting them:

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

A non-unital right semiring (sometimes referred to as a bimonoid) is a pre-semiring with a mempty element that is neutral with respect to both addition and multiplication.

A unital right semiring is a pre-semiring with two distinct neutral elements, mempty and unit, such that mempty is right-neutral wrt addition, unit is right-neutral wrt multiplication, and mempty is right-annihilative wrt multiplication.

Note that unit needn't be distinct from mempty.

Instances also need not be commutative nor left-distributive.

See the properties module for a detailed specification of the laws.

Minimal complete definition

(><)

Methods

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

fromBoolean :: Monoid r => Bool -> r Source #

Instances
Semiring Bool Source # 
Instance details

Defined in Data.Semiring

Semiring Int Source # 
Instance details

Defined in Data.Semiring

Methods

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

fromBoolean :: Bool -> Int Source #

Semiring Natural Source # 
Instance details

Defined in Data.Semiring

Semiring Ordering Source # 
Instance details

Defined in Data.Semiring

Semiring Word Source # 
Instance details

Defined in Data.Semiring

Semiring () Source # 
Instance details

Defined in Data.Semiring

Methods

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

fromBoolean :: Bool -> () Source #

Semiring All Source # 
Instance details

Defined in Data.Semiring

Methods

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

fromBoolean :: Bool -> All Source #

Semiring Any Source # 
Instance details

Defined in Data.Semiring

Methods

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

fromBoolean :: Bool -> Any Source #

Monoid a => Semiring [a] Source # 
Instance details

Defined in Data.Semiring

Methods

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

fromBoolean :: Bool -> [a] Source #

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

Defined in Data.Semiring

Methods

(><) :: Maybe a -> Maybe a -> Maybe a Source #

fromBoolean :: Bool -> Maybe a Source #

(Monoid a, Semiring a) => Semiring (IO a) Source # 
Instance details

Defined in Data.Semiring

Methods

(><) :: IO a -> IO a -> IO a Source #

fromBoolean :: Bool -> IO a Source #

Semiring (Predicate a) Source # 
Instance details

Defined in Data.Semiring

Semiring (Comparison a) Source # 
Instance details

Defined in Data.Semiring

Semiring (Equivalence a) Source # 
Instance details

Defined in Data.Semiring

Ord a => Semiring (Min a) Source # 
Instance details

Defined in Data.Semiring

Methods

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

fromBoolean :: Bool -> Min a Source #

Ord a => Semiring (Max a) Source # 
Instance details

Defined in Data.Semiring

Methods

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

fromBoolean :: Bool -> Max a Source #

Semigroup a => Semiring (First a) Source #

'First a' forms a pre-semiring for any semigroup a.

>>> foldMap1 First $ 1 :| [2..(5 :: Int)] >< 1 :| [2..(5 :: Int)]
First {getFirst = 1}
>>> product1 First $ 1 :| [2..(5 :: Int)]
First {getFirst = 15}
>>> foldMap1 First $ Nothing :| [Just (5 :: Int), Just 6,  Nothing]
First {getFirst = Nothing}
>>> product1 First $ Nothing :| [Just (5 :: Int), Just 6,  Nothing]
First {getFirst = Just 11}
Instance details

Defined in Data.Semiring

Methods

(><) :: First a -> First a -> First a Source #

fromBoolean :: Bool -> First a Source #

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

Defined in Data.Semiring

Methods

(><) :: Last a -> Last a -> Last a Source #

fromBoolean :: Bool -> Last a Source #

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

Defined in Data.Semiring

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

Defined in Data.Semiring

Methods

(><) :: Dual a -> Dual a -> Dual a Source #

fromBoolean :: Bool -> Dual a Source #

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

Defined in Data.Semiring

Monoid a => Semiring (IntMap a) Source # 
Instance details

Defined in Data.Semiring

Methods

(><) :: IntMap a -> IntMap a -> IntMap a Source #

fromBoolean :: Bool -> IntMap a Source #

Monoid a => Semiring (Seq a) Source # 
Instance details

Defined in Data.Semiring

Methods

(><) :: Seq a -> Seq a -> Seq a Source #

fromBoolean :: Bool -> Seq a Source #

Ord a => Semiring (Set a) Source # 
Instance details

Defined in Data.Semiring

Methods

(><) :: Set a -> Set a -> Set a Source #

fromBoolean :: Bool -> Set a Source #

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

Defined in Data.Semiring

Methods

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

fromBoolean :: Bool -> a -> b Source #

Semigroup a => Semiring (Either e a) Source # 
Instance details

Defined in Data.Semiring

Methods

(><) :: Either e a -> Either e a -> Either e a Source #

fromBoolean :: Bool -> Either e a Source #

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

Defined in Data.Semiring

Methods

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

fromBoolean :: Bool -> (a, b) Source #

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

Defined in Data.Semiring

Methods

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

fromBoolean :: Bool -> Op a b Source #

(Ord k, Monoid k, Monoid a) => Semiring (Map k a) Source # 
Instance details

Defined in Data.Semiring

Methods

(><) :: Map k a -> Map k a -> Map k a Source #

fromBoolean :: Bool -> Map k a Source #

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

Defined in Data.Semiring

Methods

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

fromBoolean :: Bool -> Const a b Source #

unit :: (Monoid r, Semiring r) => r Source #

fromBooleanDef :: (Monoid r, Semiring r) => r -> Bool -> r Source #

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

Fold over a collection using the multiplicative operation of a semiring.

product f ≡ foldr' ((><) . f) unit
>>> (foldMap . product) id [[1, 2], [3, (4 :: Int)]] -- 1 >< 2 <> 3 >< 4
14
>>> (product . foldMap) id [[1, 2], [3, (4 :: Int)]] -- 1 <> 2 >< 3 <> 4
21

For semirings without a distinct multiplicative unit this is equivalent to const mempty:

>>> product Just [1..(5 :: Int)]
Just 0

In this situation you most likely want to use product1.

product1 :: (Foldable1 t, Semiring r) => (a -> r) -> t a -> r Source #

Fold over a non-empty collection using the multiplicative operation of a semiring.

As the collection is non-empty this does not require a distinct multiplicative unit:

>>> product1 Just $ 1 :| [2..(5 :: Int)]
Just 120

cross :: (Foldable t, Applicative t, Monoid r, Semiring r) => t r -> t r -> r Source #

Cross-multiply two collections.

>>> cross [1,2,3 ::Int] [1,2,3]
36
>>> cross [1,2,3 ::Int] []
0

cross1 :: (Foldable1 t, Apply t, Semiring r) => t r -> t r -> r Source #

foldPresemiring :: Semiring r => (a -> r) -> NonEmpty (NonEmpty a) -> r Source #

Fold with no additive or multiplicative unit.

foldNonunital :: (Monoid r, Semiring r) => (a -> r) -> [NonEmpty a] -> r Source #

Fold with no multiplicative unit.

foldUnital :: (Monoid r, Semiring r) => (a -> r) -> [[a]] -> r Source #

Fold with additive & multiplicative units.

This function will zero out if there is no multiplicative unit.

replicate' :: (Monoid r, Semiring r) => Natural -> r -> r Source #

(^) :: (Monoid r, Semiring r) => r -> Natural -> r infixr 8 Source #

powers :: (Monoid r, Semiring r) => Natural -> r -> r Source #

newtype Prod a Source #

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

Constructors

Prod 

Fields

Instances
Functor Prod Source # 
Instance details

Defined in Data.Semiring

Methods

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

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

Applicative Prod Source # 
Instance details

Defined in Data.Semiring

Methods

pure :: a -> Prod a #

(<*>) :: Prod (a -> b) -> Prod a -> Prod b #

liftA2 :: (a -> b -> c) -> Prod a -> Prod b -> Prod c #

(*>) :: Prod a -> Prod b -> Prod b #

(<*) :: Prod a -> Prod b -> Prod a #

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

Defined in Data.Semiring

Methods

minBound :: Prod a #

maxBound :: Prod a #

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

Defined in Data.Semiring

Methods

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

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

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

Defined in Data.Semiring

Methods

compare :: Prod a -> Prod a -> Ordering #

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

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

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

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

max :: Prod a -> Prod a -> Prod a #

min :: Prod a -> Prod a -> Prod a #

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

Defined in Data.Semiring

Methods

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

show :: Prod a -> String #

showList :: [Prod a] -> ShowS #

Generic (Prod a) Source # 
Instance details

Defined in Data.Semiring

Associated Types

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

Methods

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

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

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

Defined in Data.Semiring

Methods

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

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

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

(Monoid a, Semiring a) => Monoid (Prod a) Source # 
Instance details

Defined in Data.Semiring

Methods

mempty :: Prod a #

mappend :: Prod a -> Prod a -> Prod a #

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

Generic1 Prod Source # 
Instance details

Defined in Data.Semiring

Associated Types

type Rep1 Prod :: k -> Type #

Methods

from1 :: Prod a -> Rep1 Prod a #

to1 :: Rep1 Prod a -> Prod a #

type Rep (Prod a) Source # 
Instance details

Defined in Data.Semiring

type Rep (Prod a) = D1 (MetaData "Prod" "Data.Semiring" "rings-0.0.1-ENwDaj1sjwXLe2A9n0ZKRO" True) (C1 (MetaCons "Prod" PrefixI True) (S1 (MetaSel (Just "getProd") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 Prod Source # 
Instance details

Defined in Data.Semiring

type Rep1 Prod = D1 (MetaData "Prod" "Data.Semiring" "rings-0.0.1-ENwDaj1sjwXLe2A9n0ZKRO" True) (C1 (MetaCons "Prod" PrefixI True) (S1 (MetaSel (Just "getProd") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))