Difference between revisions of "Nested lambdas"

From HaskellWiki
Jump to navigation Jump to search
(with kind permission of Bas van Dijk)
 
m (Looks retarded otherwise.)
 
(One intermediate revision by one other user not shown)
Line 32: Line 32:
 
</haskell>
 
</haskell>
   
<code>
 
$ ghc -ddump-simpl Difference.hs
 
   
  +
$ ghc -ddump-simpl Difference.hs
==================== Tidy Core ====================
 
  +
Difference.bar :: forall b_a5j a_a5k.
 
  +
==================== Tidy Core ====================
(GHC.Num.Num b_a5j) =>
 
  +
Difference.bar :: forall b_a5j a_a5k.
a_a5k -> b_a5j -> b_a5j
 
  +
(GHC.Num.Num b_a5j) =>
[GlobalId]
 
  +
a_a5k -> b_a5j -> b_a5j
[Arity 1
 
  +
[GlobalId]
NoCafRefs]
 
  +
[Arity 1
Difference.bar =
 
  +
NoCafRefs]
\ (@ b_a9E) (@ a_a9F) ($dNum_a9L :: GHC.Num.Num b_a9E) ->
 
  +
Difference.bar =
let {
 
lit_a9J :: b_a9E
+
\ (@ b_a9E) (@ a_a9F) ($dNum_a9L :: GHC.Num.Num b_a9E) ->
[]
+
let {
lit_a9J =
+
lit_a9J :: b_a9E
case $dNum_a9L
+
[]
of tpl_B1
+
lit_a9J =
{ GHC.Num.:DNum tpl1_B2
+
case $dNum_a9L
tpl2_B3
+
of tpl_B1
tpl3_B4
+
{ GHC.Num.:DNum tpl1_B2
tpl4_B5
+
tpl2_B3
tpl5_B6
+
tpl3_B4
tpl6_B7
+
tpl4_B5
tpl7_B8
+
tpl5_B6
tpl8_B9
+
tpl6_B7
tpl9_Ba ->
+
tpl7_B8
  +
tpl8_B9
tpl9_Ba (GHC.Num.S# 1)
 
}
+
tpl9_Ba ->
  +
tpl9_Ba (GHC.Num.S# 1)
} in
 
\ (ds_dad :: a_a9F) (n_a79 :: b_a9E) ->
+
}
case $dNum_a9L
+
} in
  +
\ (ds_dad :: a_a9F) (n_a79 :: b_a9E) ->
of tpl_B1
 
{ GHC.Num.:DNum tpl1_B2
+
case $dNum_a9L
tpl2_B3
+
of tpl_B1
tpl3_B4
+
{ GHC.Num.:DNum tpl1_B2
tpl4_B5
+
tpl2_B3
tpl5_B6
+
tpl3_B4
tpl6_B7
+
tpl4_B5
tpl7_B8
+
tpl5_B6
tpl8_B9
+
tpl6_B7
tpl9_Ba ->
+
tpl7_B8
tpl3_B4 lit_a9J n_a79
+
tpl8_B9
}
+
tpl9_Ba ->
  +
tpl3_B4 lit_a9J n_a79
  +
}
  +
  +
Difference.foo :: forall b_a5m a_a5n.
  +
(GHC.Num.Num b_a5m) =>
  +
a_a5n -> b_a5m -> b_a5m
  +
[GlobalId]
  +
[Arity 1
  +
NoCafRefs]
  +
Difference.foo =
  +
\ (@ b_aa0) (@ a_aa1) ($dNum_aa7 :: GHC.Num.Num b_aa0) ->
  +
let {
  +
lit_aa5 :: b_aa0
  +
[]
  +
lit_aa5 =
  +
case $dNum_aa7
  +
of tpl_B1
  +
{ GHC.Num.:DNum tpl1_B2
  +
tpl2_B3
  +
tpl3_B4
  +
tpl4_B5
  +
tpl5_B6
  +
tpl6_B7
  +
tpl7_B8
  +
tpl8_B9
  +
tpl9_Ba ->
  +
tpl9_Ba (GHC.Num.S# 1)
  +
}
  +
} in
  +
\ (ds_dae :: a_aa1) (n_a5q :: b_aa0) ->
  +
case $dNum_aa7
  +
of tpl_B1
  +
{ GHC.Num.:DNum tpl1_B2
  +
tpl2_B3
  +
tpl3_B4
  +
tpl4_B5
  +
tpl5_B6
  +
tpl6_B7
  +
tpl7_B8
  +
tpl8_B9
  +
tpl9_Ba ->
  +
tpl3_B4 lit_aa5 n_a5q
  +
}
   
Difference.foo :: forall b_a5m a_a5n.
 
(GHC.Num.Num b_a5m) =>
 
a_a5n -> b_a5m -> b_a5m
 
[GlobalId]
 
[Arity 1
 
NoCafRefs]
 
Difference.foo =
 
\ (@ b_aa0) (@ a_aa1) ($dNum_aa7 :: GHC.Num.Num b_aa0) ->
 
let {
 
lit_aa5 :: b_aa0
 
[]
 
lit_aa5 =
 
case $dNum_aa7
 
of tpl_B1
 
{ GHC.Num.:DNum tpl1_B2
 
tpl2_B3
 
tpl3_B4
 
tpl4_B5
 
tpl5_B6
 
tpl6_B7
 
tpl7_B8
 
tpl8_B9
 
tpl9_Ba ->
 
tpl9_Ba (GHC.Num.S# 1)
 
}
 
} in
 
\ (ds_dae :: a_aa1) (n_a5q :: b_aa0) ->
 
case $dNum_aa7
 
of tpl_B1
 
{ GHC.Num.:DNum tpl1_B2
 
tpl2_B3
 
tpl3_B4
 
tpl4_B5
 
tpl5_B6
 
tpl6_B7
 
tpl7_B8
 
tpl8_B9
 
tpl9_Ba ->
 
tpl3_B4 lit_aa5 n_a5q
 
}
 
</code>
 
   
   

Latest revision as of 10:59, 10 April 2009

Problem

Question:

The following two lines seem to behave identical. Is there a substantive difference between them?

\_ n -> 1 + n
\_ -> (\n -> 1 + n)


Answer:

Actually the first line is syntactic sugar for the second one.


How GHC handles it

You can check this out your self by compiling this program and looking at the generated core program like this:

module Difference where

foo :: Num b => a -> b -> b
foo = \_ n -> 1 + n

bar :: Num b => a -> b -> b
bar = \_ -> (\n -> 1 + n)


 $ ghc -ddump-simpl Difference.hs
  ==================== Tidy Core ====================
 Difference.bar :: forall b_a5j a_a5k.
                   (GHC.Num.Num b_a5j) =>
                   a_a5k -> b_a5j -> b_a5j
 [GlobalId]
 [Arity 1
  NoCafRefs]
 Difference.bar =
   \ (@ b_a9E) (@ a_a9F) ($dNum_a9L :: GHC.Num.Num b_a9E) ->
     let {
       lit_a9J :: b_a9E
       []
       lit_a9J =
         case $dNum_a9L
         of tpl_B1
         { GHC.Num.:DNum tpl1_B2
                         tpl2_B3
                         tpl3_B4
                         tpl4_B5
                         tpl5_B6
                         tpl6_B7
                         tpl7_B8
                         tpl8_B9
                         tpl9_Ba ->
         tpl9_Ba (GHC.Num.S# 1)
         }
     } in
       \ (ds_dad :: a_a9F) (n_a79 :: b_a9E) ->
         case $dNum_a9L
         of tpl_B1
         { GHC.Num.:DNum tpl1_B2
                         tpl2_B3
                         tpl3_B4
                         tpl4_B5
                         tpl5_B6
                         tpl6_B7
                         tpl7_B8
                         tpl8_B9
                         tpl9_Ba ->
         tpl3_B4 lit_a9J n_a79
         }
 Difference.foo :: forall b_a5m a_a5n.
                   (GHC.Num.Num b_a5m) =>
                   a_a5n -> b_a5m -> b_a5m
 [GlobalId]
 [Arity 1
  NoCafRefs]
 Difference.foo =
   \ (@ b_aa0) (@ a_aa1) ($dNum_aa7 :: GHC.Num.Num b_aa0) ->
     let {
       lit_aa5 :: b_aa0
       []
       lit_aa5 =
         case $dNum_aa7
         of tpl_B1
         { GHC.Num.:DNum tpl1_B2
                         tpl2_B3
                         tpl3_B4
                         tpl4_B5
                         tpl5_B6
                         tpl6_B7
                         tpl7_B8
                         tpl8_B9
                         tpl9_Ba ->
         tpl9_Ba (GHC.Num.S# 1)
         }
     } in
       \ (ds_dae :: a_aa1) (n_a5q :: b_aa0) ->
         case $dNum_aa7
         of tpl_B1
         { GHC.Num.:DNum tpl1_B2
                         tpl2_B3
                         tpl3_B4
                         tpl4_B5
                         tpl5_B6
                         tpl6_B7
                         tpl7_B8
                         tpl8_B9
                         tpl9_Ba ->
         tpl3_B4 lit_aa5 n_a5q
         }


This looks very scary so let me try to explain:

The Core language [2] (formally called System FC [3]) is actually very similar to Haskell because both are based on the lambda calculus. One imported difference is that in the Core language a function can take a type as an argument and it can be applied to a type. This is needed to implement polymorphic functions. foo and bar for example are polymorphic in all their arguments. This means that when you want to apply foo or bar to some arguments x and y you should first apply it to the types of x and y.

Another major difference with Haskell is the way overloaded function are implemented. Note that in both foo and bar you use an overloaded literal 1 (1 is translated to fromInteger 1) and overloaded function +. The following quote from [3] explains briefly how overloaded functions are translated:

"Generally, type classes are translated into SystemF [17] by (1) turning each class into a record type, called a dictionary, containing the class methods, (2) converting each instance into a dictionary value, and (3) passing such dictionaries to whichever function mentions a class in its signature."

Now with this knowledge lets look at the Core output for bar:

You see that bar is a lambda abstraction that takes the two types that we talked about: @ b_a9E @ a_a9F (the @ indicates that it are types) these correspond to the types a and b in our original Haskell program. The lambda abstraction also takes a third argument which is the dictionary we talked about: $dNum_a9L :: GHC.Num.Num b_a9E (the $ indicates that it's a dictionary). Note that the dictionary type constructor is applied to the type b_a9E.

On to the body of the lambda abstraction. First you see that a variable lit_a9J :: b_a9E is defined. This is going to be the overloaded literal 1. As I said when you write 1 in Haskell it is translated to fromInteger 1 where fromInteger is an overloaded function (a method in the Num type class [4]) and 1 is a concrete Integer. Note that bar has received the dictionary for Num that contains all the methods of Num like +, - and fromInteger. The only thing we need to do is extract the right method (fromInteger) from the dictionary and apply it to a concrete Integer. This is what happens in the case expression: we extract the method tpl9_Ba and apply it to GHC.Num.S# 1.

Now that our literal 1 is defined, a lambda abstraction is created that takes two arguments ds_dad :: a_a9F and n_a79 :: b_a9E which correspond to the arguments in our original Haskell program. Now the overloaded function + should be applied to the defined literal lit_a9J and the resulting function should be applied to the argument n_a79. Because + is overloaded the same thing happens as we saw with the overloaded literal 1.

Now that you can read GHC Core programs :-) you can observe that foo and bar are the same.


References

  1. http://www.haskell.org/ghc/dist/current/docs/users_guide/options-debugging.html
  2. http://hackage.haskell.org/trac/ghc/wiki/Commentary/Compiler/CoreSynType
  3. http://research.microsoft.com/%7Esimonpj/papers/ext%2Df/fc-tldi.pdf
  4. http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v%3AfromInteger