How to keep reading (using read instance) til the end of string?

import Text.Read hiding ((+++))
import Text.ParserCombinators.ReadP
import Data.Char (isDigit)

data FruitType
  = Apple
  | Banana
  deriving Show

instance Read FruitType where
  readPrec = readP_to_Prec (const readFruitType)

readFruitType :: ReadP FruitType
readFruitType = (string "A" >> pure Apple)
            +++ (string "B" >> pure Banana)

data FruitPack = FruitPack FruitType Int
  deriving Show

instance Read FruitPack where
  readPrec = readP_to_Prec (const readFruitPack)

readNumber :: ReadP Int
readNumber = do
    i <- munch1 isDigit
    pure $ read i

readFruitPack :: ReadP FruitPack
readFruitPack = do
  skipSpaces
  t <- readFruitType
  skipSpaces
  i <- readNumber
  skipSpaces
  eof
  pure $ FruitPack t i

main :: IO ()
main = do
  let as = read <$> [" A 10","B 300 "] :: [FruitPack]
  print as
  let bs = read "A 10 B 3 A 20 B 400" :: [FruitPack]
  print bs

I can read single FruitPack, but How can I read chain of them (as in bs) without having to split the string using <space> as delimiter?

$ runhaskell read.hs
[FruitPack Apple 10,FruitPack Banana 300]
read.hs: Prelude.read: no parse
1 Like

The read function will use the read instance that belongs to the result type to determine how to read the string.

In the first case you map the read function over a list of strings and each of those calls of read produces a value of type FruitPack. To do that it uses your implementation of the readPrec function.

In the second case you call read on a string and it should produce a result of type [FruitPack]. So it will use the readPrec function that is defined for lists (defined here). That implementation parses the list syntax with square brackets and comma seperated values. It uses your readPrec implementation internally to perse the comma seperated values.

So the input for the second case should be: read "[A 10, B 3, A 20, B 400]". If you try that it will still not work, because you put a eof inside your readFruitPack function. If you remove that then it will work (the end of input is handled automatically in the read function).

That might not be what you want, because you probably want to parse a string that has no square brackets or commas in it. To do that it would be best if you stop using the read function and just use the ReadP parsers directly, because the Read typeclass is not intended for parsing arbitrarily structured data.

To implement a parser that will parse your format you could use your readFruitPack function (with the eof removed) combined with the many, <* and eof functions.

  let bs = fst (head (readP_to_S (many readFruitPack <* eof) "A 10 B 3 A 20 B 400")) :: [FruitPack]