aeson-value-parser-0.19.7.2: API for parsing "aeson" JSON tree into Haskell types
Safe HaskellSafe-Inferred
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
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] #

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 #

Functor Value Source # 
Instance details

Defined in AesonValueParser

Methods

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

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

runAsValueParser :: Value a -> Value -> Parser a Source #

Convert into a function directly applicable as definition of parseJSON.

Here's an example of how it can be used:

data Artist = Artist
  { artistName :: Text,
    artistGenres :: [Text]
  }

instance FromJSON Artist where
  parseJSON = runAsValueParser $
    object $ do
      name <- field "name" $ string text
      genres <- field "genres" $ array $ elementList $ string text
      return $ Artist name genres

data Error Source #

Constructors

Error 

Fields

Instances

Instances details
IsString Error Source # 
Instance details

Defined in AesonValueParser.Error

Methods

fromString :: String -> Error #

Monoid Error Source # 
Instance details

Defined in AesonValueParser.Error

Methods

mempty :: Error #

mappend :: Error -> Error -> Error #

mconcat :: [Error] -> Error #

Semigroup Error Source # 
Instance details

Defined in AesonValueParser.Error

Methods

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

sconcat :: NonEmpty Error -> Error #

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

Show Error Source # 
Instance details

Defined in AesonValueParser.Error

Methods

showsPrec :: Int -> Error -> ShowS #

show :: Error -> String #

showList :: [Error] -> ShowS #

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
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] #

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 #

Functor String Source # 
Instance details

Defined in AesonValueParser

Methods

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

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

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

Number parsers

data Number a Source #

Instances

Instances details
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] #

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 #

Functor Number Source # 
Instance details

Defined in AesonValueParser

Methods

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

(<$) :: a -> Number b -> 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 Value parser.

Instances

Instances details
MonadFail Object Source # 
Instance details

Defined in AesonValueParser

Methods

fail :: String -> 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] #

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 #

Functor Object Source # 
Instance details

Defined in AesonValueParser

Methods

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

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

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 #

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 #

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

Array parsers

data Array a Source #

JSON Value parser.

Instances

Instances details
MonadFail Array Source # 
Instance details

Defined in AesonValueParser

Methods

fail :: String -> 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] #

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 #

Functor Array Source # 
Instance details

Defined in AesonValueParser

Methods

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

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

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 #

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 #