Add a Functor instance to Kleisli

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

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
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@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

+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
mailto:kovanikov@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@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

Lovely
On Thu, Apr 18, 2019 at 12:43 AM Tony Morris
+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
: 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@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing listLibraries@haskell.orghttp://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
participants (4)
-
Carter Schonwald
-
Dmitriy Kovanikov
-
Fumiaki Kinoshita
-
Tony Morris