
Hi All, Is there a program for expanding 'do' notation? I am trying to understand why the following code (from the Fannkuch entry) doesn't hold onto the list 'p' causing a space leak. main = do n <- getArgs >>= return . read . head let p = permutations [1..n] mapM_ (putStrLn . concatMap show) $ take 30 p putStr $ "Pfannkuchen(" ++ show n ++ ") = " putStrLn . show $ foldl' (flip (max . steps 0)) 0 p If I add a line which refers to 'p' at the end, there is a space leak. print (head p) Thanks. Cheers, David ---------without extra line ./Latest 9 +RTS -K256m -c -sstderr 123456789 ... Pfannkuchen(9) = 30 244,215,012 bytes allocated in the heap 613,972 bytes copied during GC 3,920 bytes maximum residency (1 sample(s)) 931 collections in generation 0 ( 0.06s) 1 collections in generation 1 ( 0.00s) 1 Mb total memory in use INIT time 0.00s ( 0.01s elapsed) MUT time 2.20s ( 2.72s elapsed) GC time 0.06s ( 0.13s elapsed) EXIT time 0.00s ( 0.00s elapsed) Total time 2.26s ( 2.86s elapsed) %GC time 2.7% (4.5% elapsed) Alloc rate 111,006,823 bytes per MUT second Productivity 97.3% of total user, 76.9% of total elapsed --------with extra line ./Latest 9 +RTS -K256m -c -sstderr ... Pfannkuchen(9) = 30 [1,2,3,4,5,6,7,8,9] 244,216,248 bytes allocated in the heap 19,804,816 bytes copied during GC 10,586,416 bytes maximum residency (6 sample(s)) 931 collections in generation 0 ( 0.96s) 6 collections in generation 1 ( 1.28s) 18 Mb total memory in use INIT time 0.00s ( 0.01s elapsed) MUT time 2.30s ( 2.72s elapsed) GC time 2.24s ( 3.15s elapsed) EXIT time 0.00s ( 0.00s elapsed) Total time 4.54s ( 5.88s elapsed) %GC time 49.3% (53.6% elapsed) Alloc rate 106,180,977 bytes per MUT second Productivity 50.7% of total user, 39.1% of total elapsed -------------------------------- David F. Place mailto:d@vidplace.com

David F. Place wrote:
Hi All,
Is there a program for expanding 'do' notation? I am trying to understand why the following code (from the Fannkuch entry) doesn't hold onto the list 'p' causing a space leak.
You can desugar (i.e. expand) the do notation relatively easily, but that won't tell you what optimisations are being performed (e.g. code rearrangements) if any. Of course the compiler can't perform IO actions in the wrong order - but it can in principle generate code which generates a value from p early on, and then p can be garbage collected. I have no idea whether that's what's happening here, though. -- Robin

David F. Place wrote:
Hi All,
Is there a program for expanding 'do' notation? I am trying to understand why the following code (from the Fannkuch entry) doesn't hold onto the list 'p' causing a space leak.
You mean "doesn't hold onto the list 'p' preventing a space leak. ^^^^^^^^^^
main = do n <- getArgs >>= return . read . head let p = permutations [1..n] mapM_ (putStrLn . concatMap show) $ take 30 p putStr $ "Pfannkuchen(" ++ show n ++ ") = " putStrLn . show $ foldl' (flip (max . steps 0)) 0 p
If I add a line which refers to 'p' at the end, there is a space leak.
print (head p)
Thanks.
Cheers, David
This is all about lazy evaluation. The "mapM_ (putStrLn . concatMap show) $ take 30 p" command generates the first 30 permutations and prints them, and takes no more space than that. The 31st permutation is never created. The "foldl' (...) 0 p" expression is the left-fold so it requires the elements of "p" one by one. "foldl'" send them with the running maximum , which starts at "0", into "(flip (max . steps 0))" which returns the updated running maximum. Since it is the primed version "foldl'" instead of "foldl", it does this with strict evaluation : the new maxiumum is computed before taking the next value of "p". Since the old values of "p" are never re-used, they are discarded by the garbage collector. So the "foldl'" runs in constant space, which is what it is designed for. When you put "print (head p)" at then end, it keeps a reference to the whole list "p" which is your space leak. If you want to store the head of p, this *should* work:
main = do n <- getArgs >>= return . read . head let p = permutations [1..n] headOfP <- return (head p) mapM_ (putStrLn . concatMap show) $ take 30 p putStr $ "Pfannkuchen(" ++ show n ++ ") = " putStrLn . show $ foldl' (flip (max . steps 0)) 0 p print headOfP
The "headOfP" is computed as an IO action at that point in the program, so "headOfP" does not hold a reference to "p" as a whole. -- Chris

