RE: Differences in pattern matching syntax?

Hi, I do not use -O to compile, as far as I know. I use eclipsefp and I use the defaults from it. I will upload my modules as a zip file, so you can reproduce the error. It also contains a README.txt file that explains how to reproduce it. Hope that helps. http://www.nabble.com/file/p21439653/src.zip src.zip Simon Peyton-Jones wrote:
I agree that's odd. Are you using -O? Can you give us a reproducible test case?
(The only think I can think is that the line | Gc{} -> Tm (grspe r) will build a thunk for (grspe r), and depending on the context I suppose you might get a lot of those.)
Thanks
Simon
| -----Original Message----- | From: glasgow-haskell-users-bounces@haskell.org [mailto:glasgow-haskell-users- | bounces@haskell.org] On Behalf Of Han Joosten | Sent: 12 January 2009 21:54 | To: glasgow-haskell-users@haskell.org | Subject: Differences in pattern matching syntax? | | | Hi, | | I have two alternatives to specify a specific function. They both compile | ok, but the first one crashes (Stack space overflow) while the second one | runs fine. | I use GHC 6.10.1 on windowsXP | | Alternative 1: | antecedent :: Rule -> Expression | antecedent r = case r of | Ru{} -> if (rrsrt r == AlwaysExpr) then error ("(Module | ADLdataDef:) illegal call to antecedent of rule "++show r) | else | rrant r | Sg{} -> antecedent (srsig r) | Gc{} -> Tm (grspe r) | Fr{} -> frcmp r | | Alternative 2: | antecedent :: Rule -> Expression | antecedent r@(Ru AlwaysExpr _ _ _ _ _ _ _ _) = error ("(Module ADLdef:) | illegal call to antecedent of rule "++show r) | antecedent (Ru _ a _ _ _ _ _ _ _) = a | antecedent (Sg _ rule _ _ _ _ _) = antecedent rule | antecedent (Gc _ d _ _ _ _ _) = Tm d | antecedent (Fr _ _ e _) = e | | Both alternatives compile, but if i use Alternative 2, then my program runs | fine. If I use Alternative 1 instead, I get a stack space overflow. | | I would think that both alternatives would have the same semantics. So i am | surprised that one runs fine, while the other one crashes. | | Could anyone explain what is going on? | Thanks! | | Han Joosten | | ---------------------------- | Might help, here is the data definition: | | data Rule = | -- Ru c antc p cons cpu expla sgn nr pn | Ru { rrsrt :: RuleType -- ^ One of the following: | -- | Implication if this is an | implication; | -- | Equivalence if this is an | equivalence; | -- | AlwaysExpr if this is an | ALWAYS expression. | , rrant :: Expression -- ^ Antecedent | , rrfps :: FilePos -- ^ Position in the ADL file | , rrcon :: Expression -- ^ Consequent | , r_cpu :: Expressions -- ^ This is a list of | subexpressions, which must be computed. | , rrxpl :: String -- ^ Explanation | , rrtyp :: (Concept,Concept) -- ^ Sign of this rule | , runum :: Int -- ^ Rule number | , r_pat :: String -- ^ Name of pattern in which it was | defined. | } | -- Sg p rule expla sgn nr pn signal | | Sg { srfps :: FilePos -- ^ position in the ADL file | , srsig :: Rule -- ^ the rule to be signalled | , srxpl :: String -- ^ explanation | , srtyp :: (Concept,Concept) -- ^ type | , runum :: Int -- ^ rule number | , r_pat :: String -- ^ name of pattern in which it was | defined. | , srrel :: Declaration -- ^ the signal relation | } | -- Gc p antc cons cpu _ _ _ | | Gc { grfps :: FilePos -- ^ position in the ADL file | , grspe :: Morphism -- ^ specific | , grgen :: Expression -- ^ generic | , r_cpu :: Expressions -- ^ This is a list of | subexpressions, which must be computed. | , grtyp :: (Concept,Concept) -- ^ declaration | , runum :: Int -- ^ rule number | , r_pat :: String -- ^ name of pattern in which it was | defined. | } | -- Fr t d expr pn -- represents an automatic computation, such as * or +. | | Fr { fraut :: AutType -- ^ the type of automatic | computation | , frdec :: Declaration -- ^ where the result is to be | stored | , frcmp :: Expression -- ^ expression to be computed | , frpat :: String -- ^ name of pattern in which it was | defined. | } | | -- | View this message in context: http://www.nabble.com/Differences-in-pattern-matching-syntax-- | tp21416338p21416338.html | Sent from the Haskell - Glasgow-haskell-users mailing list archive at Nabble.com. | | _______________________________________________ | Glasgow-haskell-users mailing list | Glasgow-haskell-users@haskell.org | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
-- View this message in context: http://www.nabble.com/Differences-in-pattern-matching-syntax--tp21416338p214... Sent from the Haskell - Glasgow-haskell-users mailing list archive at Nabble.com.

