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

Safe HaskellNone
LanguageHaskell2010

Data.Conduit.Parsers.GetC

Description

This module provides the GetC monad transformer, and all functions, which could not be defined using GetC public interface only.

Synopsis

Documentation

class DecodingState s where Source #

Minimal complete definition

decoded

Associated Types

type DecodingToken s :: * Source #

Methods

decoded :: DecodingToken s -> s -> s Source #

data Decoding s i Source #

GetC monad state.

Instances
(DecodingState s, DecodingToken s ~ i) => DecodingState (Decoding s i) Source # 
Instance details

Defined in Data.Conduit.Parsers.GetC

Associated Types

type DecodingToken (Decoding s i) :: * Source #

Methods

decoded :: DecodingToken (Decoding s i) -> Decoding s i -> Decoding s i Source #

(DecodingState s, DecodingElemsRead s) => DecodingElemsRead (Decoding s i) Source # 
Instance details

Defined in Data.Conduit.Parsers

(DecodingState s, DecodingColumnsRead s) => DecodingColumnsRead (Decoding s i) Source # 
Instance details

Defined in Data.Conduit.Parsers.Text

(DecodingState s, DecodingLinesRead s) => DecodingLinesRead (Decoding s i) Source # 
Instance details

Defined in Data.Conduit.Parsers.Text

type DecodingToken (Decoding s i) Source # 
Instance details

Defined in Data.Conduit.Parsers.GetC

startDecoding :: s -> Decoding s i Source #

Construct GetC initial state.

continueDecoding :: s -> [i] -> Decoding s i -> Decoding s i Source #

Adjust GetC state. This is low-level function, not supposed to directly use.

decodingRead :: Decoding s i -> s Source #

Get the total number of bytes read to this point.

data GetC s i e m a Source #

Internal transformers for GetT with error type e, base monad m, and decoder result a.

Instances
MonadBase b m => MonadBase b (GetC s i e m) Source # 
Instance details

Defined in Data.Conduit.Parsers.GetC

Methods

liftBase :: b α -> GetC s i e m α #

MonadBaseControl b m => MonadBaseControl b (GetC s i e m) Source # 
Instance details

Defined in Data.Conduit.Parsers.GetC

Associated Types

type StM (GetC s i e m) a :: * #

Methods

liftBaseWith :: (RunInBase (GetC s i e m) b -> b a) -> GetC s i e m a #

restoreM :: StM (GetC s i e m) a -> GetC s i e m a #

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

Defined in Data.Conduit.Parsers.GetC

Methods

throwError :: e -> GetC s i e m a #

catchError :: GetC s i e m a -> (e -> GetC s i e m a) -> GetC s i e m a #

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 #

MonadTrans (GetC s i e) Source # 
Instance details

Defined in Data.Conduit.Parsers.GetC

Methods

lift :: Monad m => m a -> GetC s i e m a #

MonadTransControl (GetC s i e) Source # 
Instance details

Defined in Data.Conduit.Parsers.GetC

Associated Types

type StT (GetC s i e) a :: * #

Methods

liftWith :: Monad m => (Run (GetC s i e) -> m a) -> GetC s i e m a #

restoreT :: Monad m => m (StT (GetC s i e) a) -> GetC s i e m a #

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

Defined in Data.Conduit.Parsers.GetC

Methods

(>>=) :: GetC s i e m a -> (a -> GetC s i e m b) -> GetC s i e m b #

(>>) :: GetC s i e m a -> GetC s i e m b -> GetC s i e m b #

return :: a -> GetC s i e m a #

fail :: String -> GetC s i e m a #

Functor m => Functor (GetC s i e m) Source # 
Instance details

Defined in Data.Conduit.Parsers.GetC

Methods

fmap :: (a -> b) -> GetC s i e m a -> GetC s i e m b #

(<$) :: a -> GetC s i e m b -> GetC s i e m a #

MonadFix m => MonadFix (GetC s i e m) Source # 
Instance details

Defined in Data.Conduit.Parsers.GetC

Methods

mfix :: (a -> GetC s i e m a) -> GetC s i e m a #

MonadFail m => MonadFail (GetC s i e m) Source # 
Instance details

Defined in Data.Conduit.Parsers.GetC

Methods

fail :: String -> GetC s i e m a #

(Functor m, Monad m) => Applicative (GetC s i e m) Source # 
Instance details

Defined in Data.Conduit.Parsers.GetC

Methods

pure :: a -> GetC s i e m a #

