jordan-0.2.0.0: JSON with Structure
Safe HaskellNone
LanguageHaskell2010

Jordan.FromJSON.Internal.UnboxedParser

Description

A parser module using unboxed types for speed.

This is done because parsing to a JSON error report needs custom handling.

Synopsis

Documentation

type WordPrim = Word# Source #

Type of word8 in GHC prim land. On the GHC 8 series, this is Word#.

newtype InputState Source #

Newtype wrapper around the state of an input.

This is just the offset into the buffer.

Constructors

InputState# 

Fields

pattern InputState :: Int# -> InputState Source #

Pattern synonym so we can use our above unlifted newtype like a record, if we do desire.

newtype InputRead Source #

Environment of a parser.

This is basically unpacked parts of a ByteString.

Constructors

InputRead# 

newtype AccumE err a Source #

Unboxed type similar to AccumE.

Constructors

AccumE 

Fields

pattern AccumER :: a -> AccumE err a Source #

pattern AccumEL :: err -> AccumE err a Source #

newtype ParseResult# err res Source #

Constructors

ParseResult# 

Fields

pattern JustParseResult :: InputState -> AccumE err res -> ParseResult# err res Source #

pattern NoParseResult :: ParseResult# err res Source #

bimapAcc :: (err -> err') -> (a -> a') -> AccumE err a -> AccumE err' a' Source #

eitherAcc :: Either err a -> AccumE err a Source #

appAcc :: Semigroup err => AccumE err (a1 -> a2) -> AccumE err a1 -> AccumE err a2 Source #

accSet :: a1 -> AccumE err a2 -> AccumE err a1 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.

Constructors

Parser# 

Fields

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 #

apParser :: Semigroup err => Parser# s err (a -> b) -> Parser# s err a -> Parser# s err b 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.

newtype Parser err res Source #

Constructors

Parser 

Fields

Instances

Instances details
Bifunctor Parser Source # 
Instance details

Defined in Jordan.FromJSON.Internal.UnboxedParser

Methods

bimap :: (a -> b) -> (c -> d) -> Parser a c -> Parser b d #

first :: (a -> b) -> Parser a c -> Parser b c #

second :: (b -> c) -> Parser a b -> Parser a c #

Semigroup err => Monad (Parser err) Source # 
Instance details

Defined in Jordan.FromJSON.Internal.UnboxedParser

Methods

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

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

return :: a -> Parser err a #

Functor (Parser err) Source # 
Instance details

Defined in Jordan.FromJSON.Internal.UnboxedParser

Methods

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

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

Semigroup err => Applicative (Parser err) Source # 
Instance details

Defined in Jordan.FromJSON.Internal.UnboxedParser

Methods

pure :: a -> Parser err a #

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

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

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

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

Monoid err => Alternative (Parser err) Source # 
Instance details

Defined in Jordan.FromJSON.Internal.UnboxedParser

Methods

empty :: Parser err a #

(<|>) :: Parser err a -> Parser err a -> Parser err a #

some :: Parser err a -> Parser err [a] #

many :: Parser err a -> Parser err [a] #

Monoid err => Semigroup (Parser err res) Source # 
Instance details

Defined in Jordan.FromJSON.Internal.UnboxedParser

Methods

(<>) :: Parser err res -> Parser err res -> Parser err res #

sconcat :: NonEmpty (Parser err res) -> Parser err res #

stimes :: Integral b => b -> Parser err res -> Parser err res #

Monoid err => Monoid (Parser err res) Source # 
Instance details

Defined in Jordan.FromJSON.Internal.UnboxedParser

Methods

mempty :: Parser err res #

mappend :: Parser err res -> Parser err res -> Parser err res #

mconcat :: [Parser err res] -> Parser err res #

parseBSIO :: Parser err res -> ByteString -> IO (Maybe (AccumE err res)) Source #

parseBS :: Parser err res -> ByteString -> Maybe (AccumE err res) Source #

orFail :: Parser err (Maybe a) -> Parser err a Source #

failWith :: err -> Parser err a Source #

asFailure :: Parser err err -> Parser err a 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

peekWord :: Parser err Word8 Source #

Peek the next word, fail if there's nothing there

peekWordMaybe :: Parser err (Maybe Word8) Source #

Peek a word, or nothing. Never fails.

skipWord8# :: (WordPrim -> Bool) -> Parser err () Source #

Skip over while the callback returns true.

Unlifted version, probably use skipWord8

skipWord8 :: (Word8 -> Bool) -> Parser err () Source #

Skip over while the callback returns true

skipWord8CB# :: (WordPrim -> Bool) -> InputRead -> InputState -> State# RealWorld -> (# State# RealWorld, ParseResult# err () #) Source #

Private: callback used for skipWord8

signed :: (Monoid err, Num a) => Parser err a -> Parser err a Source #

orNegative :: (Monoid err, Num a) => Parser err a -> Parser err a 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 #

parseIntegralGo :: (Monoid err, Integral i) => Int -> i -> Parser err (Int, i) Source #

takeWord8Cont :: Semigroup err => (Word8 -> Bool) -> (ByteString -> a) -> Parser err a Source #

takeWord81Cont :: Semigroup err => (Word8 -> Bool) -> (ByteString -> b) -> Parser err b Source #