Giter Club home page Giter Club logo

semirings's Introduction

semirings

Hackage Build Status

Haskellers are usually familiar with monoids and semigroups. A monoid has an appending operation <> or mappend and an identity element mempty. A semigroup has an append <>, but does not require an mempty element.

A Semiring has two appending operations, 'plus' and 'times', and two respective identity elements, 'zero' and 'one'.

More formally, A semiring R is a set equipped with two binary relations + and *, such that:

  • (R, +) is a commutative monoid with identity element 0:
    • (a + b) + c = a + (b + c)
    • 0 + a = a + 0 = a
    • a + b = b + a
  • (R, *) is a monoid with identity element 1:
    • (a * b) * c = a * (b * c)
    • 1 * a = a * 1 = a
  • Multiplication left and right distributes over addition
    • a * (b + c) = (a * b) + (a * c)
    • (a + b) * c = (a * c) + (b * c)
  • Multiplication by '0' annihilates R:
    • 0 * a = a * 0 = 0

*-semirings

A *-semiring (pron. "star-semiring") is any semiring with an additional operation 'star' (read as "asteration"), such that:

  • star a = 1 + a * star a = 1 + star a * a

A derived operation called "aplus" can be defined in terms of star by:

  • star :: a -> a
  • star a = 1 + aplus a
  • aplus :: a -> a
  • aplus a = a * star a

As such, a minimal instance of the typeclass 'Star' requires only 'star' or 'aplus' to be defined.

use cases

semirings themselves are useful as a way to express that a type that supports a commutative and associative operation. Some examples:

  • Numbers {Int, Integer, Word, Double, etc.}:
    • 'plus' is 'Prelude.+'
    • 'times' is 'Prelude.*'
    • 'zero' is 0.
    • 'one' is 1.
  • Booleans:
    • 'plus' is '||'
    • 'times' is '&&'
    • 'zero' is 'False'
    • 'one' is 'True'
  • Set:
    • 'plus' is 'union'
    • 'times' is 'intersection'
    • 'zero' is the empty Set.
    • 'one' is the singleton Set containing the 'one' element of the underlying type.
  • NFA:
    • 'plus' unions two NFAs.
    • 'times' appends two NFAs.
    • 'zero' is the NFA that acceptings nothing.
    • 'one' is the empty NFA.
  • DFA:
    • 'plus' unions two DFAs.
    • 'times' intersects two DFAs.
    • 'zero' is the DFA that accepts nothing.
    • 'one' is the DFA that accepts everything.

*-semirings are useful in a number of applications; such as matrix algebra, regular expressions, kleene algebras, graph theory, tropical algebra, dataflow analysis, power series, and linear recurrence relations.

Some relevant (informal) reading material:

http://stedolan.net/research/semirings.pdf

http://r6.ca/blog/20110808T035622Z.html

https://byorgey.wordpress.com/2016/04/05/the-network-reliability-problem-and-star-semirings/

additional credit

Some of the code in this library was lifted directly from the Haskell library 'semiring-num'.

semirings's People

Contributors

amesgen avatar andreasabel avatar andrewthad avatar bodigrim avatar chessai avatar danielsmw avatar erikd avatar konsumlamm avatar kozross avatar

Stargazers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

Watchers

 avatar  avatar  avatar  avatar  avatar

semirings's Issues

Does not build with GHC 7.4

Error message:

Resolving dependencies...
Build profile: -w ghc-7.4.2 -O1
In order, the following will be built (use -v for more details):
 - semirings-0.2.0.1 (lib) (first run)
Configuring library for semirings-0.2.0.1..
Preprocessing library for semirings-0.2.0.1..
Building library for semirings-0.2.0.1..
[1 of 2] Compiling Data.Semiring    ( Data/Semiring.hs, /home/amartin/Development/semirings/dist-7.4.2/build/x86_64-linux/ghc-7.4.2/semirings-
0.2.0.1/build/Data/Semiring.o )

