I am learning haskell currently and I am having a really hard time wrapping my head around how to explain <$> and <*>'s behavior.
For some context this all came from searching how to use an or operation when using takeWhile and the answer I found was this
takeWhile ((||) <$> isDigit <*> (=='.'))
In most of the documentation I have seen, <*> is used with a container type.
show <*> Maybe 10
By looking at
(<$>) :: Functor f => (a -> b) -> f a -> f b
It tells me that <*> keeps the outer container if its contents and applies the right to the inside, then wraps it back into the container
a b f a f b
([Int] -> String) -> [Just]([Int]) -> [Just]([String])
This makes sense to me, in my mind the f a is essentially happening inside the container, but when I try the same logic, I can make sense to me but I cant correlate the logic
f = (+) <$> (read)
so for f it becomes
a b f a f b
([Int] -> [Int -> Int]) -> ([String] -> [Int]) -> ([String] -> [Int -> Int])
So f being the container really confuses me when I try and work out what this code is going to do. I understand when I write it out like this, I can work it out and see its basically equivalent to the .
(.) :: (b -> c) -> (a -> b) -> a -> c
b c a b a c
([Int] -> [Int -> Int]) -> ([String] -> [Int]) -> ([String] -> [Int -> Int])
so it can be written as
f = (+) . read
Why not just write it as just that? Why wasn't the original snippet just written as
takeWhile ((||) . isDigit <*> (=='.'))
or does <$> imply something in this context that . des not?
Now looking at <*>, it seems like it is basicly exactly the same as the <$> except it takes two containers, uses the inner of both, then puts it pack in the container
(<*>) :: Applicative f => f (a -> b) -> f a -> f b
so
Just show <*> Just 10
f a b f a f b
[Just]([Int->Int]->[Int]) -> [Just]([Int->Int]) -> [Just]([Int])
However with functions, it becomes murky how things are being passed around to each other.
Looking at the original snippit and breaking it up
f1 :: Char -> Bool -> Bool
f1 = (||) . isDigit
f2 :: Char -> Bool
f2 = f1 <*> (== '.')
<*> behavior in f2 is
f a b f a f b
([Char] -> [Bool] -> [Bool]) -> ([Char] -> [Bool]) -> ([Char] -> [Bool])
So using previous logic, I see it as Char -> is the container, but its not very useful for me when working out what's happening.
It looks to me as if <*> is passing the function parameter into right side, then passing the same function parameter, and the return value into the left?
So to me, it looks equivalent to
f2 :: Char -> Bool
f2 x = f1 x (x=='_')
Its a bit of mental gymnastics for me to work out where the data is flowing when I see <*> and <$>. I guess im just looking for how an experienced haskell-er would read these operations in their head.
The applicative instance for functions is quite simple:
f <*> g = \x -> f x (g x)
You can verify for yourself that the types match up. And as you said,
(<$>) = (.)
(Ignoring fixity)
So you can rewrite your function:
(||) <$> isDigit <*> (=='.')
(||) . isDigit <*> (=='.')
\x -> ((||) . isDigit) x ((=='.') x)
-- Which can simply be rewritten as:
\x -> isDigit x || x == '.'
But it's important to understand why the function instance is as it is and how it works. Let's begin with Maybe:
instance Applicative Maybe where
pure :: a -> Maybe a
pure x = Just x
(<*>) :: Maybe (a -> b) -> Maybe a -> Maybe b
Nothing <*> _ = Nothing
_ <*> Nothing = Nothing
(Just f) <*> (Just x) = Just (f x)
Ignore the implementation here and just look at the types. First, notice that we've made Maybe an instance of Applicative. What exactly is Maybe? You might say that it's a type, but that isn't true - I can't write something like
x :: Maybe
- that doesn't make sense. Instead, I need to write
x :: Maybe Int
-- Or
x :: Maybe Char
or any other type after Maybe. So we give Maybe a type like Int or Char, and it suddenly becomes a type itself! That's why Maybe is what's known as a type constructor.
And that's exactly what the Applicative typeclass expects - a type constructor, which you can put any other type inside. So, using your analogy, we can think of giving Applicative a container type.
Now, what do I mean by
a -> b
?
We can rewrite it using prefix notation (the same way 1 + 2 = (+) 1 2)
(->) a b
And here we see that the arrow (->) itself is also just a type constructor - but unlike Maybe, it takes two types. But Applicative only wants a type constructor which takes one type. So we give it this:
instance Applicative ((->) r)
Which means that for any r, (->) r is an Applicative. Continuing the container analogy, (->) r is now a container for any type b such that the resulting type is r -> b. What that means is that the contained type is actually the future result of the function on giving it an r.
Now for the actual instance:
(<*>) :: Applicative f => f (a -> b) -> f a -> f b
Substituting (->) r as the applicative,
(<*>) :: ((->) r (a -> b)) -> ((->) r a) ((->) r b)
-- Rewriting it in infix notation:
(<*>) :: (r -> (a -> b)) -> (r -> a) -> (r -> b)
How would we go about writing the instance? Well, we need a way to get the contained type out of the container - but we can't use pattern matching like we did with Maybe. So, we use a lambda:
(f :: r -> (a -> b)) <*> (g :: r -> a) = \(x :: r) -> f x (g x)
And the type of f x (g x) is b, so the entire lambda has type r -> b, which is exactly what we were looking for!
EDIT: I noticed that I didn't talk about the implementation of pure for functions - I could update the answer, but try seeing if you can use the type signature to work it out yourself!
Related
This is yet another Haskell-through-category-theory question.
Let's take something simple and well-known as an example. fmap?
So fmap :: (a -> b) -> f a -> f b, omitting the fact that f is actually a Functor. As far as I understand, (a -> b) -> f a -> f b is nothing but a syntax sugar for the (a -> b) -> (f a -> f b); hence conclusion:
(1) fmap is a function producing a function.
Now, Hask contains functions as well, so (a -> b) and, in particular, (f a -> f b) is an object of the Hask (because objects of the Hask are well-defined Haskell types - a-ka mathematical sets - and there indeed exists set of type (a -> b) for each possible a, right?). So, once again:
(2) (a -> b) is an object of the Hask.
Now weird thing happens: fmap, obviously, is a morphism of the Hask, so it is a function, that takes another function and transform it to a yet another function; final function hasn't been applied yet.
Hence, one needs one more Hask's morphism to get from the (f a -> f b) to the f b. For each item i of type a there exists a morphism apply_i :: (f a -> f b) -> f b defined as \f -> f (lift i), where lift i is a way to build an f a with particular i inside.
The other way to see it is GHC-style: (a -> b) -> f a -> f b. On the contrast with what I've written above, (a -> b) -> f a is mapping to the regular object of the Hask. But such a view contradicts fundamental Haskell's axiom - no multivariate functions, but applied (curried) alternatives.
I'd like to ask at this point: is (a -> b) -> f a -> f b suppose to be an (a -> b) -> (f a -> f b) -> f b, sugared for simplicity, or am I missing something really, really important there?
is (a -> b) -> f a -> f b suppose to be an (a -> b) -> (f a -> f b) -> f b, sugared for simplicity
No. I think what you're missing, and it's not really your fault, is that it's only a very special case that the middle arrow in (a -> b) -> (f a -> f b) can be called morphism in the same way as the outer (a -> b) -> (f a -> f b) can. The general case of a Functor class would be (in pseudo-syntax)
class (Category (──>), Category (~>)) => Functor f (──>) (~>) where
fmap :: (a ──> b) -> f a ~> f b
So, it maps morphisms in the category whose arrows are denoted ──> to morphisms in the category ~>, but this morphism-mapping itself is just plainly a function. Your right, in Hask specifically function-arrows are the same sort of arrows as the morphism arrows, but this is mathematically speaking a rather degenerate scenario.
fmap is actually an entire family of morphisms. A morphism in Hask is always from a concrete type to another concrete type. You can think of a function as a morphism if the function has a concrete argument type and a concrete return type. A function of type Int -> Int represents a morphism (an endomorphism, really) from Int to Int in Hask. fmap, however has type Functor f => (a -> b) -> f a -> f b. Not a concrete type in sight! We just have type variables and a quasi-operator => to deal with.
Consider the following set of concrete function types.
Int -> Int
Char -> Int
Int -> Char
Char -> Char
Further, consider the following type constructors
[]
Maybe
[] applied to Int returns a type we could call List-of-Ints, but we usually just call [Int]. (One of the most confusing things about functors when I started out was that we just don't have separate names to refer to the types that various type constructors produce; the output is just named by the expression that evaluates to it.) Maybe Int returns the type we just call, well, Maybe Int.
Now, we can define a bunch of functions like the following
fmap_int_int_list :: (Int -> Int) -> [Int] -> [Int]
fmap_int_char_list :: (Int -> Char) -> [Int] -> [Char]
fmap_char_int_list :: (Char -> Int) -> [Char] -> [Int]
fmap_char_char_list :: (Char -> Char) -> [Char] -> [Char]
fmap_int_int_maybe :: (Int -> Int) -> Maybe Int -> Maybe Int
fmap_int_char_maybe :: (Int -> Char) -> Maybe Int -> Maybe Char
fmap_char_int_maybe:: (Char -> Int) -> Maybe Char -> Maybe Int
fmap_char_char_maybe :: (Char -> Char) -> Maybe Char -> Maybe Char
Each of these is a distinct morphism in Hask, but when we define them in Haskell, there's a lot of repetition.
fmap_int_int_list f xs = map f xs
fmap_int_char_list f xs = map f xs
fmap_char_int_list f xs = map f xs
fmap_char_char_list f xs = map f xs
fmap_int_int_maybe f x = case x of Nothing -> Nothing; Just y -> Just (f y)
fmap_int_char_maybe f x = case x of Nothing -> Nothing; Just y -> Just (f y)
fmap_char_int_maybe f x = case x of Nothing -> Nothing; Just y -> Just (f y)
fmap_char_char_maybe f x = case x of Nothing -> Nothing; Just y -> Just (f y)
The definitions don't differ when the type of f differs, only when the type of x/xs differs. That means we can define the following polymorphic functions
fmap_a_b_list f xs = map f xs
fmap_a_b_maybe f x = case x of Nothing -> Nothing; Just y -> Just (f y)
each of which represents a set of morphisms in Hask.
fmap itself is an umbrella term we use to refer to constructor-specific morphisms referred to by all the polymorphic functions.
With that out of the way, we can better understand fmap :: Functor f => (a -> b) -> f a -> f b.
Given fmap f, we first look at the type of f. We might find out, for example, that f :: Int -> Int, which means fmap f has to return one of fmap_int_int_list or fmap_int_int_maybe, but we're not sure which yet. So instead, it returns a constrained function of type Functor f => (Int -> Int) -> f Int -> f Int. Once that function is applied to a value of type [Int] or Maybe Int, we'll finally have enough information to know which morphism is actually meant.
Now weird thing happens: fmap, obviously, is a morphism of the Hask, so it is a function, that takes another function and transform it to a yet another function; final function hasn't been applied yet.
Hence, one needs one more Hask's morphism to get from the (f a -> f b) to the f b. For each item i of type a there exists a morphism apply_i :: (f a -> f b) -> f b defined as \f -> f (lift i), where lift i is a way to build an f a with particular i inside.
The notion of application in category theory is modelled in the form of CCC's - Cartesian Closed Categories. A category 𝓒 is a CCC if you have a natural bijection 𝓒(X×Y,Z) ≅ 𝓒(X,Y⇒Z).
In particular this implies that there exists a natural transformation 𝜺 (the evaluation), where 𝜺[Y,Z]:(Y⇒Z)×Y→Z, such that for every g:X×Y→Z there exists a 𝝀g:X→(Y⇒Z) such that, g = 𝝀g×id;𝜺[Y,Z]. So when you say,
Hence, one needs one more Hask's morphism to get from the (f a -> f b) to the f b.
The way you go from (f a -> f b) to the f b, or using the notation above, from (f a ⇒ f b) is via 𝜺[f a,f b]:(f a ⇒ f b) × f a → f b.
The other important point to keep in mind is that in Category Theory "elements" are not primitive concepts. Rather an element is an arrow of the form 𝟏→X,where 𝟏 is the terminal object. If you take X=𝟏 you have that 𝓒(Y,Z) ≅ 𝓒(𝟏×Y,Z) ≅ 𝓒(𝟏,Y⇒Z). That is, the morphisms g:Y→Z are in bijection to elements 𝝀g:𝟏→(Y⇒Z).
In Haskell this means functions are precisely the "elements" of arrow types. So in Haskell an application h y would be modelled via the evaluation of 𝝀h:𝟏→(Y⇒Z) on y:𝟏→Y. That is, the evaluation of (𝝀h)×y:𝟏→(Y⇒Z)×Y, which is given by the composition (𝝀h)×y;𝜺[Y,Z]:𝟏→Z.
For the sake of completeness, this answer focuses on a point that was addressed in various comments, but not by the the other answers.
The other way to see it is GHC-style: (a -> b) -> f a -> f b. On the contrast with what I've written above, (a -> b) -> f a is mapping to the regular object of the Hask.
-> in type signatures is right-associative. That being so, (a -> b) -> f a -> f b is really the same as (a -> b) -> (f a -> f b), and seeing (a -> b) -> f a in it would be a syntactic mix-up. It is no different from how...
(++) :: [a] -> [a] -> [a]
... doesn't mean that partially applying (++) will give us an [a] list (rather, it gives us a function that prepends some list).
From this point of view, the category theory questions you raise (for instance, on "need[ing] one more Hask's morphism to get from the (f a -> f b) to the f b") are a separate matter, addressed well by Jorge Adriano's answer.
I am reading in the haskellbook about applicative and trying to understand it.
In the book, the author mentioned:
So, with Applicative, we have a Monoid for our structure and function
application for our values!
How is monoid connected to applicative?
Remark: I don't own the book (yet), and IIRC, at least one of the authors is active on SO and should be able to answer this question. That being said, the idea behind a monoid (or rather a semigroup) is that you have a way to create another object from two objects in that monoid1:
mappend :: Monoid m => m -> m -> m
So how is Applicative a monoid? Well, it's a monoid in terms of its structure, as your quote says. That is, we start with an f something, continue with f anotherthing, and we get, you've guessed it a f resulthing:
amappend :: f (a -> b) -> f a -> f b
Before we continue, for a short, a very short time, let's forget that f has kind * -> *. What do we end up with?
amappend :: f -> f -> f
That's the "monodial structure" part. And that's the difference between Applicative and Functor in Haskell, since with Functor we don't have that property:
fmap :: (a -> b) -> f a -> f b
-- ^
-- no f here
That's also the reason we get into trouble if we try to use (+) or other functions with fmap only: after a single fmap we're stuck, unless we can somehow apply our new function in that new structure. Which brings us to the second part of your question:
So, with Applicative, we have [...] function application for our values!
Function application is ($). And if we have a look at <*>, we can immediately see that they are similar:
($) :: (a -> b) -> a -> b
(<*>) :: f (a -> b) -> f a -> f b
If we forget the f in (<*>), we just end up with ($). So (<*>) is just function application in the context of our structure:
increase :: Int -> Int
increase x = x + 1
five :: Int
five = 5
increaseA :: Applicative f => f (Int -> Int)
increaseA = pure increase
fiveA :: Applicative f => f Int
fiveA = pure 5
normalIncrease = increase $ five
applicativeIncrease = increaseA <*> fiveA
And that's, I guessed, what the author meant with "function application". We suddenly can take those functions that are hidden away in our structure and apply them on other values in our structure. And due to the monodial nature, we stay in that structure.
That being said, I personally would never call that monodial, since <*> does not operate on two arguments of the same type, and an applicative is missing the empty element.
1 For a real semigroup/monoid that operation should be associative, but that's not important here
Although this question got a great answer long ago, I would like to add a bit.
Take a look at the following class:
class Functor f => Monoidal f where
unit :: f ()
(**) :: f a -> f b -> f (a, b)
Before explaining why we need some Monoidal class for a question about Applicatives, let us first take a look at its laws, abiding by which gives us a monoid:
f a (x) is isomorphic to f ((), a) (unit ** x), which gives us the left identity. (** unit) :: f a -> f ((), a), fmap snd :: f ((), a) -> f a.
f a (x) is also isomorphic f (a, ()) (x ** unit), which gives us the right identity. (unit **) :: f a -> f (a, ()), fmap fst :: f (a, ()) -> f a.
f ((a, b), c) ((x ** y) ** z) is isomorphic to f (a, (b, c)) (x ** (y ** z)), which gives us the associativity. fmap assoc :: f ((a, b), c) -> f (a, (b, c)), fmap assoc' :: f (a, (b, c)) -> f ((a, b), c).
As you might have guessed, one can write down Applicative's methods with Monoidal's and the other way around:
unit = pure ()
f ** g = (,) <$> f <*> g = liftA2 (,) f g
pure x = const x <$> unit
f <*> g = uncurry id <$> (f ** g)
liftA2 f x y = uncurry f <$> (x ** y)
Moreover, one can prove that Monoidal and Applicative laws are telling us the same thing. I asked a question about this a while ago.
Haskell newbie here.
So (<$>) is defined as
(<$>) :: Functor f => (a -> b) -> f a -> f b
And (<*>) is defined as
(<*>) :: Applicative f => f (a -> b) -> f a -> f b
But I feel like Applicative is two concepts in one:
One would be that of a functor
And one would be this:
(<#>) :: MyConcept m => m (a -> b) -> a -> b
So e.g. thinking in terms of Maybe:
I have an let i = 4 and I have a let foo = Nothing :: Num a => Maybe (a -> a).
Basically I have a function that may or may not be there, that takes an Int and returns an Int, and an actual Int.
Of course I could just wrap i by saying:
foo <*> Just i
But that requires me to know the what Applicative foo is wrapped in.
Is there something equivalent to what I described here? How would I go about implementing that function <#> myself?
It would be something like this:
let (<#>) func i = func <*> ??? i
You can use pure:
pure :: Applicative f => a -> f a
foo <*> pure i
although you could just use fmap:
fmap (\f -> f i) foo
or
fmap ($ i) foo
(<#>) :: MyConcept m => m (a -> b) -> a -> b
To see if this is like an Applicative try deriving <#> from <*> and pure. You will find that it is impossible.
Where you can find <#> in a more general form is extract :: (Counit w) => w a -> a for comonads.
Can you implement extract for Maybe? What do you do when the value is Nothing?
I'm trying to write a function (called hide here), which can apply a sufficiently polymorphic function inside an existential wrapper (or lift functions to work on wrappers with hidden types; hence "hide"):
{-# LANGUAGE GADTs
, RankNTypes
#-}
data Some f
where Some :: f a -> Some f
hide :: (forall a. f a -> g b) -> Some f -> Some g
hide f (Some x) = Some (f x)
data Phantom a = Phantom
cast :: Phantom a -> Phantom b
cast Phantom = Phantom
works :: Some Phantom -> Some Phantom
works = hide cast
doesn't :: Functor f => Some f -> Some f
doesn't = hide (fmap $ \x -> [x])
{-
foo.hs:23:17:
Couldn't match type ‘b0’ with ‘[a]’
because type variable ‘a’ would escape its scope
This (rigid, skolem) type variable is bound by
a type expected by the context: f a -> f b0
at foo.hs:23:11-33
Expected type: f a -> f b0
Actual type: f a -> f [a]
In the first argument of ‘hide’, namely ‘(fmap $ \ x -> [x])’
In the expression: hide (fmap $ \ x -> [x])
In an equation for ‘doesn't’: doesn't = hide (fmap $ \ x -> [x])
Failed, modules loaded: none.
-}
but :: Functor f => Some f -> Some f
but = hide' (fmap $ \x -> [x])
where hide' :: (forall a. f a -> g [a]) -> Some f -> Some g
hide' f (Some x) = Some (f x)
So I pretty much understand why this is happening; works shows that hide does in fact work when the return type is completely unrelated to the input type, but in doesn't I'm calling hide with an argument of type a -> [a]. hide is supposed to get to "choose" the type a (RankNTypes), but b is ordinarily polymorphic. When b in fact depends on a, a could leak out.
But in the context where I'm actually calling it, a doesn't in fact leak out; I immediately wrap it up in Some. And in fact I can write an alternate hide' that accepts specifically a -> [a] functions and works with the exact same implementation, just a different type signature.
Is there any way I can type the implementation hide f (Some x) = Some (f x) so that it works more generally? Really I'm interested in lifting functions with type a -> q a, where q is some arbitrary type function; i.e. I expect the return type to depend on a, but I don't care how it does so. There probably are use cases where q a is a constant (i.e. the return type doesn't depend on a), but I imagine they'll be much rarer.
This example is pretty silly, obviously. In my real use case I have a GADT Schema a that roughly speaking represents types in an external type system; the phantom parameter gives a Haskell type that could be used to represent values in the external type system. I need that phantom parameter to keep everything type safe, but sometimes I construct Schemas based on runtime data, in which case I don't know what that parameter type is.
So I appear to need another type which is agnostic about the type parameter. Rather than make (yet) another parallel type, I was hoping to use a simple existential wrapper like Some to construct it from Schema, and be able to lift functions of type forall a. Schema a -> Schema b to Some Schema -> Some Schema. So if I have an XY problem and I'd be better of using some other means of passing around Schema a for unknown a, that would also solve my problem.
As David Young says, you can write
hide' :: (forall a. f a -> g (q a)) -> Some f -> Some g
hide' f (Some x) = Some (f x)
does :: Functor f => Some f -> Some f
does = hide' (fmap (:[]))
but instead of making hide fmap-like, you can make it bind-like:
hide'' :: (forall a. f a -> Some g) -> Some f -> Some g
hide'' f (Some x) = f x
does :: Functor f => Some f -> Some f
does = hide'' (Some . fmap (:[]))
But this is a bit boilerplateable.
Or, more generally
elim :: (forall a. f a -> c) -> Some f -> c
elim f (Some x) = f x
I'm not sure how useful this is for your larger use-case as you'd have to refactor all your existing operations to use continuation passing style, but continuations can be used to implement a hide that works for both of your examples and keeps b completely generic.
hide :: (forall r a. f a -> (forall b. g b -> r g) -> r g) -> Some f -> Some g
hide f (Some x) = f x Some
cast :: Phantom a -> (forall b. Phantom b -> r Phantom) -> r Phantom
cast Phantom f = f Phantom
works :: Some Phantom -> Some Phantom
works = hide cast
alsoWorks :: Functor f => Some f -> Some f
alsoWorks = hide (\a f -> f $ fmap (\x -> [x]) a)
You can make it somewhat nicer by factoring out the CPS-conversion which allows you to more easily use existing functions like your original cast:
hide :: (forall r a. f a -> (forall b. g b -> r g) -> r g) -> Some f -> Some g
hide f (Some x) = f x Some
cps :: (f a -> g b) -> (f a -> (forall c. g c -> r) -> r)
cps f a c = c (f a)
cast :: Phantom a -> Phantom b
cast Phantom = Phantom
works :: Some Phantom -> Some Phantom
works = hide $ cps cast
alsoWorks :: Functor f => Some f -> Some f
alsoWorks = hide $ cps $ fmap (\x -> [x])
New to Haskell, and am trying to figure out this Monad thing. The monadic bind operator -- >>= -- has a very peculiar type signature:
(>>=) :: Monad m => m a -> (a -> m b) -> m b
To simplify, let's substitute Maybe for m:
(>>=) :: Maybe a -> (a -> Maybe b) -> Maybe b
However, note that the definition could have been written in three different ways:
(>>=) :: Maybe a -> (Maybe a -> Maybe b) -> Maybe b
(>>=) :: Maybe a -> ( a -> Maybe b) -> Maybe b
(>>=) :: Maybe a -> ( a -> b) -> Maybe b
Of the three the one in the centre is the most asymmetric. However, I understand that the first one is kinda meaningless if we want to avoid (what LYAH calls boilerplate code). However, of the next two, I would prefer the last one. For Maybe, this would look like:
When this is defined as:
(>>=) :: Maybe a -> (a -> b) -> Maybe b
instance Monad Maybe where
Nothing >>= f = Nothing
(Just x) >>= f = return $ f x
Here, a -> b is an ordinary function. Also, I don't immediately see anything unsafe, because Nothing catches the exception before the function application, so the a -> b function will not be called unless a Just a is obtained.
So maybe there is something that isn't apparent to me which has caused the (>>=) :: Maybe a -> (a -> Maybe b) -> Maybe b definition to be preferred over the much simpler (>>=) :: Maybe a -> (a -> b) -> Maybe b definition? Is there some inherent problem associated with the (what I think is a) simpler definition?
It's much more symmetric if you think in terms the following derived function (from Control.Monad):
(>=>) :: Monad m => (a -> m b) -> (b -> m c) -> (a -> m c)
(f >=> g) x = f x >>= g
The reason this function is significant is that it obeys three useful equations:
-- Associativity
(f >=> g) >=> h = f >=> (g >=> h)
-- Left identity
return >=> f = f
-- Right identity
f >=> return = f
These are category laws and if you translate them to use (>>=) instead of (>=>), you get the three monad laws:
(m >>= g) >>= h = m >>= \x -> (g x >>= h)
return x >>= f = f x
m >>= return = m
So it's really not (>>=) that is the elegant operator but rather (>=>) is the symmetric operator you are looking for. However, the reason we usually think in terms of (>>=) is because that is what do notation desugars to.
Let us consider one of the common uses of the Maybe monad: handling errors. Say I wanted to divide two numbers safely. I could write this function:
safeDiv :: Int -> Int -> Maybe Int
safeDiv _ 0 = Nothing
safeDiv n d = n `div` d
Then with the standard Maybe monad, I could do something like this:
foo :: Int -> Int -> Maybe Int
foo a b = do
c <- safeDiv 1000 b
d <- safeDiv a c -- These last two lines could be combined.
return d -- I am not doing so for clarity.
Note that at each step, safeDiv can fail, but at both steps, safeDiv takes Ints, not Maybe Ints. If >>= had this signature:
(>>=) :: Maybe a -> (a -> b) -> Maybe b
You could compose functions together, then give it either a Nothing or a Just, and either it would unwrap the Just, go through the whole pipeline, and re-wrap it in Just, or it would just pass the Nothing through essentially untouched. That might be useful, but it's not a monad. For it to be of any use, we have to be able to fail in the middle, and that's what this signature gives us:
(>>=) :: Maybe a -> (a -> Maybe b) -> Maybe b
By the way, something with the signature you devised does exist:
flip fmap :: Maybe a -> (a -> b) -> Maybe b
The more complicated function with a -> Maybe b is the more generic and more useful one and can be used to implement the simple one. That doesn't work the other way around.
You can build a a -> Maybe b function from a function f :: a -> b:
f' :: a -> Maybe b
f' x = Just (f x)
Or, in terms of return (which is Just for Maybe):
f' = return . f
The other way around is not necessarily possible. If you have a function g :: a -> Maybe b and want to use it with the "simple" bind, you would have to convert it into a function a -> b first. But this doesn't usually work, because g might return Nothing where the a -> b function needs to return a b value.
So generally the "simple" bind can be implemented in terms of the "complicated" one, but not the other way around. Additionally, the complicated bind is often useful and not having it would make many things impossible. So by using the more generic bind monads are applicable to more situations.
The problem with the alternative type signature for (>>=) is that it only accidently works for the Maybe monad, if you try it out with another monad (i.e. List monad) you'll see it breaks down at the type of b for the general case. The signature you provided doesn't describe a monadic bind and the monad laws can't don't hold with that definition.
import Prelude hiding (Monad, return)
-- assume monad was defined like this
class Monad m where
(>>=) :: m a -> (a -> b) -> m b
return :: a -> m a
instance Monad Maybe where
Nothing >>= f = Nothing
(Just x) >>= f = return $ f x
instance Monad [] where
m >>= f = concat (map f m)
return x = [x]
Fails with the type error:
Couldn't match type `b' with `[b]'
`b' is a rigid type variable bound by
the type signature for >>= :: [a] -> (a -> b) -> [b]
at monadfail.hs:12:3
Expected type: a -> [b]
Actual type: a -> b
In the first argument of `map', namely `f'
In the first argument of `concat', namely `(map f m)'
In the expression: concat (map f m)
The thing that makes a monad a monad is how 'join' works. Recall that join has the type:
join :: m (m a) -> m a
What 'join' does is "interpret" a monad action that returns a monad action in terms of a monad action. So, you can think of it peeling away a layer of the monad (or better yet, pulling the stuff in the inner layer out into the outer layer). This means that the 'm''s form a "stack", in the sense of a "call stack". Each 'm' represents a context, and 'join' lets us join contexts together, in order.
So, what does this have to do with bind? Recall:
(>>=) :: m a -> (a -> m b) -> m b
And now consider that for f :: a -> m b, and ma :: m a:
fmap f ma :: m (m b)
That is, the result of applying f directly to the a in ma is an (m (m b)). We can apply join to this, to get an m b. In short,
ma >>= f = join (fmap f ma)