aeson-optics-1.1.0.1: Law-abiding optics for aeson

Copyright(c) Oleg Grenrus 2019 (c) Edward Kmett 2013-2019 (c) Paul Wilson 2012
LicenseMIT
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Aeson.Optics

Contents

Description

This module also exports orphan Ixed Value and Plated Value instances.

Synopsis

Numbers

class AsNumber t where Source #

Minimal complete definition

Nothing

Methods

_Number :: Prism' t Scientific Source #

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

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

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

_Double :: Prism' t Double Source #

Prism into an Double over a Value, Primitive or Scientific

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

_Integer :: Prism' t Integer Source #

Prism 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
Instances
AsNumber ByteString Source # 
Instance details

Defined in Data.Aeson.Optics

AsNumber ByteString Source # 
Instance details

Defined in Data.Aeson.Optics

AsNumber Scientific Source # 
Instance details

Defined in Data.Aeson.Optics

AsNumber Text Source # 
Instance details

Defined in Data.Aeson.Optics

AsNumber Value Source # 
Instance details

Defined in Data.Aeson.Optics

AsNumber Text Source # 
Instance details

Defined in Data.Aeson.Optics

AsNumber String Source # 
Instance details

Defined in Data.Aeson.Optics

AsNumber Primitive Source # 
Instance details

Defined in Data.Aeson.Optics

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

Access Integer Values as Integrals.

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

nonNull :: Prism' Value Value Source #

Prism 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 # 
Instance details

Defined in Data.Aeson.Optics

Data Primitive Source # 
Instance details

Defined in Data.Aeson.Optics

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 # 
Instance details

Defined in Data.Aeson.Optics

Show Primitive Source # 
Instance details

Defined in Data.Aeson.Optics

AsPrimitive Primitive Source # 
Instance details

Defined in Data.Aeson.Optics

AsNumber Primitive Source # 
Instance details

Defined in Data.Aeson.Optics

class AsNumber t => AsPrimitive t where Source #

Minimal complete definition

Nothing

Methods

_Primitive :: Prism' 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 => Prism' 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 :: Prism' t Text Source #

>>> "{\"a\": \"xyz\", \"b\": true}" ^? key "a" % _String
Just "xyz"
>>> "{\"a\": \"xyz\", \"b\": true}" ^? key "b" % _String
Nothing
>>> _Object # HashMap.fromList [("key", _String # "value")] :: String
"{\"key\":\"value\"}"

_Bool :: Prism' t Bool Source #

>>> "{\"a\": \"xyz\", \"b\": true}" ^? key "b" % _Bool
Just True
>>> "{\"a\": \"xyz\", \"b\": true}" ^? key "a" % _Bool
Nothing
>>> _Bool # True :: String
"true"
>>> _Bool # False :: String
"false"

_Null :: Prism' t () Source #

>>> "{\"a\": \"xyz\", \"b\": null}" ^? key "b" % _Null
Just ()
>>> "{\"a\": \"xyz\", \"b\": null}" ^? key "a" % _Null
Nothing
>>> _Null # () :: String
"null"
Instances
AsPrimitive ByteString Source # 
Instance details

Defined in Data.Aeson.Optics

AsPrimitive ByteString Source # 
Instance details

Defined in Data.Aeson.Optics

AsPrimitive Text Source # 
Instance details

Defined in Data.Aeson.Optics

AsPrimitive Value Source # 
Instance details

Defined in Data.Aeson.Optics

AsPrimitive Text Source # 
Instance details

Defined in Data.Aeson.Optics

AsPrimitive String Source # 
Instance details

Defined in Data.Aeson.Optics

AsPrimitive Primitive Source # 
Instance details

Defined in Data.Aeson.Optics

Objects and Arrays

class AsPrimitive t => AsValue t where Source #

Minimal complete definition

_Value

Methods

_Value :: Prism' t Value Source #

>>> preview _Value "[1,2,3]" == Just (Array (Vector.fromList [Number 1.0,Number 2.0,Number 3.0]))
True

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

>>> "{\"a\": {}, \"b\": null}" ^? key "a" % _Object
Just (fromList [])
>>> "{\"a\": {}, \"b\": null}" ^? key "b" % _Object
Nothing
>>> _Object # HashMap.fromList [("key", _String # "value")] :: String
"{\"key\":\"value\"}"

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

>>> preview _Array "[1,2,3]" == Just (Vector.fromList [Number 1.0,Number 2.0,Number 3.0])
True

key :: AsValue t => Text -> AffineTraversal' 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 => IxTraversal' Text t Value Source #

An indexed Traversal into Object properties

>>> Data.List.sort (itoListOf (members % _Number) "{\"a\": 4, \"b\": 7}")
[("a",4.0),("b",7.0)]
>>> "{\"a\": 4}" & members % _Number %~ (*10)
"{\"a\":40}"

nth :: AsValue t => Int -> AffineTraversal' 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 => IxTraversal' Int t Value Source #

An indexed 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 #

Methods

_JSON :: (FromJSON a, ToJSON b) => Prism t t a b Source #

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

Instances
AsJSON ByteString Source # 
Instance details

Defined in Data.Aeson.Optics

AsJSON ByteString Source # 
Instance details

Defined in Data.Aeson.Optics

AsJSON Text Source # 
Instance details

Defined in Data.Aeson.Optics

Methods

_JSON :: (FromJSON a, ToJSON b) => Prism Text Text a b Source #

AsJSON Value Source # 
Instance details

Defined in Data.Aeson.Optics

Methods

_JSON :: (FromJSON a, ToJSON b) => Prism Value Value a b Source #

AsJSON Text Source # 
Instance details

Defined in Data.Aeson.Optics

Methods

_JSON :: (FromJSON a, ToJSON b) => Prism Text Text a b Source #

AsJSON String Source # 
Instance details

Defined in Data.Aeson.Optics

Methods

_JSON :: (FromJSON a, ToJSON b) => Prism String String a b Source #

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

Pattern Synonyms

pattern JSON :: (FromJSON a, ToJSON a, AsJSON t) => a -> t Source #

pattern Value_ :: (FromJSON a, ToJSON a) => a -> Value Source #

pattern Number_ :: AsNumber t => Scientific -> t Source #

pattern Double :: AsNumber t => Double -> t Source #

pattern Integer :: AsNumber t => Integer -> t Source #

pattern Integral :: (AsNumber t, Integral a) => a -> t Source #

pattern Primitive :: AsPrimitive t => Primitive -> t Source #

pattern Bool_ :: AsPrimitive t => Bool -> t Source #

pattern String_ :: AsPrimitive t => Text -> t Source #

pattern Null_ :: AsPrimitive t => t Source #

Orphan instances

Ixed Value Source # 
Instance details