| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Waargonaut.Encode
Contents
Description
Types and functions to encode your data types to Json.
Synopsis
- newtype Encoder f a = Encoder (a -> f Json)
- type Encoder' = Encoder Identity
- encodeA :: (a -> f Json) -> Encoder f a
- encodePureA :: (a -> Json) -> Encoder' a
- runPureEncoder :: Encoder' a -> a -> Json
- runEncoder :: Encoder f a -> a -> f Json
- simpleEncodeNoSpaces :: Applicative f => Encoder f a -> a -> f ByteString
- simplePureEncodeNoSpaces :: Encoder' a -> a -> ByteString
- int :: Applicative f => Encoder f Int
- scientific :: Applicative f => Encoder f Scientific
- bool :: Applicative f => Encoder f Bool
- text :: Applicative f => Encoder f Text
- null :: Applicative f => Encoder f ()
- either :: Encoder f a -> Encoder f b -> Encoder f (Either a b)
- maybe :: Encoder f () -> Encoder f a -> Encoder f (Maybe a)
- maybeOrNull :: Applicative f => Encoder f a -> Encoder f (Maybe a)
- traversable :: (Applicative f, Traversable t) => Encoder f a -> Encoder f (t a)
- list :: Applicative f => Encoder f a -> Encoder f [a]
- nonempty :: Applicative f => Encoder f a -> Encoder f (NonEmpty a)
- mapToObj :: Applicative f => Encoder f a -> (k -> Text) -> Encoder f (Map k a)
- json :: Applicative f => Encoder f Json
- prismE :: Prism' a b -> Encoder f a -> Encoder f b
- mapLikeObj :: (AsJType Json ws a, Monoid ws, Semigroup ws, Applicative f) => (i -> MapLikeObj ws a -> MapLikeObj ws a) -> Encoder f i
- atKey :: (At t, IxValue t ~ Json, Applicative f) => Index t -> Encoder f a -> a -> t -> f t
- intAt :: Text -> Int -> MapLikeObj WS Json -> MapLikeObj WS Json
- textAt :: Text -> Text -> MapLikeObj WS Json -> MapLikeObj WS Json
- boolAt :: Text -> Bool -> MapLikeObj WS Json -> MapLikeObj WS Json
- traversableAt :: (At t, Traversable f, IxValue t ~ Json) => Encoder' a -> Index t -> f a -> t -> t
- listAt :: (At t, IxValue t ~ Json) => Encoder' a -> Index t -> [a] -> t -> t
- nonemptyAt :: (At t, IxValue t ~ Json) => Encoder' a -> Index t -> NonEmpty a -> t -> t
- encAt :: Applicative f => Encoder f b -> Text -> (a -> b) -> a -> JObject WS Json -> f (JObject WS Json)
- keyValuesAsObj :: (Foldable g, Monad f) => g (a -> JObject WS Json -> f (JObject WS Json)) -> Encoder f a
- onObj :: Applicative f => Text -> b -> Encoder f b -> JObject WS Json -> f (JObject WS Json)
- keyValueTupleFoldable :: (Monad f, Foldable g) => Encoder f a -> Encoder f (g (Text, a))
- int' :: Encoder' Int
- scientific' :: Encoder' Scientific
- bool' :: Encoder' Bool
- text' :: Encoder' Text
- null' :: Encoder' ()
- either' :: Encoder' a -> Encoder' b -> Encoder' (Either a b)
- maybe' :: Encoder' () -> Encoder' a -> Encoder' (Maybe a)
- maybeOrNull' :: Encoder' a -> Encoder' (Maybe a)
- traversable' :: Traversable t => Encoder' a -> Encoder' (t a)
- nonempty' :: Encoder' a -> Encoder' (NonEmpty a)
- list' :: Encoder' a -> Encoder' [a]
- atKey' :: (At t, IxValue t ~ Json) => Index t -> Encoder' a -> a -> t -> t
- mapLikeObj' :: (AsJType Json ws a, Semigroup ws, Monoid ws) => (i -> MapLikeObj ws a -> MapLikeObj ws a) -> Encoder' i
- mapToObj' :: Encoder' a -> (k -> Text) -> Encoder' (Map k a)
- keyValuesAsObj' :: (Foldable g, Functor g) => g (a -> JObject WS Json -> JObject WS Json) -> Encoder' a
- json' :: Encoder' Json
- generaliseEncoder' :: Monad f => Encoder' a -> Encoder f a
Encoder type
Define an "encoder" as a function from some a to some Json with the
allowance for some context f.
type Encoder' = Encoder Identity Source #
As a convenience, this type is a pure Encoder over Identity in place of the f.
Creation
encodeA :: (a -> f Json) -> Encoder f a Source #
Create an Encoder' for a by providing a function from 'a -> f Json'.
encodePureA :: (a -> Json) -> Encoder' a Source #
Runners
runPureEncoder :: Encoder' a -> a -> Json Source #
Run the given Encoder to produce a lazy ByteString.
simpleEncodeNoSpaces :: Applicative f => Encoder f a -> a -> f ByteString Source #
Encode an a directly to a ByteString using the provided Encoder.
simplePureEncodeNoSpaces :: Encoder' a -> a -> ByteString Source #
As per simpleEncodeNoSpaces but specialised the f to Identity and remove it.
Provided encoders
scientific :: Applicative f => Encoder f Scientific Source #
Encode an Scientific
maybeOrNull :: Applicative f => Encoder f a -> Encoder f (Maybe a) Source #
Encode a 'Maybe a' to either 'Encoder a' or null
traversable :: (Applicative f, Traversable t) => Encoder f a -> Encoder f (t a) Source #
Encode some Traversable of a into a JSON array.
mapToObj :: Applicative f => Encoder f a -> (k -> Text) -> Encoder f (Map k a) Source #
Encode a Map in a JSON object.
Object encoder helpers
mapLikeObj :: (AsJType Json ws a, Monoid ws, Semigroup ws, Applicative f) => (i -> MapLikeObj ws a -> MapLikeObj ws a) -> Encoder f i Source #
Apply a function to update a MapLikeObj and encode that as a JSON object.
For example, given the following data type:
data Image = Image
{ _imageW :: Int
, _imageH :: Int
, _imageTitle :: Text
, _imageAnimated :: Bool
, _imageIDs :: [Int]
}
We can use this function to create an encoder, composing the individual update functions to set the keys and values as desired.
encodeImage :: Applicative f => Encoder f Image encodeImage = mapLikeObj $ \img -> intAt "Width" (_imageW img) . -- ^ Set anIntvalue at the "Width" key. intAt "Height" (_imageH img) . textAt "Title" (_imageTitle img) . boolAt "Animated" (_imageAnimated img) . arrayAt int "IDs" (_imageIDs img) -- ^ Set an[Int]value at the "IDs" key.
atKey :: (At t, IxValue t ~ Json, Applicative f) => Index t -> Encoder f a -> a -> t -> f t Source #
When encoding a MapLikeObj, this function lets you encode a value at a specific key
traversableAt :: (At t, Traversable f, IxValue t ~ Json) => Encoder' a -> Index t -> f a -> t -> t Source #
Encode a Foldable of a at the given index on a JSON object.
listAt :: (At t, IxValue t ~ Json) => Encoder' a -> Index t -> [a] -> t -> t Source #
Encode a standard Haskell list at the given index on a JSON object.
nonemptyAt :: (At t, IxValue t ~ Json) => Encoder' a -> Index t -> NonEmpty a -> t -> t Source #
Encode a NonEmpty list at the given index on a JSON object.
encAt :: Applicative f => Encoder f b -> Text -> (a -> b) -> a -> JObject WS Json -> f (JObject WS Json) Source #
Using a given Encoder, encode a key value pair on the JSON object, using
the accessor function to retrieve the value.
keyValuesAsObj :: (Foldable g, Monad f) => g (a -> JObject WS Json -> f (JObject WS Json)) -> Encoder f a Source #
Encode key value pairs as a JSON object, allowing duplicate keys.
onObj :: Applicative f => Text -> b -> Encoder f b -> JObject WS Json -> f (JObject WS Json) Source #
When encoding a JSON object that may contain duplicate keys, this function
works the same as the atKey function for MapLikeObj.
keyValueTupleFoldable :: (Monad f, Foldable g) => Encoder f a -> Encoder f (g (Text, a)) Source #
Encode some Foldable of (Text, a) as a JSON object. This permits duplicate
keys.
Encoders specialised to Identity
scientific' :: Encoder' Scientific Source #
As per scientific but with the f specialised to Identity.
maybeOrNull' :: Encoder' a -> Encoder' (Maybe a) Source #
As per maybeOrNull but with the f specialised to Identity.
traversable' :: Traversable t => Encoder' a -> Encoder' (t a) Source #
As per traversable but with the f specialised to Identity.
atKey' :: (At t, IxValue t ~ Json) => Index t -> Encoder' a -> a -> t -> t Source #
Encode an a at the given index on the JSON object.
mapLikeObj' :: (AsJType Json ws a, Semigroup ws, Monoid ws) => (i -> MapLikeObj ws a -> MapLikeObj ws a) -> Encoder' i Source #
As per mapLikeObj but specialised for Identity as the Applicative.