Safe Haskell | None |
---|---|
Language | Haskell2010 |
Types and functions for handling our representation of a JSON object.
Synopsis
- newtype JObject ws a = JObject (CommaSeparated ws (JAssoc ws a))
- class HasJObject c ws a | c -> ws a where
- data JAssoc ws a = JAssoc {
- _jsonAssocKey :: JString
- _jsonAssocKeyTrailingWS :: ws
- _jsonAssocValPreceedingWS :: ws
- _jsonAssocVal :: a
- class HasJAssoc c ws a | c -> ws a where
- jAssoc :: Lens' c (JAssoc ws a)
- jsonAssocKey :: Lens' c JString
- jsonAssocKeyTrailingWS :: Lens' c ws
- jsonAssocVal :: Lens' c a
- jsonAssocValPreceedingWS :: Lens' c ws
- data MapLikeObj ws a
- toMapLikeObj :: (Semigroup ws, Monoid ws) => JObject ws a -> (MapLikeObj ws a, [JAssoc ws a])
- fromMapLikeObj :: MapLikeObj ws a -> JObject ws a
- _MapLikeObj :: (Semigroup ws, Monoid ws) => Prism' (JObject ws a) (MapLikeObj ws a)
- parseJObject :: (Monad f, CharParsing f) => f ws -> f a -> f (JObject ws a)
Object Type
The representation of a JSON object.
The JSON RFC8259 indicates that names within an object "should" be unique. But the standard does not enforce this, leaving it to the various implementations to decide how to handle it.
As there are multiple possibilities for deciding which key to use when enforcing uniqueness, Waargonaut accepts duplicate keys, allowing you to decide how to handle it.
This type is the "list of tuples of key and value" structure, as such it is a
wrapper around the CommaSeparated
data type.
JObject (CommaSeparated ws (JAssoc ws a)) |
Instances
class HasJObject c ws a | c -> ws a where Source #
Type class to represent something that has a JObject
within it.
Key/value pair type
This type represents the key:value pair inside of a JSON object.
It is built like this so that we can preserve any whitespace information that may surround it.
JAssoc | |
|
Instances
Bifunctor JAssoc Source # | |
Bitraversable JAssoc Source # | |
Defined in Waargonaut.Types.JObject.JAssoc bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> JAssoc a b -> f (JAssoc c d) # | |
Bifoldable JAssoc Source # | |
Functor (JAssoc ws) Source # | |
Foldable (JAssoc ws) Source # | |
Defined in Waargonaut.Types.JObject.JAssoc fold :: Monoid m => JAssoc ws m -> m # foldMap :: Monoid m => (a -> m) -> JAssoc ws a -> m # foldr :: (a -> b -> b) -> b -> JAssoc ws a -> b # foldr' :: (a -> b -> b) -> b -> JAssoc ws a -> b # foldl :: (b -> a -> b) -> b -> JAssoc ws a -> b # foldl' :: (b -> a -> b) -> b -> JAssoc ws a -> b # foldr1 :: (a -> a -> a) -> JAssoc ws a -> a # foldl1 :: (a -> a -> a) -> JAssoc ws a -> a # toList :: JAssoc ws a -> [a] # length :: JAssoc ws a -> Int # elem :: Eq a => a -> JAssoc ws a -> Bool # maximum :: Ord a => JAssoc ws a -> a # minimum :: Ord a => JAssoc ws a -> a # | |
Traversable (JAssoc ws) Source # | |
Defined in Waargonaut.Types.JObject.JAssoc | |
(Eq ws, Eq a) => Eq (JAssoc ws a) Source # | |
(Show ws, Show a) => Show (JAssoc ws a) Source # | |
HasJAssoc (JAssoc ws a) ws a Source # | |
Defined in Waargonaut.Types.JObject.JAssoc |
class HasJAssoc c ws a | c -> ws a where Source #
This class allows you to write connective lenses for other data structures
that may contain a JAssoc
.
jAssoc :: Lens' c (JAssoc ws a) Source #
jsonAssocKey :: Lens' c JString Source #
jsonAssocKeyTrailingWS :: Lens' c ws Source #
jsonAssocVal :: Lens' c a Source #
jsonAssocValPreceedingWS :: Lens' c ws Source #
Instances
HasJAssoc (JAssoc ws a) ws a Source # | |
Defined in Waargonaut.Types.JObject.JAssoc |
Map-like object representation
data MapLikeObj ws a Source #
This is a newtype around our JObject
for when we want to use the
"map-like" representation of our JSON object. This data type will enforce that
the first key found is treated as the desired element, and all subsequent
occurrences of that key are discarded.
Instances
toMapLikeObj :: (Semigroup ws, Monoid ws) => JObject ws a -> (MapLikeObj ws a, [JAssoc ws a]) Source #
Take a JObject
and produce a MapLikeObj
where the first key is
considered the unique value. Subsequence occurrences of that key and it's value
are collected and returned as a list.
fromMapLikeObj :: MapLikeObj ws a -> JObject ws a Source #
Access the underlying JObject
.
_MapLikeObj :: (Semigroup ws, Monoid ws) => Prism' (JObject ws a) (MapLikeObj ws a) Source #
Prism
for working with a JObject
as a MapLikeObj
. This optic will keep
the first unique key on a given JObject
and this information is not
recoverable. If you want to create a MapLikeObj
from a JObject
and keep
what is removed, then use the toMapLikeObj
function.
Parser
parseJObject :: (Monad f, CharParsing f) => f ws -> f a -> f (JObject ws a) Source #
>>>
testparse (parseJObject parseWhitespace parseWaargonaut) "{\"foo\":null }"
Right (JObject (CommaSeparated (WS []) (Just (Elems {_elemsElems = [], _elemsLast = Elem {_elemVal = JAssoc {_jsonAssocKey = JString' [UnescapedJChar (Unescaped 'f'),UnescapedJChar (Unescaped 'o'),UnescapedJChar (Unescaped 'o')], _jsonAssocKeyTrailingWS = WS [], _jsonAssocValPreceedingWS = WS [], _jsonAssocVal = Json (JNull (WS [Space]))}, _elemTrailing = Nothing}}))))
>>>
testparse (parseJObject parseWhitespace parseWaargonaut) "{\"foo\":null, }"
Right (JObject (CommaSeparated (WS []) (Just (Elems {_elemsElems = [], _elemsLast = Elem {_elemVal = JAssoc {_jsonAssocKey = JString' [UnescapedJChar (Unescaped 'f'),UnescapedJChar (Unescaped 'o'),UnescapedJChar (Unescaped 'o')], _jsonAssocKeyTrailingWS = WS [], _jsonAssocValPreceedingWS = WS [], _jsonAssocVal = Json (JNull (WS []))}, _elemTrailing = Just (Comma,WS [Space])}}))))