microaeson-0.1.0.2: A tiny JSON library with light dependency footprint
Safe HaskellNone
LanguageHaskell2010

Data.Aeson.Micro

Description

Minimal JavaScript Object Notation (JSON) support as per RFC 8259.

This API provides a subset (with a couple of divergences; see below) of aeson API but puts the emphasis on simplicity rather than performance and features.

The ToJSON and FromJSON instances are intended to have an encoding compatible with aeson's encoding.

Limitations and divergences from aeson's API

In order to reduce the dependency footprint and keep the code simpler, the following divergences from the aeson API have to be made:

  • There are no FromJSON/ToJSON instances for Char & String.
  • The type synonym (& the constructor of the same name) Object uses containers's Map rather than a HashMap unordered-containers.
  • Array is represented by an ordinary list rather than a Vector from the vector package.
  • Number uses Double instead of Scientific
Synopsis

Core JSON types

data Value Source #

A JSON value represented as a Haskell value.

Constructors

Object !Object 
Array [Value] 
String !Text 
Number !Double 
Bool !Bool 
Null 

Instances

Instances details
NFData Value Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

rnf :: Value -> ()

Data Value Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Value -> c Value

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Value

toConstr :: Value -> Constr

dataTypeOf :: Value -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Value)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Value)

gmapT :: (forall b. Data b => b -> b) -> Value -> Value

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Value -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Value -> r

gmapQ :: (forall d. Data d => d -> u) -> Value -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Value -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Value -> m Value

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Value -> m Value

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Value -> m Value

IsString Value Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

fromString :: String -> Value

Generic Value Source # 
Instance details

Defined in Data.Aeson.Micro

Associated Types

type Rep Value 
Instance details

Defined in Data.Aeson.Micro

type Rep Value = D1 ('MetaData "Value" "Data.Aeson.Micro" "microaeson-0.1.0.2-inplace" 'False) ((C1 ('MetaCons "Object" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Object)) :+: (C1 ('MetaCons "Array" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Value])) :+: C1 ('MetaCons "String" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))) :+: (C1 ('MetaCons "Number" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Double)) :+: (C1 ('MetaCons "Bool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :+: C1 ('MetaCons "Null" 'PrefixI 'False) (U1 :: Type -> Type))))

Methods

from :: Value -> Rep Value x

to :: Rep Value x -> Value

Read Value Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

readsPrec :: Int -> ReadS Value

readList :: ReadS [Value]

readPrec :: ReadPrec Value

readListPrec :: ReadPrec [Value]

Show Value Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

showsPrec :: Int -> Value -> ShowS

show :: Value -> String

showList :: [Value] -> ShowS

Eq Value Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

(==) :: Value -> Value -> Bool

(/=) :: Value -> Value -> Bool

FromJSON Value Source # 
Instance details

Defined in Data.Aeson.Micro

ToJSON Value Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

toJSON :: Value -> Value Source #

type Rep Value Source # 
Instance details

Defined in Data.Aeson.Micro

type Rep Value = D1 ('MetaData "Value" "Data.Aeson.Micro" "microaeson-0.1.0.2-inplace" 'False) ((C1 ('MetaCons "Object" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Object)) :+: (C1 ('MetaCons "Array" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Value])) :+: C1 ('MetaCons "String" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))) :+: (C1 ('MetaCons "Number" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Double)) :+: (C1 ('MetaCons "Bool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :+: C1 ('MetaCons "Null" 'PrefixI 'False) (U1 :: Type -> Type))))

type Object = Map Text Value Source #

A JSON "object" (key/value map).

type Pair = (Text, Value) Source #

A key/value pair for an Object

Constructors

(.=) :: ToJSON v => Text -> v -> Pair infixr 8 Source #

A key-value pair for encoding a JSON object.

object :: [Pair] -> Value Source #

Create a Value from a list of name/value Pairs.

emptyArray :: Value Source #

The empty JSON Array (i.e. []).

emptyObject :: Value Source #

The empty JSON Object (i.e. {}).

Accessors

(.:) :: FromJSON a => Object -> Text -> Parser a Source #

(.:?) :: FromJSON a => Object -> Text -> Parser (Maybe a) Source #

(.:!) :: FromJSON a => Object -> Text -> Parser (Maybe a) Source #

(.!=) :: Parser (Maybe a) -> a -> Parser a Source #

Encoding and decoding

encode :: ToJSON a => a -> ByteString Source #

Serialise value as JSON/UTF-8-encoded lazy ByteString

encodeStrict :: ToJSON a => a -> ByteString Source #

Serialise value as JSON/UTF-8-encoded strict ByteString

encodeToBuilder :: ToJSON a => a -> Builder Source #

Serialise value as JSON/UTF8-encoded Builder

decodeStrict :: FromJSON a => ByteString -> Maybe a Source #

Decode a single JSON document

decode :: FromJSON a => ByteString -> Maybe a Source #

Decode a single JSON document

decodeStrictN :: FromJSON a => ByteString -> Maybe [a] Source #

Decode multiple concatenated JSON documents

Prism-style parsers

withObject :: String -> (Object -> Parser a) -> Value -> Parser a Source #

withText :: String -> (Text -> Parser a) -> Value -> Parser a Source #

withArray :: String -> ([Value] -> Parser a) -> Value -> Parser a Source #

withNumber :: String -> (Double -> Parser a) -> Value -> Parser a Source #

