{-# LANGUAGE FlexibleContexts #-} module Saturn.Unstable.Extra.ParsecSpec where import qualified Data.Either as Either import qualified Data.List.NonEmpty as NonEmpty import qualified Saturn.Unstable.Extra.Parsec as Parsec import qualified Test.Hspec as Hspec import qualified Text.Parsec as Parsec spec :: Hspec.Spec spec :: Spec spec = forall a. HasCallStack => String -> SpecWith a -> SpecWith a Hspec.describe String "Saturn.Unstable.Extra.Parsec" forall a b. (a -> b) -> a -> b $ do forall a. HasCallStack => String -> SpecWith a -> SpecWith a Hspec.describe String "either" forall a b. (a -> b) -> a -> b $ do let parsec :: (Parsec.Stream s m Char) => Parsec.ParsecT s u m (Either Char Char) parsec :: forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m (Either Char Char) parsec = forall s u (m :: * -> *) a b. ParsecT s u m a -> ParsecT s u m b -> ParsecT s u m (Either a b) Parsec.either (forall s (m :: * -> *) u. Stream s m Char => Char -> ParsecT s u m Char Parsec.char Char 'a') (forall s (m :: * -> *) u. Stream s m Char => Char -> ParsecT s u m Char Parsec.char Char 'b') forall a. (HasCallStack, Example a) => String -> a -> SpecWith (Arg a) Hspec.it String "succeeds with left" forall a b. (a -> b) -> a -> b $ do forall s t a. Stream s Identity t => Parsec s () a -> String -> s -> Either ParseError a Parsec.parse forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m (Either Char Char) parsec String "" String "a" forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation `Hspec.shouldBe` forall a b. b -> Either a b Right (forall a b. a -> Either a b Left Char 'a') forall a. (HasCallStack, Example a) => String -> a -> SpecWith (Arg a) Hspec.it String "succeeds with right" forall a b. (a -> b) -> a -> b $ do forall s t a. Stream s Identity t => Parsec s () a -> String -> s -> Either ParseError a Parsec.parse forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m (Either Char Char) parsec String "" String "b" forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation `Hspec.shouldBe` forall a b. b -> Either a b Right (forall a b. b -> Either a b Right Char 'b') forall a. (HasCallStack, Example a) => String -> a -> SpecWith (Arg a) Hspec.it String "fails with neither" forall a b. (a -> b) -> a -> b $ do forall s t a. Stream s Identity t => Parsec s () a -> String -> s -> Either ParseError a Parsec.parse forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m (Either Char Char) parsec String "" String "c" forall a. (HasCallStack, Show a) => a -> (a -> Bool) -> Expectation `Hspec.shouldSatisfy` forall a b. Either a b -> Bool Either.isLeft forall a. HasCallStack => String -> SpecWith a -> SpecWith a Hspec.describe String "sepByNE" forall a b. (a -> b) -> a -> b $ do let parsec :: (Parsec.Stream s m Char) => Parsec.ParsecT s u m (NonEmpty.NonEmpty Char) parsec :: forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m (NonEmpty Char) parsec = forall s u (m :: * -> *) a sep. ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m (NonEmpty a) Parsec.sepByNE (forall s (m :: * -> *) u. Stream s m Char => Char -> ParsecT s u m Char Parsec.char Char 'a') (forall s (m :: * -> *) u. Stream s m Char => Char -> ParsecT s u m Char Parsec.char Char ' ') forall a. (HasCallStack, Example a) => String -> a -> SpecWith (Arg a) Hspec.it String "succeeds with one" forall a b. (a -> b) -> a -> b $ do forall s t a. Stream s Identity t => Parsec s () a -> String -> s -> Either ParseError a Parsec.parse forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m (NonEmpty Char) parsec String "" String "a" forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation `Hspec.shouldBe` forall a b. b -> Either a b Right (Char 'a' forall a. a -> [a] -> NonEmpty a NonEmpty.:| []) forall a. (HasCallStack, Example a) => String -> a -> SpecWith (Arg a) Hspec.it String "succeeds with many" forall a b. (a -> b) -> a -> b $ do forall s t a. Stream s Identity t => Parsec s () a -> String -> s -> Either ParseError a Parsec.parse forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m (NonEmpty Char) parsec String "" String "a a" forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation `Hspec.shouldBe` forall a b. b -> Either a b Right (Char 'a' forall a. a -> [a] -> NonEmpty a NonEmpty.:| String "a") forall a. (HasCallStack, Example a) => String -> a -> SpecWith (Arg a) Hspec.it String "fails with none" forall a b. (a -> b) -> a -> b $ do forall s t a. Stream s Identity t => Parsec s () a -> String -> s -> Either ParseError a Parsec.parse forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m (NonEmpty Char) parsec String "" String "" forall a. (HasCallStack, Show a) => a -> (a -> Bool) -> Expectation `Hspec.shouldSatisfy` forall a b. Either a b -> Bool Either.isLeft