binary-ext-2.0.3: An alternate with strong-typed errors for `Data.Binary.Get` monad from `binary` package.

Safe HaskellNone
LanguageHaskell2010

Data.Conduit.Parsers.Text.Parser

Synopsis

Documentation

class (MonadError e m_e, MonadError e' m_e') => MonadMapError e m_e e' m_e' | m_e -> e, m_e' -> e', m_e e' -> m_e', m_e' e -> m_e where Source #

Minimal complete definition

mapError

Methods

mapError :: (e -> e') -> m_e a -> m_e' a Source #

Instances
MonadMapError e (Either e) e' (Either e') Source # 
Instance details

Defined in Control.Monad.Error.Map

Methods

mapError :: (e -> e') -> Either e a -> Either e' a Source #

Monad m => MonadMapError e (ExceptT e m) e' (ExceptT e' m) Source # 
Instance details

Defined in Control.Monad.Error.Map

Methods

mapError :: (e -> e') -> ExceptT e m a -> ExceptT e' m a Source #

MonadMapError e m_e e' m_e' => MonadMapError e (ConduitT i o m_e) e' (ConduitT i o m_e') Source # 
Instance details

Defined in Control.Monad.Error.Map

Methods

mapError :: (e -> e') -> ConduitT i o m_e a -> ConduitT i o m_e' a Source #

Monad m => MonadMapError e (GetC s i e m) e' (GetC s i e' m) Source # 
Instance details

Defined in Data.Conduit.Parsers.GetC

Methods

mapError :: (e -> e') -> GetC s i e m a -> GetC s i e' m a Source #

(?=>>) :: (MonadMapError e m_e (Either e e') m_Either_e_e', MonadMapError Void m_Void (Either e e') m_Either_e_e', MonadMapError (Either e e') m_Either_e_e' e' m_e') => m_e a -> (e -> m_Void e') -> m_e' a infixl 1 Source #

(?>>) :: (MonadMapError () m_Unit (Maybe e) m_Maybe_e, MonadMapError Void m_Void (Maybe e) m_Maybe_e, MonadMapError (Maybe e) m_Maybe_e e m_e) => m_Unit a -> m_Void e -> m_e a infixl 1 Source #

type GetT s i o e m = ConduitT i o (GetC s i e m) Source #

A ConduitT with internal transformers supposed to a binary deserialization.

type Parser e a = forall s o m. (DefaultParsingState s, Monad m) => GetT s Text o e m a Source #

The shortening of GetT for the most common use case of text deserialization.

runParser :: Monad m => GetT TextOffset i o e m a -> ConduitT i o m (Either e a) Source #

Run a decoder presented as a Get monad. Returns decoder result and consumed bytes count.

charsRead :: (DecodingState s, DecodingElemsRead s, Monad m) => GetT s i o e m Word64 Source #

Get the total number of bytes read to this point.

linesRead :: (DecodingState s, DecodingLinesRead s, Monad m) => GetT s i o e m Word64 Source #

Get the total number of bytes read to this point.

columnsRead :: (DecodingState s, DecodingColumnsRead s, Monad m) => GetT s i o e m Word64 Source #

Get the total number of bytes read to this point.

castParser :: (DecodingState s, DecodingToken s ~ Text, Monad m) => Parser a -> GetT s Text o (NonEmpty String) m a Source #

Run the given Get monad from binary package and convert result into Get.

satisfyWith :: (Char -> a) -> (a -> Bool) -> Parser () a Source #

skip1 :: (Char -> Bool) -> Parser () () Source #

inClass :: String -> Char -> Bool #

Match any character in a set.

vowel = inClass "aeiou"

Range notation is supported.

halfAlphabet = inClass "a-nA-N"

To add a literal '-' to a set, place it at the beginning or end of the string.

notInClass :: String -> Char -> Bool #

Match any character not in a set.

skipWhile :: (Char -> Bool) -> Parser e () Source #

scan :: s -> (s -> Char -> Maybe s) -> Parser e Text Source #

runScanner :: s -> (s -> Char -> Maybe s) -> Parser e (Text, s) Source #

isEndOfLine :: Char -> Bool #

A predicate that matches either a carriage return '\r' or newline '\n' character.

isHorizontalSpace :: Char -> Bool #

A predicate that matches either a space ' ' or horizontal tab '\t' character.

choice :: Alternative f => [f a] -> f a #

choice ps tries to apply the actions in the list ps in order, until one of them succeeds. Returns the value of the succeeding action.

count :: Monad m => Int -> m a -> m [a] #

Apply the given action repeatedly, returning every result.

option'' :: (MonadPlus m_Unit, MonadMapError e m_e () m_Unit, MonadMapError () m_Unit e' m_e') => m_e a -> m_e' (Maybe a) Source #

many'' :: (MonadPlus m_Unit, MonadMapError e m_e () m_Unit, MonadMapError () m_Unit e' m_e') => m_e a -> m_e' [a] Source #

many1'' :: (MonadPlus m_Unit, MonadMapError e m_e () m_Unit, MonadMapError () m_Unit e m_e) => m_e a -> m_e (NonEmpty a) Source #

manyTill'' :: (MonadPlus m_Unit, MonadMapError e' m_e' () m_Unit, MonadMapError () m_Unit e m_e) => m_e a -> m_e' b -> m_e [a] Source #

sepBy'' :: (MonadPlus m_Unit, MonadMapError e m_e () m_Unit, MonadMapError () m_Unit e'' m_e'', MonadMapError e' m_e' () m_Unit, MonadMapError () m_Unit () m_Unit) => m_e a -> m_e' s -> m_e'' [a] Source #

sepBy1'' :: (MonadPlus m_Unit, MonadMapError e m_e () m_Unit, MonadMapError () m_Unit e m_e, MonadMapError e' m_e' () m_Unit, MonadMapError () m_Unit () m_Unit) => m_e a -> m_e' s -> m_e (NonEmpty a) Source #

skipMany'' :: (MonadPlus m_Unit, MonadMapError e m_e () m_Unit, MonadMapError () m_Unit e' m_e') => m_e a -> m_e' () Source #

skipMany1'' :: (MonadPlus m_Unit, MonadMapError e m_e () m_Unit, MonadMapError () m_Unit e m_e) => m_e a -> m_e () Source #

eitherP :: Alternative f => f a -> f b -> f (Either a b) #

Combine two alternatives.

matchP :: (DecodingState s, Monoid (DecodingToken s), Monad m) => GetT s (DecodingToken s) o e m a -> GetT s (DecodingToken s) o e m (DecodingToken s, a) Source #

tryP :: Monad m => GetT s i o e m a -> GetT s i o e m a Source #

Leftover consumed input on error.

pEnum :: (Eq a, Ord a, Enum a, Bounded a, Show a) => Int -> Parser () a Source #