withBool :: String -> (Bool -> Parser a) -> Value -> Parser a Source #

Type conversion

class FromJSON a where Source #

A type that JSON can be deserialised into

Methods

parseJSON :: Value -> Parser a Source #

Decode a JSON value into a native Haskell type

Instances

Instances details
FromJSON Int16 Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

parseJSON :: Value -> Parser Int16 Source #

FromJSON Int32 Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

parseJSON :: Value -> Parser Int32 Source #

FromJSON Int64 Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

parseJSON :: Value -> Parser Int64 Source #

FromJSON Int8 Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

parseJSON :: Value -> Parser Int8 Source #

FromJSON Word16 Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

parseJSON :: Value -> Parser Word16 Source #

FromJSON Word32 Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

parseJSON :: Value -> Parser Word32 Source #

FromJSON Word64 Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

parseJSON :: Value -> Parser Word64 Source #

FromJSON Word8 Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

parseJSON :: Value -> Parser Word8 Source #

FromJSON Ordering Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

parseJSON :: Value -> Parser Ordering Source #

FromJSON Value Source # 
Instance details

Defined in Data.Aeson.Micro

FromJSON Text Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

parseJSON :: Value -> Parser Text Source #

FromJSON Text Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

parseJSON :: Value -> Parser Text Source #

FromJSON Integer Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

parseJSON :: Value -> Parser Integer Source #

FromJSON () Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

parseJSON :: Value -> Parser () Source #

FromJSON Bool Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

parseJSON :: Value -> Parser Bool Source #

FromJSON Double Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

parseJSON :: Value -> Parser Double Source #

FromJSON Float Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

parseJSON :: Value -> Parser Float Source #

FromJSON Int Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

parseJSON :: Value -> Parser Int Source #

FromJSON Word Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

parseJSON :: Value -> Parser Word Source #

FromJSON a => FromJSON (Maybe a) Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

parseJSON :: Value -> Parser (Maybe a) Source #

FromJSON a => FromJSON [a] Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

parseJSON :: Value -> Parser [a] Source #

FromJSON v => FromJSON (Map Text v) Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

parseJSON :: Value -> Parser (Map Text v) Source #

(FromJSON a, FromJSON b) => FromJSON (a, b) Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

parseJSON :: Value -> Parser (a, b) Source #

(FromJSON a, FromJSON b, FromJSON c) => FromJSON (a, b, c) Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

parseJSON :: Value -> Parser (a, b, c) Source #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d) => FromJSON (a, b, c, d) Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

parseJSON :: Value -> Parser (a, b, c, d) Source #

data Parser a Source #

JSON Parser Monad used by FromJSON

Instances

Instances details
Applicative Parser Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

pure :: a -> Parser a

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

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

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

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

Functor Parser Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

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

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

Monad Parser Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

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

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

return :: a -> Parser a

MonadFail Parser Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

fail :: String -> Parser a

parseMaybe :: (a -> Parser b) -> a -> Maybe b Source #

Run Parser.

A common use-case is parseMaybe parseJSON.

class ToJSON a where Source #

A type that can be converted to JSON.

Methods

toJSON :: a -> Value Source #

Convert a Haskell value to a JSON-friendly intermediate type.

Instances

Instances details
ToJSON Int16 Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

toJSON :: Int16 -> Value Source #

ToJSON Int32 Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

toJSON :: Int32 -> Value Source #

ToJSON Int64 Source #

Possibly lossy due to conversion to Double

Instance details

Defined in Data.Aeson.Micro

Methods

toJSON :: Int64 -> Value Source #

ToJSON Int8 Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

toJSON :: Int8 -> Value Source #

ToJSON Word16 Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

toJSON :: Word16 -> Value Source #

ToJSON Word32 Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

toJSON :: Word32 -> Value Source #

ToJSON Word64 Source #

Possibly lossy due to conversion to Double

Instance details

Defined in Data.Aeson.Micro

Methods

toJSON :: Word64 -> Value Source #

ToJSON Word8 Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

toJSON :: Word8 -> Value Source #

ToJSON Value Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

toJSON :: Value -> Value Source #

ToJSON Text Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

toJSON :: Text -> Value Source #

ToJSON Text Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

toJSON :: Text -> Value Source #

ToJSON Integer Source #

Possibly lossy due to conversion to Double

Instance details

Defined in Data.Aeson.Micro

Methods

toJSON :: Integer -> Value Source #

ToJSON () Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

toJSON :: () -> Value Source #

ToJSON Bool Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

toJSON :: Bool -> Value Source #

ToJSON Double Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

toJSON :: Double -> Value Source #

ToJSON Float Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

toJSON :: Float -> Value Source #

ToJSON Int Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

toJSON :: Int -> Value Source #

ToJSON Word Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

toJSON :: Word -> Value Source #

ToJSON a => ToJSON (Maybe a) Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

toJSON :: Maybe a -> Value Source #

ToJSON a => ToJSON [a] Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

toJSON :: [a] -> Value Source #

ToJSON v => ToJSON (Map Text v) Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

toJSON :: Map Text v -> Value Source #

(ToJSON a, ToJSON b) => ToJSON (a, b) Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

toJSON :: (a, b) -> Value Source #

(ToJSON a, ToJSON b, ToJSON c) => ToJSON (a, b, c) Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

toJSON :: (a, b, c) -> Value Source #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d) => ToJSON (a, b, c, d) Source # 
Instance details

Defined in Data.Aeson.Micro

Methods

toJSON :: (a, b, c, d) -> Value Source #