
I don't like that this function is implemented for Monads, I think that it makes sense for some other functors as well. Though to do this 'properly' we would probably end up with another typeclass "StrictFunctor" or something, and that is perhaps too much unnecessary complexity. In the same vein as strict fmap, does a strict (<*>) make sense as well? -- | A strict version of `Control.Applicative.<*>` for monads (<*!>) :: Monad m => m (a -> b) -> m a -> m b mf <*!> mx = do f <- mf x <- mx return $! f x We might also call these fmap' and ap', but I prefer the operator. Twan On 29/11/13 12:07, Johan Tibell wrote:
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
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries