How to translate Haskell to other languages?

Hello, I was thinking about translating Haskell to other languages, python being the main one at the moment. Here is my attempt at manually encoding Haskell in Python: \begin{code} import types class thunk: '''Thunks allow us to delay a computation and they also store their value inside themselves once they have been accessed.''' def __init__(self, v): self.v = v def value(self): '''Force the thunk to be calculated by referencing it.''' while self.isReducible(): self.reduce() return self.v def reduce(self): '''Reduces the thunk, by either calling the represented function or reducing the layers of thunk.''' if (type(self.v) == types.FunctionType): self.v = self.v() else: self.v = self.v.value() return self.v def isReducible(self): '''Returns True when the thunk is still callable.''' return isinstance(self.v, thunk) or \ type(self.v) == types.FunctionType class nil: '''Empty list element''' def __init__(self): pass class cons: '''Non-empty lists''' def __init__(self, head, tail): self.head = head self.tail = tail '''Unpack the cons cell''' def uncons(self): return self.head, self.tail def htail(t): '''This function works like Haskell's tail function.''' l = t.value() x, xs = l.uncons() return xs def plus(t1, t2): '''Adds numbers''' i1 = t1.value() i2 = t2.value() return thunk(i1+i2) def zipWith(f, t1, t2): '''This is like Haskell's zipWith function.''' l1 = t1.value() if isinstance(l1, nil): return thunk(nil()) l2 = t2.value() if isinstance(l2, nil): return thunk(nil()) x, xs = l1.uncons() y, ys = l2.uncons() zw = thunk(lambda: zipWith(f, xs, ys)) fxy = thunk(lambda: f(x,y)) return thunk(cons(fxy, zw)) def fibs(): '''This is the classic fibs: fibs = 1 : 1 : zipWith (+) fibs (tail fibs)''' f1 = thunk(1) f2 = thunk(1) fn = thunk(fibs) rest = thunk(lambda: zipWith(plus, fn, htail(fn))) restlist = thunk(cons(f2, rest)) fiblist = thunk(cons(f1, restlist)) return fiblist def hmap(f, t): '''map _ [] = [] map f (x:xs) = f x : map f xs''' l = t.value() if isinstance(l, nil): return thunk(nil()) x, xs = l.uncons() fx = thunk(lambda: f(x)) mapfxs = thunk(lambda: hmap(f, xs)) return thunk(cons(fx, mapfxs)) def show(t): '''show :: a -> String''' v = t.value() return thunk(str(v)) def printList(t): '''This just gives us a way to debug lists.''' v = t.value() print "[", while True: h,t = v.uncons() print "%s" % h.value(), if isinstance(t.value(), nil): break else: print ", ", v = t.value() print "]" def take(tn, tl): '''take n _ | n <= 0 = [] take _ [] = [] take n (x:xs) = x : take (n-1) xs''' n = tn.value() if n <= 0: return thunk(nil()) l = tl.value() if isinstance(l, nil): return thunk(nil()) x,xs = l.uncons() nminusone = thunk(lambda: plus(tn, thunk(-1))) takerec = thunk(lambda: take(nminusone, xs)) return thunk(cons(x, takerec)) \end{code} You can try this out in python with: tenfibs = take(thunk(10), fibs()) printList(tenfibs) This will print the first 10 fibs. Questions: I think the examples above are correctly lazy. Have I missed something? I noticed my thunks can get wrapped in each other, is this to be expected, or am I doing it wrong? Is there an easier encoding using generators? When I started I was using generators instead of thunk, but I found it was complicating my design so I removed it. And yet, since generators are python's version of thunks, it seems like there should be a more natural encoding there. I'm not explicitly using a graph reduction algorithm to reach WHNF, does this mean my translation is wrong? Are there some well known test cases I should try? Anyone know of a paper that discusses making this translation? I am trying to avoid writing an interpreter in Python for Haskell. My goal is to translate Haskell functions into the equivalent Python. I'm also hoping to avoid needing a G-machine. Thanks! Jason

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? 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. :-) 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. def nil() : return (lambda n: lambda c: n) def cons() : return (lambda x: lambda xs: lambda n: lambda c: c(x)(xs)) 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))) 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]
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". 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. 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! NOTE 2: "i" could be replaced with anything above --- it is never actually inspected. For the sake of interest, there is also a "dual" transformation which gives a program that enforces strict evaluation, no matter how it is evaluated. Let's call it S for "Strict". S[e0 e1] = \k. S[e0] (\f. S[e1] (\x. k (f x))) S[v] = \k. k v S[f] = \k. k f I believe this is commonly referred to as the CPS (continuation-passing style) transformation. 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. 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. Matthew.

