Additional thunk for function
Victor Nazarov
asviraspossible at gmail.com
Fri Sep 21 07:04:54 EDT 2007
What is the purpose for GHC to allocate a thunk for some functions?
Why Test.map is not a function, but updatable thunk, which should
become equal to the function just after the first call? Here is the
details:
> % ghc -c test.hs -ddump-stg
>
> ==================== STG syntax: ====================
> Test.map =
> \u []
> let {
> map1_sdR =
> \r [f_sdN ds_sdI]
> case ds_sdI of wild_sdU {
> [] -> [] [];
> : x_sdM xs_sdQ ->
> let { sat_sdT = \u [] map1_sdR f_sdN xs_sdQ; } in
> let { sat_sdP = \u [] f_sdN x_sdM; } in : [sat_sdP sat_sdT];
> };
> } in map1_sdR;
> SRT(Test.map): []
>
>
> % cat test.hs
> module Test where
>
> map f [] = []
> map f (x:xs) = f x : Test.map f xs
--
Thanks in advance
Victor
More information about the Glasgow-haskell-users
mailing list