
A few days ago, for various reasons, I've started to look at Haskell. At first I was quite impressed, after reading some FAQ, and some tutorials. Evrything was nice and easy ... until I've started writing some code on my own. What I should have been told about upfront: - the syntax for an expression - the syntax for a block - the adhoc syntax rules (how to distinguish among a tuple and a pharanthesized expression and how to find the start and end of a block for example ) - the fact that lambda expressions are not the same thing as "algebraic data" values - what guarantees are made by the LANGUAGE that an IO action (such as do putStrLn "Hello world" ) is not performed twice - the lambda expressions can be written (input) but cannot be printed (output) The biggest problem for me, so far, is the last one. Here is some strange example: module Hugs where aa::Int aa=7 cc:: (Int->Int)->(Int->Int->Int)->Int->(Int->Int) cc a op b = \x-> case x of { _ | x==aa -> x+1 ; _-> a x `op` b } f::Int->Int f(1)=1 f(2)=2 f(_)=3 g::Int->Int g(1)=13 g(2)=23 g(_)=33 h::[Int->Int] -> Int ->Int h [] x = x h [rr] x = let { u=Hugs.f ; v=Hugs.g } in case rr of { u -> Hugs.g(x)+aa ; v -> Hugs.f(x)+aa ; _ ->rr (x) + aa } h (rr:ll) x = h [rr] x + h (ll) x What I don't understand is why I'm forced to use guards like x==aa in cc, when aa is clearly bounded (is 7) and why in function h, the bounded u and v become free variables in the case expression. ________ Information from NOD32 ________ This message was checked by NOD32 Antivirus System for Linux Mail Servers. part000.txt - is OK http://www.eset.com

On Dec 18, 2007 7:31 AM, Cristian Baboi
Here is some strange example:
module Hugs where
aa::Int aa=7
cc:: (Int->Int)->(Int->Int->Int)->Int->(Int->Int) cc a op b = \x-> case x of { _ | x==aa -> x+1 ; _-> a x `op` b }
f::Int->Int f(1)=1 f(2)=2 f(_)=3
g::Int->Int g(1)=13 g(2)=23 g(_)=33
h::[Int->Int] -> Int ->Int h [] x = x h [rr] x = let { u=Hugs.f ; v=Hugs.g } in case rr of { u -> Hugs.g(x)+aa ; v -> Hugs.f(x)+aa ; _ ->rr (x) + aa } h (rr:ll) x = h [rr] x + h (ll) x
What I don't understand is why I'm forced to use guards like x==aa in cc, when aa is clearly bounded (is 7) and why in function h, the bounded u and v become free variables in the case expression.
It's a simple issue of scoping. The left side of case expressions are *patterns*, which bind new names, and don't look outside their scope for names. This is a good thing. Say you have: case Left 0 of Left x -> x Right y -> show y (The values are instances of the Either type, specifically Either Int) This will match the value "Left 0" against an expression which either looks like "Left x" or "Right y", for any x or y, and act accordingly. If you decided to add x :: Int x = 42 To the top level of your program, you wouldn't want the first case only to match "Left 42" when it previously matched any value starting with "Left", would you? It is the same as scoping in C (or whatever language your background is, they all support it); you don't want names in a larger scope to interfere with names in a smaller scope. Each case in a case expression introduces a scope, and the left side of the arrow binds new names. I hope this helps, Luke