(<*>) :: GetC s i e m (a -> b) -> GetC s i e m a -> GetC s i e m b #

liftA2 :: (a -> b -> c) -> GetC s i e m a -> GetC s i e m b -> GetC s i e m c #

(*>) :: GetC s i e m a -> GetC s i e m b -> GetC s i e m b #

(<*) :: GetC s i e m a -> GetC s i e m b -> GetC s i e m a #

(Functor m, Monad m, Monoid e) => Alternative (GetC s i e m) Source # 
Instance details

Defined in Data.Conduit.Parsers.GetC

Methods

empty :: GetC s i e m a #

(<|>) :: GetC s i e m a -> GetC s i e m a -> GetC s i e m a #

some :: GetC s i e m a -> GetC s i e m [a] #

many :: GetC s i e m a -> GetC s i e m [a] #

(Monad m, Monoid e) => MonadPlus (GetC s i e m) Source # 
Instance details

Defined in Data.Conduit.Parsers.GetC

Methods

mzero :: GetC s i e m a #

mplus :: GetC s i e m a -> GetC s i e m a -> GetC s i e m a #

MonadIO m => MonadIO (GetC s i e m) Source # 
Instance details

Defined in Data.Conduit.Parsers.GetC

Methods

liftIO :: IO a -> GetC s i e m a #

(Monoid e, Monad m) => Alternative (GetT s i o e m) Source # 
Instance details

Defined in Data.Conduit.Parsers.GetC

Methods

empty :: GetT s i o e m a #

(<|>) :: GetT s i o e m a -> GetT s i o e m a -> GetT s i o e m a #

some :: GetT s i o e m a -> GetT s i o e m [a] #

many :: GetT s i o e m a -> GetT s i o e m [a] #

(Monoid e, Monad m) => MonadPlus (GetT s i o e m) Source # 
Instance details

Defined in Data.Conduit.Parsers.GetC

Methods

mzero :: GetT s i o e m a #

mplus :: GetT s i o e m a -> GetT s i o e m a -> GetT s i o e m a #

type StT (GetC s i e) a Source # 
Instance details

Defined in Data.Conduit.Parsers.GetC

type StT (GetC s i e) a = StT (StateT (Decoding s i)) (StT (ExceptT e) a)
type StM (GetC s i e m) a Source # 
Instance details

Defined in Data.Conduit.Parsers.GetC

type StM (GetC s i e m) a = ComposeSt (GetC s i e) m a

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.

runGetC :: Monad m => Decoding s i -> GetT s i o e m a -> ConduitT i o m (Either e a, Decoding s i) Source #

Run a GetT monad, unwrapping all internal transformers in a reversible way.

getC . flip runGetC = id

getC :: Monad m => (Decoding s i -> ConduitT i o m (Either e a, Decoding s i)) -> GetT s i o e m a Source #

Custom GetT.

getC . flip runGetC = id

Example (Get is a shortening of GetT):

skipUntilZero :: Get e Bool
skipUntilZero = getC $ flip runStateC $ untilJust $ do
  !m_inp <- await
  case m_inp of
    Nothing -> return $ Just $ Right False
    Just !inp -> do
      case SB.elemIndex 0 inp of
        Nothing -> do
          lift $ modify' $ decoded inp
          return Nothing
        Just !i -> do
          let (!h, !t) = SB.splitAt i inp
          leftover t
          lift $ modify' $ decoded h
          return $ Just $ Right True

trackP :: Monad m => GetT s i o e m a -> GetT s i o ([i], e) m ([i], a) Source #

Run a decoder, storing input stream.

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

Leftover consumed input on error.

maybeG :: Monad m => GetT s i o e m (Maybe a) -> GetT s i o e (ExceptT (Decoding s i) m) a Source #

Wrap the base monad in ExceptT, pushing Maybe to a monad transformers stack.

runMaybeG :: Monad m => GetT s i o e (ExceptT (Decoding s i) m) a -> GetT s i o e m (Maybe a) Source #

Run ExceptT in the base monad, pulling Maybe from a monad transformers stack.

exceptG :: Monad m => GetT s i o e' m (Either e a) -> GetT s i o e' (ExceptT (e, Decoding s i) m) a Source #

Wrap the base monad in ExceptT, pushing Either to a monad transformers stack.

runExceptG :: Monad m => GetT s i o e' (ExceptT (e, Decoding s i) m) a -> GetT s i o e' m (Either e a) Source #

