Skip to content

Commit

Permalink
Add tests for the reversed branches in parsnip, bump to 0.0.0.1
Browse files Browse the repository at this point in the history
  • Loading branch information
ArturGajowy committed Jun 8, 2021
1 parent 828179d commit d993792
Show file tree
Hide file tree
Showing 2 changed files with 62 additions and 1 deletion.
9 changes: 8 additions & 1 deletion parsnip/parsnip.cabal
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
cabal-version: 2.2
name: parsnip
version: 0
version: 0.0.0.1
synopsis: A fast, minimal parser
description:
A fast, minimal parser.
Expand Down Expand Up @@ -67,3 +67,10 @@ library
Text.Parsnip.Internal.Parser
Text.Parsnip.Internal.Private
Text.Parsnip.Internal.Simple

test-suite spec
import: base
type: exitcode-stdio-1.0
hs-source-dirs: test
build-depends: parsnip >= 0.0.0.1, hspec, tasty, tasty-hspec
main-is: Spec.hs
54 changes: 54 additions & 0 deletions parsnip/test/Spec.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,54 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Main
( main
) where

import Test.Hspec as Hspec
import Test.Tasty
import Test.Tasty.Hspec

import Text.Parsnip
import qualified Text.Parsnip.Word8 as PW

import Data.Function (on)
import Data.ByteString.Internal (c2w)


spec :: IO TestTree
spec = testSpec "spec" $ do

describe "parsnip" $ do
it "while" $ parse (while ('A' ==)) "AAB" `shouldBe` Right "AA"
it "while edge" $ parse (while ('B' ==)) "AAB" `shouldBe` Right ""
it "while NUL" $ parse (while ('A' ==)) "A\0AB" `shouldBe` Right "A"
-- These are failing. Is this a bug? Or just a necessity due to the design?
-- it "while" $ parse (while (== 'A')) "AAB" `shouldBe` Right "AA"
-- it "while edge" $ parse (while (== 'B')) "AAB" `shouldBe` Right ""
-- it "while NUL" $ parse (while (== 'A')) "A\0AB" `shouldBe` Right "A"
it "till" $ parse (till (== 'B')) "AAB" `shouldBe` Right "AA"
it "till edge" $ parse (till (== 'A')) "AAB" `shouldBe` Right ""
it "till NUL" $ parse (till (== 'B')) "A\0AB" `shouldBe` Right "A"

describe "parsnip Word8" $ do
it "while" $ parse (PW.while (c2w 'A' ==)) "AAB" `shouldBe` Right "AA"
it "while edge" $ parse (PW.while (c2w 'B' ==)) "AAB" `shouldBe` Right ""
it "while NUL" $ parse (PW.while (c2w 'A' ==)) "A\0AB" `shouldBe` Right "A"
-- These are failing. Is this a bug? Or just a necessity due to the design?
-- it "while" $ parse (PW.while (== c2w 'A')) "AAB" `shouldBe` Right "AA"
-- it "while edge" $ parse (PW.while (== c2w 'B')) "AAB" `shouldBe` Right ""
-- it "while NUL" $ parse (PW.while (== c2w 'A')) "A\0AB" `shouldBe` Right "A"
it "till" $ parse (PW.till (== c2w 'B')) "AAB" `shouldBe` Right "AA"
it "till edge" $ parse (PW.till (== c2w 'A')) "AAB" `shouldBe` Right ""
it "till NUL" $ parse (PW.till (== c2w 'B')) "A\0AB" `shouldBe` Right "A"


instance Eq Location where
(==) = (==) `on` show

main :: IO ()
main = do
tests <- spec
defaultMain tests

0 comments on commit d993792

Please sign in to comment.