Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Parser.Lathe.Unsafe
Description
Parser internals, helper operations and unsafe functions.
Implementation
Parser keeps a non-empty cons-list of known chunks
(strict ByteString
plus a lazy ByteString
) and a snoc-list
of all chunks it may need when rolling back ( Rollback
).
Chunks themselves are never modified, instead a ChunkOffset
is used to
keep track of position within the current chunk.
TotalOffset
is a sum of lengths of all chunks before the current one.
A request for more input (Resupply
) only occurs when parser reaches the
the end of the current chunk, no more chunks are known, More
input is
available and more parsing is necessary. Current chunk is then replaced with the
new one and both offsets are adjusted accordingly.
A rollback may only occur if a function above requested so (Policy
).
Any new chunks received while in the Keep
state are
additionally added to the Rollback
, which is then managed by the function above
when it gains control again.
Synopsis
- type TotalOffset = Int64
- type ChunkOffset = Int
- data More
- data Rollback
- = Rollback !Rollback !ByteString
- | Bottom
- data Policy
- type Core = (# TotalOffset, ChunkOffset, ByteString, ByteString, More, Rollback #)
- data Resupply
- newtype Res e a where
- newtype Dec e a where
- newtype Parser e a = Parser {}
- data Blank = Blank !TotalOffset !ChunkOffset !ByteString !ByteString !More
- data UnexpectedPartial = UnexpectedPartial
- unsafeSkip :: Int64 -> end -> Parser end ()
- unsafeSkipEndOr :: Int64 -> Parser never ()
- unsafeByteString :: Int -> end -> Parser end ByteString
- unsafeRead :: Int -> (ByteString -> (# Res e a #)) -> e -> Parser e a
- unsafeShortByteString :: Int -> end -> Parser end ShortByteString
- unsafeLazyByteString :: Int -> end -> Parser end ByteString
Itself
type TotalOffset = Int64 Source #
Global offset of the start of the current chunk, in bytes.
type ChunkOffset = Int Source #
Local offset inside the chunk, in bytes.
Whether more input can be supplied.
A snoc-list of all consumed chunks needed in the future.
Constructors
Rollback !Rollback !ByteString | |
Bottom |
Chunk retention policy.
type Core = (# TotalOffset, ChunkOffset, ByteString, ByteString, More, Rollback #) Source #
Common parser state bundled together for convenience.
Providing additional input to the decoder.
Constructors
Supply !ByteString | A chunk of the input. It should not be empty. N.B.: Lazy |
EndOfInput |
Unboxed Partial
counterpart.
The parser type, parametrized by an error type e
and a return type a
.
Note that there is no Alternative
instance for this parser,
see instead catch
.
Internal processing state.
Constructors
Blank !TotalOffset !ChunkOffset !ByteString !ByteString !More | Mirrors the |
Run
Immediate
data UnexpectedPartial Source #
Constructors
UnexpectedPartial |
Instances
Exception UnexpectedPartial Source # | |
Defined in Parser.Lathe.Internal Methods toException :: UnexpectedPartial -> SomeException # | |
Show UnexpectedPartial Source # | |
Defined in Parser.Lathe.Internal Methods showsPrec :: Int -> UnexpectedPartial -> ShowS # show :: UnexpectedPartial -> String # showList :: [UnexpectedPartial] -> ShowS # |
Parse
No output
unsafeSkip :: Int64 -> end -> Parser end () Source #
Skip ahead \(n\) bytes.
\(n\) must be non-negative.
Optional
unsafeSkipEndOr :: Int64 -> Parser never () Source #
Skip ahead \(n\) or fewer bytes.
\(n\) must be non-negative.
Strict ByteString
unsafeByteString :: Int -> end -> Parser end ByteString Source #
Consume \(n\) bytes into a ShortByteString
.
\(n\) must be non-negative.
unsafeRead :: Int -> (ByteString -> (# Res e a #)) -> e -> Parser e a Source #
Consume \(n\) bytes into a strict ByteString
and use that to produce a result.
\(n\) must be non-negative.
The returned string, if it points to a continuous segment of a single input chunk, is not a copy and is not trimmed properly.
Only the unboxed tuple is evaluated to WHNF before returning;
the Res
inside it is not touched.
Short ByteString
unsafeShortByteString :: Int -> end -> Parser end ShortByteString Source #
Consume \(n\) bytes into a ShortByteString
.
\(n\) must be non-negative.
Lazy ByteString
unsafeLazyByteString :: Int -> end -> Parser end ByteString Source #
Consume \(n\) bytes into a lazy ByteString
.
\(n\) must be non-negative.