Safe Haskell | None |
---|---|
Language | Haskell2010 |
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 forChar
&String
. - The type synonym (& the constructor of the same name)
Object
usescontainers
'sMap
rather than aHashMap
unordered-containers
. Array
is represented by an ordinary list rather than aVector
from thevector
package.Number
usesDouble
instead ofScientific
Synopsis
- data Value
- type Object = Map Text Value
- type Pair = (Text, Value)
- (.=) :: ToJSON v => Text -> v -> Pair
- object :: [Pair] -> Value
- emptyArray :: Value
- emptyObject :: Value
- (.:) :: FromJSON a => Object -> Text -> Parser a
- (.:?) :: FromJSON a => Object -> Text -> Parser (Maybe a)
- (.:!) :: FromJSON a => Object -> Text -> Parser (Maybe a)
- (.!=) :: Parser (Maybe a) -> a -> Parser a
- encode :: ToJSON a => a -> ByteString
- encodeStrict :: ToJSON a => a -> ByteString
- encodeToBuilder :: ToJSON a => a -> Builder
- decodeStrict :: FromJSON a => ByteString -> Maybe a
- decode :: FromJSON a => ByteString -> Maybe a
- decodeStrictN :: FromJSON a => ByteString -> Maybe [a]
- withObject :: String -> (Object -> Parser a) -> Value -> Parser a
- withText :: String -> (Text -> Parser a) -> Value -> Parser a
- withArray :: String -> ([Value] -> Parser a) -> Value -> Parser a
- withNumber :: String -> (Double -> Parser a) -> Value -> Parser a
- withBool :: String -> (Bool -> Parser a) -> Value -> Parser a
- class FromJSON a where
- data Parser a
- parseMaybe :: (a -> Parser b) -> a -> Maybe b
- class ToJSON a where
Core JSON types
A JSON value represented as a Haskell value.
Instances
NFData Value Source # | |||||
Defined in Data.Aeson.Micro | |||||
Data Value Source # | |||||
Defined in Data.Aeson.Micro 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 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 # | |||||
Defined in Data.Aeson.Micro fromString :: String -> Value | |||||
Generic Value Source # | |||||
Defined in Data.Aeson.Micro
| |||||
Read Value Source # | |||||
Defined in Data.Aeson.Micro | |||||
Show Value Source # | |||||
Eq Value Source # | |||||
FromJSON Value Source # | |||||
ToJSON Value Source # | |||||
type Rep Value Source # | |||||
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)))) |
Constructors
emptyArray :: Value Source #
The empty JSON Array
(i.e. []
).
emptyObject :: Value Source #
The empty JSON Object
(i.e. {}
).
Accessors
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
decodeStrictN :: FromJSON a => ByteString -> Maybe [a] Source #
Decode multiple concatenated JSON documents
Prism-style parsers
Type conversion
class FromJSON a where Source #
A type that JSON can be deserialised into
Instances
FromJSON Int16 Source # | |
FromJSON Int32 Source # | |
FromJSON Int64 Source # | |
FromJSON Int8 Source # | |
FromJSON Word16 Source # | |
FromJSON Word32 Source # | |
FromJSON Word64 Source # | |
FromJSON Word8 Source # | |
FromJSON Ordering Source # | |
FromJSON Value Source # | |
FromJSON Text Source # | |
FromJSON Text Source # | |
FromJSON Integer Source # | |
FromJSON () Source # | |
FromJSON Bool Source # | |
FromJSON Double Source # | |
FromJSON Float Source # | |
FromJSON Int Source # | |
FromJSON Word Source # | |
FromJSON a => FromJSON (Maybe a) Source # | |
FromJSON a => FromJSON [a] Source # | |
FromJSON v => FromJSON (Map Text v) Source # | |
(FromJSON a, FromJSON b) => FromJSON (a, b) Source # | |
(FromJSON a, FromJSON b, FromJSON c) => FromJSON (a, b, c) Source # | |
(FromJSON a, FromJSON b, FromJSON c, FromJSON d) => FromJSON (a, b, c, d) Source # | |
JSON Parser Monad
used by FromJSON
parseMaybe :: (a -> Parser b) -> a -> Maybe b Source #
Run Parser
.
A common use-case is
.parseMaybe
parseJSON
A type that can be converted to JSON.