Alternative instance for Const
Andreas Abel
andreas.abel at ifi.lmu.de
Sun Mar 22 09:27:07 UTC 2020
> 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 . <chessai1996 at gmail.com
> <mailto:chessai1996 at 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 at haskell.org <mailto:Libraries at haskell.org>
> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
>
>
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
>
More information about the Libraries
mailing list