| Copyright | (c) Edward Kmett 2013-2019 (c) Paul Wilson 2012 | 
|---|---|
| License | BSD3 | 
| Maintainer | Edward Kmett <ekmett@gmail.com> | 
| Stability | experimental | 
| Portability | non-portable | 
| Safe Haskell | Trustworthy | 
| Language | Haskell2010 | 
Data.Aeson.Lens
Synopsis
- class AsNumber t where
- _Integral :: (AsNumber t, Integral a) => Prism' t a
- nonNull :: Prism' Value Value
- data Primitive- = StringPrim !Text
- | NumberPrim !Scientific
- | BoolPrim !Bool
- | NullPrim
 
- class AsNumber t => AsPrimitive t where
- class AsPrimitive t => AsValue t where
- key :: AsValue t => Text -> Traversal' t Value
- members :: AsValue t => IndexedTraversal' Text t Value
- nth :: AsValue t => Int -> Traversal' t Value
- values :: AsValue t => IndexedTraversal' Int t Value
- class AsJSON t where
- _JSON' :: (AsJSON t, FromJSON a, ToJSON a) => Prism' t a
- pattern JSON :: (FromJSON a, ToJSON a, AsJSON t) => a -> t
- pattern Value_ :: (FromJSON a, ToJSON a) => a -> Value
- pattern Number_ :: AsNumber t => Scientific -> t
- pattern Double :: AsNumber t => Double -> t
- pattern Integer :: AsNumber t => Integer -> t
- pattern Integral :: (AsNumber t, Integral a) => a -> t
- pattern Primitive :: AsPrimitive t => Primitive -> t
- pattern Bool_ :: AsPrimitive t => Bool -> t
- pattern String_ :: AsPrimitive t => Text -> t
- pattern Null_ :: AsPrimitive t => t
Numbers
class AsNumber t where Source #
Minimal complete definition
Nothing
Methods
_Number :: Prism' t Scientific Source #
>>>"[1, \"x\"]" ^? nth 0 . _NumberJust 1.0
>>>"[1, \"x\"]" ^? nth 1 . _NumberNothing
default _Number :: AsPrimitive t => Prism' t Scientific Source #
_Double :: Prism' t Double Source #
Prism into an Double over a Value, Primitive or Scientific
>>>"[10.2]" ^? nth 0 . _DoubleJust 10.2
_Integer :: Prism' t Integer Source #
Prism into an Integer over a Value, Primitive or Scientific
>>>"[10]" ^? nth 0 . _IntegerJust 10
>>>"[10.5]" ^? nth 0 . _IntegerJust 10
>>>"42" ^? _IntegerJust 42
Instances
| AsNumber ByteString Source # | |
| Defined in Data.Aeson.Lens | |
| AsNumber ByteString Source # | |
| Defined in Data.Aeson.Lens | |
| AsNumber Scientific Source # | |
| Defined in Data.Aeson.Lens | |
| AsNumber String Source # | |
| AsNumber Text Source # | |
| AsNumber Value Source # | |
| AsNumber Text Source # | |
| AsNumber Primitive Source # | |
_Integral :: (AsNumber t, Integral a) => Prism' t a Source #
Access Integer Values as Integrals.
>>>"[10]" ^? nth 0 . _IntegralJust 10
>>>"[10.5]" ^? nth 0 . _IntegralJust 10
nonNull :: Prism' Value Value Source #
Prism into non-Null values
>>>"{\"a\": \"xyz\", \"b\": null}" ^? key "a" . nonNullJust (String "xyz")
>>>"{\"a\": {}, \"b\": null}" ^? key "a" . nonNullJust (Object (fromList []))
>>>"{\"a\": \"xyz\", \"b\": null}" ^? key "b" . nonNullNothing
Primitive
Primitives of Value
Constructors
| StringPrim !Text | |
| NumberPrim !Scientific | |
| BoolPrim !Bool | |
| NullPrim | 
Instances
| Eq Primitive Source # | |
| Data Primitive Source # | |
| Defined in Data.Aeson.Lens 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 :: forall r r'. (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 #
Minimal complete definition
Nothing
Methods
_Primitive :: Prism' t Primitive Source #
>>>"[1, \"x\", null, true, false]" ^? nth 0 . _PrimitiveJust (NumberPrim 1.0)
>>>"[1, \"x\", null, true, false]" ^? nth 1 . _PrimitiveJust (StringPrim "x")
>>>"[1, \"x\", null, true, false]" ^? nth 2 . _PrimitiveJust NullPrim
>>>"[1, \"x\", null, true, false]" ^? nth 3 . _PrimitiveJust (BoolPrim True)
>>>"[1, \"x\", null, true, false]" ^? nth 4 . _PrimitiveJust (BoolPrim False)
_String :: Prism' t Text Source #
>>>"{\"a\": \"xyz\", \"b\": true}" ^? key "a" . _StringJust "xyz"
>>>"{\"a\": \"xyz\", \"b\": true}" ^? key "b" . _StringNothing
>>>_Object._Wrapped # [("key" :: Text, _String # "value")] :: String"{\"key\":\"value\"}"
_Bool :: Prism' t Bool Source #
>>>"{\"a\": \"xyz\", \"b\": true}" ^? key "b" . _BoolJust True
>>>"{\"a\": \"xyz\", \"b\": true}" ^? key "a" . _BoolNothing
>>>_Bool # True :: String"true"
>>>_Bool # False :: String"false"
>>>"{\"a\": \"xyz\", \"b\": null}" ^? key "b" . _NullJust ()
>>>"{\"a\": \"xyz\", \"b\": null}" ^? key "a" . _NullNothing
>>>_Null # () :: String"null"
Instances
| AsPrimitive ByteString Source # | |
| Defined in Data.Aeson.Lens Methods _Primitive :: Prism' ByteString Primitive Source # _String :: Prism' ByteString Text Source # _Bool :: Prism' ByteString Bool Source # _Null :: Prism' ByteString () Source # | |
| AsPrimitive ByteString Source # | |
| Defined in Data.Aeson.Lens Methods _Primitive :: Prism' ByteString Primitive Source # _String :: Prism' ByteString Text Source # _Bool :: Prism' ByteString Bool Source # _Null :: Prism' ByteString () Source # | |
| AsPrimitive String Source # | |
| AsPrimitive Text Source # | |
| AsPrimitive Value Source # | |
| AsPrimitive Text Source # | |
| AsPrimitive Primitive Source # | |
Objects and Arrays
class AsPrimitive t => AsValue t where Source #
Minimal complete definition
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" . _ObjectJust (fromList [])
>>>"{\"a\": {}, \"b\": null}" ^? key "b" . _ObjectNothing
>>>_Object._Wrapped # [("key" :: Text, _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
members :: AsValue t => IndexedTraversal' Text t Value Source #
An indexed Traversal into Object properties
>>>Data.List.sort ("{\"a\": 4, \"b\": 7}" ^@.. members . _Number)[("a",4.0),("b",7.0)]
>>>"{\"a\": 4}" & members . _Number *~ 10"{\"a\":40}"
nth :: AsValue t => Int -> Traversal' t Value Source #
Like ix, but for Arrays with Int indexes
>>>"[1,2,3]" ^? nth 1Just (Number 2.0)
>>>"{\"a\": 100, \"b\": 200}" ^? nth 1Nothing
>>>"[1,2,3]" & nth 1 .~ Number 20"[1,20,3]"
values :: AsValue t => IndexedTraversal' 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
Methods
Instances
| AsJSON ByteString Source # | |
| Defined in Data.Aeson.Lens Methods _JSON :: (FromJSON a, ToJSON b) => Prism ByteString ByteString a b Source # | |
| AsJSON ByteString Source # | |
| Defined in Data.Aeson.Lens Methods _JSON :: (FromJSON a, ToJSON b) => Prism ByteString ByteString a b Source # | |
| AsJSON String Source # | |
| AsJSON Text Source # | |
| AsJSON Value Source # | |
| AsJSON Text Source # | |
Pattern Synonyms
pattern Number_ :: AsNumber t => Scientific -> 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 #