Verma Anurag wrote:
module Mark where

data Mark = Mark Int deriving (Show)

instance Read Mark where
readsPrec _ str = [(Mark x, t') | ("mark",t) <- reads str, (x,t') <- reads t


The problem with this instance is that reads expect Strings to be enclosed in double quotes:

*Mark> read "mark" :: String
"*** Exception: Prelude.read: no parse
*Mark> read "\"mark\"" :: String
"mark"

Let's try this with your instance:

*Mark> read "\"mark\" 4" :: Mark
Mark 4

That works, but is probably not what you want. You can use the lex function to parse identifiers not enclosed in quotes:

> instance Read Mark where
>   readsPrec _ str = [(Mark x, t') | ("mark",t) <- lex str,
>                                     (x,t') <- reads t

Now, it's working fine:

*Mark> read "mark 4" :: Mark
Mark 4

  Tillmann
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to