On Jan 7, 2006, at 11:56 AM, Chris Kuklewicz wrote:
This is all about lazy evaluation.
Actually, I understand about lazy evaluation. What I don't understand is the extent of variable bindings. If I desugar the code this far: main = do n <- getArgs >>= return . read . head main' n main' n = let p = permutations [1..n] in do mapM_ (putStrLn . concatMap show) $ take 30 p putStr $ "Pfannkuchen(" ++ show n ++ ") = " putStrLn . show $ foldl' (flip (max . steps 0)) 0 p 'p' is a variable bound by a normal 'let.' Why isn't 'p' kept around until the whole 'in' expression is evaluated? If it were, then I assume the GC would be obliged to copy everything it pointed to. In the original version, the author called 'permutations' twice and didn't create a variable binding. Cheers, David -------------------------------- David F. Place mailto:d@vidplace.com

David F. Place wrote:
On Jan 7, 2006, at 11:56 AM, Chris Kuklewicz wrote:
This is all about lazy evaluation.
Ah. Sorry then.
Actually, I understand about lazy evaluation. What I don't understand is the extent of variable bindings.
The binding has a lexical extent. The "p" in the source file means "permutation [1..n] for the whole block, as you show correctly below:
If I desugar the code this far:
main = do n <- getArgs >>= return . read . head main' n
main' n = let p = permutations [1..n] in do mapM_ (putStrLn . concatMap show) $ take 30 p putStr $ "Pfannkuchen(" ++ show n ++ ") = " putStrLn . show $ foldl' (flip (max . steps 0)) 0 p
'p' is a variable bound by a normal 'let.' Why isn't 'p' kept around until the whole 'in' expression is evaluated?
"p" is lexically available to refer to by you source code for the whole block. After it is compiled and run, the dynamic garbage collection whittles away the *elements* of p that can no longer (a dynamic concept) be accessed. At the same time, the *elements* of p that are demanded are computed lazily.
If it were, then I assume the GC would be obliged to copy everything it pointed to. In the original version, the author called 'permutations' twice and didn't create a variable binding.
Cheers, David
the mind-bending-thing I had to learn with Haskell is that the "let p =" creates source code *shorthand*. In C++,Scheme,Lisp,Java,Python it allocates a particular part of memory that is called "p" and refers to a list. This could then be altered with "p=q" or "(set! p q)" depending on the language. In Haskell, a binding "let p =" is not a variable in memory anywhere like "int p" or "int **p" that can be mutated. The Haskell binding is just syntactic shorthand to make your code easier for you to read.
Spoon boy: Do not try and bend the spoon. That's impossible. Instead... only try to realize the truth. Neo: What truth? Spoon boy: There is no spoon. Neo: There is no spoon? Spoon boy: Then you'll see, that it is not the spoon that bends, it is only yourself.
There is no allocated "p" that points to the head of the permutations at run time and lives the duration of the lexical block. Also, note that if write makeP n = let p = permutations [1..10] in return p Then the permutations clearly exist after the lexical scope of the "let binding". Allocation is done when lazy things get evaluated and de-allocation is done when the garbage collector can discard unreachable elements. -- Chris

Hi Chris, Yes, this is just what I need to understand. Could you point me to a description of this? I couldn't find any discussion of it in the reference document. Thanks. Cheers, David On Jan 7, 2006, at 12:25 PM, Chris Kuklewicz wrote:
the mind-bending-thing I had to learn with Haskell is that the "let p =" creates source code *shorthand*.
-------------------------------- David F. Place mailto:d@vidplace.com

