aeson-value-parser-0.19.6: API for parsing "aeson" JSON tree into Haskell types
Safe HaskellNone
LanguageHaskell2010

AesonValueParser

Synopsis

Documentation

data Value a Source #

JSON Value AST parser.

Its Alternative instance implements the logic of choosing between the possible types of JSON values.

Instances

Instances details
Functor Value Source # 
Instance details

Defined in AesonValueParser

Methods

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

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

Applicative Value Source # 
Instance details

Defined in AesonValueParser

Methods

pure :: a -> Value a #

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

liftA2 :: (a -> b -> c) -> Value a -> Value b -> Value c #

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

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

Alternative Value Source #

Implements the logic of choosing between the possible types of JSON values.

If you have multiple parsers of the same type of JSON value composed, only the leftmost will be affective. The errors from deeper parsers do not trigger the alternation, instead they get propagated to the top.

Instance details

Defined in AesonValueParser

Methods

empty :: Value a #

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

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

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

data Error Source #

Constructors

Error 

Fields

Instances

Instances details
Show Error Source # 
Instance details

Defined in AesonValueParser.Error

Methods

showsPrec :: Int -> Error -> ShowS #

show :: Error -> String #

showList :: [Error] -> ShowS #

IsString Error Source # 
Instance details

Defined in AesonValueParser.Error

Methods

fromString :: String -> Error #

Semigroup Error Source # 
Instance details

Defined in AesonValueParser.Error

Methods

(<>) :: Error -> Error -> Error #

sconcat :: NonEmpty Error -> Error #

stimes :: Integral b => b -> Error -> Error #

Monoid Error Source # 
Instance details

Defined in AesonValueParser.Error

Methods

mempty :: Error #

mappend :: Error -> Error -> Error #

mconcat :: [Error] -> Error #

MonadError Error Array Source # 
Instance details

Defined in AesonValueParser

Methods

throwError :: Error -> Array a #

catchError :: Array a -> (Error -> Array a) -> Array a #

MonadError Error Object Source # 
Instance details

Defined in AesonValueParser

Methods

throwError :: Error -> Object a #

catchError :: Object a -> (Error -> Object a) -> Object a #

Value parsers

String parsers

data String a Source #

Instances

Instances details
Functor String Source # 
Instance details

Defined in AesonValueParser

Methods

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

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

Applicative String Source # 
Instance details

Defined in AesonValueParser

Methods

pure :: a -> String a #

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

liftA2 :: (a -> b -> c) -> String a -> String b -> String c #

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

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

Alternative String Source # 
Instance details

Defined in AesonValueParser

Methods

empty :: String a #

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

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

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

mappedText :: [(Text, a)] -> String a Source #

Number parsers

data Number a Source #

Instances

Instances details
Functor Number Source # 
Instance details

Defined in AesonValueParser

Methods

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

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

Applicative Number Source # 
Instance details

Defined in AesonValueParser

Methods

pure :: a -> Number a #

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

liftA2 :: (a -> b -> c) -> Number a -> Number b -> Number c #

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

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

Alternative Number Source # 
Instance details

Defined in AesonValueParser

Methods

empty :: Number a #

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

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

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

matchedInteger :: (Integral integer, Bounded integer) => (integer -> Either Text a) -> Number a Source #

matchedFloating :: RealFloat floating => (floating -> Either Text a) -> Number a Source #

Object parsers

data Object a Source #

JSON Object parser.

Instances

Instances details
Monad Object Source # 
Instance details

Defined in AesonValueParser

Methods

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

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

return :: a -> Object a #

Functor Object Source # 
Instance details

Defined in AesonValueParser

Methods

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

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

MonadFail Object Source # 
Instance details

Defined in AesonValueParser

Methods

fail :: String -> Object a #

Applicative Object Source # 
Instance details

Defined in AesonValueParser

Methods

pure :: a -> Object a #

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

liftA2 :: (a -> b -> c) -> Object a -> Object b -> Object c #

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

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

Alternative Object Source # 
Instance details

Defined in AesonValueParser

Methods

empty :: Object a #

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

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

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

MonadPlus Object Source # 
Instance details

Defined in AesonValueParser

Methods

mzero :: Object a #

mplus :: Object a -> Object a -> Object a #

MonadError Error Object Source # 
Instance details

Defined in AesonValueParser

Methods

throwError :: Error -> Object a #

catchError :: Object a -> (Error -> Object a) -> Object a #

field :: Text -> Value a -> Object a Source #

fieldMap :: (Eq a, Hashable a) => String a -> Value b -> Object (HashMap a b) Source #

foldlFields :: (state -> key -> field -> state) -> state -> String key -> Value field -> Object state Source #

Array parsers

data Array a Source #

JSON Array parser.

Instances

Instances details
Monad Array Source # 
Instance details

Defined in AesonValueParser

Methods

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

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

return :: a -> Array a #

Functor Array Source # 
Instance details

Defined in AesonValueParser

Methods

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

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

MonadFail Array Source # 
Instance details

Defined in AesonValueParser

Methods

fail :: String -> Array a #

Applicative Array Source # 
Instance details

Defined in AesonValueParser

Methods

pure :: a -> Array a #

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

liftA2 :: (a -> b -> c) -> Array a -> Array b -> Array c #

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

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

Alternative Array Source # 
Instance details

Defined in AesonValueParser

Methods

empty :: Array a #

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

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

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

MonadPlus Array Source # 
Instance details

Defined in AesonValueParser

Methods

mzero :: Array a #

mplus :: Array a -> Array a -> Array a #

MonadError Error Array Source # 
Instance details

Defined in AesonValueParser

Methods

throwError :: Error -> Array a #

catchError :: Array a -> (Error -> Array a) -> Array a #

element :: Int -> Value a -> Array a Source #

foldlElements :: (state -> Int -> element -> state) -> state -> Value element -> Array state Source #

foldrElements :: (Int -> element -> state -> state) -> state -> Value element -> Array state Source #