RE: infix constructor in a pattern

1999-12-14 Thread Simon Marlow

> 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.

Actually the other way around: it's ok on the right, but not on the left.
This is indeed a bug in GHC, but I don't think we'll fix it, at least not in
the near future.

The reason is that to correctly parse these left-hand-sides means knowing
all the fixity info, which can't be known until the whole file has been
parsed and all the interface files have been read.  This means deferring
some things which we currently do during parsing (like grouping the
equations by name) until much later.  Incedentally, there are several other
fixity-related examples that GHC gets wrong (and Hugs, HBC and NHC for that
matter).

Workaround: use explicit parentheses on the left hand side.  Thanks for the
report.

Cheers,
Simon



infix constructor in a pattern

1999-12-14 Thread Ilya Beylin

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.