I'm currently solving AOC 4th task where there is following input format, a line of numbers separated by a comma and then 5x5 matrices:
27,14,70,7,85,66,65
31 23 52 26 8
27 89 37 80 46
97 19 63 34 79
13 59 45 12 73
42 25 22 6 39
27 71 24 3 0
79 42 32 72 62
99 52 11 92 33
38 22 16 44 39
35 26 76 49 58
27 71 24 ...
I have the following parser:
{-# LANGUAGE TupleSections #-}
module Lib4Parse (parseAll) where
import Control.Applicative
import Control.Monad
import Data.Attoparsec.ByteString.Char8 (Parser, Result, char, count, decimal, eitherResult, endOfInput, endOfLine, isDigit, isEndOfLine, isSpace, many', many1, option, parse, parseOnly, parseTest, scientific, sepBy, signed, skipMany, skipMany1, skipSpace, skipWhile, space, takeTill)
import qualified Data.ByteString as B
newtype BoardEntry = MkBoardEntry (Bool, Int) deriving (Show, Eq)
newtype Board = MkBoard [[BoardEntry]] deriving (Show, Eq)
parseAll :: B.ByteString -> Maybe ([Int], [Board])
parseAll input =
either (const Nothing) Just $
parseOnly ((,) <$> inputNumbers <*> boards) input
inputNumbers :: Parser [Int]
inputNumbers = decimal `sepBy` char ','
boardEntry :: Parser [BoardEntry]
boardEntry = map (\x -> MkBoardEntry (False, x)) <$> (decimal `sepBy` many1 (char ' '))
board :: Parser Board
board =
MkBoard <$> count 5 (boardEntry <* (skipWhile isSpace <|> endOfInput))
boards :: Parser [Board]
boards = takeTill isDigit >> many board
The problem is that when I use many
in the boards function it hangs (when calling the parseAll
function).
But, in case the boards function looks like this it works:
boards :: Parser [Board]
boards = takeTill isDigit >> count 5 board
However, I want to parse all boards not just specified number of them.
Questions
What is the problem that this hangs, how could this be solved?
How to debug such parsers? - I'm unable to debug this since I don't know what the parser is doing. Any tips and tricks for debugging such parsers?