
Hi \_ n -> 1 + n \_ -> (\n -> 1 + n) The outcome seems to be identical. is there a substantive difference between the two definitions? The second one seems to be more expressive of the currying principle. Any thoughts? Thanks, Paul

On Sep 20, 2007, at 0:03 , PR Stanley wrote:
\_ n -> 1 + n \_ -> (\n -> 1 + n) The outcome seems to be identical. is there a substantive difference between the two definitions? The second one seems to be more expressive of the currying principle. Any thoughts?
I *think* the former is internally converted to the latter; this is how currying works. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

I must confess that the use of "\_" had me a little confused at first but thinking about it I can see that it makes perfect sense to have an argument or a wildcard character for any value. Cheers, Paul
On Sep 20, 2007, at 0:03 , PR Stanley wrote:
\_ n -> 1 + n \_ -> (\n -> 1 + n) The outcome seems to be identical. is there a substantive difference between the two definitions? The second one seems to be more expressive of the currying principle. Any thoughts?
I *think* the former is internally converted to the latter; this is how currying works.
-- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

On Sep 20, 2007, at 0:16 , PR Stanley wrote:
I must confess that the use of "\_" had me a little confused at first but thinking about it I can see that it makes perfect sense to have an argument or a wildcard character for any value.
Sure. Remember, arguments are pattern matches in Haskell (the degenerate case being a variable name which is an irrefutable match resulting in a lambda binding). As such, it's useful to have a wildcard pattern which matches irrefutably without binding. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1 PR Stanley wrote:
I must confess that the use of "\_" had me a little confused at first but thinking about it I can see that it makes perfect sense to have an argument or a wildcard character for any value. Cheers, Paul
FYI If \_ -> foo confuses you, you might wish to use const foo instead. Tony Morris http://tmorris.net/ -----BEGIN PGP SIGNATURE----- Version: GnuPG v1.4.6 (GNU/Linux) Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org iD8DBQFG8fizmnpgrYe6r60RAqKBAKCKQ76HMtJ8jsgJ5nmX8ECROOcirQCfQgKS OQflRMDqHqX2TUWibG4oiB4= =L6C4 -----END PGP SIGNATURE-----

G'day all.
Quoting PR Stanley
\_ n -> 1 + n \_ -> (\n -> 1 + n) The outcome seems to be identical. is there a substantive difference between the two definitions?
Certainly, GHC compiles these to the same code. But be careful! Consider the following two defintions: test1 n _ = 1 + n test2 n = \_ -> 1 + n I don't know if it's still the case, but GHC used to compile different code for these at high optimisation levels. The first was essentially compiled to: test1 = \n _ -> 1+n And the second to: test2 = \n -> let x = n+1 in \_ -> x The difference is that test1 is faster if it's usually fully applied, test2 is fully lazy. Cheers, Andrew Bromage

test1 n _ = 1 + n test2 n = \_ -> 1 + n
I don't know if it's still the case, but GHC used to compile different code for these at high optimisation levels. The first was essentially compiled to:
test1 = \n _ -> 1+n
And the second to:
test2 = \n -> let x = n+1 in \_ -> x
The difference is that test1 is faster if it's usually fully applied, test2 is fully lazy.
Fully lazy? Can you elaborate please? Thanks, Paul

G'day all.
Quoting PR Stanley
Fully lazy? Can you elaborate please?
Sure. that code again: test1 = \n _ -> 1+n test2 = \n -> let x = n+1 in \_ -> x Suppose we have: f g x = g x + g x And we try two options: f (test1 4) 3 f (test2 4) 3 In the first case, (1+4) will be evaluated twice. In the second case, it will only be evaluated once. Cheers, Andrew Bromage

On Thu, 20 Sep 2007, PR Stanley
\_ n -> 1 + n \_ -> (\n -> 1 + n) The outcome seems to be identical. is there a substantive difference between the two definitions?
No, since you do not pattern match on the first argument. Otherwise, due to the way these definitions are translated into the core fragment of Haskell in the report, and the presence of seq, the two definitions can have observably different semantics. See "Chasing Bottoms: A Case Study in Program Verification in the Presence of Partial and Infinite Values", page 4. http://www.cs.chalmers.se/~nad/publications/danielsson-jansson-mpc2004.html -- /NAD

On 9/20/07, PR Stanley
Hi \_ n -> 1 + n \_ -> (\n -> 1 + n) The outcome seems to be identical. is there a substantive difference between the two definitions?
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. regards, Bas van Dijk [1] http://www.haskell.org/ghc/dist/current/docs/users_guide/options-debugging.h... [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%3Afrom...
participants (6)
-
ajb@spamcop.net
-
Bas van Dijk
-
Brandon S. Allbery KF8NH
-
Nils Anders Danielsson
-
PR Stanley
-
Tony Morris