"Cristian Baboi"
Here is some strange example:
module Hugs where
aa::Int aa=7
Small note, it's common to use spaces around the :: and = I've never really noticed before.
cc :: (Int->Int) -> (Int->Int->Int) -> Int -> (Int->Int) cc a op b = \x-> case x of { _ | x==aa -> x+1 ; _-> a x `op` b }
What I don't understand is why I'm forced to use guards like x==aa in cc, when aa is clearly bounded (is 7)
I don't quite understand what you mean. You don't have to use guards, the function could equally well have been written using if-then-else. Why not cc a op b x = if x==aa then (x+1) else a x `op` b Oh, wait, you're asking why you can't write case x of aa -> x+1 _ -> a x `op` b The answer is that case introduces a new binding for 'aa', so the above is equivalent to let aa = x in x+1 Case is really for deconstructing values with pattern matching, a simple variable like aa (or _) will match any pattern.
f::Int->Int f(1)=1 f(2)=2 f(_)=3
You can drop the parentheses here.
g::Int->Int g(1)=13 g(2)=23 g(_)=33
h :: [Int->Int] -> Int -> Int h [] x = x h [rr] x = let { u=Hugs.f ; v=Hugs.g } in case rr of { u -> Hugs.g(x)+aa ; v -> Hugs.f(x)+aa ; _ ->rr (x) + aa } h (rr:ll) x = h [rr] x + h (ll) x
Same here, if I understand you correctly. The case introduces new bindings for u and v. Note that you can't (directly) compare functions for equality either, the only way to do that properly would be to compare results over the entire domain. (f == g iff f x == g x forall x) -k -- If I haven't seen further, it is by standing in the footprints of giants

"Cristian Baboi"
What I should have been told about upfront:
- the syntax for an expression
Since there are only declarations and expressions, the syntax of an expression involves pretty much all of the language, so it would be difficult to tell it "upfront".
- the syntax for a block
Not sure what you mean by "block". do a <- [1..10] b <- [3,4] return (a,b) is an expression... you can write that same expression as do {a <- [1..10]; b <- [3,4]; return (a,b)} too.
- the adhoc syntax rules (how to distinguish among a tuple and a pharanthesized expression
a tuple has commas in it. I'll grant that (x) not being a 1-tuple is a little ad-hoc, but there really is very little ad-hockery in Haskell (and a 1-tuple behaves very much like a plain value after all).
and how to find the start and end of a block for example )
again, I don't know what you mean by block, but if you write the above expression with the braces ({}), it's obvious, I think, and the layout rule just inserts braces as necessary when the indentation changes. do a b c -- this is less indented, so will cause the end of the do.
- the fact that lambda expressions are not the same thing as "algebraic data" values
It might help to know why you think they might be the same; the syntax is different and the name is different...
- what guarantees are made by the LANGUAGE that an IO action (such as do putStrLn "Hello world" ) is not performed twice
As has been pointed out, «do putStrLn "Hello world"» is an expression that you can bind to a variable and use as many times as you like. Incidentally, it means the same as «putStrLn "Hello World"»; do connects a sequence of bindings and expressions, so you don't need it if there's nothing to be connected to.
- the lambda expressions can be written (input) but cannot be printed (output)
This is a fundamental property of the language. A lambda expression is programme and at runtime the system doesn't know one lambda expression from another (all it can do with one is apply it to something).
The biggest problem for me, so far, is the last one.
I can't see how your example illustrates that, I'm afraid.
Here is some strange example:
What I don't understand is why I'm forced to use guards like x==aa in cc, when aa is clearly bounded (is 7) and why in function h, the bounded u and v become free variables in the case expression.
I would have liked the language design to have permitted case to pattern match against variables too, but the question is, what would the syntax be? There was a fair bit of discussion about this when the language was designed (and since), but no-one could come up with a good way of doing it. One aspect of it is this: we want f 0 = 42 f x = 3*x to work, and we want all function definitions to be translated into the core language in the same way, so you get f = \a -> case a of 0 -> 42 x -> 3*x and given that, you can't have a variable on the LHS of -> do anything other than get bound to the value of the expression in the case (a in the example). It's not just a the top level, either: f Nothing = 0 f (Just n) = n+1 just means f = \v -> case v of Nothing -> 0 Just n -> n+1 so you can't have variables inside constructors do anything but get bound at that point. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk http://www.chaos.org.uk/~jf/Stuff-I-dont-want.html (updated 2007-05-07)

