
I have been following the recent "Monad tutorial" discussion with interest, and even read the tutorial, which is a useful addition to the existing Haskell documentation. So useful in fact that it raises a question... The whole monad mechanism seems to geared towards functions of one argument, plus eventually state, that get chained together. How about functions with several arguments? As an example, I'll use the Maybe monad. Suppose I want to write code to handle experimental data, in which there might be missing values. I might then decide to represent measurements by data of type "Maybe Double", with missing values represented by "Nothing". I could then go on to define functions on missing values, which would return "Nothing" when their argument is "Nothing", and I could string these functions together via the monad mechanism. Fine. But how would I handle e.g. addition of two such values? The result should be "Nothing" when either of its arguments is "Nothing". Is there any mechanism to handle that? Konrad.

On Tuesday, 2003-08-19, 12:42, CEST, Konrad Hinsen wrote:
I have been following the recent "Monad tutorial" discussion with interest, and even read the tutorial, which is a useful addition to the existing Haskell documentation. So useful in fact that it raises a question...
The whole monad mechanism seems to geared towards functions of one argument, plus eventually state, that get chained together. How about functions with several arguments?
As an example, I'll use the Maybe monad. Suppose I want to write code to handle experimental data, in which there might be missing values. I might then decide to represent measurements by data of type "Maybe Double", with missing values represented by "Nothing". I could then go on to define functions on missing values, which would return "Nothing" when their argument is "Nothing", and I could string these functions together via the monad mechanism. Fine. But how would I handle e.g. addition of two such values? The result should be "Nothing" when either of its arguments is "Nothing". Is there any mechanism to handle that?
Yes, liftM2. Defined in module Monad (or Data.Monad resp.).
Konrad.
Wolfgang

Hi
As an example, I'll use the Maybe monad. Suppose I want to write code to handle experimental data, in which there might be missing values. I might then decide to represent measurements by data of type "Maybe Double", with missing values represented by "Nothing". I could then go on to define functions on missing values, which would return "Nothing" when their argument is "Nothing", and I could string these functions together via the monad mechanism. Fine. But how would I handle e.g. addition of two such values? The result should be "Nothing" when either of its arguments is "Nothing". Is there any mechanism to handle that?
Yes, liftM2. Defined in module Monad (or Data.Monad resp.).
Konrad.
Wolfgang
Or, more generally, infixl 9 <$> (<$>) :: Monad m => m (s -> t) -> m s -> m t mf <$> ms = do f <- mf s <- ms return (f s) Now your lifted sum is return (+) <$> mx <$> my Being a sick type class hacker (a symptom of the Haskell guilt caused by working with dependent types) I've constructed an overloaded operator fun :: Monad m => (t0 -> ... -> tn) -> (m t0 -> ... -> m tn) where tn is of ground type. Effectively fun f x0 ... xn-1 = return f <$> x0 <$> ... <$> xn-1 In fact, it's good to weaken the requirement (on fun and <^>) from `being a Monad' to being Fun, where class Fun f where eta :: x -> f x (<$>) :: f (s -> t) -> f s -> f t `supporting return and <$>', as there are plenty of such structures which are not monadic (eg. lists wrt repeat and zipWith ($)). It's even more fun to work with lifted functors class LFunctor f where (<^>) :: Fun m => (s -> m t) -> f s -> m (f t) with, for example instance LFunctor [] where f <^> [] = fun [] f <^> (x : xs) = fun (:) (f x) (f <^> xs) You can use <^> to define mapping, flattening and all sorts of other goodies. What it comes down to, I suppose, is that sometimes we want to use the functional idiom to write programs modulo some modality, eg Maybe-ness statefulness, non-determinism, etc. I guess that Arrows generalize all this stuff still further, but the Fun class above is cheap and remarkably cheerful. I use it all the time... Cheers Conor

On Tue, 19 Aug 2003 14:09:16 +0100 (BST)
C T McBride
Hi
As an example, I'll use the Maybe monad. Suppose I want to write code to handle experimental data, in which there might be missing values. I might then decide to represent measurements by data of type "Maybe Double", with missing values represented by "Nothing". I could then go on to define functions on missing values, which would return "Nothing" when their argument is "Nothing", and I could string these functions together via the monad mechanism. Fine. But how would I handle e.g. addition of two such values? The result should be "Nothing" when either of its arguments is"Nothing". Is there any mechanism to handle that?
Yes, liftM2. Defined in module Monad (or Data.Monad resp.).
Konrad.
Wolfgang
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

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

