input-parsers-0.2.3.2: Extension of the parsers library with more capability and efficiency
Safe HaskellNone
LanguageHaskell2010

Text.Parser.Deterministic

Description

Deterministic parsers can be restricted to succeed with a single parsing result.

Synopsis

Documentation

class Parsing m => DeterministicParsing m where Source #

Combinator methods for constructing deterministic parsers, i.e., parsers that can succeed with only a single result.

Minimal complete definition

Nothing

Methods

(<<|>) :: m a -> m a -> m a infixl 3 Source #

Left-biased choice: if the left alternative succeeds, the right one is never tried.

takeOptional :: m a -> m (Maybe a) Source #

Like optional, but never succeeds with Nothing if the argument parser can succeed.

takeMany :: m a -> m [a] Source #

Like many, but always consuming the longest matching sequence of input.

takeSome :: m a -> m [a] Source #

Like some, but always consuming the longest matching sequence of input.

concatAll :: Monoid a => m a -> m a Source #

Like concatMany, but always consuming the longest matching sequence of input.

skipAll :: m a -> m () Source #

Like skipMany, but always consuming the longest matching sequence of input.

Instances

Instances details
DeterministicParsing Parser Source # 
Instance details

Defined in Text.Parser.Deterministic

DeterministicParsing Parser Source # 
Instance details

Defined in Text.Parser.Deterministic

DeterministicParsing ReadP Source # 
Instance details

Defined in Text.Parser.Deterministic

DeterministicParsing (Strict Get) Source # 
Instance details

Defined in Text.Parser.Deterministic

DeterministicParsing (Lazy Get) Source # 
Instance details

Defined in Text.Parser.Deterministic

(Monad m, DeterministicParsing m) => DeterministicParsing (IdentityT m) Source # 
Instance details

Defined in Text.Parser.Deterministic

(MonadPlus m, DeterministicParsing m) => DeterministicParsing (ReaderT e m) Source # 
Instance details

Defined in Text.Parser.Deterministic

Methods

(<<|>) :: ReaderT e m a -> ReaderT e m a -> ReaderT e m a Source #

takeOptional :: ReaderT e m a -> ReaderT e m (Maybe a) Source #

takeMany :: ReaderT e m a -> ReaderT e m [a] Source #

takeSome :: ReaderT e m a -> ReaderT e m [a] Source #

concatAll :: Monoid a => ReaderT e m a -> ReaderT e m a Source #

skipAll :: ReaderT e m a -> ReaderT e m () Source #

(MonadPlus m, DeterministicParsing m, Monoid w) => DeterministicParsing (StateT w m) Source # 
Instance details

Defined in Text.Parser.Deterministic

Methods

(<<|>) :: StateT w m a -> StateT w m a -> StateT w m a Source #

takeOptional :: StateT w m a -> StateT w m (Maybe a) Source #

takeMany :: StateT w m a -> StateT w m [a] Source #

takeSome :: StateT w m a -> StateT w m [a] Source #

concatAll :: Monoid a => StateT w m a -> StateT w m a Source #

skipAll :: StateT w m a -> StateT w m () Source #

(MonadPlus m, DeterministicParsing m, Monoid w) => DeterministicParsing (StateT w m) Source # 
Instance details

Defined in Text.Parser.Deterministic

Methods

(<<|>) :: StateT w m a -> StateT w m a -> StateT w m a Source #

takeOptional :: StateT w m a -> StateT w m (Maybe a) Source #

takeMany :: StateT w m a -> StateT w m [a] Source #

takeSome :: StateT w m a -> StateT w m [a] Source #

concatAll :: Monoid a => StateT w m a -> StateT w m a Source #

skipAll :: StateT w m a -> StateT w m () Source #

(MonadPlus m, DeterministicParsing m, Monoid w) => DeterministicParsing (WriterT w m) Source # 
Instance details

Defined in Text.Parser.Deterministic

Methods

(<<|>) :: WriterT w m a -> WriterT w m a -> WriterT w m a Source #

takeOptional :: WriterT w m a -> WriterT w m (Maybe a) Source #

takeMany :: WriterT w m a -> WriterT w m [a] Source #

takeSome :: WriterT w m a -> WriterT w m [a] Source #

concatAll :: Monoid a => WriterT w m a -> WriterT w m a Source #

skipAll :: WriterT w m a -> WriterT w m () Source #

(MonadPlus m, DeterministicParsing m, Monoid w) => DeterministicParsing (WriterT w m) Source # 
Instance details

Defined in Text.Parser.Deterministic

Methods

(<<|>) :: WriterT w m a -> WriterT w m a -> WriterT w m a Source #

takeOptional :: WriterT w m a -> WriterT w m (Maybe a) Source #

takeMany :: WriterT w m a -> WriterT w m [a] Source #

takeSome :: WriterT w m a -> WriterT w m [a] Source #

concatAll :: Monoid a => WriterT w m a -> WriterT w m a Source #

skipAll :: WriterT w m a -> WriterT w m () Source #

(MonadPlus m, DeterministicParsing m, Monoid w) => DeterministicParsing (RWST r w s m) Source # 
Instance details

Defined in Text.Parser.Deterministic

Methods

(<<|>) :: RWST r w s m a -> RWST r w s m a -> RWST r w s m a Source #

takeOptional :: RWST r w s m a -> RWST r w s m (Maybe a) Source #

takeMany :: RWST r w s m a -> RWST r w s m [a] Source #

takeSome :: RWST r w s m a -> RWST r w s m [a] Source #

concatAll :: Monoid a => RWST r w s m a -> RWST r w s m a Source #

skipAll :: RWST r w s m a -> RWST r w s m () Source #

(MonadPlus m, DeterministicParsing m, Monoid w) => DeterministicParsing (RWST r w s m) Source # 
Instance details

Defined in Text.Parser.Deterministic

Methods

(<<|>) :: RWST r w s m a -> RWST r w s m a -> RWST r w s m a Source #

takeOptional :: RWST r w s m a -> RWST r w s m (Maybe a) Source #

takeMany :: RWST r w s m a -> RWST r w s m [a] Source #

takeSome :: RWST r w s m a -> RWST r w s m [a] Source #

concatAll :: Monoid a => RWST r w s m a -> RWST r w s m a Source #

skipAll :: RWST r w s m a -> RWST r w s m () Source #