Mmmm...now I had to go look it up. David F. Place wrote:
Hi Chris,
Yes, this is just what I need to understand. Could you point me to a description of this? I couldn't find any discussion of it in the reference document. Thanks.
Cheers, David
On Jan 7, 2006, at 12:25 PM, Chris Kuklewicz wrote:
the mind-bending-thing I had to learn with Haskell is that the "let p =" creates source code *shorthand*.
This is the first time I have tried to explain this. So it will not help much... The mantra is : Bindings are not variables The best, official thing to read is section 3.12 of the Haskell98 Report: http://www.haskell.org/onlinereport/exps.html#sect3.12 It shows that "let p = foo q = bar in ..." is translated to "let (~p,~q) = (foo,bar) in ..." which is translated to "case (foo,bar) of ~(~p, ~q) -> ..." Assuming it does not refer to iteself, otherwise it becomes "let (~p,~q) = fix (\ ~(~p,~q) -> (foo,bar) ) in ... " which is translated to "case fix (\ ~(~p,~q) -> (foo,bar) ) of ~(~p, ~q) -> ..." At which point you are in section "3.13 Case Expressions" So "let p = permutation [1..n]" merely pattern matches the bound name "p" to the value that "permutations [1..n]" lazily evaluates to. In Scheme/Lisp the let would allocate a specific cell "p" that would point to the strictly evaluated result of "permutations [1..n]". This Haskell pattern binding is the key to being referentially transparent. It means there is no difference between "p" and "permutations [1..n]". Allocating a memory cell for "p" would be an observable difference, thus Haskell does no allocation. This also means you can do this: let a = 1 b = 2 c = 3 d = a+b+c in a*b*c*d without it having to allocate all those variables, because they are shorthand, NOT VARIABLES. All bindings are constant, so the compiler can substitute / inline them and never specifically allocate intermediate stoage, thus "a,b,c,d" are not allocated. This lets you break up a big function into many small expressions with sensible names, and perhaps reuse the pieces. Thus "map/foldl/filter/..." -- Chris

On Jan 7, 2006, at 2:23 PM, Chris Kuklewicz wrote:
The mantra is : Bindings are not variables
The best, official thing to read is section 3.12 of the Haskell98 Report:
Yes, I had already looked there, but didn't achieve enlightenment. Thanks for your efforts in describing it. I'll work on understanding it. My mind is definitely stuck in a lisp-y world view. I wonder if there is a more lambda calculus-y way of describing this? I have a vague memory that this can all be translated into combinators that don't involve variables at all. -------------------------------- David F. Place mailto:d@vidplace.com

Hello David, Saturday, January 07, 2006, 8:37:01 PM, you wrote:
the mind-bending-thing I had to learn with Haskell is that the "let p =" creates source code *shorthand*. DFP> Yes, this is just what I need to understand. Could you point me to a DFP> description of this? I couldn't find any discussion of it in the DFP> reference document. Thanks.
i attached here two letters from july's dicussion on topic "Confused about Cyclic struture". hope this will help Daniel, i also included you in crossposting because these letters can also help you understand how "run-time compilation" works. basically it's a very simple thing: when we can compute at compile time value of some computation, many compilers will do it and substitute expression with its final value. the same can be done at the run-time - as soon as we can compute value of some expression used in program or at least simplify it using our knowing of part of arguments, this can be used to reduce number of computations which program need to perform. say, n <- readIO print (factorial n) print (factorial n) here, "factorial n" can be computed just one time. it's obvious. in this case n <- readIO flip mapM [1..100] $ \x -> print (x^n) it's not so obvious that when program read value of `n`, it can substitute instead of `x^n` the concrete, faster algorithm, say 'x*x' for n=2. Haskell's ideology of "graph reductions" makes such "run-time optimizations" automatically. it it the thing that called "run-time compilation" on those wiki page. in KMP algorithm we compile string searched to algorithm that will do the search of this concrete string. another examples from my own practice is compilation of strings representing regular expressions to functions which tests compliance with these regexprs, and compiling list of sorting criterions to compare function (you can find last example at the end of RunTimeCompilation hawiki page) -- Best regards, Bulat mailto:bulatz@HotPOP.com

