You're right. I the report is reasonable too.
One might want to say
data Wib = Wib { (#) :: Int -> Int }
and then say
f :: Wib -> Int -> Int
f w i = w # (i+2)
Although it seems odd for a selector to be infix,
it works rather well in situations like this.
We'll fix GHC.
Simon
> -----Original Message-----
> From: Koen Claessen
> Sent: Thursday, July 01, 1999 9:42 AM
> To: The Haskell Mailing List
> Subject: Field names
>
>
> Hello all,
>
> I believe the following program is valid Haskell'98:
>
> >>>
> module Main where
>
> data Hash = Hash{ (#) :: Int }
> deriving (Show, Read)
>
> main =
> do print s
> print (read s :: Hash)
> where
> s = show (Hash 3)
> <<<
>
> The problem is the use of (#) as a field name.
>
> The expected output of the program is something like:
>
> >>>
> "Hash{(#)=3}"
> Hash{(#)=3}
> <<<
>
> Hugs98's, Hbc's and Ghc's derived read and show
> all choke on it though:
>
> Hugs says:
>
> >>>
> "Hash{#=3}"
>
> Program error: Prelude.read: no parse
> <<<
>
> Hbc says:
>
> >>>
> "Hash { (#) = 3 }"
> Bug: Error: Prelude.read: no parse
> <<<
>
> Ghc says:
>
> >>>
> "Hash{#=3}"
>
> Fail: PreludeText.read: no parse
> <<<
>
> The question is: should operators be allowed to be valid
> field names or not?
>
> Regards,
> Koen.
>
> --
> Koen Claessen,
> [EMAIL PROTECTED],
> http://www.cs.chalmers.se/~koen,
> Chalmers University of Technology.
>