Add a Functor instance to Kleisli

Carter Schonwald carter.schonwald at gmail.com
Thu Apr 18 15:33:17 UTC 2019


Lovely

On Thu, Apr 18, 2019 at 12:43 AM Tony Morris <tonymorris at gmail.com> wrote:

> +1
>
> Including others such as Applicative, Alternative, etc.
> On 15/4/19 4:34 pm, Fumiaki Kinoshita wrote:
>
> 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
>>
>
> _______________________________________________
> Libraries mailing listLibraries at haskell.orghttp://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
>
> _______________________________________________
> 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/20190418/00d24185/attachment.html>


More information about the Libraries mailing list