Thanks Bulat and Chris for helping me to understand this. I just found a perfect description in Rabhi and Lapalme's book _Algorithms: a Functional Programming Approach_ , Chapter 3 "The efficiency of functional programs. On Jan 7, 2006, at 5:56 PM, Bulat Ziganshin wrote:
Hello David,
Saturday, January 07, 2006, 8:37:01 PM, you wrote:
the mind-bending-thing I had to learn with Haskell is that the "let p =" creates source code *shorthand*. DFP> Yes, this is just what I need to understand. Could you point me to a DFP> description of this? I couldn't find any discussion of it in the DFP> reference document. Thanks.
i attached here two letters from july's dicussion on topic "Confused about Cyclic struture". hope this will help
-------------------------------- David F. Place mailto:d@vidplace.com

Am Samstag, 7. Januar 2006 23:56 schrieben Sie:
Daniel, i also included you in crossposting because these letters can also help you understand how "run-time compilation" works. basically it's a very simple thing: when we can compute at compile time value of some computation, many compilers will do it and substitute expression with its final value.
Yes, I thought they did. It's a good and clever thing, but calling that RunTimeCompilation would be a misnomer, wouldn't it? That's rather CompileTimeEvaluation, isn't it?
the same can be done at the run-time - as soon as we can compute value of some expression used in program or at least simplify it using our knowing of part of arguments, this can be used to reduce number of computations which program need to perform. say,
n <- readIO print (factorial n) print (factorial n)
here, "factorial n" can be computed just one time. it's obvious. in this case
n <- readIO flip mapM [1..100] $ \x -> print (x^n)
it's not so obvious that when program read value of `n`, it can substitute instead of `x^n` the concrete, faster algorithm, say 'x*x' for n=2. Haskell's ideology of "graph reductions" makes such "run-time optimizations" automatically. it it the thing that called "run-time compilation" on those wiki page.
Cool. So let's see if I got it. If I have n <- readIO ... mapM_ (func n) list ... in my programme, the runtime system will/might build object code for func n that is then used instead of using the general code for func and supplying both arguments to that? That'd be wow, triple wow! And run-time compilation is a fitting name for that.
in KMP algorithm we compile string searched to algorithm that will do the search of this concrete string. another examples from my own practice is compilation of strings representing regular expressions to functions which tests compliance with these regexprs, and compiling list of sorting criterions to compare function (you can find last example at the end of RunTimeCompilation hawiki page)
Thanks. Unless I'm grossly mistaken, that made things much clearer. Would somebody add an explanation along these lines to the HaWiki-page (I'm pretty sure, I'm not the only one who didn't understand the wiki-page)? Cheers, Daniel

Daniel Fischer wrote:
Cool. So let's see if I got it. If I have
n <- readIO ... mapM_ (func n) list ...
in my programme, the runtime system will/might build object code for func n that is then used instead of using the general code for func and supplying both arguments to that?
That'd be wow, triple wow! And run-time compilation is a fitting name for that.
Well, it's possible to do that. But I don't know of any Haskell implementation that does. Sure, you might get a little bit of that if func is defined suitably, like func 0 = foo func 1 = bar func n = baz Implementations that have the "full laziness" property will handle one argument at a time to a function, and may do some work with just one argument to func. But it's nothing like having real run-time code generation. -- Lennart