Data/Semiring.hs:52:30:
    Module `Data.Fixed' does not export `Fixed(MkFixed)'

semiring newtype over Bool

@nprindle brought up that the following semiring might be useful:

newtype Z = Z { getZ :: Bool }
  deriving stock (Show)
  deriving newtype (Eq, Arbitrary)

instance Semiring Z where
  plus (Z x) (Z y) = Z (x `xor` y)
  times (Z x) (Z y) = Z (x && y)
  zero = Z False
  one = Z True

instance Ring Z where
  negate (Z x) = Z (not x)

instance Star Z where
  star = const 1

it is used in computing Zhegalkin Polynomials.

Support window?

Based on our Github Actions, we don't seem to support GHCs as far back as the Cabal file claims. We also have CPP for very old versions of GHC (base-4.6, which is GHC 7.6 if I remember right).

Is there an official window of support for versions of base?

Implementation of (^) does not match documentation

-- | Raise a number to a non-negative integral power.
-- If the power is negative, this will return 'zero'.
(^) :: (Semiring a, Integral b) => a -> b -> a
x ^ y = getMul (stimes y (Mul x))

In fact it throws an error for negative powers (which is IMO better then returning zero - so we need to correct the haddock), but also throws an error for zero power (which is unexpected, should be one).

I am on vacation, will prepare a PR next week, if no one picks it up earlier.

Mention RebindableSyntax in haddocks

