registry-aeson-0.3.0.0: Aeson encoders / decoders
Safe HaskellSafe-Inferred
LanguageGHC2021

Data.Registry.Aeson.Encoder

Synopsis

Documentation

data FromConstructor Source #

Minimum set of data extracted from a given type with Template Haskell in order to create the appropriate encoder given an Options value

Constructors

FromConstructor 

Fields

newtype ConstructorEncoder Source #

A ConstructorEncoder uses configuration options + type information extracted from a given data type (with TemplateHaskell) in order to produce a Value and an Encoding

Constructors

ConstructorEncoder 

Fields

newtype KeyEncoder a Source #

Constructors

KeyEncoder 

Fields

Instances

Instances details
Contravariant KeyEncoder Source # 
Instance details

Defined in Data.Registry.Aeson.Encoder

Methods

contramap :: (a' -> a) -> KeyEncoder a -> KeyEncoder a' #

(>$) :: b -> KeyEncoder b -> KeyEncoder a #

newtype Encoder a Source #

Constructors

Encoder 

Fields

  • encode :: a -> (Value, Encoding)
     

Instances

Instances details
Contravariant Encoder Source # 
Instance details

Defined in Data.Registry.Aeson.Encoder

Methods

contramap :: (a' -> a) -> Encoder a -> Encoder a' #

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

encodeValue :: Encoder a -> a -> Value Source #

encodeKey :: forall a. Typeable a => (a -> Text) -> Typed (KeyEncoder a) Source #

Make a key encoder from a function returning some text

fromValue :: (a -> Value) -> Encoder a Source #

Create an Encoder from a function returning a Value

jsonEncoder :: forall a. (ToJSON a, Typeable a) => Typed (Encoder a) Source #

Create an encoder from a Aeson instance

jsonEncoderOf :: ToJSON a => Encoder a Source #

encodeMaybeOf :: forall a. Typeable a => Typed (Encoder a -> Encoder (Maybe a)) Source #

Create an Encoder for a (Maybe a)

encodePairOf :: forall a b. (Typeable a, Typeable b) => Typed (Encoder a -> Encoder b -> Encoder (a, b)) Source #

Create an Encoder for a pair (a, b)

encodeTripleOf :: forall a b c. (Typeable a, Typeable b, Typeable c) => Typed (Encoder a -> Encoder b -> Encoder c -> Encoder (a, b, c)) Source #

Create an Encoder for a tripe (a, b, c)

tripleOfEncoder :: Encoder a -> Encoder b -> Encoder c -> Encoder (a, b, c) Source #

encodeSetOf :: forall a. Typeable a => Typed (Encoder a -> Encoder (Set a)) Source #

Create an Encoder for a Set a

encodeListOf :: forall a. Typeable a => Typed (Encoder a -> Encoder [a]) Source #

Create an Encoder for a list [a]

encodeMapOf :: forall a b. (Typeable a, Typeable b) => Typed (KeyEncoder a -> Encoder b -> Encoder (Map a b)) Source #

Create an Encoder for a map a b

encodeNonEmptyOf :: forall a. Typeable a => Typed (Encoder a -> Encoder (NonEmpty a)) Source #

Create an Encoder for a non-empty list (NonEmpty a)

array :: [Value] -> Value Source #

Shortcut function to create arrays

defaultConstructorEncoder :: ConstructorEncoder Source #

Default implementation, it can be overridden in a registry

makeEncoderFromConstructor :: Options -> FromConstructor -> (Value, Encoding) Source #

Make an Encoder from Options and the representation of a constructor for a given value to encode

makeSumEncoding :: Options -> FromConstructor -> (Value, Encoding) Source #

modifyFromConstructorWithOptions :: Options -> FromConstructor -> FromConstructor Source #

Apply Options to the constructor name + field names and remove Nothing values if necessary

valuesToObject :: [Text] -> [(Value, Encoding)] -> (Value, Encoding) Source #

Create an Object from a list of field names and a list of Values both as a Value and as an Encoding