"Simon Marlow" <[EMAIL PROTECTED]> wrote,

> > With the attached file, on both Linux and Solaris, I get the following
> > 
> > ----  Cut here -------
> > # ghci --interactive
> >    ___         ___ _
> >   / _ \ /\  /\/ __(_)
> >  / /_\// /_/ / /  | |      GHC Interactive, version 5.04.1, 
> > for Haskell 98.
> > / /_\\/ __  / /___| |      http://www.haskell.org/ghc/
> > \____/\/ /_/\____/|_|      Type :? for help.
> > 
> > Loading package base ... linking ... done.
> > Loading package haskell98 ... linking ... done.
> > Prelude> :load GHCBug
> > Compiling GHCBug           ( GHCBug.hs, interpreted )
> > Ok, modules loaded: GHCBug.
> > *GHCBug> show (read (show (Commit 1 "1" Nothing)) :: Command)
> > "*** Exception: Prelude.read: no parse
> > ----- Cut here ------------
> > 
> > NB (1) this seems to occur in ghc generally, not just in 
> > ghci.  (2) Read/Show being fairly
> > important to us, I'm afraid this means we will have to avoid 
> > using ghc5.04.1.  I hope ghc5.04.2 comes along soon.
> 
> It turns out there's a bug in the Read instance for Maybe.  It's rather
> unfortunate that there's no workaround other than defining your own
> Maybe type.

Luckily, there is a workaround (discovered by Tom Moertel on
#haskell).  If you include field names in the data
definition for which you derive Show and Read, it seems to
work fine.  

So, in George's example

  module GHCBug where

  data Command =
        NewLocation 
     |  Commit {a :: Int, b :: String, c :: (Maybe String)}
     |  Retrieve String String
     |  ListVersions String
        deriving (Read,Show)

should be all that is needed.

It seems that as soon as the value of the Maybe type is
delimited by a punctuation symbol or bracket, all is fine.

Cheers,
Manuel
_______________________________________________
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to