
Hi
Or, more generally,
infixl 9 <$>
(<$>) :: Monad m => m (s -> t) -> m s -> m t mf <$> ms = do f <- mf s <- ms return (f s)
or just liftM2 ($) or just ap
OK, I'm a bad citizen and I never look things up in the library. If it isn't in the Gentle Introduction (circa 1999) or some old Hugs -98 extension guide, I probably don't know about it. One of my favourite things about Haskell is that you can get a long way without troubling a library. Why is this? I suspect it's because Haskell has neater ways of expressing and manipulating data (especially in sum types) than, say, Java. My point, however, is not to use <$> with that type, but the more general class Fun f where eta :: x -> f x (<$>) :: f (s -> t) -> f s -> f t Is there a better name for Fun? Is it ancient and venerable? Am I an ignoramus twice over? Sure, you can take instance Monad m => Fun m where eta = return (<$>) = liftM2 ($) but you don't always want to. Consider the following non-monadic examples (1) vectorizing instance Fun [] where eta = repeat (<$>) = zipWith ($) (2) flattening newtype K x anything = K x class Monoid x where zero :: x (<+>) :: x -> x -> x instance Monoid x => Fun (K x) where eta _ = K zero K x <$> K y = K (x <+> y) Modulo some packing and unpacking, this buys you flattening for the price of lifting map. (Is this what Lambert Meertens is talking about in his paper `Functor Pulling'?) (3) composition newtype Comp g h x = Comp (g (h x)) instance (Fun g,Fun h) => Fun (Comp g h) where eta x = Comp (eta (eta x)) Comp ghf <$> Comp ghs = Comp (eta (<$>) ghf <$> ghs) That's to say, you can define <$> for the composition of two Funs, hence of two Monads, but, if I recall correctly, it's rather harder to define
= for the composition of two Monads.
(4) parsing (controversial?) I claim that you can write plausible parsers with some suitable type constructor, eg newtype Parser x = Parser (String -> Maybe (x,String)) given only Fun Parser and Monoid (Parser x). Typically, one writes syntax :: Parser syntax syntax = eta rule1 <$> syntax11 <$> ... <$> syntax1k_1 <+> ... <+> eta rulen <$> syntaxn1 <$> ... <$> syntaxnk_n where syntaxij :: Parser syntaxij and rulei :: syntaxi1 -> ... -> syntaxik_i -> syntax The point, in general, is to make lifted functional programming look as much like functional programming as possible. Of course, when something is both Monad and Fun, you can freely mix with the more imperative-style do. Cheers Conor