On Tue, 18 Dec 2007 11:56:36 +0200, Jon Fairbairn
"Cristian Baboi"
writes:
- the syntax for a block
Not sure what you mean by "block".
do a <- [1..10] b <- [3,4] return (a,b)
is an expression... you can write that same expression as do {a <- [1..10]; b <- [3,4]; return (a,b)} too.
I mean anything that you can put between "{" "}", and between ";"
- the adhoc syntax rules (how to distinguish among a tuple and a pharanthesized expression
a tuple has commas in it. I'll grant that (x) not being a 1-tuple is a little ad-hoc, but there really is very little ad-hockery in Haskell (and a 1-tuple behaves very much like a plain value after all).
Is this ([1 ,2 ,3 ,4]) a tuple or what ? It has commas in it!
- the fact that lambda expressions are not the same thing as "algebraic data" values
It might help to know why you think they might be the same; the syntax is different and the name is different...
Ah, just a thought, nothing more. Lambda expressions are values, which is just data, after all. Even C can apply a function variable to an argument (function pointers).
- what guarantees are made by the LANGUAGE that an IO action (such as do putStrLn "Hello world" ) is not performed twice
As has been pointed out, «do putStrLn "Hello world"» is an expression that you can bind to a variable and use as many times as you like. Incidentally, it means the same as «putStrLn "Hello World"»; do connects a sequence of bindings and expressions, so you don't need it if there's nothing to be connected to.
Yes, but that was not the question. What make you so sure it will be printed the exact number of times you intended ?
- the lambda expressions can be written (input) but cannot be printed (output)
This is a fundamental property of the language. A lambda expression is programme and at runtime the system doesn't know one lambda expression from another (all it can do with one is apply it to something).
Even C can apply a function variable to an argument (function pointers). What make Haskell different beside the "lazy evaluation" and "mutable variables" things ?
The biggest problem for me, so far, is the last one.
I can't see how your example illustrates that, I'm afraid.
In a very strange way. Nevermind.
Here is some strange example:
What I don't understand is why I'm forced to use guards like x==aa in cc, when aa is clearly bounded (is 7) and why in function h, the bounded u and v become free variables in the case expression.
I would have liked the language design to have permitted case to pattern match against variables too, but the question is, what would the syntax be? There was a fair bit of discussion about this when the language was designed (and since), but no-one could come up with a good way of doing it. One aspect of it is this: we want
f 0 = 42 f x = 3*x
to work, and we want all function definitions to be translated into the core language in the same way, so you get f = \a -> case a of 0 -> 42 x -> 3*x
and given that, you can't have a variable on the LHS of -> do anything other than get bound to the value of the expression in the case (a in the example). It's not just a the top level, either:
f Nothing = 0 f (Just n) = n+1
just means f = \v -> case v of Nothing -> 0 Just n -> n+1
so you can't have variables inside constructors do anything but get bound at that point.
Thank you very much! ________ Information from NOD32 ________ This message was checked by NOD32 Antivirus System for Linux Mail Servers. part000.txt - is OK http://www.eset.com

"Cristian Baboi"
I mean anything that you can put between "{" "}", and between ";"
Okay, there you have it then: the syntax for a block is a {, followed by elements separated by ;s and terminated by a }. Perhaps you are really asking about how the layout rule works? (Which has already been answered, btw.)
Is this ([1 ,2 ,3 ,4]) a tuple or what ? It has commas in it!
Good observation. Lists also have commas in them, and strings can, too. ",,," is not a tuple, either. A tuple would have a (, and subexpressions separated by commas, and terminated by ). The subexpressions would need to be maximal, and have no superexpression except the tuple. I must admit I don't understand why you find this difficult, I've had my share of problems grokking Haskell, but tuple syntax has always seemed quite natural.
- the fact that lambda expressions are not the same thing as "algebraic data" values
It might help to know why you think they might be the same; the syntax is different and the name is different...
Ah, just a thought, nothing more. Lambda expressions are values, which is just data, after all.
Yes.
Even C can apply a function variable to an argument (function pointers).
Would you say that functions and structs in C are the same thing because of this?
This is a fundamental property of the language. A lambda expression is programme and at runtime the system doesn't know one lambda expression from another (all it can do with one is apply it to something).
Even C can apply a function variable to an argument (function pointers). What make Haskell different beside the "lazy evaluation" and "mutable variables" things ?
Referential transparency? But if you are happy about how C can print functions, perhaps you want to do: instance Show (a -> b) where show x = "A function" Main> show (+) "A function" -k -- If I haven't seen further, it is by standing in the footprints of giants

"Cristian Baboi"
On Tue, 18 Dec 2007 11:56:36 +0200, Jon Fairbairn
wrote: "Cristian Baboi"
writes: - the syntax for a block
Not sure what you mean by "block".
do a <- [1..10] b <- [3,4] return (a,b)
is an expression... you can write that same expression as do {a <- [1..10]; b <- [3,4]; return (a,b)} too.
I mean anything that you can put between "{" "}", and between ";"
That's a bit like asking for the syntax of anything you can put between "(" and ")"; The braces are used for grouping, and can group different things: case 2 of {1 -> 2 ; 2 -> 2} do {a <- Just 1; return a}
Is this ([1 ,2 ,3 ,4]) a tuple or what ? It has commas in it!
Not in any meaningful sense...
- what guarantees are made by the LANGUAGE that an IO action (such as do putStrLn "Hello world" ) is not performed twice
As has been pointed out, «do putStrLn "Hello world"» is an expression that you can bind to a variable and use as many times as you like.
Yes, but that was not the question. What make you so sure it will be printed the exact number of times you intended ?
I don't understand your question at all, then. How many times it gets printed depends on how many times the programme is run, for one thing. Otherwise, it's a matter of the definition of the semantics of the language. Evaluation of a Haskell programme proceeds from evaluation of «main», which returns an object of type IO -- a sequence of Input/Output operatens -- that is "run". IO doesn't happen when you evaluate an IO action, it happens when the IO action is run. For example, if you define f x = seq (putStrLn "foo!") (x+1) and have main = print (f 2) the «putStrLn "foo!"» is evaluated because seq forces its first argument, but the only output you get is 3.
This is a fundamental property of the language. A lambda expression is programme and at runtime the system doesn't know one lambda expression from another (all it can do with one is apply it to something).
Even C can apply a function variable to an argument (function pointers).
The secret of good language design is not what the language allows, it's what the language forbids. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

On Tuesday 18 December 2007 01:31:59 Cristian Baboi wrote:
A few days ago, for various reasons, I've started to look at Haskell. At first I was quite impressed, after reading some FAQ, and some tutorials. Evrything was nice and easy ... until I've started writing some code on my own.
What I should have been told about upfront:
- the syntax for an expression - the syntax for a block - the adhoc syntax rules (how to distinguish among a tuple and a pharanthesized expression and how to find the start and end of a block for example )
- the fact that lambda expressions are not the same thing as "algebraic data" values - what guarantees are made by the LANGUAGE that an IO action (such as do putStrLn "Hello world" ) is not performed twice - the lambda expressions can be written (input) but cannot be printed (output)
The biggest problem for me, so far, is the last one.
Here is some strange example:
module Hugs where
aa::Int aa=7
cc:: (Int->Int)->(Int->Int->Int)->Int->(Int->Int) cc a op b = \x-> case x of { _ | x==aa -> x+1 ; _-> a x `op` b }
f::Int->Int f(1)=1 f(2)=2 f(_)=3
g::Int->Int g(1)=13 g(2)=23 g(_)=33
h::[Int->Int] -> Int ->Int h [] x = x h [rr] x = let { u=Hugs.f ; v=Hugs.g } in case rr of { u -> Hugs.g(x)+aa ; v -> Hugs.f(x)+aa ; _ ->rr (x) + aa } h (rr:ll) x = h [rr] x + h (ll) x
What I don't understand is why I'm forced to use guards like x==aa in cc, when aa is clearly bounded (is 7) and why in function h, the bounded u and v become free variables in the case expression.
I don't think anyone has mentioned it yet, so I'll go ahead. Many of the questions you ask are well covered by the Haskell Report: http://haskell.org/onlinereport/ The report is terse, but quite usable as a reference. Moreover, it is The Final Word on all these semantic and syntactic questions. Cheers, Spencer Janssen
participants (5)
-
Cristian Baboi
-
Jon Fairbairn
-
Ketil Malde
-
Luke Palmer
-
Spencer Janssen