Hello Lennart, Sunday, January 08, 2006, 5:45:16 PM, you wrote:
Cool. So let's see if I got it. If I have
n <- readIO ... mapM_ (func n) list ...
in my programme, the runtime system will/might build object code for
not "object code" itslef. haskell program in compiled form is a large tree which nodes contain object code. run-time compilation can substitute instead of node which computes "func n" the node which will compute concrete "func 2" value. it is the partial case of "calculation" of lazy program by substitution evaluation results instead of function calls. the key may be just what haskell functions are curreied, so you can see fucntion "f a b" as function with two arguments returning Int, or as function with one argument returning "Int->Int". for example regexpr <- getStrLn filtered <- filterM (match regexpr) lines with definition match "*" = const True match regexp = \str -> ... when your input is "*" it will compute {match "*"} as "const True" and pass this argument to the filterM call (to be exact, it will pass unevaluated thunk {match "*"}, which will be evaluated to "const True" on first use)
func n that is then used instead of using the general code for func and supplying both arguments to that?
yes. i don't know how to guarantee it. i just define my time-critical functions as having one arguments. you can see an example on those hawiki page, another example is my regexpr code: data RegExpr = RE_End | RE_Anything | RE_FromEnd RegExpr | RE_AnyChar RegExpr | RE_Char Char RegExpr | RE_FullRE Regex is_wildcard s = s `contains_one_of` "?*[" translate_RE re = "^"++ (replaceAll "*" ".*" .replaceAll "?" "." .replaceAll "$" "\\$" .replaceAll "[[[" "[^" .replaceAll "^" "\\^" .replaceAll "[^" "[[[" .replaceAll "+" "\\+" .replaceAll "." "\\.") re ++"$" compile_RE s = case s of "" -> RE_End "*" -> RE_Anything '*':cs -> if ('*' `elem` cs) || ('[' `elem` cs) then RE_FullRE (mkRegex$ translate_RE$ s) else RE_FromEnd (compile_RE$ reverse$ s) '[':cs -> RE_FullRE (mkRegex$ translate_RE$ s) '?':cs -> RE_AnyChar (compile_RE cs) c :cs -> RE_Char c (compile_RE cs) match_RE re s = case re of RE_End -> null s RE_Anything -> True RE_FullRE r -> isJust (matchRegex r s) RE_FromEnd r -> match_RE r (reverse s) RE_AnyChar r -> case s of "" -> False _:xs -> match_RE r xs RE_Char c r -> case s of "" -> False x:xs -> x==c && match_RE r xs match re {-s-} = match_RE (compile_RE re) {-s-} third example is the functions used in my program to combine tests for many regexprs. this also work in "run-time compilation" manner -- |Map on functions instead of its' arguments! map_functions [] x = [] map_functions (f:fs) x = f x : map_functions fs x all_functions [] = const True all_functions [f] = f all_functions fs = and . map_functions fs any_function [] = const False any_function [f] = f any_function fs = or . map_functions fs
That'd be wow, triple wow! And run-time compilation is a fitting name for that.
more or less :) LA> Well, it's possible to do that. But I don't know of any Haskell LA> implementation that does. Sure, you might get a little bit of LA> that if func is defined suitably, like LA> func 0 = foo LA> func 1 = bar LA> func n = baz LA> Implementations that have the "full laziness" property will handle LA> one argument at a time to a function, and may do some work with just LA> one argument to func. But it's nothing like having real run-time code LA> generation. of course, it's just graph reduction. and by explicitly moving last argument to the right part of function definition i help compiler to properly optimize such code -- Best regards, Bulat mailto:bulatz@HotPOP.com

Am Sonntag, 8. Januar 2006 15:45 schrieben Sie:
Daniel Fischer wrote:
Cool. So let's see if I got it. If I have
n <- readIO ... mapM_ (func n) list ...
in my programme, the runtime system will/might build object code for func n that is then used instead of using the general code for func and supplying both arguments to that?
That'd be wow, triple wow! And run-time compilation is a fitting name for that.
Well, it's possible to do that. But I don't know of any Haskell implementation that does. Sure, you might get a little bit of that if func is defined suitably, like func 0 = foo func 1 = bar func n = baz Implementations that have the "full laziness" property will handle one argument at a time to a function, and may do some work with just one argument to func. But it's nothing like having real run-time code generation.
-- Lennart
So back to square one. What then _is_ run-time compilation? Bulat said that in n <- readIO flip mapM [1 .. 100] $ \x -> print (x^n) the programme could insert (if, e.g. the value read is 2) the concrete faster algorithm for x^n. Isn't that some sort of run-time code generation? And a) how far might one expect that sort of thing done, b) how could one cajole the system to do that. Last, reverting to the search/replace example, if I have the general algorithm and also declare the function work :: String -> String work = searchReplace "pattern" "substitution", the compiler would produce specialised object code for that, or wouldn't it? Cheers, Daniel

Daniel Fischer wrote:
So back to square one. What then _is_ run-time compilation?
In the virtual machine community, run-time compilation refers to the translation of program code at run-time, for example the compilation of Java byte code to machine code in a JIT (just-in-time) compiler. Other uses include binary dynamic translators (e.g. for running IA-32 binaries on Alpha processors), binary dynamic optimizers or security monitors for binary programs. Actually, I work on dynamic analysis and transformation of functional languages at the moment and was quite surprised how this term is used in the Haskell Wiki. I would rather call it pre-computing or something (but maybe I misunderstood the RunTimeCompilation page on my first reading).
Bulat said that in
n <- readIO flip mapM [1 .. 100] $ \x -> print (x^n)
the programme could insert (if, e.g. the value read is 2) the concrete faster algorithm for x^n. Isn't that some sort of run-time code generation? And a) how far might one expect that sort of thing done,
In a prototype implementation (or rather a proof-of-concept) I have done exactly that: compile the code of a lambda-expression at the time the closure is constructed and inline the values of all enclosing lexical variables. Of course, an optimizer is needed which uses the additional information about data values, for example by constant-folding, performing strength-reduction, etc. I have only done very primitive optimizations so far. The biggest problem is probably to limit code generation to the cases where a performance gain is expected.
b) how could one cajole the system to do that.
There are two options I can see: - Operate on an intermediate representation of the program and interpret it, or - compile the program to machine code. The former method would probably loose most of the performance expected from specialization, and the latter is difficult to integrate into existing systems (the run-time system and especially the garbage collector will need to know about dynamically generated code and how to properly handle them - you don't want to throw code away to which a pointer still exists on the run-time stack, for example :-)
Last, reverting to the search/replace example, if I have the general algorithm and also declare the function
work :: String -> String work = searchReplace "pattern" "substitution",
the compiler would produce specialised object code for that, or wouldn't it?
Yes, this is just a more complicated example of the code above, which could specialize x^n. The compiler would have to know how to work with strings, of course. If you're interested in that kind of stuff, you might want to read in the direction of "virtual machines", "jit compilation", "partial evaluation" and "meta programming". Cheers, Martin

David F. Place wrote:
main' n = let p = permutations [1..n] in do mapM_ (putStrLn . concatMap show) $ take 30 p putStr $ "Pfannkuchen(" ++ show n ++ ") = " putStrLn . show $ foldl' (flip (max . steps 0)) 0 p
In the original version, the author called 'permutations' twice and didn't create a variable binding.
As a side note, I expected GHC to do common subexpression elimination and evaluate permutations [1..n] only once, caching the 30 results that are used twice. I didn't try to find out whether it actually did though. Bertram

On 1/7/06, Chris Kuklewicz
When you put "print (head p)" at then end, it keeps a reference to the whole list "p" which is your space leak. If you want to store the head of p, this *should* work:
main = do n <- getArgs >>= return . read . head let p = permutations [1..n] headOfP <- return (head p) mapM_ (putStrLn . concatMap show) $ take 30 p putStr $ "Pfannkuchen(" ++ show n ++ ") = " putStrLn . show $ foldl' (flip (max . steps 0)) 0 p print headOfP
The "headOfP" is computed as an IO action at that point in the program, so "headOfP" does not hold a reference to "p" as a whole.
Without having tried this I'd say that you should use Control.Excection.evaluate instead of 'return'. Or you could use 'seq'. I suspect that otherwise the 'head p' will not be evaluated until the last line and you will have the same problem as before. Cheers, /Josef

Josef Svenningsson wrote:
On 1/7/06, *Chris Kuklewicz*
mailto:haskell@list.mightyreason.com> wrote: When you put "print (head p)" at then end, it keeps a reference to the whole list "p" which is your space leak. If you want to store the head of p, this *should* work:
> main = do n <- getArgs >>= return . read . head > let p = permutations [1..n] > headOfP <- return (head p) > mapM_ (putStrLn . concatMap show) $ take 30 p > putStr $ "Pfannkuchen(" ++ show n ++ ") = " > putStrLn . show $ foldl' (flip (max . steps 0)) 0 p > print headOfP
The "headOfP" is computed as an IO action at that point in the program, so "headOfP" does not hold a reference to "p" as a whole.
Without having tried this I'd say that you should use Control.Excection.evaluate instead of 'return'. Or you could use 'seq'. I suspect that otherwise the 'head p' will not be evaluated until the last line and you will have the same problem as before.
Cheers,
/Josef
Thanks Josef. headOfP <- return $! (head p) headOfP <- (head p) `seq` return (head p) headOfP <- return (Control.Excection.evaluate (head p)) Are strict enough to do the trick.
participants (10)
-
Bertram Felgenhauer
-
Bulat Ziganshin
-
Chris Kuklewicz
-
Daniel Fischer
-
David F. Place
-
David F.Place
-
Josef Svenningsson
-
Lennart Augustsson
-
Martin Grabmueller
-
Robin Green