OO structure rebuilt in Haskell - worth the troubel to understand?

I’m going through Get Programming with Haskell by W. Kurt. (Sorry, not an open-source book.) and I find chapter 10 a hard nut to crack. It talks about “how to build OOP [object-oriented programming] by using closures, lambdas, and first-class functions”.

This is certainly a beginner’s question. To describe better what’s troubling me here I show the “OO” structure set up in the book, a system for cups of liquid and the volumes of these cups. (I adapt the code to the metric system, so that I don’t copy the book’s code too bluntly.)

First we define a “constructor” helper function for cup “objects”. These objects contain exactly one property, the cup size in millilitres:

cup ml = \msg -> msg ml

Then we “instantiate” a specific cup:

mediumCup = cup 250

And finally we define a “getter” helper function to read out the size of a specify cup:

getSize aCup = aCup (\ml -> ml)

When I now type in the expression

getSize mediumCup

I get in GHCi to my amazement the size of the cup back:

Main> 250

It dawns upon me that the magic happens because the “objects” are functions themselves! But then I look at the inferred types of the helper functions. HLS tells me:

cup :: t1 -> (t1 -> t2) -> t2
cup ml = \msg -> msg ml

mediumCup :: (Integer -> t2) -> t2
mediumCup = cup 250

getSize :: ((p -> p) -> t) -> t
getSize aCup = aCup (\ml -> ml)

Here I am surprised that getSize has the type ((p -> p) -> t) and not ((p -> t) -> t). Because,if I understand it correctly, the argument aCup is of the type of mediumCup. i.e. a function (Integer -> t2) -> t2.

And this is only the beginning of what’s clouding my head. The whole structure is pretty mind blowing. Is it worth it to get to the bottom of this “OO” chapter?

1 Like

…in the expression getSize mediumCup, not in the definition of getSize itself.

To get what you were expecting, a type declaration is needed:

{-# LANGUAGE RankNTypes #-}

newtype Cup = MkCup (forall r . (Integer -> r) -> r)

cup :: Integer -> Cup
cup ml = MkCup (\msg -> msg ml)

mediumCup :: Cup
mediumCup = cup 250

getSize :: Cup -> Integer
getSize (MkCup aCup) = aCup (\ml -> ml)

…not quite as tidy as the original definitions, but the type signatures are more informative.

You’re not so much “building OOP” as “emulating OOP by using closures, lambdas, and first-class functions” e.g. there’s no OOP-style inheritance or subtyping being used here.

3 Likes

Some possibly-helpful reading from The Wiki: are closures a poor man’s objects? Are objects a poor man’s closures? Both? Neither?
http://wiki.c2.com/?ClosuresAndObjectsAreEquivalent

1 Like

Is it worth it to get to the bottom of this “OO” chapter?

I’m sure the ideas in this chapter are good practice for thinking about functions and using lambda expressions, but I don’t think they’re a vital stepping stone that you need to learn about right now. So if you’re stuck, maybe move on to the next chapter and come back when you’ve had more practice?

But the “magic” in these functions isn’t really that mind-blowing once you understand it. The main problem is that the author wrote the functions in an unusual way, to encourage you to think of them as if they were OO constructors or getters. If you rewrite them in a more normal way, they seem much less mysterious.

I can write out simpler versions of the functions if you want, but maybe it would be more rewarding for you to look at them yourself? So instead I have some suggested exercises to try:

  1. Look at the type signatures for cup and mediumCup, and count how many parameters each has. Notice how the definitions of cup and mediumCup use fewer parameters than this: they use partial application.

  2. Try rewriting the definitions of cup and mediumCup, adding in the missing parameters on the left hand side, and not using lambda expressions.

  3. Try rewriting the definition of mediumCup so that it doesn’t use cup.

  4. Look at the expression (\ml -> ml) in the definition of getSize. If you think of it as an independent function, f = (\ml -> ml), what does it do? In fact, this function is in the standard library – do you know its name?

I hope this helps.

3 Likes

Thanks @atravers, @jackdk and @gcox . Very kind of you to take the time telling a newbie about the background here. :smiley:

This is enlightening: Cup should be a custom type!

(The author of Get Programming with Haskell does not use custom types in this demonstartion, because he hasn’t introduced them yet. – Next chapter! :smiley_cat: : )

Makes total sense.

I’m taking up the challenge:

Written out, the definitions are:

cup ml msg = msg ml

mediumCup msg = cup 250 msg
mediumCup' msg = msg 250

This is truly illuminating! A specific cup like mediumCup is a function with a specific, fixed argument - but the function itself is not “defined” yet, right?

It is the identiy function id. So getSize can be written as:

getSize' aCup = aCup (id)

Wow, this means that only at the very end, getSize “defines” the msg function for mediumCup, right? To an old imperative guy like me this feels like putting the cart before the horse

Thanks a lot for these exercises – they made the concept quite a bit clearer.

1 Like

Yes, I agree both times! And of course all your answers are correct too.

To an old imperative guy like me this feels like putting the cart before the horse

Yes, it seems a little unusual to me too. A function normally defines a computation and has parameters you can use to pass in the data to be computed. But as you say, mediumCup is backwards: all it really does is hold a value, and you have to pass in a function to use that value with.

I can’t think of an example of this idiom being widely used in Haskell, although maybe that’s just lack of experience and there are some uses I don’t know about.

On a side point, I’m guessing that the OO the book is talking about is specifically Smalltalk-style OO. I don’t know much about Smalltalk, but apparently it does everything by passing messages to objects, which fits with the way the functions in the book work, and msg being used as a variable name seems like a hint too.

2 Likes

…well there is one particular use case, but it’s usually “syntactically disguised”. Since I’ve already given away part of one chapter from the textbook: make a note of the following pseudo-code:

mystery :: this -> (is -> that) -> that
mystery w y = ...

and just keep working through the textbook (so no more “previews” ;-)

1 Like

Mmmh, you lost me here, but I don’t think that matters. Sooo much to learn!

I think this requires a bit of a perspective shift : what’s going on is that by applying a function input to another value (in this case id) you’re really specializing it. Under the hood, the type inference algorithm tries to come up with the “most general type” that satisfies all the use sites of a given value.

Consider the following :

λ> :t \x -> x
\x -> x :: a -> a

λ> :t \x -> x 1
\x -> x 1 :: Num t1 => (t1 -> a) -> a

λ> :t \x -> x 1 "hello"
\x -> x 1 "hello" :: Num t1 => (t1 -> String -> a) -> a

The identity function is really the most general 1-parameter function you can have; its parameter can be anything (a function, an object …), as long as it’s returned unchanged. The next declarations are more restricted : the parameter can only be a function of a certain type, since it is applied to given arguments in the body of the lambda. HTH!

Not exactly in Haskell, but in lambda calculus (that I’ll write in Haskell):

pair x y = \f -> f x y

myPair = pair "This" "That"

firstOfPair p = p const       -- Prelude.const :: a -> b -> a

firstOfPair myPair            -- ===> "This"

Now we don’t do that in Haskell; we represent a pair as ( "This", "That" ); and use a selector function to extract the components. (Or better use pattern matching, or a named type/data constructor, with names for the components.)

That’s for efficiency reasons: piling up all those lambda suspensions then cascading argument-to-function-apply-to-argument-… is fandango on stack; and for readability reasons: extending the pair idea to express datatypes with multiple constructors gives eye-watering lambda suspensions.

1 Like