Dialogues vs continuations (and algebraic effects) to implement I/O

Here’s how you can implement the same thing using algebraic effects:

3 Likes

…and from 2008:

https://web.archive.org/web/20090215004126/http://lukepalmer.wordpress.com/2008/03/29/io-monad-the-continuation-presentation

So are there any substantial differences?

Indeed, even in 2008 people already knew about this. See also the famous Data Types a la Carte paper. I just mean to say that the dialogue approach is outdated. There is a better way to model I/O now, namely using algebraic effects! I see no reason to keep linking the dialogue approach except as a historical curiosity.

2 Likes

Indeed, even in 2008 people already knew about this.

o_0 …algebraic effects using continuations? Those have been around since (at least!) the early 1990s; for example, Nigel Perry’s result continuations in his Ph.D thesis. But Haskell continued to use its dialogue-based continuations until 1996.

So if algebraic effects are so amazing…why didn’t they replace dialogues back then?


I see no reason to keep linking the dialogue approach except as a historical curiosity.

…and for a time it was standard Haskell. So what are the chances of any effect system ever being part of a future Haskell standard?

Phil Wadler beat Nigel Perry to the punch with his Comprehending Monads paper in 1990, and showed together with @simonpj in 1992 that you could also use them for I/O. I don’t know why it took another 4 more years to work out the details, but I’d imagine people back then were already convinced monads would be the way forward for Haskell’s I/O.

I personally think it is quite a shame that representing effectful programs using continuations was so quickly discarded, because I think continuations (a.k.a. callbacks) are much easier to explain to beginners than the current State# RealWorld business. I imagine performance was the biggest consideration; using a lambda for every continuation is not free. Though, I think it would not be impossible to optimize the overhead away. We now have join points which can do this locally within a function, so we’d only need some kind of annotation to propagate this information across function boundaries (such annotations could even be reserved for these built-in I/O operations, so users never even have to think about them).

However, just representing a program as one big pure algebraic data type does not buy you much. If you cut your program up into many small pure continuation “slices” which are separated by opaque I/O operations, many properties which you might want to prove will inevitably cross over an opaque I/O operation which prevents further reasoning. That is, unless you have laws which tell you how those I/O operations behave, that is exactly what algebraic operations (Plotkin and Power, 2003) add to the continuation approach.

2 Likes

I think continuations (a.k.a. callbacks) are much easier to explain than the current State# RealWorld business.


I imagine performance was the biggest consideration; using a lambda for every continuation is not free.

There’s another problem - reuse of exposed continuations:

(\ k -> k 1 + k 2)

…much like reuse of exposed State# RealWorld values, both of which are solved by using an abstract data type…which then leaves the choice of interface that abstract type should use:


[…] you have laws which tell you how those I/O operations behave […]

So would this entail:

  • adding new laws for each FFI I/O call?
  • then checking what other I/O laws are affected?

That looks rather like O(n 2) complexity to me - alright for a few primitive or FFI I/O operations; not so wonderful if you’re using a lot of them. And remember - side effects are arbitrary, so there can be an arbitrary number of them…


Plotkin and Power, 2003

That’s not how the continuations in these systems work. The user never gets their hands on a continuation. Instead, the user only provides a continuation to these primitive I/O operations.

The operations are implemented either as built-in functions in the language, or as data constructors. I’d prefer the latter for transparency reasons, but the former might be more efficient.

That’s not how the continuations in these systems work. The user never gets their hands on a continuation.

I presume you’re referring to this paragraph from Imperative Functional Programming:

Well, this is more-or-less what the monadic interface supports:

unitIO :: a -> IO a
bindIO :: IO a -> (a -> IO b) -> IO b

In both cases, the user provides a continuation that accepts the value produced by an I/O action, rather than a rest-of-the-program continuation. So this would seem to be yet another reason in favour of having an abstract monadic I/O type…

(…hmm; these different varieties of continuations could be confusing for those new to FP - anyone for a tutorial? ;-)


Instead, the user only provides a continuation to these primitive I/O operations.

This can still cause problems:

That problem can be mitigated by providing a monadic interface on top of the continuation-based I/O primitives, like I did in that free-io example:

The benefit of using continuations under the hood would be that we can easily show to beginners simple examples, like how getChar >>= putChar evaluates to something like \k -> GetChar (\c -> PutChar c k), which only uses an ADT and lambdas. I know those two things are also something people need to learn, but I’d expect it to be much easier to grasp than to just say people should not look at the internals of IO, or worse, try to explain whatever State# RealWorld -> (# Char, State# RealWorld #) means.

