[Haskell-beginners] curry in a hurry
Daniel Fischer
daniel.is.fischer at web.de
Sat Jul 3 19:17:45 EDT 2010
On Sunday 04 July 2010 00:19:24, prad wrote:
> today i'm trying to understand curry and uncurry (in 3 parts with
> specific questions labelled as subsections of the parts).
>
>
> part 1
>
> if we have
>
> f (x,y) = x + y
> this is a function working on a single argument (x,y) albeit composed
> of 2 parameters. however, since all functions are curried in haskell
> (read that here: http://www.haskell.org/haskellwiki/Currying), what is
> really happening is
>
> (f x) y
Not really, f takes a tuple as argument.
> or specific to this case (+ x) y since f ends up being (+) as defined.
It would be ((+) x), which is the same as (x +) rather than (+ x)
>
> now if we write
> g = curry f
> we are naming a function whose purpose is to (f x) whatever comes its
> way allowing us to do neat things like:
>
> map (g 3) [4,5,6]
> [7,8,9]
>
> which we can't do by map (f 3) [4,5,6] because
You'd have to use
map (f . (,) 3) [4,5,6]
generally,
curry fun x
is tha same as
fun . (,) x
the function composed with the partially applied tuple constructor.
> f :: (Num t) => (t, t) -> t
> meaning f
> - is a function ... the (Num t)
> - applies itself ... the =>
> - to a Pair of (Num t)s
> - gives back a Num t
>
> 1.1 am i reading the type statement correctly?
No, correctly, it would read
f is a function taking a pair of t's and returning a t, provided t is a
member of the Num class
or
for all members t of Num, f is a function from (t,t) to t
>
> while
> g :: Integer -> Integer -> Integer
> means g takes an Integer, applies itself and that Integer to another
> Integer and computes another Integer.
>
> 1.2 how come these are Integer suddenly and not Num t?
It's the monomorphism restriction.
By the monomorphism restriction, a name boud by a binding of the form
val = rhs
without a type signature must have a monomorphic type. Thus the natural
polymorphic type of g is made monomorphic by instantiating the type
variable t to Integer.
You can avoid that by
- giving a type signature for g
- binding g by a function binding, i.e. with at least one argument to the
left of '='
or
- turning off the monomorphism restriction.
Since the monomorphism restriction bites mostly in ghci sessions, it is
generally a good idea to put the line
:set -XNoMonomorphismRestriction
in your .ghci file
(you can turn it off in source files with
{-# LANGUAGE NoMonomorphismRestriction #-}
or on the command line with -XNoMonomorphismRestriction
)
>
> this is a problem because while i can do
> f (2.3,9.3)
> i get an error when i try
> (g 2.3) 9.3
> ghci wants an instance declaration for (Fractional Integer) which
> puzzles me because g came about through currying f which is fine with
> fractions.
Since g's type was monomorphised to Integer -> Integer -> Integer, ghci
tries to interpret 2.3 and 9.3 as Integers.
But numeric literals of that form have type
Fractional a => a
(and are interpreted as
fromRational 2.3)
so ghci wants to have an instance of the Fractional calss for Integer to
know how to interpret 2.3 and 9.3 as Integers.
>
>
> part 2
>
> now the next discovery is really strange to me.
>
> if i name
>
> f x y = x + y
> we see f :: (Num a) => a -> a -> a
Yes, f is defined with arguments to the left of '=', so it isn't subjected
to the monomorphism restriction.
If you'd defined
f = \x y -> x + y
the MR would kick in again.
> which looks like the curried form of f (x,y)
not only looks it like that, it is that
> in fact that's what it exactly is and i can do
> map (f 3) [4,5,6]
> [7,8,9]
> just as i did with g before!!
>
> which is what the wiki statement says too:
>
> f :: a -> b -> c
> is the curried form of
> g :: (a, b) -> c
>
> however, it starts by stating:
>
> "Currying is the process of transforming a function that takes multiple
> arguments into a function that takes just a single argument and returns
> another function if any arguments are still needed."
> http://www.haskell.org/haskellwiki/Currying
Which is somewhat incorrect. Every function takes exactly one argument,
curried or not. (It is however, much more convenient to speak of functions
taking four arguments of types a1 a2 a3 a4 and returning a value of type b
than of functions taking an argument of type a1 returning a function taking
anargument of type a2 returning a function taking an argument of type a3
..., so we do that usually).
Some functions, however, take a tuple as argument.
And there's a natural correspondence between
(a,b) -> c
and
a -> b -> c
that correspondence in one direction is curry, in the other direction,
uncurry
>
> 2.1 so does all this mean that
>
> f (x,y) is the function that takes multiple arguments and not a single
> argument as i initially thought
No, your initial thought is correct, f takes a single argument, which is a
pair. (Well, since tuples are composed of several components, it is also a
common way of speech to say that functions taking a tuple argument take
several arguments. In that sense, f takes two arguments. But in Haskell-
speak, it's more common to say a function
fun :: a -> b -> c
takes two arguments - of course, if c is a function type, we can also say
that f takes three [or more] arguments.)
>
> and
>
> f x y is the function that actually takes a single argument twice?
>
That is more correct.
>
>
>
> part 3
>
> some of the above seems to be confirmed by looking at these types
>
> c x y = x + y
> c :: (Num a) => a -> a -> a
> so that's curried
Yes.
>
> u (x,y) = x + y
> u :: (Num t) => (t,t) -> t
> so that's uncurried
Yes.
>
> :t uncurry c
>
> uncurry c :: (Num a) => (a, a) -> a
>
> :t curry u
>
> curry u :: (Num a) => a -> a -> a
>
>
> but
>
> :t uncurry u
>
> uncurry u :: (Num (b -> c)) => ((b -> c, b -> c), b) -> c
> we're trying to uncurry something that is already uncurried
Yes. To apply uncurry, u must have a type a -> b -> c
u has the type (t,t) -> t [we ignore the Num constraint here, as it's not
important]
to match (t,t) -> t with a -> b -> c [or, with parentheses, a -> (b -> c)]
we must match the types before the '->', i.e.
a ~ (t,t)
and the types after the '->', i.e.
(b -> c) ~ t
So, with these matchings, the type of u must be
u :: (b -> c, b -> c) -> b -> c
with a Num constraint on (b -> c) ~ t.
(there's no standard Num instance for any function type, but you can write
such instances [more or less sensible if the result type is a Num
instance].
>
> and
>
> :t curry c
>
> curry c :: (Num (a, b)) => a -> b -> (a, b) -> (a, b)
> we're trying to curry something that is already curried
Yes, we have
c :: Num n => n -> n -> n
curry :: ((a,b) -> d) -> a -> b -> d
So to figure out curry c, we must match c's type to the type of curry's
argument, i.e. we must match n -> n -> n to (a,b) -> d [again ignoring the
Num constraint for the moment].
We must match the types before the '->', i.e.
n ~ (a,b)
and the types after, i.e.
n -> n ~ d
so
c :: Num (a,b) => (a,b) -> (a,b) -> (a,b)
and
curry c :: Num (a,b) => a -> b -> (a,b) -> (a,b)
>
> 3.1 just what are these strange looking things and how should their
> types be interpreted?
HTH,
Daniel
More information about the Beginners
mailing list