Run ExceptT in the base monad, pulling Either from a monad transformers stack.

catchExceptG :: Monad m => GetT s i o e' (ExceptT (e, Decoding s i) m) r -> (e -> GetT s i o e' (ExceptT (e, Decoding s i) m) r) -> GetT s i o e' (ExceptT (e, Decoding s i) m) r Source #

Catch an error in the base monad.

readerG :: Monad m => (r -> GetT s i o e m a) -> GetT s i o e (ReaderT r m) a Source #

Wrap the base monad in ReaderT.

runReaderG :: Monad m => r -> GetT s i o e (ReaderT r m) a -> GetT s i o e m a Source #

Run ReaderT in the base monad.

stateLG :: Monad m => (t -> GetT s i o e m (a, t)) -> GetT s i o e (StateT t m) a Source #

Wrap the base monad in StateT.

runStateLG :: Monad m => t -> GetT s i o e (StateT t m) a -> GetT s i o e m (a, t) Source #

Run StateT in the base monad.

evalStateLG :: Monad m => t -> GetT s i o e (StateT t m) a -> GetT s i o e m a Source #

Evaluate StateT in the base monad.

execStateLG :: Monad m => t -> GetT s i o e (StateT t m) a -> GetT s i o e m t Source #

Execute StateT in the base monad.

stateG :: Monad m => (t -> GetT s i o e m (a, t)) -> GetT s i o e (StateT t m) a Source #

Wrap the base monad in StateT.

runStateG :: Monad m => t -> GetT s i o e (StateT t m) a -> GetT s i o e m (a, t) Source #

Run StateT in the base monad.

evalStateG :: Monad m => t -> GetT s i o e (StateT t m) a -> GetT s i o e m a Source #

Evaluate StateT in the base monad.

execStateG :: Monad m => t -> GetT s i o e (StateT t m) a -> GetT s i o e m t Source #

Execute StateT in the base monad.

writerLG :: (Monad m, Monoid t) => GetT s i o e m (a, t) -> GetT s i o e (WriterT t m) a Source #

Wrap the base monad in WriterT.

runWriterLG :: (Monad m, Monoid t) => GetT s i o e (WriterT t m) a -> GetT s i o e m (a, t) Source #

Run WriterT in the base monad.

execWriterLG :: (Monad m, Monoid t) => GetT s i o e (WriterT t m) a -> GetT s i o e m t Source #

Execute WriterT in the base monad.

writerG :: (Monad m, Monoid t) => GetT s i o e m (a, t) -> GetT s i o e (WriterT t m) a Source #

Wrap the base monad in WriterT.

runWriterG :: (Monad m, Monoid t) => GetT s i o e (WriterT t m) a -> GetT s i o e m (a, t) Source #

Run WriterT in the base monad.

execWriterG :: (Monad m, Monoid t) => GetT s i o e (WriterT t m) a -> GetT s i o e m t Source #

Execute WriterT in the base monad.

rwsLG :: (Monad m, Monoid w) => (r -> t -> GetT s i o e m (a, t, w)) -> GetT s i o e (RWST r w t m) a Source #

Wrap the base monad in RWST.

runRWSLG :: (Monad m, Monoid w) => r -> t -> GetT s i o e (RWST r w t m) a -> GetT s i o e m (a, t, w) Source #

Run RWST in the base monad.

evalRWSLG :: (Monad m, Monoid w) => r -> t -> GetT s i o e (RWST r w t m) a -> GetT s i o e m (a, w) Source #

Evaluate RWST in the base monad.

execRWSLG :: (Monad m, Monoid w) => r -> t -> GetT s i o e (RWST r w t m) a -> GetT s i o e m (t, w) Source #

Execute RWST in the base monad.

rwsG :: (Monad m, Monoid w) => (r -> t -> GetT s i o e m (a, t, w)) -> GetT s i o e (RWST r w t m) a Source #

Wrap the base monad in RWST.

runRWSG :: (Monad m, Monoid w) => r -> t -> GetT s i o e (RWST r w t m) a -> GetT s i o e m (a, t, w) Source #

Run RWST in the base monad.

evalRWSG :: (Monad m, Monoid w) => r -> t -> GetT s i o e (RWST r w t m) a -> GetT s i o e m (a, w) Source #

Evaluate RWST in the base monad.

execRWSG :: (Monad m, Monoid w) => r -> t -> GetT s i o e (RWST r w t m) a -> GetT s i o e m (t, w) Source #

Execute RWST in the base monad.