
interestingly, the below test fails. May I ask: If "case" a1 is not the same as "where" a1, what is its value? Why does x=1 match against a1? note: result1 indent is aligned with a1 on the previous line ------ test module TestCase where import Test.Hspec main::IO() main = hspec $ do describe "TestCase" $ do it "case 1 - pass" $ do result1 1 `shouldBe` "one" it "case 2 - fail" $ do result1 2 `shouldBe` "two" where a1 = 2 result1 x = case x of a1 -> "one" 2 -> "two"

ok with a small tweak I can see "case" a1 value is x: result1 x = case x of a1 -> trace (show a1) "one" 2 -> "two"

Hi Imants, On Tue, Jul 07, 2015 at 12:28:58PM +0200, Imants Cekusins wrote:
ok with a small tweak I can see "case" a1 value is x:
result1 x = case x of a1 -> trace (show a1) "one" 2 -> "two"
'a1' is new variable which is always bound to the value of 'x' and this case is always matching. You should also get a warning for this: Warning: Pattern match(es) are overlapped In a case alternative: 2 -> ... Greetings, Daniel

'a1' is new variable
Thank you Daniel! is there a way to "freeze" outside variables into constants which can be used as "case" statement patterns? for example if I use "if", the below test passes. It would be handy to use case statement instead of multiple ifs or guards main::IO() main = hspec $ do describe "TestCase" $ do it "case 1 - pass" $ do result1 1 `shouldBe` "one" it "case 2 - pass" $ do result1 2 `shouldBe` "two" where result1 x = if x == a1 then "one" else if x == a2 then "two" else "three" where a1 = 1 a2 = 2

Hi Imants, On Tue, Jul 07, 2015 at 12:46:25PM +0200, Imants Cekusins wrote:
is there a way to "freeze" outside variables into constants which can be used as "case" statement patterns?
I don't think so.
result1 x = if x == a1 then "one" else if x == a2 then "two" else "three" where a1 = 1 a2 = 2
There're several other ways to solve this: result1 1 = "one" result1 2 = "two" result1 _ = "three" Or: result1 x | x == 1 = "one" | x == 2 = "two" | _ = "three" Greetings, Daniel

On Tue, Jul 7, 2015 at 8:04 AM, Imants Cekusins
This "case" behaviour (patterns allow no access to outer scope variables) is different from some other languages.
In most functional languages, "case" is about structure, not values. You specify the structure in terms of constructors, which must be literal. Variables in patterns always capture values associated with those constructors, never to values outside the case expression. That said, doing a value-based comparison ("switch"-type construct) is rather annoying, and most of Haskell's (and ghc extension) mechanisms only reduce the pain somewhat. :/ -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

Thank you Brandon. Well in Erlang you can mix and match patterns with outer scope variables. It is very handy, I agree. Here is an example. You can try this code in browser here: http://tryerl.seriyps.ru/#id=e3f2 % -*- coding: utf8 -*- -module(main). -export([main/0]). main() -> check(2), check({other,4}). check(X)-> A1 = 1, A2 = 2, case X of A1 -> io:format("A1~n"); A2 -> io:format("A2~n"); {other,X1} -> io:format("~p~n",[X1]) end.
participants (3)
-
Brandon Allbery
-
Daniel Trstenjak
-
Imants Cekusins