
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