json-incremental-decoder-0.1.2: Incremental JSON parser with early termination and a declarative DSL

Safe HaskellNone
LanguageHaskell2010

JSONIncrementalDecoder

Contents

Description

A DSL for specification of a single-pass incremental and possibly partial parser of JSON.

Synopsis

Execution

valueToSupplementedParser :: Value a -> Supplemented Parser a Source #

Converts the Value specification into a Supplemented Attoparsec Parser.

valueToParser :: Value a -> Parser (a, Parser ()) Source #

Essentially just a helper, which is the same as

runSupplemented . valueToSupplementedParser

valueToByteStringToEither :: Value a -> ByteString -> Either Text a Source #

Converts the Value specification into a function, which decodes a strict ByteString.

valueToLazyByteStringToEither :: Value a -> ByteString -> Either Text a Source #

Converts the Value specification into a function, which decodes a strict LazyByteString.

Value

data Value a Source #

Instances

Functor Value Source # 

Methods

fmap :: (a -> b) -> Value a -> Value b #

(<$) :: a -> Value b -> Value a #

Monoid (Value a) Source #

Provides support for alternatives.

E.g,

fmap Left bool <> fmap Right string

will succeed for either a Boolean or String value.

Methods

mempty :: Value a #

mappend :: Value a -> Value a -> Value a #

mconcat :: [Value a] -> Value a #

ObjectRows

row :: (a -> b -> c) -> Matcher Text a -> Value b -> ObjectRows c Source #

ObjectLookup

ArrayElements

Matcher

data Matcher a b :: * -> * -> * #

A composable abstraction for checking or converting a context value.

Instances

Arrow Matcher 

Methods

arr :: (b -> c) -> Matcher b c #

first :: Matcher b c -> Matcher (b, d) (c, d) #

second :: Matcher b c -> Matcher (d, b) (d, c) #

(***) :: Matcher b c -> Matcher b' c' -> Matcher (b, b') (c, c') #

(&&&) :: Matcher b c -> Matcher b c' -> Matcher b (c, c') #

Profunctor Matcher 

Methods

dimap :: (a -> b) -> (c -> d) -> Matcher b c -> Matcher a d #

lmap :: (a -> b) -> Matcher b c -> Matcher a c #

rmap :: (b -> c) -> Matcher a b -> Matcher a c #

(#.) :: Coercible * c b => (b -> c) -> Matcher a b -> Matcher a c #

(.#) :: Coercible * b a => Matcher b c -> (a -> b) -> Matcher a c #

Monad (Matcher a) 

Methods

(>>=) :: Matcher a a -> (a -> Matcher a b) -> Matcher a b #

(>>) :: Matcher a a -> Matcher a b -> Matcher a b #

return :: a -> Matcher a a #

fail :: String -> Matcher a a #

Functor (Matcher a) 

Methods

fmap :: (a -> b) -> Matcher a a -> Matcher a b #

(<$) :: a -> Matcher a b -> Matcher a a #

Applicative (Matcher a) 

Methods

pure :: a -> Matcher a a #

(<*>) :: Matcher a (a -> b) -> Matcher a a -> Matcher a b #

(*>) :: Matcher a a -> Matcher a b -> Matcher a b #

(<*) :: Matcher a a -> Matcher a b -> Matcher a a #

Alternative (Matcher a) 

Methods

empty :: Matcher a a #

(<|>) :: Matcher a a -> Matcher a a -> Matcher a a #

some :: Matcher a a -> Matcher a [a] #

many :: Matcher a a -> Matcher a [a] #

MonadPlus (Matcher a) 

Methods

mzero :: Matcher a a #

mplus :: Matcher a a -> Matcher a a -> Matcher a a #

Category * Matcher 

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat a c #

equals :: Eq a => a -> Matcher a () #

Tests the matched value on equality with the provided value.

satisfies :: (a -> Bool) -> Matcher a () #

Checks whether the matched value satisfies the provided predicate.

converts :: (a -> Either Text b) -> Matcher a b #

Tries to convert the matched value to an output value, with Either encoding the success or failure of the conversion.

whatever :: Matcher a () #

The matcher, which is always satisfied.