Is currying worth it?

I have been thinking about making Haskell easier to learn. One big hurdle seems to be currying. So, I am starting to question whether the benefits of currying outweigh the drawbacks. In this post, I present what I think the two most important advantages of currying are, and why I think they might not be worth the cost.

Please let me know what you think, especially if you are a beginning Haskeller. I would love to hear about your experience of learning how currying works. And for the more proficient Haskellers: do you know any other advantages or do you see big problems with the things proposed in this post?

Partial application

The Haskell wiki page about currying lists this advantage:

[…] the curried form is usually more convenient because it allows partial application.

But I think currying is rather something that holds back better mechanisms for partial application. Currying only allows partial application in the order of the arguments. Some other languages allow you to partially apply function arguments in any order. For example you could indicate the missing arguments with an underscore:

> map (add 1 _) [1,2,3]
[2,3,4]

Or even numbered underscores:

> map (_2, _1) [(1,2), (3,4)]
[(2,1), (4,3)]

I feel like that has a much better UX and is more intuitive than currying.

Here is one other example from a stackoverflow answer about the benefits of currying:

incElems = map (+1)
--non-curried equivalent: incElems = (\elems -> map (\i -> (+) 1 i) elems)

I think that comment is rather disingenuous: operator sections do not require currying and this assumes the language puts absolutely no effort in partial application syntax. With my proposed syntax you would write it like this:

incElems = map (_ + 1) _

Or if you also add operator sections, which are now less necessary, you could write it with only one underscore:

incElems = map (+ 1) _

One question that I have skipped over is how the scope of the underscores is determined. You could say the scope ends at the first set of enclosing parentheses, then map (_ + 1) [1,2,3] would work, but map ((_) + 1) [1,2,3] would not work. I think that would be enough to completely subsume currying for partial application, but you could imagine more complicated scenarios where you might want the scope to be larger than just the enclosing parentheses. For that you could introduce a second set of parentheses, perhaps (( and )) which don’t capture the scope of the underscores, so this would be valid: map ( (( _ )) + 1) [1,2,3]. Then this is much more powerful than currying.

Polymorphic functions

Currying allows you to “request” additional arguments from polymorphic functions.

An example that I have some experience with is foldr. You can add an accumulator argument to the fold because of currying. For example sum can be implemented as follows:

sum :: [Integer] -> Integer
sum xs = foldr (\y k acc -> k (y + acc)) (\acc -> acc) xs

The type of foldr is (a -> b -> b) -> b -> [a] -> b so you wouldn’t expect to see three arguments as I did in the first argument of foldr (and indeed I think it is not intuitive unless you have much experience with it). However, you can instantiate the type variable b to a function type c -> d, or in the case above Integer -> Integer.

Without currying we could write a separate function foldrAcc :: ((a, b -> c, b) -> c), b -> c, [a], b) -> c. And we could write the accumulating sum function as follows:

sum xs = foldrAcc (\(y, k, acc) -> k (y + acc), \acc -> acc, xs, 0)

In fact, I only notice now that I forgot to pass the initial value 0 in the example above; did you catch that mistake? Also note that in this example I am using normal Haskell syntax, but the language could be change so that you wouldn’t have to write all the tuples explicitly.

This has the advantage of making it clear that something more complicated than a “simple” foldr is happening.

Edit: How could I forget the f <$> x <*> y <*> z pattern. I think that is only really possible with currying. Perhaps using the !-notation from Idris is a solution for this. Then you could write: f !x !y !z which is even nicer than the Haskell version and again this is explicit special notation which doesn’t confuse beginners with complicated type signatures (although it is something you need to learn like do-notation).

Was/is learning about currying easy or difficult?
  • very easy
  • easy
  • difficult
  • very difficult
  • I don’t remember

0 voters

5 Likes

Anecdote: I write Scala day-to-day, and I find this style vastly more annoying to read and maintain. I’d much rather just write a function with the arguments in the order I want them than rely on fragile positional parsing. This is absolutely necessary in Scala since every dang thing is a method, so you must write xs.map(_.doThing), but Haskell doesn’t have this issue. If I want a function which calls doThing on every element of any Functor at all, that’s just fmap doThing forever and ever. If I want that in Scala, I must write

val mapDoThing = xs => xs.map(_.doThing)

which ends up having an unfortunate type if it’s expected to work with anything that implements .map.

