[Haskell-cafe] How to translate Haskell to other languages?

Jason Dagit dagit at codersbase.com
Sat Oct 11 17:23:43 EDT 2008


On Sat, Oct 11, 2008 at 8:55 AM, Matthew Naylor <
mfn-haskell-cafe at cs.york.ac.uk> wrote:

> Hi Jason,
>
> I don't know Python, but let me share some thoughts that you might
> find useful.
>
> First, a few questions about your manual translations.  Are your
> functions curried?  For example, can I partially apply zipWith?  Also,
> you put a "thunk" around things like "cons(...)" --- should it not be
> the arguments to "cons" that are thunked?


I don't recall if I mentioned this in my original email.  My goal is to do
automatic translations.  So, no you can't partially apply zipWith, but then
that's because Python doesn't support partial application.  On the other
hand, you can easily use a lambda to get around this.  So in an automatic
translation I would replace partial application with lambdas.  This
shouldn't be a problem right?

My rule was to put a thunk around any "Haskell value".  So I put cons cells
in thunks and I even wrapped functions in thunks.  The exception was that
there were quite a few places where I could tell by inspection that a
particular value would already be in a thunk.  For example, since I require
in my translation that putting a value in a cons requires the value to be a
thunk then when I pull values out of a cons I already know they are thunks
so no need to rewrap them.

Now, on to an automatic translation.  As you may know already, Haskell
> programs can be transformed to "combinator programs" which are quite
> simple and easy to work with.  Here is what I mean by a "combinator
> program":
>
>  p ::= d*            (a program is a list of combinator definitions)
>  d ::= c v* = e      (combinator definition)
>  e ::= e e           (application)
>     |  v             (variable/argument)
>     |  c             (constant: integer literal, combinator name, etc.)
>
> As an example of a combinator program, here is one that reverses the
> list [0,1,2].
>
>  rev v acc     = v acc (rev2 acc)
>  rev2 acc x xs = rev xs (cons x acc)
>  cons x xs n c = c x xs
>  nil n c       = n
>
>  main          = rev (cons 0 (cons 1 (cons 2 nil))) nil
>
> This program does not type-check in Haskell!  But Python, being
> dynamically typed, doesn't suffer from this problem. :-)


I plan to exploit this in my translations as well.  I will assume type
checked Haskell programs as input to the translator.


>
>
> A translation scheme, D[], from a combinator definition to a Python
> definition might look as follows.
>
>  D[c v* = e]   =   def c() : return (lambda v1: ... lambda vn: E[e])
>  E[e0 e1]      =   E[e0] (E[e1])
>  E[v]          =   v
>  E[c]          =   c()
>
> Here is the result of (manually) applying D to the list-reversing program.
>

If nil() corresponds to [] in Haskell, then how did you arrive at this
definition?  As Derek Elkins points out your transformation is a CPS based.
So I'm going to guess that c is the continuation and n represents the nil?

>
>  def nil()  : return (lambda n: lambda c: n)


This one makes a little bit of sense to me.  I see the components of the
list, the x and xs, and you apply the continuation to them.  What's going on
with n?

  def cons() : return (lambda x: lambda xs: lambda n: lambda c: c(x)(xs))


Now, now this is a getting a bit hard to read :)

>
>  def rev2() : return (lambda acc: lambda x: lambda xs:
>                         rev()(xs)(cons()(x)(acc)))
>  def rev()  : return (lambda v: lambda acc: v(acc)(rev2()(acc)))
>

I'm glad I don't have to maintain code that looks like this :)

  def main() : return (rev() (cons()(0)(
>                                cons()(1)(
>                                  cons()(2)(
>                                    nil()))))(nil()))
>
> The result of main() is a partially-applied function, which python
> won't display.  But using the helper
>
>  def list(f) : return (f([])(lambda x: lambda xs: [x] + list(xs)))
>
> we can see the result of main():
>
>  >>> list(main())
>  [2, 1, 0]


Cool!

So, supposing I went with a translation scheme like what you gave.  I think
I would end up with deeply nested function calls, this is probably very bad
for the python run-time.  Also, how do I allow Python to then access the
Haskell values?  I guess your definition of list above is an example of
that, but I'm not sure how I'd pull that off in general.


>
> Of course, Python is a strict language, so we have lost Haskell's
> non-strictness during the translation.  However, there exists a
> transformation which, no matter how a combinator program is evaluated
> (strictly, non-strictly, or lazily), the result will be just as if it
> had been evaluated non-strictly.  Let's call it N, for "Non-strict" or
> "call-by-Name".


Interesting.


>
>
>  N[e0 e1]   =   N[e0] (\x. N[e1])
>  N[v]       =   v (\x. x)
>  N[f]       =   f
>
> I've cheekily introduced lambdas on the RHS here --- they are not
> valid combinator expressions!  But since Python supports lambdas, this
> is not a big worry.


Right, not so bad.  My translation was doing the same thing actually.  A
common thing to see in my code is, x = thunk(lambda: y).


>
> NOTE 1: We can't remove the lambdas above by introducing combinators
> because the arguments to the combinator would be evaluated and that
> would defeat the purpose of the transformation!


Okay, I get that.



>
> NOTE 2: "i" could be replaced with anything above --- it is never
> actually inspected.


What "i" are you referring to?


> Now, non-strict evaluation is all very well, but what we really want
> is lazy evaluation.  Let's take the N transformation, rename it to L
> for "Lazy", and indulge in a side-effecting reference, ML style.


Could you explain this a bit more.  I don't know ML, so the code is a bit
hard for me to read, but also I was wondering why you introduced a
side-effecting reference?  Is that basically the same as my thunk type?


>
>
>  L[e0 e1]   =   L[e0] (let r = ref None in
>                          \x. match !r with
>                                 None -> let b = L[e1] in r := Some b ; b
>                               | Some b -> b)
>  L[v]       =   v (\x. x)
>  L[f]       =   f
>
> I don't know enough to define L w.r.t Python.
>
> I haven't tried too hard to fully understand your translation, and
> likewise, you may not try to fully understand mine!  But I thought I'd
> share my view, and hope that it might be useful (and correct!) in some
> way.


Thanks!

Jason
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20081011/3f7f8686/attachment-0001.htm


More information about the Haskell-Cafe mailing list