[Haskell-cafe] Read instance for constructors?

Semen Trygubenko / Семен Тригубенко semen at trygub.com
Mon Mar 10 13:11:25 UTC 2014


Dear Haskell-cafe,

When deriving (Read), only values can be read in.
If one wants to be able to read in constructors, too, is there an easy way out?
E.g., the code below works, but the extra book-keeping

f "A" = A
...

is unpleasant — perhaps there's a simpler solution?

{-# LANGUAGE FlexibleInstances #-}

data D = A Int
       | B Int
        deriving (Show,Read)

instance Read (Int -> D) where
    readsPrec = \_ s -> [(f s,"")]
                  where f "A"       = A
                        f "B"       = B
                        f x         = error $ "Invalid constructor " ++ x 

main = do let x = read "A 1" :: D
          print x
          let g s = read s :: (Int -> D)
          print $ g "B" 2
          print $ g "C" 3

Many thanks in advance,
Semen



-- 
Семен Тригубенко http://trygub.com
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 196 bytes
Desc: not available
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20140310/53d2b8e1/attachment.sig>


More information about the Haskell-Cafe mailing list