In article
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?
Ancient and venerable almost certainly, but not well-known. Lost Knowledge of Haskell, perhaps. People keep reinventing this class (which is a subclass of Functor btw). In HBase I call it FunctorApplyReturn. My hierarchy looks more or less like this: class HasReturn f where return :: a -> f a -- eta class Functor f where fmap :: (a -> b) -> f a -> f b class (Functor f) => FunctorApply f where fApply :: f (a -> b) -> f a -> f b -- (<$>) fPassTo :: f a -> f (a -> b) -> f b (>>) :: f a -> f b -> f b fPassTo = liftF2 (\a ab -> ab a) liftF2 func fa = fApply (fmap func fa) class (FunctorApply f,HasReturn f) => FunctorApplyReturn f instance (FunctorApply f,HasReturn f) => FunctorApplyReturn f class (FunctorApplyReturn f) => Monad f where (>>=) :: f a -> (a -> f b) -> f b fail :: String -> f a; fail = error; Certain functions that seem to require Monads actually work with any FunctorApplyReturn. For instance: class (Functor f) => ExtractableFunctor f where fExtract :: (FunctorApplyReturn m) => f (m a) -> m (f a) for :: (ExtractableFunctor f,FunctorApplyReturn m) => (a -> m b) -> (f a -> m (f b)); for foo fa = fExtract (fmap foo fa) All sorts of useful types such as [] and Maybe can be made ExtractableFunctors. And then 'for' can iterate on them. IMO something like all this should be in the standard libraries. The downside is that people would have to make instances for HasReturn, Functor and FunctorApply with every Monad instance. -- Ashley Yakeley, Seattle WA

Hi all Sorry I've been slow replying: I'm not around much at the moment. Thanks for all the responses. I did think, when I started playing with what I call eta and <$>, that I couldn't possibly be alone. Would it be good if we sought some more standardized presentation of this structure? In terms of *** 1 what to call the class and its methods: I have no particular attachment to any of the names I've used (also for stuff below) *** 2 what other bits and pieces we'd like to have also; in the Epigram source, I currently have the more general n-ary lifting operator fun, defined thus (again, I'm not attached to the names)
class Fun f => Funnel f s t | f s -> t, s t -> f, f t -> s where fun :: s -> t funnel :: f s -> t
instance Funnel f t u => Funnel f (s -> t) (f s -> u) where fun g = funnel (eta g) funnel fg fx = funnel (fg <$> fx)
(defun base-funnel (data) (insert (concat "\n\n" "> instance Fun f => Funnel f " data " (f " data") where\n" "> fun = eta\n" "> funnel = id\n" ))) and then a Funnel instance for each base type, but I'd rather have
instance Fun f => Funnel f data (f data) where fun = eta funnel = id
I believe it's that overlapping instances vs fundep problem... Also `ExtractableFunctor'...
infixl 9 <^> class Functorial g where (<^>) :: Fun f => (s -> f t) -> g s -> f (g t)
...and flattening...
infixr 5 <+> class Monoidal x where m0 :: x (<+>) :: x -> x -> x
newtype K s t = K {unK :: s} deriving (Show,Eq)
instance Monoidal s => Fun (K s) where eta _ = K m0 K x <$> K y = K (x <+> y)
infixl 9
() :: (Functorial g,Monoidal s) => (x -> s) -> g x -> s f gx = unK ((K . f) <^> gx)
*** 3 what extra syntax might be nice for work in this style, the way do-notation supports monads; one interesting question is how much of the lifting can be inferred silently, within the scope of a general hint that we're `working under f' I'm certainly interested in giving a serviceable presentation to this style of working: I use it all the time. Is it worth trying to get some sort of consensus? Cheers Conor

