Proposal: Data.Functor.<.> for `fmap f2 . f1`

Ivan Lazar Miljenovic ivan.miljenovic at gmail.com
Sun Sep 20 10:34:22 UTC 2015


On 20 September 2015 at 11:30, Ömer Sinan Ağacan <omeragacan at gmail.com> wrote:
> I don't know if "I find this very useful" is enough for adding a function to
> base, but here it goes:
>
>     infixl 4 <.>
>     (<.>) :: Functor f => (b -> c) -> (a -> f b) -> (a -> f c)
>     f1 <.> f2 = fmap f1 . f2
>     {-# INLINE (<.>) #-}
>
> I first defined this couple of months ago and I find myself looking for this
> function all the time now.
>
> One problem with this is that the name is used by widely used `filepath`
> library.

Apart from the clashing with other libraries, I mislike this because
of it's lack of symmetry: to me it seems odd that the Functor is only
on one side (admittedly though, the variant of type (b -> f c) -> (a
-> f b) -> a -> f c requires Monad rather than just Functor).

-- 
Ivan Lazar Miljenovic
Ivan.Miljenovic at gmail.com
http://IvanMiljenovic.wordpress.com


More information about the Libraries mailing list