Bugs item #609944, was opened at 2002-09-16 14:28
You can respond by visiting:
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=609944&group_id=8032
Category: Compiler
Group: 5.04.1
Status: Open
Resolution: None
Priority: 7
Submitted By: Manuel M. T. Chakravarty (chak)
Assigned to: Nobody/Anonymous (nobody)
>Summary: deriving Read leads to "no parse"
Initial Comment:
The program
------ Start Offending Program -----
module Main
where
data T = C (Maybe Int) Int
deriving (Show, Read, Eq)
main =
do
let v = C Nothing 1
print v
print $ read (show v) == v
------ End Offending Program -----
leads to
AttitudeAdjuster chak 5 (~/haskell): ghc Main.hs
AttitudeAdjuster chak 6 (~/haskell): ./a.out
C Nothing 1
Fail: Prelude.read: no parse
AttitudeAdjuster chak 7 (~/haskell):
Experimentation suggests that it is the `Maybe' type
appearing in the type for which Read is derived that
causes the problem. This problem does *not* occur with
GHC 5.04; ie, has been introduced with patchlevel 1.
(I am not sure whether it is a problem in the Prelude
or the deriving mechanism.)
This bug is pretty serious for me, as it utterly breaks
C->Haskell.
/me waits for GHC 5.04.2...
----------------------------------------------------------------------
>Comment By: Manuel M. T. Chakravarty (chak)
Date: 2002-09-17 07:12
Message:
Logged In: YES
user_id=10359
This bug can be circumvented by using field labels in the
data declaration; ie, in the above example, use
data T = C {a :: (Maybe Int), b :: Int}
(This workaround has been suggested by Tom Moertel.)
----------------------------------------------------------------------
You can respond by visiting:
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=609944&group_id=8032
_______________________________________________
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs