The following code is accepted by hugs and hbc, but produces an error in ghc-4.04-1

---------------------
module Bug where
infix 5 |- 
infix 9 :=

data Equal = Char := Int

(|-) :: Int -> Equal -> Bool
0 |-  x:=y  = 1 |- x:=y
2 |- (x:=y) = 0 |- x:=y
_ |-  _     = False  
---------------------
Bug.hs:8:
    `|-' is not a data constructor
    In the pattern: 0 |- x := y

Compilation had errors
---------------------
As one can guess,  0 |-  x:=y  is parsed
correctly as  0 |- (x:=y) when on left hand side,
but not on the right hand side.

Reply via email to