
I'm trying to do a first very simple example with attoparsec. The file "test.txt" contains the line: START 111 2222 333 END The following code works and gives the result: Done "\n" ["111","2222","333"] {-# LANGUAGE OverloadedStrings #-} import qualified Data.ByteString as BS import Control.Applicative import Data.Attoparsec.ByteString as P main :: IO() main = do bs <- BS.readFile "test.txt" parseTest pTest bs pTest :: Parser [BS.ByteString] pTest = do string "START" n1 <- pNumber n2 <- pNumber n3 <- pNumber string "END" return [n1, n2, n3] pNumber :: Parser BS.ByteString pNumber = do pSkipSpaces term <- P.takeWhile (\c -> c >= 0x31 && c <= 0x39) pSkipSpaces return term pSkipSpaces :: Parser () pSkipSpaces = do P.takeWhile (\c -> c == 0x20) return () Unfortunately I must have exactly three numbers between START and END. To make this more flexible, I changed pTest: pTest :: Parser [BS.ByteString] pTest = do string "START" ns <- P.many1 $ pNumber <* (string "END") return ns Now the program fails with: Fail "2222 333 END\n" [] "Failed reading: takeWith" Why ?? Many thanks for your help!