{-# LANGUAGE GADTs, UndecidableInstances #-}
module Distribution.Compat.Parsing
(
choice
, option
, optional
, skipOptional
, between
, some
, many
, sepBy
, sepByNonEmpty
, sepEndByNonEmpty
, sepEndBy
, endByNonEmpty
, endBy
, count
, chainl
, chainr
, chainl1
, chainr1
, manyTill
, Parsing(..)
) where
import Prelude ()
import Distribution.Compat.Prelude
import Control.Applicative ((<**>), optional)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.State.Lazy as Lazy
import Control.Monad.Trans.State.Strict as Strict
import Control.Monad.Trans.Writer.Lazy as Lazy
import Control.Monad.Trans.Writer.Strict as Strict
import Control.Monad.Trans.RWS.Lazy as Lazy
import Control.Monad.Trans.RWS.Strict as Strict
import Control.Monad.Trans.Reader (ReaderT (..))
import Control.Monad.Trans.Identity (IdentityT (..))
import Data.Foldable (asum)
import qualified Data.List.NonEmpty as NE
import qualified Text.Parsec as Parsec
choice :: Alternative m => [m a] -> m a
choice :: [m a] -> m a
choice = [m a] -> m a
forall (t :: * -> *) (f :: * -> *) a.
(Foldable t, Alternative f) =>
t (f a) -> f a
Evidence bound by a type signature of the constraint type Alternative m
External instance of the constraint type Foldable []
asum
{-# INLINE choice #-}
option :: Alternative m => a -> m a -> m a
option :: a -> m a -> m a
option a
x m a
p = m a
p m a -> m a -> m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
Evidence bound by a type signature of the constraint type Alternative m
<|> a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a type signature of the constraint type Alternative m
pure a
x
{-# INLINE option #-}
skipOptional :: Alternative m => m a -> m ()
skipOptional :: m a -> m ()
skipOptional m a
p = (() () -> m a -> m ()
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a type signature of the constraint type Alternative m
<$ m a
p) m () -> m () -> m ()
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
Evidence bound by a type signature of the constraint type Alternative m
<|> () -> m ()
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a type signature of the constraint type Alternative m
pure ()
{-# INLINE skipOptional #-}
between :: Applicative m => m bra -> m ket -> m a -> m a
between :: m bra -> m ket -> m a -> m a
between m bra
bra m ket
ket m a
p = m bra
bra m bra -> m a -> m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
Evidence bound by a type signature of the constraint type Applicative m
*> m a
p m a -> m ket -> m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
Evidence bound by a type signature of the constraint type Applicative m
<* m ket
ket
{-# INLINE between #-}
sepBy :: Alternative m => m a -> m sep -> m [a]
sepBy :: m a -> m sep -> m [a]
sepBy m a
p m sep
sep = NonEmpty a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
External instance of the constraint type Foldable NonEmpty
toList (NonEmpty a -> [a]) -> m (NonEmpty a) -> m [a]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a type signature of the constraint type Alternative m
<$> m a -> m sep -> m (NonEmpty a)
forall (m :: * -> *) a sep.
Alternative m =>
m a -> m sep -> m (NonEmpty a)
Evidence bound by a type signature of the constraint type Alternative m
sepByNonEmpty m a
p m sep
sep m [a] -> m [a] -> m [a]
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
Evidence bound by a type signature of the constraint type Alternative m
<|> [a] -> m [a]
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a type signature of the constraint type Alternative m
pure []
{-# INLINE sepBy #-}
sepByNonEmpty :: Alternative m => m a -> m sep -> m (NonEmpty a)
sepByNonEmpty :: m a -> m sep -> m (NonEmpty a)
sepByNonEmpty m a
p m sep
sep = a -> [a] -> NonEmpty a
forall a. a -> [a] -> NonEmpty a
(:|) (a -> [a] -> NonEmpty a) -> m a -> m ([a] -> NonEmpty a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a type signature of the constraint type Alternative m
<$> m a
p m ([a] -> NonEmpty a) -> m [a] -> m (NonEmpty a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a type signature of the constraint type Alternative m
<*> m a -> m [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
Evidence bound by a type signature of the constraint type Alternative m
many (m sep
sep m sep -> m a -> m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a type signature of the constraint type Alternative m
*> m a
p)
{-# INLINE sepByNonEmpty #-}
sepEndByNonEmpty :: Alternative m => m a -> m sep -> m (NonEmpty a)
sepEndByNonEmpty :: m a -> m sep -> m (NonEmpty a)
sepEndByNonEmpty m a
p m sep
sep = a -> [a] -> NonEmpty a
forall a. a -> [a] -> NonEmpty a
(:|) (a -> [a] -> NonEmpty a) -> m a -> m ([a] -> NonEmpty a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a type signature of the constraint type Alternative m
<$> m a
p m ([a] -> NonEmpty a) -> m [a] -> m (NonEmpty a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a type signature of the constraint type Alternative m
<*> ((m sep
sep m sep -> m [a] -> m [a]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a type signature of the constraint type Alternative m
*> m a -> m sep -> m [a]
forall (m :: * -> *) a sep. Alternative m => m a -> m sep -> m [a]
Evidence bound by a type signature of the constraint type Alternative m
sepEndBy m a
p m sep
sep) m [a] -> m [a] -> m [a]
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
Evidence bound by a type signature of the constraint type Alternative m
<|> [a] -> m [a]
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a type signature of the constraint type Alternative m
pure [])
sepEndBy :: Alternative m => m a -> m sep -> m [a]
sepEndBy :: m a -> m sep -> m [a]
sepEndBy m a
p m sep
sep = NonEmpty a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
External instance of the constraint type Foldable NonEmpty
toList (NonEmpty a -> [a]) -> m (NonEmpty a) -> m [a]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a type signature of the constraint type Alternative m
<$> m a -> m sep -> m (NonEmpty a)
forall (m :: * -> *) a sep.
Alternative m =>
m a -> m sep -> m (NonEmpty a)
Evidence bound by a type signature of the constraint type Alternative m
sepEndByNonEmpty m a
p m sep
sep m [a] -> m [a] -> m [a]
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
Evidence bound by a type signature of the constraint type Alternative m
<|> [a] -> m [a]
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a type signature of the constraint type Alternative m
pure []
{-# INLINE sepEndBy #-}
endByNonEmpty :: Alternative m => m a -> m sep -> m (NonEmpty a)
endByNonEmpty :: m a -> m sep -> m (NonEmpty a)
endByNonEmpty m a
p m sep
sep = m a -> m (NonEmpty a)
forall (f :: * -> *) a. Alternative f => f a -> f (NonEmpty a)
Evidence bound by a type signature of the constraint type Alternative m
NE.some1 (m a
p m a -> m sep -> m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a type signature of the constraint type Alternative m
<* m sep
sep)
{-# INLINE endByNonEmpty #-}
endBy :: Alternative m => m a -> m sep -> m [a]
endBy :: m a -> m sep -> m [a]
endBy m a
p m sep
sep = m a -> m [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
Evidence bound by a type signature of the constraint type Alternative m
many (m a
p m a -> m sep -> m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a type signature of the constraint type Alternative m
<* m sep
sep)
{-# INLINE endBy #-}
count :: Applicative m => Int -> m a -> m [a]
count :: Int -> m a -> m [a]
count Int
n m a
p | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
<= Int
0 = [a] -> m [a]
forall (f :: * -> *) a. Applicative f => a -> f a
Evidence bound by a type signature of the constraint type Applicative m
pure []
| Bool
otherwise = [m a] -> m [a]
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
Evidence bound by a type signature of the constraint type Applicative m
External instance of the constraint type Traversable []
sequenceA (Int -> m a -> [m a]
forall a. Int -> a -> [a]
replicate Int
n m a
p)
{-# INLINE count #-}
chainr :: Alternative m => m a -> m (a -> a -> a) -> a -> m a
chainr :: m a -> m (a -> a -> a) -> a -> m a
chainr m a
p m (a -> a -> a)
op a
x = m a -> m (a -> a -> a) -> m a
forall (m :: * -> *) a.
Alternative m =>
m a -> m (a -> a -> a) -> m a
Evidence bound by a type signature of the constraint type Alternative m
chainr1 m a
p m (a -> a -> a)
op m a -> m a -> m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
Evidence bound by a type signature of the constraint type Alternative m
<|> a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a type signature of the constraint type Alternative m
pure a
x
{-# INLINE chainr #-}
chainl :: Alternative m => m a -> m (a -> a -> a) -> a -> m a
chainl :: m a -> m (a -> a -> a) -> a -> m a
chainl m a
p m (a -> a -> a)
op a
x = m a -> m (a -> a -> a) -> m a
forall (m :: * -> *) a.
Alternative m =>
m a -> m (a -> a -> a) -> m a
Evidence bound by a type signature of the constraint type Alternative m
chainl1 m a
p m (a -> a -> a)
op m a -> m a -> m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
Evidence bound by a type signature of the constraint type Alternative m
<|> a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a type signature of the constraint type Alternative m
pure a
x
{-# INLINE chainl #-}
chainl1 :: Alternative m => m a -> m (a -> a -> a) -> m a
chainl1 :: m a -> m (a -> a -> a) -> m a
chainl1 m a
p m (a -> a -> a)
op = m a
scan where
scan :: m a
scan = m a
p m a -> m (a -> a) -> m a
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a type signature of the constraint type Alternative m
<**> m (a -> a)
rst
rst :: m (a -> a)
rst = (\a -> a -> a
f a
y a -> a
g a
x -> a -> a
g (a -> a -> a
f a
x a
y)) ((a -> a -> a) -> a -> (a -> a) -> a -> a)
-> m (a -> a -> a) -> m (a -> (a -> a) -> a -> a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a type signature of the constraint type Alternative m
<$> m (a -> a -> a)
op m (a -> (a -> a) -> a -> a) -> m a -> m ((a -> a) -> a -> a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a type signature of the constraint type Alternative m
<*> m a
p m ((a -> a) -> a -> a) -> m (a -> a) -> m (a -> a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a type signature of the constraint type Alternative m
<*> m (a -> a)
rst m (a -> a) -> m (a -> a) -> m (a -> a)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
Evidence bound by a type signature of the constraint type Alternative m
<|> (a -> a) -> m (a -> a)
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a type signature of the constraint type Alternative m
pure a -> a
forall a. a -> a
id
{-# INLINE chainl1 #-}
chainr1 :: Alternative m => m a -> m (a -> a -> a) -> m a
chainr1 :: m a -> m (a -> a -> a) -> m a
chainr1 m a
p m (a -> a -> a)
op = m a
scan where
scan :: m a
scan = m a
p m a -> m (a -> a) -> m a
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a type signature of the constraint type Alternative m
<**> m (a -> a)
rst
rst :: m (a -> a)
rst = ((a -> a -> a) -> a -> a -> a
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((a -> a -> a) -> a -> a -> a)
-> m (a -> a -> a) -> m (a -> a -> a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a type signature of the constraint type Alternative m
<$> m (a -> a -> a)
op m (a -> a -> a) -> m a -> m (a -> a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a type signature of the constraint type Alternative m
<*> m a
scan) m (a -> a) -> m (a -> a) -> m (a -> a)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
Evidence bound by a type signature of the constraint type Alternative m
<|> (a -> a) -> m (a -> a)
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a type signature of the constraint type Alternative m
pure a -> a
forall a. a -> a
id
{-# INLINE chainr1 #-}
manyTill :: Alternative m => m a -> m end -> m [a]
manyTill :: m a -> m end -> m [a]
manyTill m a
p m end
end = m [a]
go where go :: m [a]
go = ([] [a] -> m end -> m [a]
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a type signature of the constraint type Alternative m
<$ m end
end) m [a] -> m [a] -> m [a]
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
Evidence bound by a type signature of the constraint type Alternative m
<|> ((:) (a -> [a] -> [a]) -> m a -> m ([a] -> [a])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a type signature of the constraint type Alternative m
<$> m a
p m ([a] -> [a]) -> m [a] -> m [a]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a type signature of the constraint type Alternative m
<*> m [a]
go)
{-# INLINE manyTill #-}
infixr 0 <?>
class Alternative m => Parsing m where
try :: m a -> m a
(<?>) :: m a -> String -> m a
skipMany :: m a -> m ()
skipMany m a
p = () () -> m [a] -> m ()
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a superclass of: Parsing of the constraint type forall (m :: * -> *). Parsing m => Alternative m
Evidence bound by a type signature of the constraint type Parsing m
<$ m a -> m [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
Evidence bound by a superclass of: Parsing of the constraint type forall (m :: * -> *). Parsing m => Alternative m
Evidence bound by a type signature of the constraint type Parsing m
many m a
p
{-# INLINE skipMany #-}
skipSome :: m a -> m ()
skipSome m a
p = m a
p m a -> m () -> m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a superclass of: Parsing of the constraint type forall (m :: * -> *). Parsing m => Alternative m
Evidence bound by a type signature of the constraint type Parsing m
*> m a -> m ()
forall (m :: * -> *) a. Parsing m => m a -> m ()
Evidence bound by a type signature of the constraint type Parsing m
skipMany m a
p
{-# INLINE skipSome #-}
unexpected :: String -> m a
eof :: m ()
notFollowedBy :: Show a => m a -> m ()
instance (Parsing m, MonadPlus m) => Parsing (Lazy.StateT s m) where
try :: StateT s m a -> StateT s m a
try (Lazy.StateT s -> m (a, s)
m) = (s -> m (a, s)) -> StateT s m a
forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
Lazy.StateT ((s -> m (a, s)) -> StateT s m a)
-> (s -> m (a, s)) -> StateT s m a
forall a b. (a -> b) -> a -> b
$ m (a, s) -> m (a, s)
forall (m :: * -> *) a. Parsing m => m a -> m a
Evidence bound by a type signature of the constraint type Parsing m
try (m (a, s) -> m (a, s)) -> (s -> m (a, s)) -> s -> m (a, s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. s -> m (a, s)
m
{-# INLINE try #-}
Lazy.StateT s -> m (a, s)
m <?> :: StateT s m a -> String -> StateT s m a
<?> String
l = (s -> m (a, s)) -> StateT s m a
forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
Lazy.StateT ((s -> m (a, s)) -> StateT s m a)
-> (s -> m (a, s)) -> StateT s m a
forall a b. (a -> b) -> a -> b
$ \s
s -> s -> m (a, s)
m s
s m (a, s) -> String -> m (a, s)
forall (m :: * -> *) a. Parsing m => m a -> String -> m a
Evidence bound by a type signature of the constraint type Parsing m
<?> String
l
{-# INLINE (<?>) #-}
unexpected :: String -> StateT s m a
unexpected = m a -> StateT s m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
Evidence bound by a type signature of the constraint type MonadPlus m
External instance of the constraint type forall s. MonadTrans (StateT s)
lift (m a -> StateT s m a) -> (String -> m a) -> String -> StateT s m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> m a
forall (m :: * -> *) a. Parsing m => String -> m a
Evidence bound by a type signature of the constraint type Parsing m
unexpected
{-# INLINE unexpected #-}
eof :: StateT s m ()
eof = m () -> StateT s m ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
Evidence bound by a type signature of the constraint type MonadPlus m
External instance of the constraint type forall s. MonadTrans (StateT s)
lift m ()
forall (m :: * -> *). Parsing m => m ()
Evidence bound by a type signature of the constraint type Parsing m
eof
{-# INLINE eof #-}
notFollowedBy :: StateT s m a -> StateT s m ()
notFollowedBy (Lazy.StateT s -> m (a, s)
m) = (s -> m ((), s)) -> StateT s m ()
forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
Lazy.StateT
((s -> m ((), s)) -> StateT s m ())
-> (s -> m ((), s)) -> StateT s m ()
forall a b. (a -> b) -> a -> b
$ \s
s -> m a -> m ()
forall (m :: * -> *) a. (Parsing m, Show a) => m a -> m ()
Evidence bound by a type signature of the constraint type Show a
Evidence bound by a type signature of the constraint type Parsing m
notFollowedBy ((a, s) -> a
forall a b. (a, b) -> a
fst ((a, s) -> a) -> m (a, s) -> m a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a superclass of: Parsing of the constraint type forall (m :: * -> *). Parsing m => Alternative m
Evidence bound by a type signature of the constraint type Parsing m
<$> s -> m (a, s)
m s
s) m () -> m ((), s) -> m ((), s)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
Evidence bound by a type signature of the constraint type MonadPlus m
>> ((), s) -> m ((), s)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
Evidence bound by a type signature of the constraint type MonadPlus m
return ((),s
s)
{-# INLINE notFollowedBy #-}
instance (Parsing m, MonadPlus m) => Parsing (Strict.StateT s m) where
try :: StateT s m a -> StateT s m a
try (Strict.StateT s -> m (a, s)
m) = (s -> m (a, s)) -> StateT s m a
forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
Strict.StateT ((s -> m (a, s)) -> StateT s m a)
-> (s -> m (a, s)) -> StateT s m a
forall a b. (a -> b) -> a -> b
$ m (a, s) -> m (a, s)
forall (m :: * -> *) a. Parsing m => m a -> m a
Evidence bound by a type signature of the constraint type Parsing m
try (m (a, s) -> m (a, s)) -> (s -> m (a, s)) -> s -> m (a, s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. s -> m (a, s)
m
{-# INLINE try #-}
Strict.StateT s -> m (a, s)
m <?> :: StateT s m a -> String -> StateT s m a
<?> String
l = (s -> m (a, s)) -> StateT s m a
forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
Strict.StateT ((s -> m (a, s)) -> StateT s m a)
-> (s -> m (a, s)) -> StateT s m a
forall a b. (a -> b) -> a -> b
$ \s
s -> s -> m (a, s)
m s
s m (a, s) -> String -> m (a, s)
forall (m :: * -> *) a. Parsing m => m a -> String -> m a
Evidence bound by a type signature of the constraint type Parsing m
<?> String
l
{-# INLINE (<?>) #-}
unexpected :: String -> StateT s m a
unexpected = m a -> StateT s m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
Evidence bound by a type signature of the constraint type MonadPlus m
External instance of the constraint type forall s. MonadTrans (StateT s)
lift (m a -> StateT s m a) -> (String -> m a) -> String -> StateT s m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> m a
forall (m :: * -> *) a. Parsing m => String -> m a
Evidence bound by a type signature of the constraint type Parsing m
unexpected
{-# INLINE unexpected #-}
eof :: StateT s m ()
eof = m () -> StateT s m ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
Evidence bound by a type signature of the constraint type MonadPlus m
External instance of the constraint type forall s. MonadTrans (StateT s)
lift m ()
forall (m :: * -> *). Parsing m => m ()
Evidence bound by a type signature of the constraint type Parsing m
eof
{-# INLINE eof #-}
notFollowedBy :: StateT s m a -> StateT s m ()
notFollowedBy (Strict.StateT s -> m (a, s)
m) = (s -> m ((), s)) -> StateT s m ()
forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
Strict.StateT
((s -> m ((), s)) -> StateT s m ())
-> (s -> m ((), s)) -> StateT s m ()
forall a b. (a -> b) -> a -> b
$ \s
s -> m a -> m ()
forall (m :: * -> *) a. (Parsing m, Show a) => m a -> m ()
Evidence bound by a type signature of the constraint type Show a
Evidence bound by a type signature of the constraint type Parsing m
notFollowedBy ((a, s) -> a
forall a b. (a, b) -> a
fst ((a, s) -> a) -> m (a, s) -> m a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a superclass of: Parsing of the constraint type forall (m :: * -> *). Parsing m => Alternative m
Evidence bound by a type signature of the constraint type Parsing m
<$> s -> m (a, s)
m s
s) m () -> m ((), s) -> m ((), s)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
Evidence bound by a type signature of the constraint type MonadPlus m
>> ((), s) -> m ((), s)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
Evidence bound by a type signature of the constraint type MonadPlus m
return ((),s
s)
{-# INLINE notFollowedBy #-}
instance (Parsing m, MonadPlus m) => Parsing (ReaderT e m) where
try :: ReaderT e m a -> ReaderT e m a
try (ReaderT e -> m a
m) = (e -> m a) -> ReaderT e m a
forall r (m :: * -> *) a. (r -> m a) -> ReaderT r m a
ReaderT ((e -> m a) -> ReaderT e m a) -> (e -> m a) -> ReaderT e m a
forall a b. (a -> b) -> a -> b
$ m a -> m a
forall (m :: * -> *) a. Parsing m => m a -> m a
Evidence bound by a type signature of the constraint type Parsing m
try (m a -> m a) -> (e -> m a) -> e -> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> m a
m
{-# INLINE try #-}
ReaderT e -> m a
m <?> :: ReaderT e m a -> String -> ReaderT e m a
<?> String
l = (e -> m a) -> ReaderT e m a
forall r (m :: * -> *) a. (r -> m a) -> ReaderT r m a
ReaderT ((e -> m a) -> ReaderT e m a) -> (e -> m a) -> ReaderT e m a
forall a b. (a -> b) -> a -> b
$ \e
e -> e -> m a
m e
e m a -> String -> m a
forall (m :: * -> *) a. Parsing m => m a -> String -> m a
Evidence bound by a type signature of the constraint type Parsing m
<?> String
l
{-# INLINE (<?>) #-}
skipMany :: ReaderT e m a -> ReaderT e m ()
skipMany (ReaderT e -> m a
m) = (e -> m ()) -> ReaderT e m ()
forall r (m :: * -> *) a. (r -> m a) -> ReaderT r m a
ReaderT ((e -> m ()) -> ReaderT e m ()) -> (e -> m ()) -> ReaderT e m ()
forall a b. (a -> b) -> a -> b
$ m a -> m ()
forall (m :: * -> *) a. Parsing m => m a -> m ()
Evidence bound by a type signature of the constraint type Parsing m
skipMany (m a -> m ()) -> (e -> m a) -> e -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> m a
m
{-# INLINE skipMany #-}
unexpected :: String -> ReaderT e m a
unexpected = m a -> ReaderT e m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
Evidence bound by a type signature of the constraint type MonadPlus m
External instance of the constraint type forall r. MonadTrans (ReaderT r)
lift (m a -> ReaderT e m a)
-> (String -> m a) -> String -> ReaderT e m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> m a
forall (m :: * -> *) a. Parsing m => String -> m a
Evidence bound by a type signature of the constraint type Parsing m
unexpected
{-# INLINE unexpected #-}
eof :: ReaderT e m ()
eof = m () -> ReaderT e m ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
Evidence bound by a type signature of the constraint type MonadPlus m
External instance of the constraint type forall r. MonadTrans (ReaderT r)
lift m ()
forall (m :: * -> *). Parsing m => m ()
Evidence bound by a type signature of the constraint type Parsing m
eof
{-# INLINE eof #-}
notFollowedBy :: ReaderT e m a -> ReaderT e m ()
notFollowedBy (ReaderT e -> m a
m) = (e -> m ()) -> ReaderT e m ()
forall r (m :: * -> *) a. (r -> m a) -> ReaderT r m a
ReaderT ((e -> m ()) -> ReaderT e m ()) -> (e -> m ()) -> ReaderT e m ()
forall a b. (a -> b) -> a -> b
$ m a -> m ()
forall (m :: * -> *) a. (Parsing m, Show a) => m a -> m ()
Evidence bound by a type signature of the constraint type Show a
Evidence bound by a type signature of the constraint type Parsing m
notFollowedBy (m a -> m ()) -> (e -> m a) -> e -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> m a
m
{-# INLINE notFollowedBy #-}
instance (Parsing m, MonadPlus m, Monoid w) => Parsing (Strict.WriterT w m) where
try :: WriterT w m a -> WriterT w m a
try (Strict.WriterT m (a, w)
m) = m (a, w) -> WriterT w m a
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
Strict.WriterT (m (a, w) -> WriterT w m a) -> m (a, w) -> WriterT w m a
forall a b. (a -> b) -> a -> b
$ m (a, w) -> m (a, w)
forall (m :: * -> *) a. Parsing m => m a -> m a
Evidence bound by a type signature of the constraint type Parsing m
try m (a, w)
m
{-# INLINE try #-}
Strict.WriterT m (a, w)
m <?> :: WriterT w m a -> String -> WriterT w m a
<?> String
l = m (a, w) -> WriterT w m a
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
Strict.WriterT (m (a, w)
m m (a, w) -> String -> m (a, w)
forall (m :: * -> *) a. Parsing m => m a -> String -> m a
Evidence bound by a type signature of the constraint type Parsing m
<?> String
l)
{-# INLINE (<?>) #-}
unexpected :: String -> WriterT w m a
unexpected = m a -> WriterT w m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
Evidence bound by a type signature of the constraint type MonadPlus m
External instance of the constraint type forall w. Monoid w => MonadTrans (WriterT w)
Evidence bound by a type signature of the constraint type Monoid w
lift (m a -> WriterT w m a)
-> (String -> m a) -> String -> WriterT w m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> m a
forall (m :: * -> *) a. Parsing m => String -> m a
Evidence bound by a type signature of the constraint type Parsing m
unexpected
{-# INLINE unexpected #-}
eof :: WriterT w m ()
eof = m () -> WriterT w m ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
Evidence bound by a type signature of the constraint type MonadPlus m
External instance of the constraint type forall w. Monoid w => MonadTrans (WriterT w)
Evidence bound by a type signature of the constraint type Monoid w
lift m ()
forall (m :: * -> *). Parsing m => m ()
Evidence bound by a type signature of the constraint type Parsing m
eof
{-# INLINE eof #-}
notFollowedBy :: WriterT w m a -> WriterT w m ()
notFollowedBy (Strict.WriterT m (a, w)
m) = m ((), w) -> WriterT w m ()
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
Strict.WriterT
(m ((), w) -> WriterT w m ()) -> m ((), w) -> WriterT w m ()
forall a b. (a -> b) -> a -> b
$ m a -> m ()
forall (m :: * -> *) a. (Parsing m, Show a) => m a -> m ()
Evidence bound by a type signature of the constraint type Show a
Evidence bound by a type signature of the constraint type Parsing m
notFollowedBy ((a, w) -> a
forall a b. (a, b) -> a
fst ((a, w) -> a) -> m (a, w) -> m a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a superclass of: Parsing of the constraint type forall (m :: * -> *). Parsing m => Alternative m
Evidence bound by a type signature of the constraint type Parsing m
<$> m (a, w)
m) m () -> (() -> m ((), w)) -> m ((), w)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
Evidence bound by a type signature of the constraint type MonadPlus m
>>= \()
x -> ((), w) -> m ((), w)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
Evidence bound by a type signature of the constraint type MonadPlus m
return (()
x, w
forall a. Monoid a => a
Evidence bound by a type signature of the constraint type Monoid w
mempty)
{-# INLINE notFollowedBy #-}
instance (Parsing m, MonadPlus m, Monoid w) => Parsing (Lazy.WriterT w m) where
try :: WriterT w m a -> WriterT w m a
try (Lazy.WriterT m (a, w)
m) = m (a, w) -> WriterT w m a
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
Lazy.WriterT (m (a, w) -> WriterT w m a) -> m (a, w) -> WriterT w m a
forall a b. (a -> b) -> a -> b
$ m (a, w) -> m (a, w)
forall (m :: * -> *) a. Parsing m => m a -> m a
Evidence bound by a type signature of the constraint type Parsing m
try m (a, w)
m
{-# INLINE try #-}
Lazy.WriterT m (a, w)
m <?> :: WriterT w m a -> String -> WriterT w m a
<?> String
l = m (a, w) -> WriterT w m a
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
Lazy.WriterT (m (a, w)
m m (a, w) -> String -> m (a, w)
forall (m :: * -> *) a. Parsing m => m a -> String -> m a
Evidence bound by a type signature of the constraint type Parsing m
<?> String
l)
{-# INLINE (<?>) #-}
unexpected :: String -> WriterT w m a
unexpected = m a -> WriterT w m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
Evidence bound by a type signature of the constraint type MonadPlus m
External instance of the constraint type forall w. Monoid w => MonadTrans (WriterT w)
Evidence bound by a type signature of the constraint type Monoid w
lift (m a -> WriterT w m a)
-> (String -> m a) -> String -> WriterT w m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> m a
forall (m :: * -> *) a. Parsing m => String -> m a
Evidence bound by a type signature of the constraint type Parsing m
unexpected
{-# INLINE unexpected #-}
eof :: WriterT w m ()
eof = m () -> WriterT w m ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
Evidence bound by a type signature of the constraint type MonadPlus m
External instance of the constraint type forall w. Monoid w => MonadTrans (WriterT w)
Evidence bound by a type signature of the constraint type Monoid w
lift m ()
forall (m :: * -> *). Parsing m => m ()
Evidence bound by a type signature of the constraint type Parsing m
eof
{-# INLINE eof #-}
notFollowedBy :: WriterT w m a -> WriterT w m ()
notFollowedBy (Lazy.WriterT m (a, w)
m) = m ((), w) -> WriterT w m ()
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
Lazy.WriterT
(m ((), w) -> WriterT w m ()) -> m ((), w) -> WriterT w m ()
forall a b. (a -> b) -> a -> b
$ m a -> m ()
forall (m :: * -> *) a. (Parsing m, Show a) => m a -> m ()
Evidence bound by a type signature of the constraint type Show a
Evidence bound by a type signature of the constraint type Parsing m
notFollowedBy ((a, w) -> a
forall a b. (a, b) -> a
fst ((a, w) -> a) -> m (a, w) -> m a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a superclass of: Parsing of the constraint type forall (m :: * -> *). Parsing m => Alternative m
Evidence bound by a type signature of the constraint type Parsing m
<$> m (a, w)
m) m () -> (() -> m ((), w)) -> m ((), w)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
Evidence bound by a type signature of the constraint type MonadPlus m
>>= \()
x -> ((), w) -> m ((), w)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
Evidence bound by a type signature of the constraint type MonadPlus m
return (()
x, w
forall a. Monoid a => a
Evidence bound by a type signature of the constraint type Monoid w
mempty)
{-# INLINE notFollowedBy #-}
instance (Parsing m, MonadPlus m, Monoid w) => Parsing (Lazy.RWST r w s m) where
try :: RWST r w s m a -> RWST r w s m a
try (Lazy.RWST r -> s -> m (a, s, w)
m) = (r -> s -> m (a, s, w)) -> RWST r w s m a
forall r w s (m :: * -> *) a.
(r -> s -> m (a, s, w)) -> RWST r w s m a
Lazy.RWST ((r -> s -> m (a, s, w)) -> RWST r w s m a)
-> (r -> s -> m (a, s, w)) -> RWST r w s m a
forall a b. (a -> b) -> a -> b
$ \r
r s
s -> m (a, s, w) -> m (a, s, w)
forall (m :: * -> *) a. Parsing m => m a -> m a
Evidence bound by a type signature of the constraint type Parsing m
try (r -> s -> m (a, s, w)
m r
r s
s)
{-# INLINE try #-}
Lazy.RWST r -> s -> m (a, s, w)
m <?> :: RWST r w s m a -> String -> RWST r w s m a
<?> String
l = (r -> s -> m (a, s, w)) -> RWST r w s m a
forall r w s (m :: * -> *) a.
(r -> s -> m (a, s, w)) -> RWST r w s m a
Lazy.RWST ((r -> s -> m (a, s, w)) -> RWST r w s m a)
-> (r -> s -> m (a, s, w)) -> RWST r w s m a
forall a b. (a -> b) -> a -> b
$ \r
r s
s -> r -> s -> m (a, s, w)
m r
r s
s m (a, s, w) -> String -> m (a, s, w)
forall (m :: * -> *) a. Parsing m => m a -> String -> m a
Evidence bound by a type signature of the constraint type Parsing m
<?> String
l
{-# INLINE (<?>) #-}
unexpected :: String -> RWST r w s m a
unexpected = m a -> RWST r w s m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
Evidence bound by a type signature of the constraint type MonadPlus m
External instance of the constraint type forall w r s. Monoid w => MonadTrans (RWST r w s)
Evidence bound by a type signature of the constraint type Monoid w
lift (m a -> RWST r w s m a)
-> (String -> m a) -> String -> RWST r w s m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> m a
forall (m :: * -> *) a. Parsing m => String -> m a
Evidence bound by a type signature of the constraint type Parsing m
unexpected
{-# INLINE unexpected #-}
eof :: RWST r w s m ()
eof = m () -> RWST r w s m ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
Evidence bound by a type signature of the constraint type MonadPlus m
External instance of the constraint type forall w r s. Monoid w => MonadTrans (RWST r w s)
Evidence bound by a type signature of the constraint type Monoid w
lift m ()
forall (m :: * -> *). Parsing m => m ()
Evidence bound by a type signature of the constraint type Parsing m
eof
{-# INLINE eof #-}
notFollowedBy :: RWST r w s m a -> RWST r w s m ()
notFollowedBy (Lazy.RWST r -> s -> m (a, s, w)
m) = (r -> s -> m ((), s, w)) -> RWST r w s m ()
forall r w s (m :: * -> *) a.
(r -> s -> m (a, s, w)) -> RWST r w s m a
Lazy.RWST
((r -> s -> m ((), s, w)) -> RWST r w s m ())
-> (r -> s -> m ((), s, w)) -> RWST r w s m ()
forall a b. (a -> b) -> a -> b
$ \r
r s
s -> m a -> m ()
forall (m :: * -> *) a. (Parsing m, Show a) => m a -> m ()
Evidence bound by a type signature of the constraint type Show a
Evidence bound by a type signature of the constraint type Parsing m
notFollowedBy ((\(a
a,s
_,w
_) -> a
a) ((a, s, w) -> a) -> m (a, s, w) -> m a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a superclass of: Parsing of the constraint type forall (m :: * -> *). Parsing m => Alternative m
Evidence bound by a type signature of the constraint type Parsing m
<$> r -> s -> m (a, s, w)
m r
r s
s) m () -> (() -> m ((), s, w)) -> m ((), s, w)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
Evidence bound by a type signature of the constraint type MonadPlus m
>>= \()
x -> ((), s, w) -> m ((), s, w)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
Evidence bound by a type signature of the constraint type MonadPlus m
return (()
x, s
s, w
forall a. Monoid a => a
Evidence bound by a type signature of the constraint type Monoid w
mempty)
{-# INLINE notFollowedBy #-}
instance (Parsing m, MonadPlus m, Monoid w) => Parsing (Strict.RWST r w s m) where
try :: RWST r w s m a -> RWST r w s m a
try (Strict.RWST r -> s -> m (a, s, w)
m) = (r -> s -> m (a, s, w)) -> RWST r w s m a
forall r w s (m :: * -> *) a.
(r -> s -> m (a, s, w)) -> RWST r w s m a
Strict.RWST ((r -> s -> m (a, s, w)) -> RWST r w s m a)
-> (r -> s -> m (a, s, w)) -> RWST r w s m a
forall a b. (a -> b) -> a -> b
$ \r
r s
s -> m (a, s, w) -> m (a, s, w)
forall (m :: * -> *) a. Parsing m => m a -> m a
Evidence bound by a type signature of the constraint type Parsing m
try (r -> s -> m (a, s, w)
m r
r s
s)
{-# INLINE try #-}
Strict.RWST r -> s -> m (a, s, w)
m <?> :: RWST r w s m a -> String -> RWST r w s m a
<?> String
l = (r -> s -> m (a, s, w)) -> RWST r w s m a
forall r w s (m :: * -> *) a.
(r -> s -> m (a, s, w)) -> RWST r w s m a
Strict.RWST ((r -> s -> m (a, s, w)) -> RWST r w s m a)
-> (r -> s -> m (a, s, w)) -> RWST r w s m a
forall a b. (a -> b) -> a -> b
$ \r
r s
s -> r -> s -> m (a, s, w)
m r
r s
s m (a, s, w) -> String -> m (a, s, w)
forall (m :: * -> *) a. Parsing m => m a -> String -> m a
Evidence bound by a type signature of the constraint type Parsing m
<?> String
l
{-# INLINE (<?>) #-}
unexpected :: String -> RWST r w s m a
unexpected = m a -> RWST r w s m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
Evidence bound by a type signature of the constraint type MonadPlus m
External instance of the constraint type forall w r s. Monoid w => MonadTrans (RWST r w s)
Evidence bound by a type signature of the constraint type Monoid w
lift (m a -> RWST r w s m a)
-> (String -> m a) -> String -> RWST r w s m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> m a
forall (m :: * -> *) a. Parsing m => String -> m a
Evidence bound by a type signature of the constraint type Parsing m
unexpected
{-# INLINE unexpected #-}
eof :: RWST r w s m ()
eof = m () -> RWST r w s m ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
Evidence bound by a type signature of the constraint type MonadPlus m
External instance of the constraint type forall w r s. Monoid w => MonadTrans (RWST r w s)
Evidence bound by a type signature of the constraint type Monoid w
lift m ()
forall (m :: * -> *). Parsing m => m ()
Evidence bound by a type signature of the constraint type Parsing m
eof
{-# INLINE eof #-}
notFollowedBy :: RWST r w s m a -> RWST r w s m ()
notFollowedBy (Strict.RWST r -> s -> m (a, s, w)
m) = (r -> s -> m ((), s, w)) -> RWST r w s m ()
forall r w s (m :: * -> *) a.
(r -> s -> m (a, s, w)) -> RWST r w s m a
Strict.RWST
((r -> s -> m ((), s, w)) -> RWST r w s m ())
-> (r -> s -> m ((), s, w)) -> RWST r w s m ()
forall a b. (a -> b) -> a -> b
$ \r
r s
s -> m a -> m ()
forall (m :: * -> *) a. (Parsing m, Show a) => m a -> m ()
Evidence bound by a type signature of the constraint type Show a
Evidence bound by a type signature of the constraint type Parsing m
notFollowedBy ((\(a
a,s
_,w
_) -> a
a) ((a, s, w) -> a) -> m (a, s, w) -> m a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
Evidence bound by a superclass of: Parsing of the constraint type forall (m :: * -> *). Parsing m => Alternative m
Evidence bound by a type signature of the constraint type Parsing m
<$> r -> s -> m (a, s, w)
m r
r s
s) m () -> (() -> m ((), s, w)) -> m ((), s, w)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
Evidence bound by a type signature of the constraint type MonadPlus m
>>= \()
x -> ((), s, w) -> m ((), s, w)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
Evidence bound by a type signature of the constraint type MonadPlus m
return (()
x, s
s, w
forall a. Monoid a => a
Evidence bound by a type signature of the constraint type Monoid w
mempty)
{-# INLINE notFollowedBy #-}
instance (Parsing m, Monad m) => Parsing (IdentityT m) where
try :: IdentityT m a -> IdentityT m a
try = m a -> IdentityT m a
forall {k} (f :: k -> *) (a :: k). f a -> IdentityT f a
IdentityT (m a -> IdentityT m a)
-> (IdentityT m a -> m a) -> IdentityT m a -> IdentityT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m a -> m a
forall (m :: * -> *) a. Parsing m => m a -> m a
Evidence bound by a type signature of the constraint type Parsing m
try (m a -> m a) -> (IdentityT m a -> m a) -> IdentityT m a -> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IdentityT m a -> m a
forall {k} (f :: k -> *) (a :: k). IdentityT f a -> f a
runIdentityT
{-# INLINE try #-}
IdentityT m a
m <?> :: IdentityT m a -> String -> IdentityT m a
<?> String
l = m a -> IdentityT m a
forall {k} (f :: k -> *) (a :: k). f a -> IdentityT f a
IdentityT (m a
m m a -> String -> m a
forall (m :: * -> *) a. Parsing m => m a -> String -> m a
Evidence bound by a type signature of the constraint type Parsing m
<?> String
l)
{-# INLINE (<?>) #-}
skipMany :: IdentityT m a -> IdentityT m ()
skipMany = m () -> IdentityT m ()
forall {k} (f :: k -> *) (a :: k). f a -> IdentityT f a
IdentityT (m () -> IdentityT m ())
-> (IdentityT m a -> m ()) -> IdentityT m a -> IdentityT m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m a -> m ()
forall (m :: * -> *) a. Parsing m => m a -> m ()
Evidence bound by a type signature of the constraint type Parsing m
skipMany (m a -> m ()) -> (IdentityT m a -> m a) -> IdentityT m a -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IdentityT m a -> m a
forall {k} (f :: k -> *) (a :: k). IdentityT f a -> f a
runIdentityT
{-# INLINE skipMany #-}
unexpected :: String -> IdentityT m a
unexpected = m a -> IdentityT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
Evidence bound by a type signature of the constraint type Monad m
External instance of the constraint type MonadTrans IdentityT
lift (m a -> IdentityT m a)
-> (String -> m a) -> String -> IdentityT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> m a
forall (m :: * -> *) a. Parsing m => String -> m a
Evidence bound by a type signature of the constraint type Parsing m
unexpected
{-# INLINE unexpected #-}
eof :: IdentityT m ()
eof = m () -> IdentityT m ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
Evidence bound by a type signature of the constraint type Monad m
External instance of the constraint type MonadTrans IdentityT
lift m ()
forall (m :: * -> *). Parsing m => m ()
Evidence bound by a type signature of the constraint type Parsing m
eof
{-# INLINE eof #-}
notFollowedBy :: IdentityT m a -> IdentityT m ()
notFollowedBy (IdentityT m a
m) = m () -> IdentityT m ()
forall {k} (f :: k -> *) (a :: k). f a -> IdentityT f a
IdentityT (m () -> IdentityT m ()) -> m () -> IdentityT m ()
forall a b. (a -> b) -> a -> b
$ m a -> m ()
forall (m :: * -> *) a. (Parsing m, Show a) => m a -> m ()
Evidence bound by a type signature of the constraint type Show a
Evidence bound by a type signature of the constraint type Parsing m
notFollowedBy m a
m
{-# INLINE notFollowedBy #-}
instance (Parsec.Stream s m t, Show t) => Parsing (Parsec.ParsecT s u m) where
try :: ParsecT s u m a -> ParsecT s u m a
try = ParsecT s u m a -> ParsecT s u m a
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
Parsec.try
<?> :: ParsecT s u m a -> String -> ParsecT s u m a
(<?>) = ParsecT s u m a -> String -> ParsecT s u m a
forall s u (m :: * -> *) a.
ParsecT s u m a -> String -> ParsecT s u m a
(Parsec.<?>)
skipMany :: ParsecT s u m a -> ParsecT s u m ()
skipMany = ParsecT s u m a -> ParsecT s u m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
Parsec.skipMany
skipSome :: ParsecT s u m a -> ParsecT s u m ()
skipSome = ParsecT s u m a -> ParsecT s u m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
Evidence bound by a type signature of the constraint type Stream s m t
Parsec.skipMany1
unexpected :: String -> ParsecT s u m a
unexpected = String -> ParsecT s u m a
forall s (m :: * -> *) t u a.
Stream s m t =>
String -> ParsecT s u m a
Evidence bound by a type signature of the constraint type Stream s m t
Parsec.unexpected
eof :: ParsecT s u m ()
eof = ParsecT s u m ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
Evidence bound by a type signature of the constraint type Show t
Evidence bound by a type signature of the constraint type Stream s m t
Parsec.eof
notFollowedBy :: ParsecT s u m a -> ParsecT s u m ()
notFollowedBy = ParsecT s u m a -> ParsecT s u m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
Evidence bound by a type signature of the constraint type Show a
Evidence bound by a type signature of the constraint type Stream s m t
Parsec.notFollowedBy