Add a Functor instance to Kleisli

Dmitriy Kovanikov kovanikov at gmail.com
Mon Apr 15 06:30:22 UTC 2019


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
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/libraries/attachments/20190415/990a1ba2/attachment.html>


More information about the Libraries mailing list