Proposal: Add a strict version of <$> for monads

Johan Tibell johan.tibell at gmail.com
Fri Nov 29 12:07:58 UTC 2013


Hi all,

I propose we add a strict version of <$> to base:

    -- | A strict version of 'Data.Functor.<$>' for monads.
    (<$!>) :: Monad m => (a -> b) -> m a -> m b
    f <$!> m = do
        a <- m
        return $! f a
    {-# INLINE (<$!>) #-}

    infixl 4 <$!>

It works on Monads instead of Functors as required by us inspecting the
argument.

This version is highly convenient if you want to work with
functors/applicatives in e.g. parser and avoid spurious thunks at the same
time. I realized that it was needed while fixing large space usage (but not
space-leak) issues in cassava.

I believe Edward Kmett discovered the need for it independently as well.

Deadline: 3 weeks

Cheers,
Johan
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/libraries/attachments/20131129/5ccbb4d0/attachment.html>


More information about the Libraries mailing list