I recently discovered that it is very convenient to enable {-# LANGUAGE RebindableSyntax #-} with semirings, because it overloads fromInteger and fromRational, used for desugaring of integer and rational literals, from

fromInteger :: Num a => Integer -> a 
fromRational :: Fractional a => Rational -> a 

to

fromInteger :: Ring a => Integer -> a 
fromRational :: Field a => Rational -> a 

It means that users do not need to replace 0 and 1 by zero and one anymore.

I think it would be nice to reflect this in the documentation.

Instances for Sum and Product

It is kinda confusing that semirings Sum a and Product a operate similar (matching a itself), but Set (Sum a) and Set (Product a) are different. IMHO it may be beneficial to remove Semiring instances for Sum a and Product a: anyway it is weird to write something like Sum x * Sum y or Product x + Product y.

Same applies to Min / Max and Add / Mul.

Add some useful predicates

I think the following are useful. I have had uses for them in the past:

isZero :: Semiring a => a -> Bool
isZero x = x == zero
isOne :: Semiring a => a -> Bool
isOne x = x == one
isUnit :: Semiring a => a -> Bool
isUnit x = isZero x || isOne x

Tropical semirings

There is a third tropical semiring that extends its set with both positive and negative infinity (typically treated as the extended real number line).

implement Monad instance for Poly

this can be useful for flattening, because Poly (Poly a) is isomorphic to Poly a.
The notion of collapsing arbitrary polynomials can be implemented via the 'free' package (retract)

Euclidean: Minimal-magnitude quotients break modular arithmetic

In Prelude, the difference between quot and div is in their choice of rounding behaviour -- quot rounds towards 0, whereas div rounds to -minBound.
This has the effect of making the output of rem dependent on the sign of its first input, unlike mod. In particular, (`rem` n) takes on more than n values.
Worse, this breaks modular arithmetic: (x+y) `rem` n /= ((x `rem` n) + (y `rem` n)) `rem` n!

But that's Prelude's problem, and the committee's fault for standardizing on a poor default. We can and should do better.

The quick and dirty solution would be to just replace quotRem by divMod. Better would be to require that isJust ((x-y) `divide` m) iff x `mod` m == y `mod` m. I don't know if there's an even better solution, but this would at least be a start.

Instance for []

I tried to use semirings in one of my projects, but stumbled over Semiring instance for []. My initial expectation was that plus = (++), but then I realised that such definition would violate the commutativity law. Nevertheless, the existing instance looks quite artificial to me. Does it have any nice applications?

The thing is that AFAIU there are many possible definitions of Semiring over []. Basically, we can apply any fixed permutation to both input lists, pass results through existing plus or times and apply an inversed permutation. E. g.,

instance Semiring a => Semiring [a] where
  zero = []
  one  = [one]
  plus xs ys = reverse (listAdd (reverse xs) (reverse ys))
  times xs ys = reverse (listTimes (reverse xs) (reverse ys))

Is any of these instances more canonical (or more useful) than another?

I wonder whether it is reasonable to sacrifice an additive commutativity for lists and vectors for the sake of practical applications.

WrappedNum

Suppose there is a library foo which exports a type Int42 with Num instance. And there is a library bar, implementing a function baz :: Semiring a => a -> a. The issue is that I cannot feed Int42 to baz, unless I write an orphan instance Semigroup Int42 (and orphan instances are a pain in maintenance) and repeat all boilerplate definitions.

Can we have a WrappedNum newtype? Similar to WrappedMonad, WrappedArrow and WrappedMonoid.

{-# LANGUAGE GeneralizedNewtypeDeriving #-}

import Data.Semiring (Semiring(..))

newtype WrappedNum a = WrappedNum { unWrappedNum :: a }
  deriving (Num)

instance Num a => Semiring (WrappedNum a) where
  zero  = 0
  one   = 1
  plus  = (+)
  times = (*)

Returning to my example, such newtype will allow us to apply baz to Int42 without much fuss: baz (WrappedNum (smth :: Int42)).

I'll be glad to prepare a PR.

Remove Ring instance for Natural

It is impossible for Natural to have a Ring instance: negating anything but zero results in arithmetic underflow.

I am on vacation, will prepare a PR next week, if no one picks it up earlier.

Stackage

I am gonna use semirings in arithmoi (Bodigrim/arithmoi#142), but noticed that semirings-0.2 is no longer available from Stackage. @chessai do you have any plans to upload it back soon?

Does not build on Windows

As reported by @CarlEdman, semirings-0.3.1.1 fails to build on Windows:

Data\Semiring.hs:144:4: error:
    Module `System.Posix.Types' does not export `CCc'
    |
144 |   (CCc, CDev, CGid, CIno, CMode, CNlink,
    |    ^^^

Data\Semiring.hs:144:15: error:
    Module `System.Posix.Types' does not export `CGid'
    |
144 |   (CCc, CDev, CGid, CIno, CMode, CNlink,
    |               ^^^^

Data\Semiring.hs:144:34: error:
    Module `System.Posix.Types' does not export `CNlink'
    |
144 |   (CCc, CDev, CGid, CIno, CMode, CNlink,
    |                                  ^^^^^^

Data\Semiring.hs:145:16: error:
    Module `System.Posix.Types' does not export `CRLim'
    |
145 |    COff, CPid, CRLim, CSpeed, CSsize,
    |                ^^^^^

Data\Semiring.hs:145:23: error:
    Module `System.Posix.Types' does not export `CSpeed'
    |
145 |    COff, CPid, CRLim, CSpeed, CSsize,
    |                       ^^^^^^

Data\Semiring.hs:146:4: error:
    Module `System.Posix.Types' does not export `CTcflag'
    |
146 |    CTcflag, CUid, Fd)
    |    ^^^^^^^

Data\Semiring.hs:146:13: error:
    Module `System.Posix.Types' does not export `CUid'
    |
146 |    CTcflag, CUid, Fd)
    |             ^^^^

I believe I can fix this with CPP, reflecting #if defined(...) from System.Posix.Types. But do we actually need these instances at all? I doubt that people frequently add UserIDs or multiply GroupIDs. Someone particularly inclined to do so can use WrappedNum.

This is reasonably urgent, because it blocks the upcoming arithmoi release.

Document list instance

It is not apparent what the Semiring instance for lists is modelling and a comment in the docs would help.
Seems like it considers repeat zero equal to [], but this would deserve some explicit comment.

Multiplication of polynomials is terrible

Specifically the instance for vectors is awful

polyTimes :: Semiring a => Vector a -> Vector a -> Vector a
polyTimes x y
  = if Vector.null x then x else if Vector.null y then y else
      Vector.cons (times a b) (Vector.map (a *) q + Vector.map (* b) p + (Vector.cons zero (polyTimes p q)))
  where
    a = Vector.unsafeHead x
    b = Vector.unsafeHead y
    p = (\t d -> if Vector.null t then d else t) (Vector.tail x) (Vector.empty)
    q = (\t d -> if Vector.null t then d else t) (Vector.tail y) (Vector.empty)

Technically this is the optimum in terms of asymptotic analysis.
Proof:

C(0) = 0
C(n) = n (Vector.cons) + n (Vector.map) + n (Vector.map) + n (Vector.cons) + C(n - 1) (recursive call)

That recurrence represent the worst case running time of polyTimes. Solving this with the master method C(n) = ฮ˜(n^2). This being said the asymptotics hide some serious constants. You copy the vector into a new vector two times each recursive call because of Vector.cons. Never use Vector.cons it has to copy the entire vector into a new one that is just one element bigger. Instead rethink the algorithm to not use Vector.cons. You could completely redesign the alg or use ST and mutable vectors.

Ord instance is backward?

I was trying to debug a program and came across the bizarre fact that

Tropical 3 > (Infinity :: Tropical Minima Double)

evaluates to True. Switching Minima <--> Maxima gives False.

However, in the min-plus semiring, Infinity must be greater than the finite elements so that it can serve as the additive identity. So it seems that the definition has been reversed, unless I'm missing something stupid.

Add fields

We can add another operation here:

-- | The class of rings with a multiplicative inverse
--
--     @a '*' 'invert' a = 'one'@
class Ring a => Field a where
  invert :: a -> a

This corresponds to division/reciprocal numbers, and can be implemented for e.g. rational numbers and reals.

The overall intuition is that all these structures consist of lawfully interacting pairs of group-like structures. For semirings this is a pair of monoids (one of which is commutative), for rings a commutative group and a monoid, and for fields two commutative groups.

Commutative vs. associative

On several occasions documentation mentions that a semiring comprises of "a commutative monoid and an associative monoid". I believe this statement is worth to be reworded, because it makes a wrong impression that the first monoid is not neccessarily associative. Actually, any monoid is, so "associative monoid" is a tautologism.

GHC 9.10 support - please bump containers dep to "< 0.8"

Trying to build semirings:+containers with GHC 9.10 results in:

Resolving dependencies...
Error: cabal-3.10.2.0: Could not resolve dependencies:
[__0] trying: xmonad-0.18.0.9 (user goal)
[__1] trying: xmonad:*test
[__2] trying: quickcheck-classes-0.6.5.0 (dependency of xmonad *test)
[__3] trying: quickcheck-classes:+semirings
[__4] trying: semirings-0.6 (dependency of quickcheck-classes +semirings)
[__5] trying: semirings:+containers
[__6] trying: unix-2.8.5.1/installed-e9c3 (dependency of xmonad)
[__7] trying: os-string-2.0.2/installed-6136 (dependency of unix)
[__8] trying: exceptions-0.10.7/installed-3f06 (dependency of os-string)
[__9] next goal: containers (dependency of xmonad)
[__9] rejecting: containers-0.7/installed-76[28](https://github.com/xmonad/xmonad/actions/runs/9120841209/job/25078972815?pr=505#step:15:29) (conflict: semirings +containers => containers>=0.5.4 && <0.7)
[__9] rejecting: containers-0.7, containers-0.6.8, containers-0.6.7, containers-0.6.6, containers-0.6.5.1, containers-0.6.4.1, containers-0.6.3.1, containers-0.6.2.1, containers-0.6.1.1, containers-0.6.0.1, containers-0.5.11.0, containers-0.5.10.2, containers-0.5.10.1, containers-0.5.9.2, containers-0.5.8.2, containers-0.5.7.1, containers-0.5.7.0, containers-0.5.6.3, containers-0.5.6.2, containers-0.5.6.1, containers-0.5.6.0, containers-0.5.5.1, containers-0.5.5.0, containers-0.5.4.0, containers-0.5.3.1, containers-0.5.3.0, containers-0.5.2.1, containers-0.5.2.0, containers-0.5.1.0, containers-0.5.0.0, containers-0.4.2.1, containers-0.4.2.0, containers-0.4.1.0, containers-0.4.0.0, containers-0.3.0.0, containers-0.2.0.1, containers-0.2.0.0, containers-0.1.0.1, containers-0.1.0.0, containers-0.5.9.1, containers-0.5.8.1 (constraint from project config /__w/xmonad/xmonad/cabal.project.local requires installed instance)
[__9] fail (backjumping, conflict set: containers, semirings, xmonad, semirings:containers)
After searching the rest of the dependency tree exhaustively, these were the goals I've had most trouble fulfilling: exceptions, quickcheck-classes, containers, xmonad, semirings, unix, semirings:containers, quickcheck-classes:semirings, xmonad:test, os-string

After adding allow-newer: semirings:containers to cabal.project, everything builds just fine, so I guess just bumping the dep might be enough.
(If that's indeed the case, you could just make a Hackage revision instead of releasing a new version with updated deps.)

Replace CPP instance derivation code with TH/DerivingVia

CPP instances as written are less flexible (eg to implement #62 we'd need differing derived instances for the types that are morally integers and those that are morally fields).

Besides, it's ugly, and we have principled alternatives in terms of TH (if we want backwards compatibility) or DerivingVia (supports ghc >=8.6 only, which is two years old).

Am willing to implement this if agreeable.

Ring vs. Num

I do not have a strong opinion on the matter, just speculations.

It occurred to me that whenever one can define Ring instance, he can define Num instance as well. Namely, even if there is no sensible definition for abs, just make it trivial: abs = id, signum = const one, so that abs n * signum n == n. And fromInteger can be expressed in terms of fromNatural and negate.

It is true that Ring is better grounded in theory, but practically it is a burden in comparison to Num. And I am inclined to say that Ring does not have enough advantages to overweight this mental overhead.

@chessai @andrewthad what is your opinion?

some instances are unlawful!

Data.Monoid.Alt : Does not satisfy additive commutativity

Data.Sequence.Seq : many problems
Data.Set.Set : many problems
Data.HashSet : did not terminate in test suite
Data.Vector : many problems
Data.Vector.Storable : many problems
Data.Vector.Unboxed : many problems

Division is definable and useful already in Semirings

divide should be a method of Semiring, as it makes sense from the moment multiplication forms a monoid.
In particular, am currently working on the localization of an integral domain away from a prime. To normalize fractions, I need to be able to compute decompositions x=p^k*m. This doesn't need gcds to be uniquely definable in general, just at powers of a fixed prime, which they always are.
Incidentally, this decomposition is frequently useful, and can probably be given instance-specific speedups, so I recommend it also be added to the class, with default definition

decomp :: Semiring a => a -> a -> (Natural,a)
decomp p x = iterateM step (0, x)
 where
  step (k, m) = (k+1 ,) `fmap` (m `divide` p)
  iterateM f !acc = maybe !acc (iterateM f) (f acc)

(^) is stimes

It seems that the definition of (^) in Data.Semiring matches stimes:

(^) :: (Semiring a, Integral b) => a -> b -> a
x ^ y = getMul (stimes y (Mul x))

As one who has a hand in definitions of (^) and stimes in base, I believe it is worth to consider this implementation to avoid code duplication. This way it will automatically benefit from possible further improvements, new rules and specialisations, defined in base.

0.4 release

@Bodigrim @andrewthad any feature requests for the 0.4 release? the changelog entry shows what will be included thus far. I don't want Ring to go away/Fields to come in, in this release, if that helps whittle things down.

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    ๐Ÿ–– Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. ๐Ÿ“Š๐Ÿ“ˆ๐ŸŽ‰

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google โค๏ธ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.