[Haskell-cafe] Bird problem 1.6.2 -- is there an easier method?

John Millikin jmillikin at gmail.com
Wed May 19 23:39:46 EDT 2010


You've been asking a lot of very tutorial-ish questions on this list.
Although this isn't necessarily a *bad* thing, you may receive
responses more appropriate to your skill level on the
haskell-beginners list <
http://www.haskell.org/mailman/listinfo/beginners >.

I don't own the Bird book, but while reading your problem the type "f
:: (a, b) -> c" is throwing off huge warning signs. What sensible
implementation could such a function have? The only way I can think of
to implement it is "f (_, _) = undefined".

Assuming this signature is somehow valid, your reasoning for the left
side of the equation "flip (curry f)" is correct. It's a bit verbose,
but you'll learn to see the types better as you become more
experienced.

However, your reasoning for the right side is incorrect. First, lets
look at the equalities again:

flip (curry f) :: b -> a -> c
flip (curry f) = curry (f . swap)
curry (f . swap) :: b -> a -> c

The first step is to remove the "curry". Since (curry :: ((a, b) -> c)
-> a -> b -> c), there's only one possible type signature for (f .
swap):

f . swap :: (b, a) -> c

The types for (.) and f are known already. There's only one reasonable
definition for (.), so we can reason that:

(.) f g x = f (g x)

f . swap :: (b, a) -> c
f . swap = \x -> f (swap x)

>From this, it should be possible to derive the type of "swap" easily. Good luck.

2010/5/19 R J <rj248842 at hotmail.com>:
> Bird problem 1.6.2 is:
> If f :: (a, b) -> c, then define a function "swap" such that:
> flip (curry f) = curry (f . swap).
> I'd very much appreciate if someone could tell me whether there's a rigorous
> solution simpler than mine, which is:
> Since (.) :: (q -> r) -> (p -> q) -> (p -> r), we have f :: q -> r and swap
> :: p -> q.  Type unification of f requires q = (a, b) and r = c.
> Since f :: (a, b) -> c and curry :: ((l, m) -> n) -> (l -> m -> n), type
> unification requires l = a, b = m, and n = c.  Therefore,
> curry :: ((a, b) -> c) -> (a -> b -> c), and (curry f) :: a -> b -> c.
> Since flip :: (s -> t -> u) -> t -> s -> u, type unification requires
> s = a, t = b, and u = c.  Therefore, flip :: (a -> b -> c) -> b -> a -> c,
> and flip (curry f) :: b -> a -> c.
> Therefore, curry (f . swap) ::  b -> a -> c, and p :: b -> a.  Therefore,
> swap :: b -> a -> (a, b), and:
>
> swap                       :: b -> a -> (a, b)
> swap x y                   =  (y, x)
>
>
> ________________________________
> Hotmail has tools for the New Busy. Search, chat and e-mail from your inbox.
> Learn more.
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>


More information about the Haskell-Cafe mailing list