Safe Haskell | None |
---|---|
Language | Haskell2010 |
A parser module using unboxed types for speed.
This is done because parsing to a JSON error report needs custom handling.
Synopsis
- type WordPrim = Word#
- newtype InputState = InputState# {}
- pattern InputState :: Int# -> InputState
- maxOffset :: InputState -> InputState -> InputState
- newtype InputRead = InputRead# {
- getInputRead :: (# ForeignPtrContents, Addr#, Int# #)
- pattern InputRead :: ForeignPtrContents -> Addr# -> Int# -> InputRead
- newtype AccumE err a = AccumE {
- getAccumE :: (# err | a #)
- pattern AccumER :: a -> AccumE err a
- pattern AccumEL :: err -> AccumE err a
- newtype ParseResult# err res = ParseResult# {
- getParseResult# :: (# (# InputState, AccumE err res #) | (# #) #)
- pattern JustParseResult :: InputState -> AccumE err res -> ParseResult# err res
- pattern NoParseResult :: ParseResult# err res
- bimapAcc :: (err -> err') -> (a -> a') -> AccumE err a -> AccumE err' a'
- eitherAcc :: Either err a -> AccumE err a
- appAcc :: Semigroup err => AccumE err (a1 -> a2) -> AccumE err a1 -> AccumE err a2
- accSet :: a1 -> AccumE err a2 -> AccumE err a1
- newtype Parser# s err res = Parser# {
- runParser :: InputRead -> InputState -> State# s -> (# State# s, ParseResult# err res #)
- bimapParser :: (err -> err') -> (a -> a') -> Parser# s err a -> Parser# s err' a'
- fmapParser :: (a -> res) -> Parser# s err a -> Parser# s err res
- pureParser :: Semigroup err => a -> Parser# s err a
- apParser :: Semigroup err => Parser# s err (a -> b) -> Parser# s err a -> Parser# s err b
- altParser :: Monoid err => Parser# s err a -> Parser# s err a -> Parser# s err a
- bindParser :: Parser# s err a -> (a -> Parser# s err b) -> Parser# s err b
- emptyParser :: Parser# s err a
- newtype Parser err res = Parser {}
- parseBSIO :: Parser err res -> ByteString -> IO (Maybe (AccumE err res))
- parseBS :: Parser err res -> ByteString -> Maybe (AccumE err res)
- currentOffset :: Parser err Int
- getEndOffset :: Parser err Int
- parsedPtr :: Parser err (ForeignPtr Word8)
- currentEnv :: Parser err (ForeignPtrContents, Ptr a, Int)
- failParse :: Parser err a
- maybeWord :: Parser err (Maybe Word8)
- orFail :: Parser err (Maybe a) -> Parser err a
- failWith :: err -> Parser err a
- asFailure :: Parser err err -> Parser err a
- lowerErr :: Parser err (Either err a) -> Parser err a
- hasFurther :: Parser err Bool
- advanceWord :: Parser err ()
- peekWord :: Parser err Word8
- peekWordMaybe :: Parser err (Maybe Word8)
- word :: Parser err Word8
- specificWord :: Word8 -> Parser err ()
- skipWord8# :: (WordPrim -> Bool) -> Parser err ()
- skipWord8 :: (Word8 -> Bool) -> Parser err ()
- skipWord8CB# :: (WordPrim -> Bool) -> InputRead -> InputState -> State# RealWorld -> (# State# RealWorld, ParseResult# err () #)
- skipWhitespace :: Parser err ()
- skipWhitespaceCB :: InputRead -> InputState -> State# RealWorld -> (# State# RealWorld, ParseResult# err () #)
- signed :: (Monoid err, Num a) => Parser err a -> Parser err a
- orNegative :: (Monoid err, Num a) => Parser err a -> Parser err a
- parseIntegral :: forall err i. (Monoid err, Integral i) => Parser err (Int, i)
- parseIntegralNoLeadingZero :: forall err i. (Monoid err, Integral i) => Parser err (Int, i)
- parseIntegralGo :: (Monoid err, Integral i) => Int -> i -> Parser err (Int, i)
- takeWord8Cont :: Semigroup err => (Word8 -> Bool) -> (ByteString -> a) -> Parser err a
- takeWord8 :: Semigroup err => (Word8 -> Bool) -> Parser err ByteString
- takeWord81 :: Semigroup err => (Word8 -> Bool) -> Parser err ByteString
- takeWord81Cont :: Semigroup err => (Word8 -> Bool) -> (ByteString -> b) -> Parser err b
- peekRest :: Semigroup err => Parser err ByteString
- chunkOfLength :: Int -> Parser err ByteString
- parseChunk :: ByteString -> Parser err ()
- testParser :: Parser () (Word8, ByteString)
Documentation
newtype InputState Source #
Newtype wrapper around the state of an input.
This is just the offset into the buffer.
pattern InputState :: Int# -> InputState Source #
Pattern synonym so we can use our above unlifted newtype like a record, if we do desire.
maxOffset :: InputState -> InputState -> InputState Source #
Environment of a parser.
This is basically unpacked parts of a ByteString.
InputRead# | |
|
newtype ParseResult# err res Source #
ParseResult# | |
|
pattern JustParseResult :: InputState -> AccumE err res -> ParseResult# err res Source #
pattern NoParseResult :: ParseResult# err res Source #
newtype Parser# s err res Source #
We need a parser with *error recovery*. So the basic idea is that we separate errors reported during parsing from errors that make parsing stop. IE, if we expect a JSON null but we get a JSON string, and the string is well-formed, we can keep parsing, but we will *report* an error.
Parser# | |
|
bimapParser :: (err -> err') -> (a -> a') -> Parser# s err a -> Parser# s err' a' Source #
fmapParser :: (a -> res) -> Parser# s err a -> Parser# s err res Source #
pureParser :: Semigroup err => a -> Parser# s err a Source #
altParser :: Monoid err => Parser# s err a -> Parser# s err a -> Parser# s err a Source #
Alternative instance for a parser. This has weird behavior in that, if we have two results with delayed errors, this will act as if it skipped the *largest* amount of said errors.
bindParser :: Parser# s err a -> (a -> Parser# s err b) -> Parser# s err b Source #
Monadic bind for these parsers.
Note that this breaks the monad laws, as we do more error accumulation with (*) than we do ap. Oh well.
emptyParser :: Parser# s err a Source #
newtype Parser err res Source #
Instances
Bifunctor Parser Source # | |
Semigroup err => Monad (Parser err) Source # | |
Functor (Parser err) Source # | |
Semigroup err => Applicative (Parser err) Source # | |
Defined in Jordan.FromJSON.Internal.UnboxedParser | |
Monoid err => Alternative (Parser err) Source # | |
Monoid err => Semigroup (Parser err res) Source # | |
Monoid err => Monoid (Parser err res) Source # | |
currentOffset :: Parser err Int Source #
getEndOffset :: Parser err Int Source #
currentEnv :: Parser err (ForeignPtrContents, Ptr a, Int) Source #
lowerErr :: Parser err (Either err a) -> Parser err a Source #
Lower a parsed error to a *parser error*.
hasFurther :: Parser err Bool Source #
Do we have any further input?
advanceWord :: Parser err () Source #
Advance forward one word, fail if we can't
specificWord :: Word8 -> Parser err () Source #
skipWord8# :: (WordPrim -> Bool) -> Parser err () Source #
Skip over while the callback returns true.
Unlifted version, probably use skipWord8
skipWord8CB# :: (WordPrim -> Bool) -> InputRead -> InputState -> State# RealWorld -> (# State# RealWorld, ParseResult# err () #) Source #
Private: callback used for skipWord8
skipWhitespace :: Parser err () Source #
skipWhitespaceCB :: InputRead -> InputState -> State# RealWorld -> (# State# RealWorld, ParseResult# err () #) Source #
parseIntegral :: forall err i. (Monoid err, Integral i) => Parser err (Int, i) Source #
Parse an integral number with possible leading zeros.
parseIntegralNoLeadingZero :: forall err i. (Monoid err, Integral i) => Parser err (Int, i) Source #
takeWord8Cont :: Semigroup err => (Word8 -> Bool) -> (ByteString -> a) -> Parser err a Source #
takeWord81 :: Semigroup err => (Word8 -> Bool) -> Parser err ByteString Source #
takeWord81Cont :: Semigroup err => (Word8 -> Bool) -> (ByteString -> b) -> Parser err b Source #
chunkOfLength :: Int -> Parser err ByteString Source #
parseChunk :: ByteString -> Parser err () Source #
testParser :: Parser () (Word8, ByteString) Source #