Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class DecodingState s where
- type DecodingToken s :: *
- data Decoding s i
- startDecoding :: s -> Decoding s i
- continueDecoding :: s -> [i] -> Decoding s i -> Decoding s i
- decodingRead :: Decoding s i -> s
- data GetC s i e m a
- type GetT s i o e m = ConduitT i o (GetC s i e m)
- runGetC :: Monad m => Decoding s i -> GetT s i o e m a -> ConduitT i o m (Either e a, Decoding s i)
- getC :: Monad m => (Decoding s i -> ConduitT i o m (Either e a, Decoding s i)) -> GetT s i o e m a
- trackP :: Monad m => GetT s i o e m a -> GetT s i o ([i], e) m ([i], a)
- tryP :: Monad m => GetT s i o e m a -> GetT s i o e m a
- maybeG :: Monad m => GetT s i o e m (Maybe a) -> GetT s i o e (ExceptT (Decoding s i) m) a
- runMaybeG :: Monad m => GetT s i o e (ExceptT (Decoding s i) m) a -> GetT s i o e m (Maybe a)
- exceptG :: Monad m => GetT s i o e' m (Either e a) -> GetT s i o e' (ExceptT (e, Decoding s i) m) a
- runExceptG :: Monad m => GetT s i o e' (ExceptT (e, Decoding s i) m) a -> GetT s i o e' m (Either e a)
- 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
- readerG :: Monad m => (r -> GetT s i o e m a) -> GetT s i o e (ReaderT r m) a
- runReaderG :: Monad m => r -> GetT s i o e (ReaderT r m) a -> GetT s i o e m a
- stateLG :: Monad m => (t -> GetT s i o e m (a, t)) -> GetT s i o e (StateT t m) a
- runStateLG :: Monad m => t -> GetT s i o e (StateT t m) a -> GetT s i o e m (a, t)
- evalStateLG :: Monad m => t -> GetT s i o e (StateT t m) a -> GetT s i o e m a
- execStateLG :: Monad m => t -> GetT s i o e (StateT t m) a -> GetT s i o e m t
- stateG :: Monad m => (t -> GetT s i o e m (a, t)) -> GetT s i o e (StateT t m) a
- runStateG :: Monad m => t -> GetT s i o e (StateT t m) a -> GetT s i o e m (a, t)
- evalStateG :: Monad m => t -> GetT s i o e (StateT t m) a -> GetT s i o e m a
- execStateG :: Monad m => t -> GetT s i o e (StateT t m) a -> GetT s i o e m t
- writerLG :: (Monad m, Monoid t) => GetT s i o e m (a, t) -> GetT s i o e (WriterT t m) a
- runWriterLG :: (Monad m, Monoid t) => GetT s i o e (WriterT t m) a -> GetT s i o e m (a, t)
- execWriterLG :: (Monad m, Monoid t) => GetT s i o e (WriterT t m) a -> GetT s i o e m t
- writerG :: (Monad m, Monoid t) => GetT s i o e m (a, t) -> GetT s i o e (WriterT t m) a
- runWriterG :: (Monad m, Monoid t) => GetT s i o e (WriterT t m) a -> GetT s i o e m (a, t)
- execWriterG :: (Monad m, Monoid t) => GetT s i o e (WriterT t m) a -> GetT s i o e m t
- 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
- 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)
- 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)
- 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)
- 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
- 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)
- 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)
- 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)
Documentation
class DecodingState s where Source #
type DecodingToken s :: * Source #
decoded :: DecodingToken s -> s -> s Source #
Instances
DecodingState ByteOffset Source # | |
Defined in Data.Conduit.Parsers.Binary.ByteOffset type DecodingToken ByteOffset :: * Source # decoded :: DecodingToken ByteOffset -> ByteOffset -> ByteOffset Source # | |
DecodingState TextOffset Source # | |
Defined in Data.Conduit.Parsers.Text.TextOffset type DecodingToken TextOffset :: * Source # decoded :: DecodingToken TextOffset -> TextOffset -> TextOffset Source # | |
(DecodingState s, DecodingToken s ~ i) => DecodingState (Decoding s i) Source # | |
Defined in Data.Conduit.Parsers.GetC type DecodingToken (Decoding s i) :: * Source # |
GetC
monad state.
Instances
(DecodingState s, DecodingToken s ~ i) => DecodingState (Decoding s i) Source # | |
Defined in Data.Conduit.Parsers.GetC type DecodingToken (Decoding s i) :: * Source # | |
(DecodingState s, DecodingElemsRead s) => DecodingElemsRead (Decoding s i) Source # | |
Defined in Data.Conduit.Parsers decodingElemsRead :: Decoding s i -> Word64 Source # | |
(DecodingState s, DecodingColumnsRead s) => DecodingColumnsRead (Decoding s i) Source # | |
Defined in Data.Conduit.Parsers.Text decodingColumnsRead :: Decoding s i -> Word64 Source # | |
(DecodingState s, DecodingLinesRead s) => DecodingLinesRead (Decoding s i) Source # | |
Defined in Data.Conduit.Parsers.Text decodingLinesRead :: Decoding s i -> Word64 Source # | |
type DecodingToken (Decoding s i) Source # | |
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.
Internal transformers for GetT
with error type e
, base monad m
, and decoder result a
.
Instances
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 #
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.
runMaybeG :: Monad m => GetT s i o e (ExceptT (Decoding s i) m) a -> GetT s i o e m (Maybe a) Source #
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 #
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 #
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.