waargonaut-0.6.1.0: JSON wrangling

Safe HaskellNone
LanguageHaskell2010

Waargonaut.Encode

Contents

Description

Types and functions to encode your data types to Json.

Synopsis

Encoder type

type Encoder f a = EncoderFns Json f a Source #

As a convenience, this type defines the i to be a specific Json structure:

type Encoder' a = EncoderFns Json Identity a Source #

As a convenience, this type is a pure Encoder over Identity in place of the f.

type ObjEncoder f a = EncoderFns (JObject WS Json) f a Source #

As a convenience, this type defines the i to be a specific 'JObject WS Json' structure:

type ObjEncoder' a = EncoderFns (JObject WS Json) Identity a Source #

As a convenience, this type is a pure ObjEncoder 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.

jsonEncoder :: (a -> f Json) -> EncoderFns Json f a Source #

Helper function for creating an Encoder, provides the default finaliseEncoding function for Json encoders.

objEncoder :: (a -> f (JObject WS Json)) -> EncoderFns (JObject WS Json) f a Source #

Helper function for creating a JSON object Encoder. Provides the default finaliseEncoding function for completing the JObject to the necessary Json type.

Runners

runPureEncoder :: EncoderFns i Identity a -> a -> Json Source #

Run any encoder to the Json representation, with the context specialised to Identity for convenience.

runEncoder :: Functor f => EncoderFns i f a -> a -> f Json Source #

Run any encoder to the Json representation, allowing for some Functor context f.

simpleEncodeWith :: (Applicative f, Monoid b, IsString t) => Builder t b -> (b -> out) -> (Builder t b -> WS -> b) -> Encoder f a -> a -> f out Source #

Encode an a directly to some output text type using the provided Builder and Encoder.

simplePureEncodeWith :: (Monoid b, IsString t) => Builder t b -> (b -> out) -> (Builder t b -> WS -> b) -> Encoder Identity a -> a -> out Source #

Encode an a directly to a Text using the provided Encoder.

simpleEncodeText :: Applicative f => Encoder f a -> a -> f Text Source #

Encode an a directly to a Text using the provided Encoder.

simpleEncodeTextNoSpaces :: Applicative f => Encoder f a -> a -> f Text Source #

Encode an a directly to a Text using the provided Encoder.

simpleEncodeByteString :: Applicative f => Encoder f a -> a -> f ByteString Source #

Encode an a directly to a ByteString using the provided Encoder.

simpleEncodeByteStringNoSpaces :: Applicative f => Encoder f a -> a -> f ByteString Source #

Encode an a directly to a ByteString using the provided Encoder.

simplePureEncodeText :: Encoder Identity a -> a -> Text Source #

As per simpleEncodeText but specialised the f to Identity.

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 :: Functor f => Encoder f a -> Encoder f b -> Encoder f (Either a b) Source #

Encode an Either value using the given Encoders

maybe :: Functor f => 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'

asJson :: Applicative f => Encoder f a -> a -> f Json Source #

Transform the given input using the Encoder to its Json data structure representation.

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) .
  listAt 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.

extendObject :: Functor f => ObjEncoder f a -> a -> (JObject WS Json -> JObject WS Json) -> f Json Source #

This function allows you to extend the fields on a JSON object created by a separate encoder.

extendMapLikeObject :: Functor f => ObjEncoder f a -> a -> (MapLikeObj WS Json -> MapLikeObj WS Json) -> f Json Source #

This function lets you extend the fields on a JSON object but enforces the uniqueness of the keys by working through the MapLikeObj structure.

This will keep the first occurence of each unique key in the map. So be sure to check your output.

combineObjects :: Applicative f => (a -> (b, c)) -> ObjEncoder f b -> ObjEncoder f c -> ObjEncoder f a Source #

Given encoders for things that are represented in JSON as objects, and a way to get to the b and c from the a. This function lets you create an encoder for a. The two objects are combined to make one single JSON object.

Given

encodeFoo :: ObjEncoder f Foo
encodeBar :: ObjEncoder f Bar
-- and some wrapping type:
data A = { _foo :: Foo, _bar :: Bar }

We can use this function to utilise our already defined ObjEncoder structures to give us an encoder for A:

combineObjects (aRecord -> (_foo aRecord, _bar aRecord)) encodeFoo encodeBar :: ObjEncoder f Bar

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.

string' :: Encoder' String Source #

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

asJson' :: Encoder Identity a -> a -> Json Source #

As per asJson, but with the Encoder specialised to Identity

generaliseEncoder :: Monad f => EncoderFns i Identity a -> EncoderFns i f a Source #

Generalise any Encoder a' to 'Encoder f a'