
"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