On Thu, Aug 21, 2003 at 11:32:47AM +0100, C T McBride wrote:
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?
It seems that something this useful should have a name, but I've been unable to find one. This interface was first used for parsers by Niklas Rojemo. Doaitse Swierstra has developed a lot of interesting parsers with this interface, roughly infixl 4 <$>, <*> class Functor f => Sequence f where eta :: a -> f a (<*>) :: f (a -> b) -> f a -> f b (<$>) :: (a -> b) -> f a -> f b (<$>) = fmap One would expect this to satisfy identity and associativity laws: eta f <*> v = f <$> v u <*> eta y = ($ y) <$> u u <*> (v <*> w) = ((.) <$> u <*> v) <*> w as well as naturality of eta and (<*>). Several other choices of primitives are available. One is: lift0 :: a -> f a lift1 :: (a -> b) -> f a -> f b lift2 :: (a -> b -> c) -> f a -> f b -> f c lift0 = eta lift1 = fmap lift2 f fa fb = f <$> fa <*> fb (<*>) = lift2 ($) Another interface is eta plus mult :: f a -> f b -> f (a,b) with axioms eta x `mult` v = fmap (\y -> (x,y)) v u `mult` eta y = fmap (\x -> (x,y)) u u `mult` (v `mult` w) = fmap assoc ((u `mult` v) `mult` w) where assoc ((x,y),z) = (x,(y,z)) These are all equivalent (or would be, if Haskell had true products). The last version generalizes to any symmetric monoidal category: it requires that f be a lax monoidal functor, with eta_1 and mult as the transformations, that eta is a transformation from the identity monoidal functor to f, plus the symmetry condition eta x `mult` v = fmap swap (v `mult` eta x) As you note, they're preserved under composition. They also compose with arrows (in the sense of Hughes) to make new arrows, and they're preserved by products (as are arrows).

On dinsdag, aug 19, 2003, at 15:09 Europe/Amsterdam, C T McBride wrote:
Hi
As an example, I'll use the Maybe monad. Suppose I want to write code to handle experimental data, in which there might be missing values. I might then decide to represent measurements by data of type "Maybe Double", with missing values represented by "Nothing". I could then go on to define functions on missing values, which would return "Nothing" when their argument is "Nothing", and I could string these functions together via the monad mechanism. Fine. But how would I handle e.g. addition of two such values? The result should be "Nothing" when either of its arguments is "Nothing". Is there any mechanism to handle that?
Yes, liftM2. Defined in module Monad (or Data.Monad resp.).
Konrad.
Wolfgang
Or, more generally,
infixl 9 <$>
(<$>) :: Monad m => m (s -> t) -> m s -> m t mf <$> ms = do f <- mf s <- ms return (f s)
In my parsing libraries I have been using <$> for function with the type: (<$>) :: Parser p => (a -> b) -> p a -> p b Yes, I know that by making p a Functor this function would be called `map`, but since all my combiantors are of the <...> form I prefer this. Your <$> is written as <*>: (<*>) :: Parser p => p ( b -> a) -> p b -> p a (<* ) :: Parser p => p a -> p b -> p a ( *>) :: Parser p => p b -> p a -> p a etc Now one can combine parsers as in: pVal = (+) <$> pInteger <* pSymbol '+' <*> pInteger <|> (*) <$> pInteger <* pSymbol '*' <*> pInteger etc Should I change this in future versions? Doaitse Swierstra
Now your lifted sum is
return (+) <$> mx <$> my
Being a sick type class hacker (a symptom of the Haskell guilt caused by working with dependent types) I've constructed an overloaded operator
fun :: Monad m => (t0 -> ... -> tn) -> (m t0 -> ... -> m tn)
where tn is of ground type. Effectively
fun f x0 ... xn-1 = return f <$> x0 <$> ... <$> xn-1
In fact, it's good to weaken the requirement (on fun and <^>) from `being a Monad' to being Fun, where
class Fun f where eta :: x -> f x (<$>) :: f (s -> t) -> f s -> f t
`supporting return and <$>', as there are plenty of such structures which are not monadic (eg. lists wrt repeat and zipWith ($)).
It's even more fun to work with lifted functors
class LFunctor f where (<^>) :: Fun m => (s -> m t) -> f s -> m (f t)
with, for example
instance LFunctor [] where f <^> [] = fun [] f <^> (x : xs) = fun (:) (f x) (f <^> xs)
You can use <^> to define mapping, flattening and all sorts of other goodies.
What it comes down to, I suppose, is that sometimes we want to use the functional idiom to write programs modulo some modality, eg Maybe-ness statefulness, non-determinism, etc. I guess that Arrows generalize all this stuff still further, but the Fun class above is cheap and remarkably cheerful. I use it all the time...
Cheers
Conor _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (7)
-
Ashley Yakeley
-
C T McBride
-
Derek Elkins
-
Doaitse Swierstra
-
Konrad Hinsen
-
Ross Paterson
-
Wolfgang Jeltsch