{-# LANGUAGE DeriveFunctor #-} module Test.Hspec.Core.Formatters.Pretty.Parser.Parser where import Prelude () import Test.Hspec.Core.Compat newtype Parser token a = Parser { forall token a. Parser token a -> [token] -> Maybe (a, [token]) runParser :: [token] -> Maybe (a, [token]) } deriving forall a b. a -> Parser token b -> Parser token a forall a b. (a -> b) -> Parser token a -> Parser token b forall token a b. a -> Parser token b -> Parser token a forall token a b. (a -> b) -> Parser token a -> Parser token b forall (f :: * -> *). (forall a b. (a -> b) -> f a -> f b) -> (forall a b. a -> f b -> f a) -> Functor f <$ :: forall a b. a -> Parser token b -> Parser token a $c<$ :: forall token a b. a -> Parser token b -> Parser token a fmap :: forall a b. (a -> b) -> Parser token a -> Parser token b $cfmap :: forall token a b. (a -> b) -> Parser token a -> Parser token b Functor instance Applicative (Parser token) where pure :: forall a. a -> Parser token a pure a a = forall token a. ([token] -> Maybe (a, [token])) -> Parser token a Parser forall a b. (a -> b) -> a -> b $ \ [token] input -> forall a. a -> Maybe a Just (a a, [token] input) <*> :: forall a b. Parser token (a -> b) -> Parser token a -> Parser token b (<*>) = forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b ap instance Monad (Parser token) where return :: forall a. a -> Parser token a return = forall (f :: * -> *) a. Applicative f => a -> f a pure Parser token a p1 >>= :: forall a b. Parser token a -> (a -> Parser token b) -> Parser token b >>= a -> Parser token b p2 = forall token a. ([token] -> Maybe (a, [token])) -> Parser token a Parser forall a b. (a -> b) -> a -> b $ forall token a. Parser token a -> [token] -> Maybe (a, [token]) runParser Parser token a p1 forall (m :: * -> *) a b c. Monad m => (a -> m b) -> (b -> m c) -> a -> m c >=> forall a b c. (a -> b -> c) -> (a, b) -> c uncurry (forall token a. Parser token a -> [token] -> Maybe (a, [token]) runParser forall b c a. (b -> c) -> (a -> b) -> a -> c . a -> Parser token b p2) instance Alternative (Parser token) where empty :: forall a. Parser token a empty = forall token a. ([token] -> Maybe (a, [token])) -> Parser token a Parser forall a b. (a -> b) -> a -> b $ forall a b. a -> b -> a const forall a. Maybe a Nothing Parser token a p1 <|> :: forall a. Parser token a -> Parser token a -> Parser token a <|> Parser token a p2 = forall token a. ([token] -> Maybe (a, [token])) -> Parser token a Parser forall a b. (a -> b) -> a -> b $ \ [token] input -> forall token a. Parser token a -> [token] -> Maybe (a, [token]) runParser Parser token a p1 [token] input forall (f :: * -> *) a. Alternative f => f a -> f a -> f a <|> forall token a. Parser token a -> [token] -> Maybe (a, [token]) runParser Parser token a p2 [token] input satisfy :: (token -> Bool) -> Parser token token satisfy :: forall token. (token -> Bool) -> Parser token token satisfy token -> Bool p = forall token a. ([token] -> Maybe (a, [token])) -> Parser token a Parser forall a b. (a -> b) -> a -> b $ \ [token] input -> case [token] input of token t : [token] ts | token -> Bool p token t -> forall a. a -> Maybe a Just (token t, [token] ts) [token] _ -> forall a. Maybe a Nothing sepBy :: Alternative m => m a -> m sep -> m [a] sepBy :: forall (m :: * -> *) a sep. Alternative m => m a -> m sep -> m [a] sepBy m a p m sep sep = forall (m :: * -> *) a sep. Alternative m => m a -> m sep -> m [a] sepBy1 m a p m sep sep forall (f :: * -> *) a. Alternative f => f a -> f a -> f a <|> forall (f :: * -> *) a. Applicative f => a -> f a pure [] sepBy1 :: Alternative m => m a -> m sep -> m [a] sepBy1 :: forall (m :: * -> *) a sep. Alternative m => m a -> m sep -> m [a] sepBy1 m a p m sep sep = (:) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> m a p forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> forall (f :: * -> *) a. Alternative f => f a -> f [a] many (m sep sep forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b *> m a p) readA :: (Alternative m, Read a) => String -> m a readA :: forall (m :: * -> *) a. (Alternative m, Read a) => String -> m a readA = forall b a. b -> (a -> b) -> Maybe a -> b maybe forall (f :: * -> *) a. Alternative f => f a empty forall (f :: * -> *) a. Applicative f => a -> f a pure forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a. Read a => String -> Maybe a readMaybe