[Haskell] Implicit parameters redux

Ben Rudiak-Gould benrg at dark.darkweb.com
Wed Jan 28 23:12:12 EST 2004


Here's an example of implicit return values from a project I worked on
recently, followed by an example of the thread idea.

Suppose I've written a decompiler -- it takes binary object code and
produces an abstract syntax tree representing source code. A very
simplified version of the output type might be

  type StatementBlock = [Expr]

  data Expr
    = Arith Expr String Expr    -- e.g. Arith (Literal 5) "+" (Literal 8)
    | Assign Expr Expr
    | ProcCall Expr [Expr]
    | Literal Int
    | TheProcedure Int
    | ...

The Int field of "TheProcedure" is the raw address of the beginning of the
procedure in the file. So code like "foo(1,2,3)" will be represented as
something like "ProcCall (TheProcedure 51034) [Literal 1, ...]"

I want to produce source code as output, so I write a function with type
StatementBlock -> String:

  showStatement exprs = concat [ showExpr x ++ ";\n" | x <- exprs ]

  showExpr (Arith left op right) =
    showExpr left ++ op ++ showExpr right

  showExpr (ProcCall proc args) =
    showExpr proc ++ "(" ++ join "," (map showExpr args) ++ ")"

  showExpr (Literal n) = show n

  showExpr (TheProcedure addr) = "procedure" ++ show addr

The last line leaves something to be desired -- it chooses very unfriendly
names for the procedures. As a matter of fact I have various heuristics
for choosing more helpful names for procedures, and I also allow the user
to supply a configuration file with names. So I encapsulate all this in a
table of names and pass it to showExpr, and I get code like

  showExpr names (TheProcedure addr) =
    lookupProcedureName names addr

But the rest of showExpr and showStatement get needlessly ugly, because
they have to pass a "names" parameter to every recursive call. This is
where ordinary implicit parameters become useful. I replace "names" with
"?names" and it gets passed around for me.

Now the decompiler may produce code which refers to procedures I don't
"know about" (haven't decompiled). I can indicate this in the source code
I produce:

  showExpr names (TheProcedure addr) =
    case lookupProcedureName names addr of
      Just name -> name
      Nothing   -> "(*** unknown procedure ***)"

But I'd like to also collect these for later use -- say, to list as part
of a summary printed at the end.

There are various ways I could do this, but let me concentrate on this
one:

  showExpr (TheProcedure addr) =
    case lookupProcedureName ?names addr of
      Just name -> (name, [])
      Nothing   -> ("(*** unknown procedure ***)", [addr])

  showExpr (Literal n) = (show n, [])

  showExpr (Arith left op right) =
    (x++op++y, p++q)
    where (x,p) = showExpr left
          (y,q) = showExpr right

This strategy lets us collect a list of unrecognized addresses at the top,
as a second return value. But the code gets very ugly -- much worse than
the implicit parameter case, in fact, since Haskell doesn't have a
convenient notation for multiple return values. I could hide this with a
modified ++ operator:

  (x,p) <++> (y,q) = (x++y, p++q)

Then I could write:

  showExpr (Arith left op right) =
    showExpr left <++> (op, []) <++> showExpr right

Better, but not great.

Implicit return values provide a much cleaner solution: just write

  showExpr (TheProcedure addr) =
    case lookupProcedureName ?names addr of
      Just name -> name
      Nothing   -> ("(*** unknown procedure ***)", %unknown = [addr])

and you're done. None of the other cases need to be modified (unless they
also produce unknown addresses).

This need to produce some form of statistical information "on the side"
comes up fairly frequently in my code.


Now state threading. Consider the following silly imperative program in C:

  char name[100];
  int i;

  puts("What is your name?");
  gets(name);
  for (i = 0; name[i]; ++i)
    name[i] = toupper(name[i]);
  puts("Your name in uppercase is:");
  puts(name);

There's all kinds of mutation and I/O going on here. In imperative
programming there's a "current state", which includes things like the
screen and the keyboard buffer and the array "name", and you give a list
of commands which do something to that state, in a particular order.

A pure functional language doesn't have any implicit state. You can model
state by passing around a state variable, e.g.

  main :: World -> World

  main theWorld =
    let theWorld'         = puts theWorld "What is your name?"
        (name,theWorld'') = gets theWorld'
        ...
    in theWorld'''''''

This isn't very convenient. Worse, theWorld can't really represent the
world, because you can reuse old values, and that isn't possible in
reality.

We can solve both problems by abstracting away from the world-passing. We
think of puts and gets and similar functions as world-transformers, and we
allow the programmer to attach the output of one to the input of another.
This is the IO monad model. There's no way to duplicate the world because
there's no transformer with one input and two outputs. (Well, there is,
actually: unsafeInterleaveIO.)

The program looks like this at a high level, with the world-threading
shown:

         +------+   +------+   +----------+   +------+   +------+
         |      |   |      |   |          |   |      |   |      |
 World >-| puts |->-| gets |->-| for-loop |->-| puts |->-| puts |->
         |      |   |      |   |          |   |      |   |      |
         +------+   +------+   +----------+   +------+   +------+

Though this closely reflects the structure of the C program, it's really
more ordering than we need. The first and fourth stages don't use the
array, and the third stage doesn't do any I/O. We really have two
completely independent state threads, with only some stages using each
one:

                           ,------>-------.
       +------+   +------+ | +----------+ | +------+   +------+
 I/O >-|      |->-|      |-' |          | `-|      |->-|      |->
       | puts |   | gets |   | for-loop |   | puts |   | puts |
       |      | ,-|      |->-|          |-. |      | ,-|      |->
       +------+ | +------+   +----------+ | +------+ | +------+
   Array >------'                         `---->-----'

Now we can see that there's no particular ordering required between the
for-loop and the "following" puts step: they could happen in the other
order, or even in parallel (in different OS threads, or on different
processors in an SMP machine).

This program is interactive, so it's important that input and output be
synchronized. But if it were a batch filter, we could separate I/O into I
and O as well, and the program would become even less linear. Another
example: in a web server, each connection could be represented by a
different state thread, and the server could spawn separate OS threads for
each connection without duplicating the whole world.

The thread model I'm proposing sets up this fancier plumbing
automatically, from a notation almost the same as "do".

Haskell already has a notion of independent state threads, but it's not
general enough for the above example. You can't put the array in an ST
thread, because there's no way to write "gets" such that it can both read
from an IO handle and write to an ST array. So my proposal has benefits
other than better concurrency: it makes it easier to use mutable state
without monolithic monads like IO gobbling everything up.


-- Ben



More information about the Haskell mailing list