8 Likes

Partial application works fine with most functions with the occasional flip, though I admit I sometimes wanted something more flexible (in a less horrific package than this).

I would like to see how the proposal interacts with other parts of the language. Even tame synctactic extensions like operator sections have small warts ((-1) vs (subtract 1)).

4 Likes

For me, learning to understand currying was difficult but worth it.

For that reason, I guess I would hold off on confronting new learners with it, but I would want to give them the opportunity to learn it eventually.

P.S. Like many things in Haskell, the autodidact will find hundreds of code golf examples in the wild that make currying seem more difficult than it really is.

9 Likes

Thanks for the responses!

@jhenahan that is some useful insight from Scala. I do think that even without currying we can keep writing maps of single argument functions over lists without extra syntactical overhead. So, your fmap doThing can still be written that way. It is really only when multiple arguments are involved that you have to do something to indicate which argument you want to “leave open”.

An advantage of avoiding currying is that you can map multi-argument functions over lists of tuples. And it allows you to compose multi-argument functions with functions that return tuples. Now in Haskell you have to write things like this example from this Haskell wiki page:

uncurry (++) . partition p

Without automatic currying you would not have to write uncurry (but you do need to add an underscore for the missing argument of partition):

(++) . (partition p _)

Here’s an old discussion where I already mentioned that currying does make some code uglier. The code in question was:

func c z = z^2 + c

diverge maxIters f x0 = (any (\x -> magnitude x > 4) . take maxIters) (iterate f x0)

On reddit, /u/BayesMind proposed (I think mostly as a joke):

func = (. (^ 2)) . (+)

diverge = (. iterate) . (.) . (any ((> 4) . magnitude) .) . take

Without currying you can write:

func = _ + _ ^ 2

diverge = any (magnitude _ > 4) (( take _ (( iterate _ _ )) ))
-- which expands to: 
-- \x y z -> any (\w -> magnitude w > 4) (take x (iterate y z))

-- alternatively
diverge = (any (magnitude _ > 4) _) . take . (_, iterate _ _)

@f-a this post is mostly intended as a thought experiment around the question: what if Haskell was not curried? Now I think currying is so deeply rooted in many API’s and code bases that I don’t think there is a realistic scenario where it is changed in the near future. I also don’t think it would be feasible to use it as an extension that is only enabled in certain modules. I don’t think there is an easy way to combine curried and uncurried code. But yeah the (-1) problem would also easily be solved by this, just write: (_-1).

@chreekat what do you mean precisely with “worth it”? I guess it is hard to predict what Haskell would look like without currying, but are you thinking of any specific examples which would be more difficult without currying? I do agree that I am probably biased due to the many small code golf examples online. I don’t have much experience with real production code bases.

3 Likes

Parens are already used for operator precedence, so it’d be confusing to also reuse them for scoping of anonymous functions. Consider, for example:

(_ + 2) * 3

I think the natural reading would be that this means \x -> (x + 2) * 3 but, if I understand the proposal correctly, it would actually mean (\x -> x + 2) * 3

8 Likes

Yes, this is an important issue. I also propose the alternative double parenthesis syntax:

((_ + 2)) * 3

which lets the hole pass through. Alternatively you could swap it around and have the normal parens pass the hole through and have the double parens “catch” the holes, but I think it is more likely that you want to catch the holes than not, so I chose the shortest syntax for the most common operation. Originally I was thinking about using a whole other bracket notation, but [] and {} are already used in Haskell and <> will cause too many ambiguities. Maybe || is still open, so you could write this to capture holes:

|(_ + 2) * 3|

Edit: Perhaps parens with a “lambda” would be a better notation for capturing the holes:

(\ (_ + 2) * 3 )

A whole other alternative is to capture immediately after the function call, then you don’t need to think about special parens at all, but it is a lot more restrictive. But do note that with currying you would have to write (+ 2) . (* 3) for the same expression anyway, so it is not worse per se.

1 Like

That ship has sailed long ago; currying of function arguments is one of the most helpful, basic features of Haskell.

6 Likes

The Haskell ship has sailed, yes, but new ships are still being built and I like to learn from the experience we’ve collected so far.

That said, I haven’t seen a clear example where using currying was undoubtedly the best way to write a certain piece of code. I think it is less helpful (or at least that the alternatives are better) than most people seem to think.