[…] we can easily show to beginners simple examples […]

  • …and they’re experienced users of functional programming! There’s also this:

  • …yes, that John Backus!

Alright, that’s the experienced users - what about potential new users? Here’s some observations about programmers in other languages who are new to Haskell:

As for “completely-new” programmers to Haskell:

Beginners don’t need more simple examples - they need a simple model of I/O in Haskell, one that doesn’t leave them feeling some thing like:

…and end up being more “random programmers who knows Haskell, or at least some Haskell”.


I know those two things are also something people need to learn […]

Only for the likes of Haskell, Agda and Idris:

I don’t understand why beginners need a “simple model of I/O in Haskell”. Do Python beginners need a “simple model of I/O in Python”?

2 Likes

I don’t understand why beginners need a “simple model of I/O in Haskell”. Do Python beginners need a “simple model of I/O in Python”?

(…nice attitude - the beginners will be impressed!)

I believe this is from some educators who built their own object-oriented programming language specifically for teaching purposes:

Moreover:

…and for GHC:



…to paraphrase a line from a sci-fi classic:

There is no State# RealWorld.

Hence jaror’s lament about trying to explain whatever State# RealWorld -> (# Char, State# RealWorld #) means, to beginners.

But I still don’t understand why one should try to explain that to beginners. IO, as implemented in a Haskell compiler, could well be a completely abstract type, in the sense that the compiler doesn’t even try to give it an implementation in Haskell, like GHC does with State# RealWorld.

3 Likes

I think many programmers learn things by looking at their definitions. When looking at I/O some will inevitably end up here:

https://hackage.haskell.org/package/base-4.20.0.1/docs/Prelude.html#t:IO

And then click “source” which takes them here:

https://hackage.haskell.org/package/ghc-prim-0.11.0/docs/src/GHC.Types.html#IO

And leave much more confused then when they started.


More importantly, I think this “tree of operations with continuations” model could be a good on-ramp to explaining I/O without having to mention monads. For example, inspired by the Hedy lessons, you could start by allowing only printing lines like this:

data Action = Print String

lesson0 = [Print "Hello, World!"]

lesson1 = [ Print "Hi there, programmer!"
          , Print "Welcome to Haskell!"
          ]

Then you could introduce ask and echo.

data Action = Print String | Ask String | Echo String

lesson2 = [ Print "Hello!"
          , Ask "What is your name?"
          , Echo "hello " -- the answer will be appended here
          ]

Of course just echoing the last answer is very limited. We might want to refer to these answers multiple times or only later on in the program. A list is no longer sufficient. Instead we can use continuations:

data Action = Print String Action | Ask String (String -> Action) | Halt

lesson3 = 
  Ask "What is your name?" $ \name ->
  Print ("Hello " ++ name) $
  Ask "How old are you?" $ \age ->
  Print (name ++ " is " ++ age ++ "years old.") $
  Halt

Etc.

I absolutely agree with you. Never have I ever showed any beginner the definition of IO. It’s useless and defeats the point of teaching to beginners.

4 Likes

Never have I ever showed any beginner the definition of IO a.

You don’t have to:

Sure, but if they did the same in Python they’d end up at the C source of the interpreter, and I don’t think anyone in the Python world wonders how to explain that to beginners. In both cases I think we should explain how I/O “works” by referring to simple examples of it (“synthetically”) rather than by breaking it into simpler pieces (“analytically”). I understand that the synthetic approach is dissatisfying to many Haskellers (some of whom delight in the false notion that “Haskell is just lambda calculus”) but nonetheless I think it would be the better approach for helping beginners understand I/O.

I absolutely agree that the free monad approach has pedagogic value, but I don’t see it as a beginner topic.

I’m not an educator nor a beginner, so my thoughts my be completely off base. I have been a beginner though and when I was I wish someone had said “Don’t bother trying to ‘understand’ IO and monads. Just use do notation and get comfortable with using them."

1 Like

[…] if they did the same in Python they’d end up at the C source […]

If the FFI was sufficiently-capable, that could also be achieved in standard Haskell:

data IO a
foreign import ccall "primUnitIO" unitIO :: a -> IO a
foreign import ccall "primBindIO" bindIO :: IO a -> (a -> IO b) -> IO b

instance Monad IO where
    return = unitIO
    (>>=)  = bindIO

instance Functor IO where
    fmap f m = m `bindIO` \ x -> unitIO (f x)

I/O tutorials begone! (and there were celebrations throughout the realm of Haskell :-)