That's a big set of modules, and I don't have eclipsefp. It'd be much easier with a smaller test case. But there may be no bug here. Compiling with -O certainly can give different space behaviour. And as I mentioned, there's one place where it really will generate different code. Try this a) Compile antecedent with -O. Does that make the two behave the same? b) In Alterantive 1 change Gc{} -> Tm (grspe r) to Gc{} -> let x = grspe r in r `seq` Tm r Does that change anything? Simon | -----Original Message----- | From: glasgow-haskell-users-bounces@haskell.org [mailto:glasgow-haskell-users- | bounces@haskell.org] On Behalf Of Han Joosten | Sent: 14 January 2009 10:31 | To: glasgow-haskell-users@haskell.org | Subject: RE: Differences in pattern matching syntax? | | | Hi, | | I do not use -O to compile, as far as I know. I use eclipsefp and I use the | defaults from it. | I will upload my modules as a zip file, so you can reproduce the error. It | also contains a README.txt file that explains how to reproduce it. | Hope that helps. | http://www.nabble.com/file/p21439653/src.zip src.zip | | | Simon Peyton-Jones wrote: | > | > I agree that's odd. Are you using -O? Can you give us a reproducible | > test case? | > | > (The only think I can think is that the line | > | Gc{} -> Tm (grspe r) | > will build a thunk for (grspe r), and depending on the context I suppose | > you might get a lot of those.) | > | > Thanks | > | > Simon | > | > | -----Original Message----- | > | From: glasgow-haskell-users-bounces@haskell.org | > [mailto:glasgow-haskell-users- | > | bounces@haskell.org] On Behalf Of Han Joosten | > | Sent: 12 January 2009 21:54 | > | To: glasgow-haskell-users@haskell.org | > | Subject: Differences in pattern matching syntax? | > | | > | | > | Hi, | > | | > | I have two alternatives to specify a specific function. They both | > compile | > | ok, but the first one crashes (Stack space overflow) while the second | > one | > | runs fine. | > | I use GHC 6.10.1 on windowsXP | > | | > | Alternative 1: | > | antecedent :: Rule -> Expression | > | antecedent r = case r of | > | Ru{} -> if (rrsrt r == AlwaysExpr) then error | > ("(Module | > | ADLdataDef:) illegal call to antecedent of rule "++show r) | > | else | > | rrant r | > | Sg{} -> antecedent (srsig r) | > | Gc{} -> Tm (grspe r) | > | Fr{} -> frcmp r | > | | > | Alternative 2: | > | antecedent :: Rule -> Expression | > | antecedent r@(Ru AlwaysExpr _ _ _ _ _ _ _ _) = error ("(Module | > ADLdef:) | > | illegal call to antecedent of rule "++show r) | > | antecedent (Ru _ a _ _ _ _ _ _ _) = a | > | antecedent (Sg _ rule _ _ _ _ _) = antecedent rule | > | antecedent (Gc _ d _ _ _ _ _) = Tm d | > | antecedent (Fr _ _ e _) = e | > | | > | Both alternatives compile, but if i use Alternative 2, then my program | > runs | > | fine. If I use Alternative 1 instead, I get a stack space overflow. | > | | > | I would think that both alternatives would have the same semantics. So i | > am | > | surprised that one runs fine, while the other one crashes. | > | | > | Could anyone explain what is going on? | > | Thanks! | > | | > | Han Joosten | > | | > | ---------------------------- | > | Might help, here is the data definition: | > | | > | data Rule = | > | -- Ru c antc p cons cpu expla sgn nr pn | > | Ru { rrsrt :: RuleType -- ^ One of the following: | > | -- | Implication if this is | > an | > | implication; | > | -- | Equivalence if this is | > an | > | equivalence; | > | -- | AlwaysExpr if this is | > an | > | ALWAYS expression. | > | , rrant :: Expression -- ^ Antecedent | > | , rrfps :: FilePos -- ^ Position in the ADL file | > | , rrcon :: Expression -- ^ Consequent | > | , r_cpu :: Expressions -- ^ This is a list of | > | subexpressions, which must be computed. | > | , rrxpl :: String -- ^ Explanation | > | , rrtyp :: (Concept,Concept) -- ^ Sign of this rule | > | , runum :: Int -- ^ Rule number | > | , r_pat :: String -- ^ Name of pattern in which it | > was | > | defined. | > | } | > | -- Sg p rule expla sgn nr pn signal | > | | Sg { srfps :: FilePos -- ^ position in the ADL file | > | , srsig :: Rule -- ^ the rule to be signalled | > | , srxpl :: String -- ^ explanation | > | , srtyp :: (Concept,Concept) -- ^ type | > | , runum :: Int -- ^ rule number | > | , r_pat :: String -- ^ name of pattern in which it | > was | > | defined. | > | , srrel :: Declaration -- ^ the signal relation | > | } | > | -- Gc p antc cons cpu _ _ _ | > | | Gc { grfps :: FilePos -- ^ position in the ADL file | > | , grspe :: Morphism -- ^ specific | > | , grgen :: Expression -- ^ generic | > | , r_cpu :: Expressions -- ^ This is a list of | > | subexpressions, which must be computed. | > | , grtyp :: (Concept,Concept) -- ^ declaration | > | , runum :: Int -- ^ rule number | > | , r_pat :: String -- ^ name of pattern in which it | > was | > | defined. | > | } | > | -- Fr t d expr pn -- represents an automatic computation, such as * | > or +. | > | | Fr { fraut :: AutType -- ^ the type of automatic | > | computation | > | , frdec :: Declaration -- ^ where the result is to be | > | stored | > | , frcmp :: Expression -- ^ expression to be computed | > | , frpat :: String -- ^ name of pattern in which it | > was | > | defined. | > | } | > | | > | -- | > | View this message in context: | > http://www.nabble.com/Differences-in-pattern-matching-syntax-- | > | tp21416338p21416338.html | > | Sent from the Haskell - Glasgow-haskell-users mailing list archive at | > Nabble.com. | > | | > | _______________________________________________ | > | Glasgow-haskell-users mailing list | > | Glasgow-haskell-users@haskell.org | > | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users | > | > _______________________________________________ | > Glasgow-haskell-users mailing list | > Glasgow-haskell-users@haskell.org | > http://www.haskell.org/mailman/listinfo/glasgow-haskell-users | > | > | | -- | View this message in context: http://www.nabble.com/Differences-in-pattern-matching-syntax-- | tp21416338p21439653.html | Sent from the Haskell - Glasgow-haskell-users mailing list archive at Nabble.com. | | _______________________________________________ | Glasgow-haskell-users mailing list | Glasgow-haskell-users@haskell.org | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

