aeson-extra-0.3.1.1: Extra goodies for aeson

Copyright(C) 2015-2016 Oleg Grenrus
LicenseBSD3
MaintainerOleg Grenrus <oleg.grenrus@iki.fi>
Safe HaskellNone
LanguageHaskell2010

Data.Aeson.Extra

Contents

Description

More or less useful newtypes for writing FromJSON & ToJSON instances

Synopsis

Strict encoding

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

Like encode, but produces strict ByteString.

Since: 0.2.3.0

Generic maps

newtype M a Source

A wrapper type to parse arbitrary maps

λ > decode "{\"1\": 1, \"2\": 2}" :: Maybe (M (H.HashMap Int Int))
Just (M {getMap = fromList [(1,1),(2,2)]})

Constructors

M 

Fields

getMap :: a
 

Instances

Functor M Source 
Foldable M Source 
Traversable M Source 
Eq a => Eq (M a) Source 
Ord a => Ord (M a) Source 
Read a => Read (M a) Source 
Show a => Show (M a) Source 
ToJSONMap m k v => ToJSON (M m) Source 
FromJSONMap m k v => FromJSON (M m) Source 

class FromJSONMap m k v | m -> k v where Source

Instances

(Eq k, Hashable k, FromJSONKey k, FromJSON v) => FromJSONMap (HashMap k v) k v Source 
(Ord k, FromJSONKey k, FromJSON v) => FromJSONMap (Map k v) k v Source 

class ToJSONMap m k v | m -> k v where Source

Instances

(ToJSONKey k, ToJSON v) => ToJSONMap (HashMap k v) k v Source 
(ToJSONKey k, ToJSON v) => ToJSONMap (Map k v) k v Source 

Symbol tag

data SymTag s Source

Singleton string encoded and decoded as ifself.

λ> encode (SymTag :: SymTag "foobar")
"\"foobar\""
decode "\"foobar\"" :: Maybe (SymTag "foobar")
Just SymTag
decode "\"foobar\"" :: Maybe (SymTag "barfoo")
Nothing

Available with: base >=4.7

Constructors

SymTag 

Singleton object

newtype SingObject s a Source

Singleton value object

λ > decode "{\"value\": 42 }" :: Maybe (SingObject "value" Int)
Just (SingObject 42)
λ > encode (SingObject 42 :: SingObject "value" Int)
"{\"value\":42}"

Available with: base >=4.7

Constructors

SingObject a 

CollapsedList

newtype CollapsedList f a Source

Collapsed list, singleton is represented as the value itself in JSON encoding.

λ > decode "null" :: Maybe (CollapsedList [Int] Int)
Just (CollapsedList [])
λ > decode "42" :: Maybe (CollapsedList [Int] Int)
Just (CollapsedList [42])
λ > decode "[1, 2, 3]" :: Maybe (CollapsedList [Int] Int)
Just (CollapsedList [1,2,3])
λ > encode (CollapsedList ([] :: [Int]))
"null"
λ > encode (CollapsedList ([42] :: [Int]))
"42"
λ > encode (CollapsedList ([1, 2, 3] :: [Int]))
"[1,2,3]"

Documentation rely on f Alternative instance behaving like lists'.

Constructors

CollapsedList (f a) 

parseCollapsedList :: (FromJSON a, FromJSON (f a), Alternative f) => Object -> Text -> Parser (f a) Source

Parses possibly collapsed array value from the object's field.

λ > newtype V = V [Int] deriving (Show)
λ > instance FromJSON V where parseJSON = withObject "V" $ \obj -> V <$> parseCollapsedList obj "value"
λ > decode "{}" :: Maybe V
Just (V [])
λ > decode "{\"value\": null}" :: Maybe V
Just (V [])
λ > decode "{\"value\": 42}" :: Maybe V
Just (V [42])
λ > decode "{\"value\": [1, 2, 3, 4]}" :: Maybe V
Just (V [1,2,3,4])

UTCTime

newtype U Source

A type to parse UTCTime

FromJSON instance accepts for example:

2015-09-07T08:16:40.807Z
2015-09-07 11:16:40.807 +03:00

Latter format is accepted by aeson staring from version 0.10.0.0.

See https://github.com/bos/aeson/blob/4667ef1029a373cf4510f7deca147c357c6d8947/Data/Aeson/Parser/Time.hs#L150

Since: aeson-extra-0.2.2.0

Constructors

U 

Fields

getU :: UTCTime
 

newtype Z Source

A type to parse ZonedTime

Since: aeson-extra-0.2.2.0

Constructors

Z 

Fields

getZ :: ZonedTime
 

Algebra

data ValueF a Source

An algebra of Value

Since: aeson-extra-0.3.1.0

type ObjectF a = HashMap Text a Source

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

Since: aeson-extra-0.3.1.0

type ArrayF a = Vector a Source

A JSON "array" (sequence).

Since: aeson-extra-0.3.1.0

Merge

merge :: (forall a. (a -> a -> a) -> ValueF a -> ValueF a -> ValueF a) -> Value -> Value -> Value Source

Generic merge.

For example https://lodash.com/docs#merge:

lodashMerge :: Value -> Value -> Value
lodashMerge x y = merge lodashMergeAlg x y

lodashMergeAlg :: (a -> a -> a) -> ValueF a -> ValueF a -> ValueF a
lodashMergeAlg r a' b' = case (a', b') of
    (ObjectF a, ObjectF b) -> ObjectF $ alignWith f a b
    (ArrayF a,  ArrayF b)  -> ArrayF $ alignWith f a b
    (_,         b)         -> b
  where f (These x y) = r x y
        f (This x)    = x
        f (That x)    = x

Since: aeson-extra-0.3.1.0

Template Haskell

mkValue :: String -> Q Exp Source

Create a Value from string representation.

This is useful in tests.

Since: aeson-extra-0.3.1.0

mkValue' :: String -> Q Exp Source

Like mkValue, but replace single quotes with double quotes before.

> $(mkValue' "{'a': 2 }")
Object (fromList [("a",Number 2.0)])

Since: aeson-extra-0.3.1.0

Re-exports