lathe-0.1.0.0: Pure incremental byte parser.
Safe HaskellSafe-Inferred
LanguageHaskell2010

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

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.

data More Source #

Whether more input can be supplied.

Constructors

More

Can prompt for more state.

End

End has been reached.

Instances

Instances details
Show More Source # 
Instance details

Defined in Parser.Lathe.Internal

Methods

showsPrec :: Int -> More -> ShowS #

show :: More -> String #

showList :: [More] -> ShowS #

Eq More Source # 
Instance details

Defined in Parser.Lathe.Internal

Methods

(==) :: More -> More -> Bool #

(/=) :: More -> More -> Bool #

data Rollback Source #

A snoc-list of all consumed chunks needed in the future.

Instances

Instances details
Show Rollback Source # 
Instance details

Defined in Parser.Lathe.Internal

data Policy Source #

Chunk retention policy.

Constructors

Drop

Do not keep the reference.

Keep

Keep the reference in the Rollback.

Instances

Instances details
Show Policy Source # 
Instance details

Defined in Parser.Lathe.Internal

type Core = (# TotalOffset, ChunkOffset, ByteString, ByteString, More, Rollback #) Source #

Common parser state bundled together for convenience.

data Resupply Source #

Providing additional input to the decoder.

Constructors

Supply !ByteString

A chunk of the input. It should not be empty.

N.B.: Lazy ByteStrings have an internal "no empty chunks" invariant. While this parser does not malfunction when encountering an empty chunk, it does not purge empty chunks and will faithfully relay them in lazy ByteStrings it produces. This may in turn break downstream consumers.

EndOfInput 

newtype Res e a Source #

Unboxed Either counterpart.

Constructors

Res (# a | e #) 

Bundled Patterns

pattern Yes :: a -> Res e a 
pattern No :: e -> Res e a 

newtype Dec e a Source #

Unboxed Partial counterpart.

Constructors

Dec (# (# Core, Res e a #) | Resupply -> Dec e a #) 

Bundled Patterns

pattern Re :: (Resupply -> Dec e a) -> Dec e a 
pattern Fin :: Core -> Res e a -> Dec e a 

newtype Parser e a Source #

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.

Constructors

Parser 

Fields

Instances

Instances details
Applicative (Parser e) Source # 
Instance details

Defined in Parser.Lathe.Internal

Methods

pure :: a -> Parser e a #

(<*>) :: Parser e (a -> b) -> Parser e a -> Parser e b #

liftA2 :: (a -> b -> c) -> Parser e a -> Parser e b -> Parser e c #

(*>) :: Parser e a -> Parser e b -> Parser e b #

(<*) :: Parser e a -> Parser e b -> Parser e a #

Functor (Parser e) Source # 
Instance details

Defined in Parser.Lathe.Internal

Methods

fmap :: (a -> b) -> Parser e a -> Parser e b #

(<$) :: a -> Parser e b -> Parser e a #

Monad (Parser e) Source # 
Instance details

Defined in Parser.Lathe.Internal

Methods

(>>=) :: Parser e a -> (a -> Parser e b) -> Parser e b #

(>>) :: Parser e a -> Parser e b -> Parser e b #

return :: a -> Parser e a #

data Blank Source #

Internal processing state.

Run

Immediate

data UnexpectedPartial Source #

Helper exception for excluding the hopefully impossible Partial result in parse.

Constructors

UnexpectedPartial 

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.