microlens-aeson-2.2.0.2: Law-abiding lenses for Aeson, using microlens.

Copyright(c) Colin Woodbury 2015 (c) Edward Kmett 2013-2014 (c) Paul Wilson 2012
LicenseBSD3
MaintainerColin Woodbury <colingw@gmail.com>
Safe HaskellTrustworthy
LanguageHaskell2010

Lens.Micro.Aeson

Contents

Description

Traversals for Data.Aeson, based on microlens for minimal dependencies.

For basic manipulation of Aeson values, full Prism functionality isn't necessary. Since all Prisms are inherently Traversals, we provide Traversals that mimic the behaviour of the Prisms found in the original Data.Aeson.Lens.

Synopsis

Numbers

class AsNumber t where Source #

Traverse into various number types.

Methods

_Number :: Traversal' t Scientific Source #

>>> "[1, \"x\"]" ^? nth 0 . _Number
Just 1.0
>>> "[1, \"x\"]" ^? nth 1 . _Number
Nothing

_Number :: AsPrimitive t => Traversal' t Scientific Source #

>>> "[1, \"x\"]" ^? nth 0 . _Number
Just 1.0
>>> "[1, \"x\"]" ^? nth 1 . _Number
Nothing

_Double :: Traversal' t Double Source #

Traversal into an Double over a Value, Primitive or Scientific

>>> "[10.2]" ^? nth 0 . _Double
Just 10.2

_Integer :: Traversal' t Integer Source #

Traversal into an Integer over a Value, Primitive or Scientific

>>> "[10]" ^? nth 0 . _Integer
Just 10
>>> "[10.5]" ^? nth 0 . _Integer
Just 10
>>> "42" ^? _Integer
Just 42

_Integral :: (AsNumber t, Integral a) => Traversal' t a Source #

Access Integer Values as Integrals.

>>> "[10]" ^? nth 0 . _Integral
Just 10
>>> "[10.5]" ^? nth 0 . _Integral
Just 10

nonNull :: Traversal' Value Value Source #

Traversal into non-Null values

>>> "{\"a\": \"xyz\", \"b\": null}" ^? key "a" . nonNull
Just (String "xyz")
>>> "{\"a\": {}, \"b\": null}" ^? key "a" . nonNull
Just (Object (fromList []))
>>> "{\"a\": \"xyz\", \"b\": null}" ^? key "b" . nonNull
Nothing

Primitive

data Primitive Source #

Primitives of Value

Instances

Eq Primitive Source # 
Data Primitive Source # 

Methods

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

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

toConstr :: Primitive -> Constr #

dataTypeOf :: Primitive -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Primitive) #

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

gmapT :: (forall b. Data b => b -> b) -> Primitive -> Primitive #

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

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

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

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

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

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

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

Ord Primitive Source # 
Show Primitive Source # 
AsPrimitive Primitive Source # 
AsNumber Primitive Source # 

class AsNumber t => AsPrimitive t where Source #

Traverse into various JSON primitives.

Methods

_Primitive :: Traversal' t Primitive Source #

>>> "[1, \"x\", null, true, false]" ^? nth 0 . _Primitive
Just (NumberPrim 1.0)
>>> "[1, \"x\", null, true, false]" ^? nth 1 . _Primitive
Just (StringPrim "x")
>>> "[1, \"x\", null, true, false]" ^? nth 2 . _Primitive
Just NullPrim
>>> "[1, \"x\", null, true, false]" ^? nth 3 . _Primitive
Just (BoolPrim True)
>>> "[1, \"x\", null, true, false]" ^? nth 4 . _Primitive
Just (BoolPrim False)

_Primitive :: AsValue t => Traversal' t Primitive Source #

>>> "[1, \"x\", null, true, false]" ^? nth 0 . _Primitive
Just (NumberPrim 1.0)
>>> "[1, \"x\", null, true, false]" ^? nth 1 . _Primitive
Just (StringPrim "x")
>>> "[1, \"x\", null, true, false]" ^? nth 2 . _Primitive
Just NullPrim
>>> "[1, \"x\", null, true, false]" ^? nth 3 . _Primitive
Just (BoolPrim True)
>>> "[1, \"x\", null, true, false]" ^? nth 4 . _Primitive
Just (BoolPrim False)

_String :: Traversal' t Text Source #

>>> "{\"a\": \"xyz\", \"b\": true}" ^? key "a" . _String
Just "xyz"
>>> "{\"a\": \"xyz\", \"b\": true}" ^? key "b" . _String
Nothing

_Bool :: Traversal' t Bool Source #

>>> "{\"a\": \"xyz\", \"b\": true}" ^? key "b" . _Bool
Just True
>>> "{\"a\": \"xyz\", \"b\": true}" ^? key "a" . _Bool
Nothing

_Null :: Traversal' t () Source #

>>> "{\"a\": \"xyz\", \"b\": null}" ^? key "b" . _Null
Just ()
>>> "{\"a\": \"xyz\", \"b\": null}" ^? key "a" . _Null
Nothing

Objects and Arrays

class AsPrimitive t => AsValue t where Source #

Traverse into JSON Objects and Arrays.

Methods

_Value :: Traversal' t Value Source #

Traverse into data that encodes a Value

_Object :: Traversal' t (HashMap Text Value) Source #

>>> "{\"a\": {}, \"b\": null}" ^? key "a" . _Object
Just (fromList [])
>>> "{\"a\": {}, \"b\": null}" ^? key "b" . _Object
Nothing

_Array :: Traversal' t (Vector Value) Source #

key :: AsValue t => Text -> Traversal' t Value Source #

Like ix, but for Object with Text indices. This often has better inference than ix when used with OverloadedStrings.

>>> "{\"a\": 100, \"b\": 200}" ^? key "a"
Just (Number 100.0)
>>> "[1,2,3]" ^? key "a"
Nothing

members :: AsValue t => Traversal' t Value Source #

A Traversal into Object properties

>>> "{\"a\": 4, \"b\": 7}" ^.. members
[Number 4.0,Number 7.0]
>>> "{\"a\": 4, \"b\": 7}" & members . _Number %~ (* 10)
"{\"a\":40,\"b\":70}"

nth :: AsValue t => Int -> Traversal' t Value Source #

Like ix, but for Arrays with Int indexes

>>> "[1,2,3]" ^? nth 1
Just (Number 2.0)
>>> "{\"a\": 100, \"b\": 200}" ^? nth 1
Nothing
>>> "[1,2,3]" & nth 1 .~ Number 20
"[1,20,3]"

values :: AsValue t => Traversal' t Value Source #

A Traversal into Array elements

>>> "[1,2,3]" ^.. values
[Number 1.0,Number 2.0,Number 3.0]
>>> "[1,2,3]" & values . _Number %~ (* 10)
"[10,20,30]"

Decoding

class AsJSON t where Source #

Traverse into actual encoded JSON.

Methods

_JSON :: (FromJSON a, ToJSON a) => Traversal' t a Source #

_JSON is a Traversal from something containing JSON to something encoded in that structure.