Alternative instance for Const

We already have instance Monoid m => Applicative (Const m) we could easily add instance Monoid m => Alternative (Const m) where empty = coerce mempty (<|>) = coerce (<>) which trivially satisfies left/right identity and associativity. I propose we add this instance to base.

No, the Alternative instance should be based on semirings instead. The one
you propose isn't distributive.
Lacking general semirings, the best we can do at the moment is newtypes for
each semiring we have. For instance:
newtype NumConst a b = NumConst { getNumConst :: a }
deriving (Functor)
instance Num a => Applicative (NumConst a) where
pure = const (NumConst 1)
(<*>) = (coerce :: (a -> a -> a) -> NumConst a (u -> v) -> NumConst a u
-> NumConst a v) (*)
instance Num a => Alternative (NumConst a) where
empty = NumConst 0
(<|>) = (coerce :: (a -> a -> a) -> NumConst a b -> NumConst a b ->
NumConst a b) (+)
On Sat, Mar 21, 2020, 13:44 chessai .
We already have
instance Monoid m => Applicative (Const m)
we could easily add
instance Monoid m => Alternative (Const m) where empty = coerce mempty (<|>) = coerce (<>)
which trivially satisfies left/right identity and associativity.
I propose we add this instance to base. _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Hi Zemyla,
Could you clarify where the requirement for distributivity comes from?
The haddocks for Alternative don't mention it:
http://downloads.haskell.org/~ghc/8.10.1-rc1/docs/html/libraries/base-4.14.0...
Thanks,
Simon
Am Sa., 21. März 2020 um 21:23 Uhr schrieb Zemyla
No, the Alternative instance should be based on semirings instead. The one you propose isn't distributive.
Lacking general semirings, the best we can do at the moment is newtypes for each semiring we have. For instance:
newtype NumConst a b = NumConst { getNumConst :: a } deriving (Functor)
instance Num a => Applicative (NumConst a) where pure = const (NumConst 1) (<*>) = (coerce :: (a -> a -> a) -> NumConst a (u -> v) -> NumConst a u -> NumConst a v) (*)
instance Num a => Alternative (NumConst a) where empty = NumConst 0 (<|>) = (coerce :: (a -> a -> a) -> NumConst a b -> NumConst a b -> NumConst a b) (+)
On Sat, Mar 21, 2020, 13:44 chessai .
wrote: We already have
instance Monoid m => Applicative (Const m)
we could easily add
instance Monoid m => Alternative (Const m) where empty = coerce mempty (<|>) = coerce (<>)
which trivially satisfies left/right identity and associativity.
I propose we add this instance to base. _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

https://wiki.haskell.org/Typeclassopedia#Laws_6 On 21.3.2020 23.46, Simon Jakobi via Libraries wrote:
Hi Zemyla,
Could you clarify where the requirement for distributivity comes from?
The haddocks for Alternative don't mention it: http://downloads.haskell.org/~ghc/8.10.1-rc1/docs/html/libraries/base-4.14.0...
Thanks, Simon
Am Sa., 21. März 2020 um 21:23 Uhr schrieb Zemyla
: No, the Alternative instance should be based on semirings instead. The one you propose isn't distributive.
Lacking general semirings, the best we can do at the moment is newtypes for each semiring we have. For instance:
newtype NumConst a b = NumConst { getNumConst :: a } deriving (Functor)
instance Num a => Applicative (NumConst a) where pure = const (NumConst 1) (<*>) = (coerce :: (a -> a -> a) -> NumConst a (u -> v) -> NumConst a u -> NumConst a v) (*)
instance Num a => Alternative (NumConst a) where empty = NumConst 0 (<|>) = (coerce :: (a -> a -> a) -> NumConst a b -> NumConst a b -> NumConst a b) (+)
On Sat, Mar 21, 2020, 13:44 chessai .
wrote: We already have
instance Monoid m => Applicative (Const m)
we could easily add
instance Monoid m => Alternative (Const m) where empty = coerce mempty (<|>) = coerce (<>)
which trivially satisfies left/right identity and associativity.
I propose we add this instance to base. _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

As far as I'm aware, distributivity is neither required nor adhered to by
many types in core libraries and beyond. Only left and right identity, and
associativity. This instance would also play well with the existing
Applicative instance.
On Sat, Mar 21, 2020, 3:54 PM Oleg Grenrus
https://wiki.haskell.org/Typeclassopedia#Laws_6
On 21.3.2020 23.46, Simon Jakobi via Libraries wrote:
Hi Zemyla,
Could you clarify where the requirement for distributivity comes from?
The haddocks for Alternative don't mention it:
http://downloads.haskell.org/~ghc/8.10.1-rc1/docs/html/libraries/base-4.14.0...
Thanks, Simon
Am Sa., 21. März 2020 um 21:23 Uhr schrieb Zemyla
: No, the Alternative instance should be based on semirings instead. The
one you propose isn't distributive.
Lacking general semirings, the best we can do at the moment is newtypes
for each semiring we have. For instance:
newtype NumConst a b = NumConst { getNumConst :: a } deriving (Functor)
instance Num a => Applicative (NumConst a) where pure = const (NumConst 1) (<*>) = (coerce :: (a -> a -> a) -> NumConst a (u -> v) -> NumConst
a u -> NumConst a v) (*)
instance Num a => Alternative (NumConst a) where empty = NumConst 0 (<|>) = (coerce :: (a -> a -> a) -> NumConst a b -> NumConst a b ->
NumConst a b) (+)
On Sat, Mar 21, 2020, 13:44 chessai .
wrote: We already have
instance Monoid m => Applicative (Const m)
we could easily add
instance Monoid m => Alternative (Const m) where empty = coerce mempty (<|>) = coerce (<>)
which trivially satisfies left/right identity and associativity.
I propose we add this instance to base. _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

No, the Alternative instance should be based on semirings instead. The one you propose isn't distributive.
+1. -1 on non-distributive default instances. On 2020-03-21 21:22, Zemyla wrote:
No, the Alternative instance should be based on semirings instead. The one you propose isn't distributive.
Lacking general semirings, the best we can do at the moment is newtypes for each semiring we have. For instance:
newtype NumConst a b = NumConst { getNumConst :: a } deriving (Functor)
instance Num a => Applicative (NumConst a) where pure = const (NumConst 1) (<*>) = (coerce :: (a -> a -> a) -> NumConst a (u -> v) -> NumConst a u -> NumConst a v) (*)
instance Num a => Alternative (NumConst a) where empty = NumConst 0 (<|>) = (coerce :: (a -> a -> a) -> NumConst a b -> NumConst a b -> NumConst a b) (+)
On Sat, Mar 21, 2020, 13:44 chessai .
mailto:chessai1996@gmail.com> wrote: We already have
instance Monoid m => Applicative (Const m)
we could easily add
instance Monoid m => Alternative (Const m) where empty = coerce mempty (<|>) = coerce (<>)
which trivially satisfies left/right identity and associativity.
I propose we add this instance to base. _______________________________________________ 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 http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
participants (5)
-
Andreas Abel
-
chessai .
-
Oleg Grenrus
-
Simon Jakobi
-
Zemyla