Instance Read a

Hello, I cannot compile this custom Read instance. Do you know how to fix this? I have tried to import “Text.Read”, but this does not fix the error.

data Fruit = APPLE | ORANGE | OTHER deriving (Eq, Show)
instance Read Fruit where
  read "APPLE" = APPLE
  read "ORANGE" = ORANGE
  read _ = OTHER

Compilation Error is:

‘read’ is not a (visible) method of class ‘Read’

Unfortunately — for historical reasons — you need to implement readsPrec:

λ> :t readsPrec
readsPrec :: Read a => Int -> ReadS a
λ> :i ReadS
type ReadS :: * -> *
type ReadS a = String -> [(a, String)]
        -- Defined in ‘Text.ParserCombinators.ReadP’

So, most likely:

instance Read Fruit where
  readsPrec _ c =
    let (s, r) = span (/= ' ') c
    in case c of
         "XYZ" -> Foo
         -- ⁝ got to buy groceries now

I wonder if that last catch-all case could come back to bite you in a creative read/show sequence in a nested data type.

1 Like

This “catch all case” does not compile, therefore I think the best thing to do is to implement a customRead :: String -> Fruit function

The -- ⁝ got to buy groceries now was actually me going to the shop to buy groceries.

instance Read Fruit where
  readsPrec _ c =
    let (s, r) = span (/= ' ') c
    in case c of
         "APPLE" -> [(APPLE, r)]
         "ORANGE" -> [(ORANGE, r)]
         _ -> [(OTHER, r)]

This should work: we are parsing a word and returning a constructor plus the rest of the stream. Again I wonder if that _ -> is a good idea, as read should complement show.

2 Likes

I think that should be in case s of.

1 Like