On Sat, 2008-10-11 at 16:55 +0100, Matthew Naylor 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?
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. :-)
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.
def nil() : return (lambda n: lambda c: n) def cons() : return (lambda x: lambda xs: lambda n: lambda c: c(x)(xs)) 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)))
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]
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".
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.
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!
NOTE 2: "i" could be replaced with anything above --- it is never actually inspected.
For the sake of interest, there is also a "dual" transformation which gives a program that enforces strict evaluation, no matter how it is evaluated. Let's call it S for "Strict".
S[e0 e1] = \k. S[e0] (\f. S[e1] (\x. k (f x))) S[v] = \k. k v S[f] = \k. k f
I believe this is commonly referred to as the CPS (continuation-passing style) transformation.
This is indeed a CPS transform. Specifically, a call-by-value CPS transform. There is also a call-by-name one. N[e0 e1] = \k. N[e0] (\f. f N[e1] k) N[v] = v N[c] = \k. k c

On Sat, Oct 11, 2008 at 8:55 AM, Matthew Naylor < mfn-haskell-cafe@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

2008/10/11 Jason Dagit
On Sat, Oct 11, 2008 at 8:55 AM, Matthew Naylor
wrote:
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)
I think this is known as the Church encoding. The parameters n and c
describe what to do with lists that are constructed with [] and (:),
respectively.
You can do this in Haskell, as well:
newtype List a = List { unList :: forall b. b -> (a -> List a -> b) -> b }
nil :: List a
nil = List (\n c -> n)
cons :: a -> List a -> List a
cons x xs = List (\n c -> c x xs)
foldListR :: (a -> b -> b) -> b -> List a -> b
foldListR f z l = unList l z (\x xs -> f x (foldListR f z xs))
compare foldListR with foldr:
foldr f z [] = z
foldr f z (x:xs) = f x (foldr f z xs)
Essentially, it represents the data in terms of how you pattern match
on it. You can in principle pull this off for any Haskell type, but
the resulting code isn't anything you'd want to work on manually.
--
Dave Menendez

"Jason Dagit"
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?
Partial application can be done in python, though somewhat awkwardly. Take a look at functools.partial. -- Green's Law of Debate: Anything is possible if you don't know what you're talking about.

Hi Jason,
So in an automatic translation I would replace partial application with lambdas. This shouldn't be a problem right?
suppose f is a 3-argument function, and you encounter the application f x. One possible translation would be to replace f x with (\y. \z. f (x,y,z)) I don't know if this is what you mean. Anyway, the problem is that f might not be a function name; it could be the argument of a higher-order function, in which case we don't know how many lambda-bound variables to introduce. It's easiest just to define f as f() = \x. \y. \z. e rather than f (x,y,z) = e, I think.
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?
Regarding terminology: be careful not to confuse the CPS transformation with the transformation that encodes data as functions. I've made this mistake in the past. To my knowledge, the "CPS transformation" refers to the transformation that enforces strict evaluation in a program. Encoding data as functions removes data constructors and case expressions from a program (albeit using continuations). I think the latter is known by at least two names: Scott's encoding, and Berarducci and Bohm's encoding. It is not the same as the Church encoding. I first read about it in a paper by Jan Martin Jansen. Jan Martin Jansen, Pieter Koopman and Rinus Plasmeijer. Efficient Interpretation by Transforming Data Types and Patterns to Functions. Trends in Functional Programming, Volume 7, Intellect, 2007. (Googling the title should reveal a PDF.) But since then, I've noticed the transformation used (anonamously) in several old texts about compiling functional languages.
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.
Converting data to function-encoded data: this can be done with a fold, e.g. "foldr cons nil" should do the trick for lists. Converting function-encoded data back to data: it should be possible to generate a function like my "list(xs)" (which returns a Python represention of a function-encoded Haskell list xs) for any given data type. Alternatively, you could just add constructors and case expressions to the syntax I gave for "combinator programs", and deal with them explicitly in the translation.
N[e0 e1] = N[e0] (\x. N[e1]) N[v] = v (\x. x) N[f] = f
What "i" are you referring to?
Woops, "i" refers to the combinator representing the function \x. x. (I wrote NOTE 2 before realising NOTE 1!) Basically, the (\x. x) above can be replaced with any expression that terminates, but preferrably one that will be cheap to evaluate.
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.
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
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?
Generally: a reference is created for every argument in a function-call. The first time that argument is evaluated, the reference is updated to store the result of the evaluation, so that it is never performed again. More specifically: * "ref" creates a mutable reference. In ML, bindings of a let are evaluated before the body of the let. * !r gets the value at a reference r, and "r := e" updates the value at reference r. * None and Some are the ML equivalents to Nothing and Just. * e0 ; e1 evaluates e0 before e1 and then returns the value of e1.
Is that basically the same as my thunk type?
I imagine it is very similar to your thunk type, but I don't know enough Python to say for sure.
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.
There are some optimisations to the translation. For example, if a function is applied to an argument, and that argument is not referenced more than once in the body of f, then there is no need to create a reference for said argument. Matthew.
participants (6)
-
David Menendez
-
Derek Elkins
-
Jason Dagit
-
mail@justinbogner.com
-
Matthew
-
Matthew Naylor