+1
Including others such as Applicative, Alternative, etc.
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@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) wherefmap :: (b -> c) -> Kleisli m a b -> Kleisli m a cfmap f (Kleisli h) = Kleisli (fmap f . h){-# INLINE fmap #-}(<$) :: c -> Kleisli m a b -> Kleisli m a cc <$ 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:
Thanks,Dmitrii Kovanikov
Libraries mailing list
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