[Haskell-cafe] New to Haskell

Miguel Mitrofanov miguelimo38 at yandex.ru
Tue Dec 18 03:29:43 EST 2007


> What I should have been told about upfront:
> - the syntax for an expression
> - the syntax for a block

Don't see your point.

> - 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 )

Oh, that's pretty easy, parenthesized expression is not divided by a comma.

> - what guarantees are made by the LANGUAGE that an IO action (such as  do  
> putStrLn "Hello world" ) is not performed twice

There are no such guarantees. If you write

a = putStrLn "Hello world"
main = do {a; a;}

then your putStrLn would be performed twice. IO actions are first-class values, that's a feature, not a bug.

> - the lambda expressions can be written (input) but cannot be printed  
> (output)

Yes, since two different lambda expressions can denote the same function.

> 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.

No, pattern matching bounds variables; if you write "case x of {aa -> ...} then aa becomes a LOCAL variable for the case statement, and shadows the global definition. The same applies to u and v in h, except that in this case local variables shadow upper-level local variables.


More information about the Haskell-Cafe mailing list