I guess the next step for me is to try to rewrite some existing code to see what it would look like without currying.

3 Likes

A lot of things don’t work great with currying — anything the relies on a lot of fliping is usually better off as a lambda or a standalone declaration. Those cases might indeed benefit from some sort of placeholder-shorthand in a different language. (Haskell already has a large enough surface syntax!)

But lots of things do work great with currying. :slight_smile: The containers package is a shining example of a library designed for use with currying. Since the container argument is usually the last argument, it’s really easy to make inline compositions or succinct definitions e.g. foo e = Set.unions . filter (Set.member e)

But now I’m just adding to the global supply of code golf examples! :smiley:

3 Likes
foo e = Set.unions . filter (Set.member e)

I’m not quite sure I understand. How does this work great with currying? Unless I’m mistaken, isn’t it just partial application?

1 Like

With currying you automatically get a form of partial application. Otherwise you need to invent other syntax, e.g.:

foo(e,_) = Set.unions . filter(Set.member(e,_),_)
3 Likes

Yeah, I definitely prefer this (which is similar to agda’s mixfix syntax) to traditional currying, in all honesty.

1 Like

FWIW, Lean has both currying and placeholder syntax: Functions - Lean Manual

You could give that a try to see how it feels. I heard that they were considering to abandon currying altogether in favor of keyword arguments and this new syntax.

2 Likes

f : (a, b) -> c and f : a -> b -> c only the same in lazy languages, right? At least, I know that currying gives worse performance so that’s somewhat different.

I have been thinking about making Haskell easier to learn. One big hurdle seems to be currying.

FWIW I don’t think it is hard to learn.

  • Manuel Chakravarty: Similarly, I teach Haskell to students every semester. I get problem reports. I rarely get a question about type errors, I never get a question about laziness. Maybe something about type classes. I get questions all about Cabal gives me these strange errors, I can’t install this library, it doesn’t work on Windows. We had a conference on practitioners, and again we hear the same questions. The language is perfectly fine, it’s just the infrastructure around it.

(from here)

I feel like that has a much better UX and is more intuitive than currying.

Is it semantically the same?

2 Likes

For me, one of the most beautiful moments of learning (I didn’t know about it before learning it in Haskell) Haskell was figuring out what currying was. It didn’t take long and it was definitely worth it.

3 Likes

Since I’m currently a bit interested in how compilers work: Can you just say that one way of writing things gives worse performance than another? Or is it actually related to the compiler and how good it is at optimization?

1 Like

I think you might find these papers interesting:

I would conclude GHC is pretty good at optimizing currying away in practice, but all program analyses are fundamentally limited (see Rice’s theorem). And reliability is also important. Optimizations obscure inefficient code. You’d have to look at Core or STG to see if the compiler actually manages to optimize everything away and small changes in your program might cause large changes in the optimizations.

4 Likes

The first time I heard that some people could have hard times understanding currying was in a context of the Roc language – that it doesn’t have currying exactly for this reason.
It was surprising and even a bit confusing. I am considering myself a slow learner (and very not mathematical person) and I had no whatsoever problems learning what currying was (years ago when I did Java and knew nothing about Haskell or FP).

2 Likes

Interesting discussion.

Since I created CodeWorld and made the choice to remove currying from its educational dialect many years ago, one might assume I’m on board with currying being bad for beginners. In truth, I think the answer is “it depends.”

The important thing to keep in mind is that currying is overloading. Maybe not in the strict technical sense, but to a typical programmer (particularly if they aren’t experienced in Haskell), there’s a big difference between the types a -> b -> c, a function with two parameters, and a -> (b -> c), a function with one parameter that returns a function. That you can switch seamlessly between them is a source of confusion in almost exactly the same way that pervasive use of type classes is a source of confusion: it’s hard to work out in which way something is being used in a given situation, and the generality takes away many helpful cues that guide interpretation.

That said, overloading a really danged useful, and even enlightening when it brings out patterns and regularity that were harder to recognize before. That’s true with currying as well as type classes and other forms of overloading. Partially, the point of learning Haskell is to encounter new ideas and kinds of abstraction, and this is part of that experience. So removing currying can be useful for beginners if they need the help; but it can also deprive them of part of the learning experience that is the whole point of their learning Haskell in the first place. The right choice definitely depends on what someone’s learning goals are.

8 Likes