waargonaut-0.3.0.0: JSON wrangling

Safe HaskellNone
LanguageHaskell2010

Waargonaut.Encode

Contents

Description

Types and functions to encode your data types to Json.

Synopsis

Encoder type

newtype Encoder f a Source #

Define an "encoder" as a function from some a to some Json with the allowance for some context f.

Constructors

Encoder (a -> f Json) 
Instances
Contravariant (Encoder f) Source # 
Instance details

Defined in Waargonaut.Encode

Methods

contramap :: (a -> b) -> Encoder f b -> Encoder f a #

(>$) :: b -> Encoder f b -> Encoder f a #

MFunctor Encoder Source # 
Instance details

Defined in Waargonaut.Encode

Methods

hoist :: Monad m => (forall a. m a -> n a) -> Encoder m b -> Encoder n b #

Wrapped (Encoder f a) Source # 
Instance details

Defined in Waargonaut.Encode

Associated Types

type Unwrapped (Encoder f a) :: * #

Methods

_Wrapped' :: Iso' (Encoder f a) (Unwrapped (Encoder f a)) #

Encoder f a ~ t => Rewrapped (Encoder f a) t Source # 
Instance details

Defined in Waargonaut.Encode

type Unwrapped (Encoder f a) Source # 
Instance details

Defined in Waargonaut.Encode

type Unwrapped (Encoder f a) = a -> f Json

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 #

As encodeA but specialised to Identity when the additional flexibility isn't needed.

Runners

runPureEncoder :: Encoder' a -> a -> Json Source #

Run the given Encoder to produce a lazy ByteString.

runEncoder :: Encoder f a -> a -> f Json Source #

Run this Encoder to convert the a to Json

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

int :: Applicative f => Encoder f Int Source #

Encode an Int

integral :: (Applicative f, Integral n) => Encoder f n Source #

Encode a numeric value of the typeclass Integral

null :: Applicative f => Encoder f () Source #

Encode an explicit null.

either :: Encoder f a -> Encoder f b -> Encoder f (Either a b) Source #

Encode an Either value using the given Encoders

maybe :: Encoder f () -> Encoder f a -> Encoder f (Maybe a) Source #

Encode a Maybe value, using the provided Encoder's to handle the different choices.

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.

list :: Applicative f => Encoder f a -> Encoder f [a] Source #

Encode a list

nonempty :: Applicative f => Encoder f a -> Encoder f (NonEmpty a) Source #

Encode a NonEmpty list

mapToObj :: Applicative f => Encoder f a -> (k -> Text) -> Encoder f (Map k a) Source #

Encode a Map in a JSON object.

json :: Applicative f => Encoder f Json Source #

Encoder' for a Waargonaut Json data structure

prismE :: Prism' a b -> Encoder f a -> Encoder f b Source #

Build an Encoder using a Prism'

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 an Int value 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

intAt :: Text -> Int -> MapLikeObj WS Json -> MapLikeObj WS Json Source #

Encode an Int at the given Text key.

textAt :: Text -> Text -> MapLikeObj WS Json -> MapLikeObj WS Json Source #

Encode a Text value at the given Text key.

boolAt :: Text -> Bool -> MapLikeObj WS Json -> MapLikeObj WS Json Source #

Encode a Bool at the given Text 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

int' :: Encoder' Int Source #

As per int but with the f specialised to Identity.

integral' :: Integral n => Encoder' n Source #

As per integral but with the f specialised to Identity.

scientific' :: Encoder' Scientific Source #

As per scientific but with the f specialised to Identity.

bool' :: Encoder' Bool Source #

As per bool but with the f specialised to Identity.

text' :: Encoder' Text Source #

As per text but with the f specialised to Identity.

null' :: Encoder' () Source #

As per null but with the f specialised to Identity.

either' :: Encoder' a -> Encoder' b -> Encoder' (Either a b) Source #

As per either but with the f specialised to Identity.

maybe' :: Encoder' () -> Encoder' a -> Encoder' (Maybe a) Source #

As per maybe 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.

nonempty' :: Encoder' a -> Encoder' (NonEmpty a) Source #

As per nonempty but with the f specialised to Identity.

list' :: Encoder' a -> Encoder' [a] Source #

As per list 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.

mapToObj' :: Encoder' a -> (k -> Text) -> Encoder' (Map k a) Source #

Using the given function to convert the k type keys to a Text value, encode a Map as a JSON object.

keyValuesAsObj' :: (Foldable g, Functor g) => g (a -> JObject WS Json -> JObject WS Json) -> Encoder' a Source #

As per keyValuesAsObj but with the f specialised to Identity.

json' :: Encoder' Json Source #

As per json but with the f specialised to Identity.

generaliseEncoder' :: Monad f => Encoder' a -> Encoder f a Source #

Generalise an Encoder a' to 'Encoder f a'