Skip to content
Snippets Groups Projects
Commit adffce21 authored by Oleg Grenrus's avatar Oleg Grenrus
Browse files

Add many-try test

parent 647c5704
Branches many-try-test
No related tags found
No related merge requests found
......@@ -114,6 +114,7 @@ test-suite parsec-tests
Bugs.Bug6
Bugs.Bug9
Bugs.Bug35
Bugs.Bug179
Features
Features.Feature80
Features.Feature150
......
......@@ -9,10 +9,12 @@ import qualified Bugs.Bug2
import qualified Bugs.Bug6
import qualified Bugs.Bug9
import qualified Bugs.Bug35
import qualified Bugs.Bug179
bugs :: [TestTree]
bugs = [ Bugs.Bug2.main
, Bugs.Bug6.main
, Bugs.Bug9.main
, Bugs.Bug35.main
, Bugs.Bug179.tests
]
module Bugs.Bug179
( tests
) where
import Control.Applicative (Alternative (..), liftA2, (<|>))
import Test.Tasty ( testGroup, TestTree )
import Test.Tasty.HUnit
import qualified Control.Applicative
import qualified Text.Parsec as P
import qualified Text.Parsec.String as P
tests :: TestTree
tests = testGroup "many try (#179)"
[ testCase "manyDefault" $ examples parser1
, testCase "C.Applicative" $ examples parser2
, testCase "Parsec" $ examples parser3
]
where
examples p = do
res1 <- parseString p $ unlines [" ", " ", "foo"]
res1 @?= "foo\n"
res2 <- parseString p $ unlines ["bar"]
res2 @?= "bar\n"
res3 <- parseString p $ unlines [" ", " ", " foo"]
res3 @?= " foo\n"
res4 <- parseString p $ unlines [" bar"]
res4 @?= " bar\n"
parseString :: P.Parser String -> String -> IO String
parseString p input =
case P.parse p "" input of
Left err -> assertFailure $ show err
Right str -> return str
parser1 :: P.Parser String
parser1 = emptyLines *> P.getInput where
emptyLines :: P.Parser String
emptyLines = manyDefault $ P.try $ P.skipMany (P.satisfy (== ' ')) *> P.char '\n'
parser2 :: P.Parser String
parser2 = emptyLines *> P.getInput where
emptyLines :: P.Parser String
emptyLines = Control.Applicative.many $ P.try $ P.skipMany (P.satisfy (== ' ')) *> P.char '\n'
parser3 :: P.Parser String
parser3 = emptyLines *> P.getInput where
emptyLines :: P.Parser String
emptyLines = P.many $ P.try $ P.skipMany (P.satisfy (== ' ')) *> P.char '\n'
-- many's default definition
manyDefault :: Alternative f => f a -> f [a]
manyDefault v = many_v
where
many_v = some_v <|> pure []
some_v = liftA2 (:) v many_v
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment