[Haskell-cafe] Why does `flip` cause function type so different ?
Daniel Fischer
daniel.is.fischer at web.de
Fri Mar 19 00:19:40 EDT 2010
Am Freitag 19 März 2010 04:34:53 schrieb zaxis:
> >let f x xs = [x:xs,xs]
> >
> > :t f
>
> f :: a -> [a] -> [[a]]
>
> >:t (>>=) .f
>
> (>>=) .f :: a -> ([[a]] -> [a] -> b) -> [a] -> b
>
> > :t (flip (>>=) .f)
>
> (flip (>>=) .f) :: a -> [[a]] -> [[a]]
>
> Why is the type of `(>>=) .f` and `flip (>>=) .f` so different ?
>
Because the types of (>>=) and flip (>>=) are different.
(>>=) :: Monad m => m a -> (a -> m b) -> m b
flip (>>=) :: Monad m => (a -> m b) -> m a -> m b
Now, for whatever f, for ((>>=) . f) to be well-typed, f must have the type
f :: s -> m t
for some Monad m. (It must be a function because it's an argument of
composition (.), and since
((>>=) . f) x === (>>=) (f x) === (f x >>=),
f's return type must be monadic.) Then (f x >>=) takes a function
g :: t -> mu, so that (f x >>= g) is a value of type m u.
The given f has type a -> [a] -> [[a]] === a -> ([a] -> [[a]]), so
m t === [a] -> [[a]] === ((->) [a]) [[a]],
i.e.
m === ((->) a)
and
t === [[a]]
(f x >>=) then takes a function g of type (t -> m b), expanded
([[a]] -> ([a] -> b)), and then f x >>= g is a value of type m b, expanded
[a] -> b.
This works because for any type w, ((->) w) is indeed a Monad, the Reader
Monad, to be specific.
On the other hand, for (flip (>>=) . f) to be well typed, f must be a
function returning something of type (t -> m u) for some Monad m, so f's
type must be s -> (t -> m u).
The given f has type
a -> [a] -> [[a]],
so s === a, t === [a], m === [] and u === [a] === t.
Then (flip (>>=) . f) x, which is (>>= f x), takes a further argument of
type m t === [[a]] and then returns a value of type m u === m t === [[a]]
More information about the Haskell-Cafe
mailing list