Differences in pattern matching syntax?

Han Joosten han.joosten at atosorigin.com
Fri Jan 16 07:41:34 EST 2009


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--tp21416338p21498536.html
Sent from the Haskell - Glasgow-haskell-users mailing list archive at Nabble.com.



More information about the Glasgow-haskell-users mailing list