Add a Functor instance to Kleisli

Fumiaki Kinoshita fumiexcel at gmail.com
Mon Apr 15 06:34:29 UTC 2019


Hello,

This has been proposed as a part of my proposal:
https://mail.haskell.org/pipermail/libraries/2019-April/029478.html

2019年4月15日(月) 15:30 Dmitriy Kovanikov <kovanikov at gmail.com>:

> Hello everyone!
>
> I would like to propose to add a `Functor` instance to the `Kleisli` data
> type from the `Control.Arrow` module. The instance can look like this:
>
>     instance Functor m => Functor (Kleisli m a) where
>         fmap :: (b -> c) -> Kleisli m a b -> Kleisli m a c
>         fmap f (Kleisli h) = Kleisli (fmap f . h)
>         {-# INLINE fmap #-}
>
>         (<$) :: c -> Kleisli m a b -> Kleisli m a c
>         c <$ Kleisli h = Kleisli (\a -> c <$ h a)
>         {-# INLINE (<$) #-}
>
> Having this instance would be really helpful in improving the
> `profunctors` package by adding QuantifiedConstraints to it. See more
> details in the discussion below:
>
>     https://github.com/ekmett/profunctors/pull/70#discussion_r267648958
>
> Thanks,
> Dmitrii Kovanikov
>
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/libraries/attachments/20190415/1c68f8e8/attachment.html>


More information about the Libraries mailing list