I wrote a little wrapper around ghc to see how what parameters were used: ghc --make -odir "C:\prive\eclipseworkspace\ADL trunk\out" -hidir "C:\prive\eclipseworkspace\ADL trunk\out" -o "C:\prive\eclipseworkspace\ADL trunk\bin\ADL" -dcore-lint Main.hs So this is only some paths and -dcore-lint. I remember trying that after I had ran into the bug. I used your hints and this is what happend. I did not use eclipsefp, but compiled directly from the command line. Also, inbetwean builds I deleted all intermediate files, just to make sure that everything was built with the same options. a1) First I compiled everything (with the original alternative 1) again with ghc --make -odir "C:\prive\eclipseworkspace\ADL trunk\out" -hidir "C:\prive\eclipseworkspace\ADL trunk\out" -o "C:\prive\eclipseworkspace\ADL trunk\bin\ADL" -dcore-lint -O Main.hs Then I ran the executable. It didn't mention a stack overflow, but it said: ADL.exe: <<loop>> after which it stoped. a2) Now I put the original alternative 2 in place, and compiled everything from scratch : ghc --make -odir "C:\prive\eclipseworkspace\ADL trunk\out" -hidir "C:\prive\eclipseworkspace\ADL trunk\out" -o "C:\prive\eclipseworkspace\ADL trunk\bin\ADL" -dcore-lint -O Main.hs Again I ran the executable, but it terminated as before, doing what I expected it to do. No stack overflow, no loop whatsoever. b) Now I tried the modified alternative 1: antecedent :: Rule -> Expression antecedent r = case r of Ru{} -> if (rrsrt r == AlwaysExpr) then error ("(Module ADLdataDef:) illegal call to antecedent of rule "++show r) else rrant r Sg{} -> antecedent (srsig r) Gc{} -> let x = grspe r in r `seq` Tm r Fr{} -> frcmp r Compiled again with: ghc --make -odir "C:\prive\eclipseworkspace\ADL trunk\out" -hidir "C:\prive\eclipseworkspace\ADL trunk\out" -o "C:\prive\eclipseworkspace\ADL trunk\bin\ADL" -dcore-lint -O Main.hs it said: ADLdataDef.hs:41:57: Couldn't match expected type `Morphism' against inferred type `Rule' In the first argument of `Tm', namely `r' In the second argument of `seq', namely `Tm r' In the expression: r `seq` Tm r I hardly use any let expressions (shame on me??) and I am not very familiar with them. But I figured out you might have mistaken, so I changed the bit to: antecedent :: Rule -> Expression antecedent r = case r of Ru{} -> if (rrsrt r == AlwaysExpr) then error ("(Module ADLdataDef:) illegal call to antecedent of rule "++show r) else rrant r Sg{} -> antecedent (srsig r) Gc{} -> let x = grspe r in r `seq` Tm x Fr{} -> frcmp r Compiled again with: ghc --make -odir "C:\prive\eclipseworkspace\ADL trunk\out" -hidir "C:\prive\eclipseworkspace\ADL trunk\out" -o "C:\prive\eclipseworkspace\ADL trunk\bin\ADL" -dcore-lint -O Main.hs Again, it sais ADL.exe: <<loop>> My conclusion is until now that I have here two variants of a piece of code that should be semantically equivalent. In the same context (the rest of the program hasn't changed) however, they behave different. Hence I suspect a bug in ghc... 8-(( Since my first posting of this thread, I have been searching around, and I have learnt that there are some pragma's that could be used. Are there any of them that I should have used when using this kind of pattern matching? I might have omitted them. Han Joosten. -- View this message in context: http://www.nabble.com/Differences-in-pattern-matching-syntax--tp21416338p214... Sent from the Haskell - Glasgow-haskell-users mailing list archive at Nabble.com.

Am Donnerstag, 15. Januar 2009 22:57 schrieb Han Joosten:
I hardly use any let expressions (shame on me??) and I am not very familiar with them. But I figured out you might have mistaken, so I changed the bit to: antecedent :: Rule -> Expression antecedent r = case r of Ru{} -> if (rrsrt r == AlwaysExpr) then error ("(Module ADLdataDef:) illegal call to antecedent of rule "++show r) else rrant r Sg{} -> antecedent (srsig r) Gc{} -> let x = grspe r in r `seq` Tm x Fr{} -> frcmp r
Perhaps you should have replaced both occurrences of 'r' with 'x': Gc{} -> let x = grspe r in x `seq` Tm x (That may or may not make a difference, depends on what your code actually does). Should be worth a try anyway. Also, try compiling with -O2 to see if that makes a difference.

antecedent :: Rule -> Expression antecedent r = case r of .. Gc{} -> let x = grspe r in r `seq` Tm r ..
This looks wrong. The idea was to replace Tm (grspe r) (where the selection expression is put into Tm unevaluated) with let x = grspe r in x `seq` Tm x ie, bind the selected expression to 'x', then force 'x' to be evaluated before putting it in 'Tm x'. Alternatively, Tm $! (grspe r) should do the same forcing. However, either variant will force evaluation of the selected field as well, not just evaluation of the selection. Consider this small example: data T x = T {field :: x} f (T x) = Just x g tx = Just (field tx) h tx = Just $! (field tx) The three functions 'f', 'g', and 'h' are different, as can be seen (in part) by evaluating *Main> Data.Maybe.isJust $ f (T undefined) True *Main> Data.Maybe.isJust $ g (T undefined) True *Main> Data.Maybe.isJust $ h (T undefined) *** Exception: Prelude.undefined f: passes the 'field' 'x' unchanged g: passes the whole record, wrapped in a selection h: passes the 'field', after evaluating it The extra wrapping in 'g' corresponds to where Simon suspects your difference in memory behaviour comes from (by the time the wrappers get evaluated, there are too many of them to fit on the stack). Neither 'g' nor 'h' are equivalent to 'f', but the equivalent of 'h' (forcing the record selection before putting it in another constructor) might fit your needs better than the equivalent of 'g'. hth, Claus
antecedent :: Rule -> Expression antecedent r = case r of .. Gc{} -> let x = grspe r in r `seq` Tm x ..
This is forcing 'r', not the selection 'x' from 'r'.

| I hardly use any let expressions (shame on me??) and I am not very familiar | with them. But I figured out you might have mistaken, so I changed the bit | to: | antecedent :: Rule -> Expression | antecedent r = case r of | Ru{} -> if (rrsrt r == AlwaysExpr) then error ("(Module | ADLdataDef:) illegal call to antecedent of rule "++show r) | else | rrant r | Sg{} -> antecedent (srsig r) | Gc{} -> let x = grspe r in r `seq` Tm x | Fr{} -> frcmp r Indeed I was wrong, as others saw too. But in any case, I now realise that adding the `seq` makes the function stricter than Alternative 2, which your application presumably doesn't like. (Hence <<loop>>, I assume.) Try this instead, which should make it more like Alternative 2: Gc{} -> case r of { GC{ grspe = x } -> Tm x } My guess is that will behave like Alternative 2. Simon

Hi, I tried Simon's : Gc{} -> case r of { GC{ grspe = x } -> Tm x } This still failed with <<Loop>>, like alternative 1. Then I tried Claus Reinke's suggestion: Gc{} -> Tm $! (grspe r) which had the same result , the <<loop>>. However, I was very fortunate to have Bas Joosten look into this with me. He suggested: {- Alternative 3 : -} antecedent :: Rule -> Expression antecedent r = case r of Ru{rrsrt = AlwaysExpr} -> error ("(Module ADLdef:) illegal call to antecedent of rule "++show r) Ru{} -> rrant r Sg{} -> antecedent (srsig r) Gc{} -> Tm (grspe r) Fr{} -> frcmp r We tried this alternative, and... It doesn't loop, as doesn't alternative 2: {- Alternative 2: -} antecedent :: Rule -> Expression antecedent r@(Ru AlwaysExpr _ _ _ _ _ _ _ _) = error ("(Module ADLdef:) illegal call to antecedent of rule "++show r) antecedent (Ru _ a _ _ _ _ _ _ _) = a antecedent (Sg _ rule _ _ _ _ _) = antecedent rule antecedent (Gc _ d _ _ _ _ _) = Tm d antecedent (Fr _ _ e _) = e In my case however, I like the syntax of alternative 3 much more than that of alternative 2. I do not exactly understand why the alternatives 3 and 1 behave differently. It probably has something to do with strictness, but that isn't really my cup of tea. I do wish to express my thanks to Simon, Claus and Daniel Fisher who took the trouble in reacting to my post. Thanks! (And of course Bas for being around at the right time 8-)) {- Alternative 3 : -} antecedent :: Rule -> Expression antecedent r = case r of Ru{rrsrt = AlwaysExpr} -> error ("(Module ADLdef:) illegal call to antecedent of rule "++show r) Ru{} -> rrant r Sg{} -> antecedent (srsig r) Gc{} -> Tm (grspe r) Fr{} -> frcmp r {- Alternative 1: -} antecedent :: Rule -> Expression antecedent r = case r of Ru{} -> if (rrsrt r == AlwaysExpr) then error ("(Module ADLdataDef:) illegal call to antecedent of rule "++show r) else rrant r Sg{} -> antecedent (srsig r) Gc{} -> Tm (grspe r) Fr{} -> frcmp r This notation is what I was looking for. I still think that -- View this message in context: http://www.nabble.com/Differences-in-pattern-matching-syntax--tp21416338p214... Sent from the Haskell - Glasgow-haskell-users mailing list archive at Nabble.com.

OK once I bit the bullet and looked at the code the bug was obvious. When you pattern match Ru{rrsrt = AlwaysExpr} -> error "blah" GHC uses, well, pattern-matching to see if rrsrt is AlwaysExpr. But when you say Ru{} -> if (rrsrt r == AlwaysExpr) then error "blah" else ... then GHC uses the (==) operation for the data type RuleType (of which AlwaysExpr) is a data constructor. Sadly you have not defined it. You just say instance Eq RuleType That uses the default methods for equality. Its equivalent to instance Eq RuleType where (==) a b = not (a /= b) (/=) a b = not (a == b) So it's not surprising that you get a loop. You probably wanted to use "deriving Eq" on your data type declaration for RuleType, or deriving instance Eq RuleType So, clearly not a bug in GHC; but it would be more felicitous if it gave you a warning about the instance declaration for Eq RuleType. The difficulty is that it's not clear when to warn; it's ok to use default methods, but you must define *either* (==) *or* (/=). Simon

Hello Simon, Friday, January 16, 2009, 7:07:09 PM, you wrote:
Sadly you have not defined it. You just say
instance Eq RuleType
this is very common error. it would be great to find some way to deal with it (for predefined classes at very least...) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On 2009 Jan 16, at 11:23, Bulat Ziganshin wrote:
Friday, January 16, 2009, 7:07:09 PM, you wrote:
instance Eq RuleType
this is very common error. it would be great to find some way to deal with it (for predefined classes at very least...)
It wouldn't catch everything, but might it make sense to output a warning on empty instance declarations? -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

On Fri, Jan 16, 2009 at 11:07 AM, Simon Peyton-Jones
So, clearly not a bug in GHC; but it would be more felicitous if it gave you a warning about the instance declaration for Eq RuleType. The difficulty is that it's not clear when to warn; it's ok to use default methods, but you must define *either* (==) *or* (/=).
Why is (/=) a member of Eq in the first place? Is there any code that
defines (/=) and uses the default for (==)?
--
Dave Menendez

Simon, Thank you *VERY* much for your effort to look into this problem. We have been searching for this loop for quite some time, and it caused us a lot of brain damage ;-) When we red your message last friday evening, we have given it a go and it sure was the problem. Looking back, I should have known better, but it shows I am human too, so blundering once in a while... These type of bugs can be hard to catch. We were close, but simply overlooked it. It certainly isn't a bug in ghc, as I suspected earlier this week. Ghc just did its job. However, it would be very helpful if it could give some kind of a clue. Using the -O option, ghc does detect the loop. I believe that in general that isn't trivial at all, but since it does the detection, It would probably be not too hard to give some sort of clue into the right direction. Such a clue could save days in hunting a bug. Anyways, thanks for helping out! A deep bow! Han Joosten -- View this message in context: http://www.nabble.com/Differences-in-pattern-matching-syntax--tp21416338p215... Sent from the Haskell - Glasgow-haskell-users mailing list archive at Nabble.com.
participants (7)
-
Brandon S. Allbery KF8NH
-
Bulat Ziganshin
-
Claus Reinke
-
Daniel Fischer
-
David Menendez
-
Han Joosten
-
Simon Peyton-Jones