Safe Haskell | None |
---|---|
Language | Haskell2010 |
Top level types and functions for Waargonaut Json
types.
Synopsis
- data JType ws a
- class AsJType r ws a | r -> ws a where
- newtype Json = Json (JType WS Json)
- parseWaargonaut :: (Monad f, CharParsing f) => f Json
- jsonTraversal :: Traversal' Json Json
- jsonWSTraversal :: Traversal Json Json WS WS
- jtypeTraversal :: Traversal (JType ws a) (JType ws a') a a'
- jtypeWSTraversal :: Traversal (JType ws a) (JType ws' a) ws ws'
- oat :: (AsJType r ws a, Semigroup ws, Monoid ws) => Text -> Traversal' r (Maybe a)
- oix :: (Semigroup ws, Monoid ws, AsJType r ws a) => Int -> Traversal' r a
- aix :: (AsJType r ws a, Semigroup ws, Monoid ws) => Int -> Traversal' r a
Inner JSON types
Individual JSON Types and their trailing whitespace.
Instances
Bifunctor JType Source # | |
Bitraversable JType Source # | |
Defined in Waargonaut.Types.Json bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> JType a b -> f (JType c d) # | |
Bifoldable JType Source # | |
Functor (JType ws) Source # | |
Foldable (JType ws) Source # | |
Defined in Waargonaut.Types.Json fold :: Monoid m => JType ws m -> m # foldMap :: Monoid m => (a -> m) -> JType ws a -> m # foldr :: (a -> b -> b) -> b -> JType ws a -> b # foldr' :: (a -> b -> b) -> b -> JType ws a -> b # foldl :: (b -> a -> b) -> b -> JType ws a -> b # foldl' :: (b -> a -> b) -> b -> JType ws a -> b # foldr1 :: (a -> a -> a) -> JType ws a -> a # foldl1 :: (a -> a -> a) -> JType ws a -> a # elem :: Eq a => a -> JType ws a -> Bool # maximum :: Ord a => JType ws a -> a # minimum :: Ord a => JType ws a -> a # | |
Traversable (JType ws) Source # | |
(Eq ws, Eq a) => Eq (JType ws a) Source # | |
(Show ws, Show a) => Show (JType ws a) Source # | |
AsJType (JType ws a) ws a Source # | |
Defined in Waargonaut.Types.Json |
class AsJType r ws a | r -> ws a where Source #
Typeclass for things that can represent a JType
_JType :: Prism' r (JType ws a) Source #
_JNull :: Prism' r ws Source #
_JBool :: Prism' r (Bool, ws) Source #
_JNum :: Prism' r (JNumber, ws) Source #
_JStr :: Prism' r (JString, ws) Source #
Instances
AsJType Json WS Json Source # | |
AsJType (JType ws a) ws a Source # | |
Defined in Waargonaut.Types.Json |
Top level JSON type
Top level Json type, we specialise the whitespace to WS
and the digit
type to Digit
. Also defining that our structures can recursively only contain
Json
types.
Instances
Eq Json Source # | |
Show Json Source # | |
Wrapped Json Source # | |
Json ~ t => Rewrapped Json t Source # | |
Defined in Waargonaut.Types.Json | |
AsJType Json WS Json Source # | |
JsonDecode (t :: k) Json Source # | |
JsonEncode (t :: k) Json Source # | |
Defined in Waargonaut.Generic | |
Monad f => MonadReader ParseFn (DecodeResult f) Source # | |
Defined in Waargonaut.Decode.Types ask :: DecodeResult f ParseFn # local :: (ParseFn -> ParseFn) -> DecodeResult f a -> DecodeResult f a # reader :: (ParseFn -> a) -> DecodeResult f a # | |
Applicative f => Divisible (EncoderFns (JObject WS Json) f) Source # | |
Defined in Waargonaut.Encode.Types divide :: (a -> (b, c)) -> EncoderFns (JObject WS Json) f b -> EncoderFns (JObject WS Json) f c -> EncoderFns (JObject WS Json) f a # | |
Applicative f => Decidable (EncoderFns (JObject WS Json) f) Source # | |
Defined in Waargonaut.Encode.Types | |
type Unwrapped Json Source # | |
Parser
parseWaargonaut :: (Monad f, CharParsing f) => f Json Source #
Parse to a Json
value, keeping all of the information about the leading
and trailing whitespace.
Traversals
jsonTraversal :: Traversal' Json Json Source #
Ignoring whitespace, traverse a Json
structure.
jsonWSTraversal :: Traversal Json Json WS WS Source #
Traverse the trailing whitespace of this Json
structure.
jtypeTraversal :: Traversal (JType ws a) (JType ws a') a a' Source #
Traverse the possible values of a JType
, skipping whitespace.
jtypeWSTraversal :: Traversal (JType ws a) (JType ws' a) ws ws' Source #
Traverse all of the whitespace of this Json
structure and every element
in the tree.
Optics
oat :: (AsJType r ws a, Semigroup ws, Monoid ws) => Text -> Traversal' r (Maybe a) Source #
A Traversal'
over the a
at the given Text
key on a JSON object.
>>>
E.simplePureEncodeTextNoSpaces E.json (obj & oat "c" ?~ E.asJson' E.int 33)
"{\"c\":33,\"a\":33,\"b\":\"Fred\"}">>>
E.simplePureEncodeTextNoSpaces E.json (obj & oat "d" ?~ E.asJson' E.text "sally")
"{\"d\":\"sally\",\"a\":33,\"b\":\"Fred\"}"
oix :: (Semigroup ws, Monoid ws, AsJType r ws a) => Int -> Traversal' r a Source #
A Traversal'
over the a
at the given Int
position in a JSON object.
>>>
E.simplePureEncodeTextNoSpaces E.json (obj & oix 0 .~ E.asJson' E.int 1)
"{\"a\":1,\"b\":\"Fred\"}">>>
E.simplePureEncodeTextNoSpaces E.json (obj & oix 1 .~ E.asJson' E.text "sally")
"{\"a\":33,\"b\":\"sally\"}"
aix :: (AsJType r ws a, Semigroup ws, Monoid ws) => Int -> Traversal' r a Source #
A Traversal'
over the a
at the given Int
position in a JSON array.
>>>
E.simplePureEncodeTextNoSpaces E.json ((E.asJson' (E.list E.int) [1,2,3]) & aix 0 .~ E.asJson' E.int 99)
"[99,2,3]">>>
E.simplePureEncodeTextNoSpaces E.json ((E.asJson' (E.list E.int) [1,2,3]) & aix 2 .~ E.asJson' E.int 44)
"[1,2,44]"