It really doesn't matter if it's not "interesting" or not surjective for some Semirings. It should be included, because:(a) Even for semirings where it is "interesting", it's not surjective (for instance, Rational or Double)(b) It's a method with a default definition, so you don't have to expend any mental effort on it(c) A lot of instances have uninteresting methods: for instance, (*>) and (<*) for Applicative ((->) e) are const id and const respectively. Haskell adds methods to classes when they're always possible and sometimes useful/interesting/faster, rather than when they're always interesting.(d) It's useful for Semiring-generic methods and instances.(e) It can achieve an asymptotic speedup on some instances. Like, if you have Semiring a => Semiring (f a) for some type f, then you can have fromNatural n = pure (fromNatural n) instead of doing the whole O(log n) song and dance with the default definition. Also, your example admits a simple definition:fromNatural n = if n == 0 then S.empty else S.singleton True(f) "zero" and "one" can be defined in terms of fromNatural, for programmers who only need to define that:zero = fromNatural 0one = fromNatural 1This leads to the MINIMAL pragma on Semiring being {-# MINIMAL plus, times, (zero, one | fromNatural) #-}(g) If it's not included in the class, but in some subclass (NaturalSemiring, you proposed), but it's possible from the class, then people will just define and use the O(log n) version instead of requiring the subclass, leading to wasted effort and duplicated code.On Tue, Feb 4, 2020, 09:20 Andreas Abel <andreas.abel@ifi.lmu.de> wrote:> There is a homomorphism from the Naturals to any Semiring
Sure, but there are many finite semirings where I would not care about
such a homomorphism, thus, why force me to define it?
> fromNatural 0 = zero
> fromNatural 1 = one
> fromNatural (m + n) = fromNatural m `plus` fromNatural n
> fromNatural (m * n) = fromNatural m `times` fromNatural n
This might not be surjective, and also not very interesting. For
instance consider the semiring
Set Bool
zero = Set.empty
one = Set.singleton True
plus = Set.union
times s t = { x == y | x <- s, y <- t }
This semiring models variances (covariant = {True}, contravariant =
{False}, constant = {}, dontknow = {True,False}). times is for function
composition and plus combination of information.
The fromNatural targets only the zero/one-fragment since plus is
idempotent. I conjecture there is not a single surjective semiring-hom
from Nat to Set Bool. Thus, a function fromNatural is totally
uninteresting for the general case of semirings.
On 2020-02-04 13:42, Zemyla wrote:
> There is a homomorphism from the Naturals to any Semiring, which obeys:
>
> fromNatural 0 = zero
> fromNatural 1 = one
> fromNatural (m + n) = fromNatural m `plus` fromNatural n
> fromNatural (m * n) = fromNatural m `times` fromNatural n
>
> The simplest implementation is this, but it's nowhere near the most
> efficient:
>
> fromNatural :: Semiring a => Natural -> a
> fromNatural 0 = zero
> fromNatural n = one `plus` fromNatural (n - 1)
>
> One which takes O(log n) time instead of O(n) would go like this:
>
> fromNatural :: Semiring a => Natural -> a
> fromNatural = go 0 zero one
> go i s m n | i `seq` s `seq` m `seq` n `seq` False = undefined
> go _ s _ 0 = s
> go i s m n
> | testBit n i = go (i + 1) (plus s m) (plus m m) (clearBit n i)
> | otherwise = go (i + 1) s (plus m m) n
>
> On Tue, Feb 4, 2020, 02:21 Andreas Abel <andreas.abel@ifi.lmu.de
> <mailto:andreas.abel@ifi.lmu.de>> wrote:
>
> > class Semiring a where
> > zero :: a
> > plus :: a -> a -> a
> > one :: a
> > times :: a -> a -> a
> > fromNatural :: Natural -> a
>
> I think `fromNatural` should not be part of the `Semiring` class,
> but we
> could have an extension (NaturalSemiring) that adds this method.
>
> In the Agda code base, we have, for lack of a standard, rolled our own
> semiring class,
>
> https://github.com/agda/agda/blob/master/src/full/Agda/Utils/SemiRing.hs
>
> and we use it for several finite semirings, e.g.,
>
>
> https://github.com/agda/agda/blob/64c0c2e813a84f91b3accd7c56efaa53712bc3f5/src/full/Agda/TypeChecking/Positivity/Occurrence.hs#L127-L155
>
> Cheers,
> Andreas
>
> On 2020-02-03 22:34, Carter Schonwald wrote:
> > Andrew: could you explain the algebra notation you were using for
> short
> > hand? I think I followed, but for people the libraries list
> might be
> > their first exposure to advanced / graduate abstract algebra (which
> > winds up being simpler than most folks expect ;) )
> >
> > On Fri, Jan 31, 2020 at 4:36 PM Carter Schonwald
> > <carter.schonwald@gmail.com <mailto:carter.schonwald@gmail.com>
> <mailto:carter.schonwald@gmail.com
> <mailto:carter.schonwald@gmail.com>>> wrote:
> >
> > that actually sounds pretty sane. I think!
> >
> > On Fri, Jan 31, 2020 at 3:38 PM Andrew Lelechenko
> > <andrew.lelechenko@gmail.com
> <mailto:andrew.lelechenko@gmail.com>
> <mailto:andrew.lelechenko@gmail.com
> <mailto:andrew.lelechenko@gmail.com>>>
> > wrote:
> >
> > On Tue, 28 Jan 2020, Dannyu NDos wrote:
> >
> > > Second, I suggest to move `abs` and `signum` from `Num` to
> > `Floating`
> >
> > I can fully relate your frustration with `abs` and
> `signum` (and
> > numeric type classes in Haskell altogether). But IMO breaking
> > both in `Num` and in `Floating` at once is not a
> promising way
> > to make things proper.
> >
> > I would rather follow the beaten track of Applicative
> Monad and
> > Semigroup Monoid proposals and - as a first step -
> introduce a
> > superclass (probably, borrowing the design from `semirings`
> > package):
> >
> > class Semiring a where
> > zero :: a
> > plus :: a -> a -> a
> > one :: a
> > times :: a -> a -> a
> > fromNatural :: Natural -> a
> > class Semiring a => Num a where ...
> >
> > Tangible benefits in `base` include:
> > a) instance Semiring Bool,
> > b) a total instance Semiring Natural (in contrast to a
> partial
> > instance Num Natural),
> > c) instance Num a => Semiring (Complex a) (in contrast to
> > instance RealFloat a => Num (Complex a)),
> > d) newtypes Sum and Product would require only Semiring
> > constraint instead of Num.
> >
> > Best regards,
> > Andrew
> >
> >
> > _______________________________________________
> > Libraries mailing list
> > Libraries@haskell.org <mailto:Libraries@haskell.org>
> <mailto:Libraries@haskell.org <mailto:Libraries@haskell.org>>
> > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
> >
> >
> > _______________________________________________
> > Libraries mailing list
> > Libraries@haskell.org <mailto:Libraries@haskell.org>
> > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
> >
> _______________________________________________
> Libraries mailing list
> Libraries@haskell.org <mailto:Libraries@haskell.org>
> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
>