Chris Stryczynski

Software Developer / Consultant

Attoparsec sepBy example

Posted on: 18/03/2018

When I first used this function, I didn’t quite understand how it works. I assumed it would ‘split’ the string according to the separator.

sepBy :: Alternative f => f a -> f s -> f [a]
sepBy p s = liftA2 (:) p ((s *> sepBy1 p s) <|> pure []) <|> pure []

My guess as to what it actually does is: it runs the p parser as it normally would, it then attempts to run the s parser, if this succeeds, it will add the previous parsed result (from p) to the list, and repeat this procedure again. This essentially means you don’t have to worry too much about how it ends, as long as the ‘prefix’ of the input can be matched upon. It also seems that the actual separator is optional, in that if you can’t find the separator it will just return whatever has been parsed by p.

You’ll probably need the following dependencies:

- base >=4.10 && <4.11
- attoparsec
- text
- HUnit
- template-haskell
- pretty-simple
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# OPTIONS -Wno-unused-imports #-}
{-# OPTIONS -Wno-unused-matches #-}
{-# LANGUAGE Strict #-}
{-# LANGUAGE StrictData #-}

module Main where

import Data.Attoparsec.Text
import qualified Data.Attoparsec.Text as AParsec
import Data.Attoparsec.Combinator
import Data.Text (Text, splitOn, strip, unlines, pack)
import qualified Data.Text.IO as TextIO
import Test.HUnit
import StrQuasi
import System.IO.Unsafe
import Text.Pretty.Simple (pPrint)
import Control.Applicative

parseExample :: Parser ([Text], Text)
parseExample = do
  numbers <- takeWhile1 (notInClass "=+") `sepBy` char '+'
  skip (== '=')
  total <- takeWhile1 (const True)
  return $ (numbers, total)


main :: IO ()
main = do
  _ <- runTestTT hUnitTests
  print "Tests completed"

hUnitTests :: Test
hUnitTests = test [
    "example"    ~: True ~=? example
  ]

example :: Bool
example = do
  let input = [str|1+2+3=6|]
  unsafeDebugEq parseExample input (((pack . show) <$> [1,2,3]), "6")

unsafeDebugEq :: (Eq a, Show a) => Parser a -> Text -> a -> Bool
unsafeDebugEq p t expected = unsafePerformIO $
  putStrLn "\n" >>
  case parse p t of
    Done i res -> do
      putStrLn "Success at parse:"
      unsafeValueEq i res expected
    Fail i i' i'' -> do
      putStrLn "Fail to parse:"
      putStrLn "Remaining input:"
      print $ i
      putStrLn "Contexts:"
      putStrLn $ show i'
      putStrLn "Parse error:"
      print i''
      return False
    Partial x -> do
      print $ "Partial result for initial"
      case x "" of
        Done _ res -> unsafeValueEq t res expected
        Fail i i' i'' -> do
          putStrLn "Fail to parse:"
          putStrLn "Remaining input:"
          print $ show i
          putStrLn "Contexts:"
          print $ show i'
          putStrLn "Parse error:"
          print i''
          return False
        _ -> error "I don't think this should ever happen, as we should have consumed all input?"

unsafeValueEq :: (Show a, Eq a) => Text -> a -> a -> IO Bool
unsafeValueEq i res expected =
      case (res == expected) of
        True -> return True
        False -> do
          putStrLn "Input:"
          TextIO.putStrLn i
          putStrLn "\nTest case failed!!!"
          putStrLn "Expected:"
          pPrint expected
          putStrLn "Actual result:"
          pPrint res
          putStrLn "\n"
          return False
Comments

No comments, yet!

Submit a comment