Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Synopsis
- data FromConstructor = FromConstructor {
- fromConstructorNames :: [Text]
- fromConstructorTypes :: [Text]
- fromConstructorName :: Text
- fromConstructorFieldNames :: [Text]
- fromConstructorValues :: [(Value, Encoding)]
- newtype ConstructorEncoder = ConstructorEncoder {
- encodeConstructor :: Options -> FromConstructor -> (Value, Encoding)
- newtype Encoder a = Encoder {
- encode :: a -> (Value, Encoding)
- encodeByteString :: Encoder a -> a -> ByteString
- encodeValue :: Encoder a -> a -> Value
- fromValue :: (a -> Value) -> Encoder a
- jsonEncoder :: forall a. (ToJSON a, Typeable a) => Typed (Encoder a)
- jsonEncoderOf :: ToJSON a => Encoder a
- encodeMaybeOf :: forall a. Typeable a => Typed (Encoder a -> Encoder (Maybe a))
- maybeOfEncoder :: Encoder a -> Encoder (Maybe a)
- encodePairOf :: forall a b. (Typeable a, Typeable b) => Typed (Encoder a -> Encoder b -> Encoder (a, b))
- pairOfEncoder :: Encoder a -> Encoder b -> Encoder (a, b)
- encodeTripleOf :: forall a b c. (Typeable a, Typeable b, Typeable c) => Typed (Encoder a -> Encoder b -> Encoder c -> Encoder (a, b, c))
- tripleOfEncoder :: Encoder a -> Encoder b -> Encoder c -> Encoder (a, b, c)
- encodeListOf :: forall a. Typeable a => Typed (Encoder a -> Encoder [a])
- listOfEncoder :: Encoder a -> Encoder [a]
- encodeNonEmptyOf :: forall a. Typeable a => Typed (Encoder a -> Encoder (NonEmpty a))
- nonEmptyOfEncoder :: Encoder a -> Encoder (NonEmpty a)
- array :: [Value] -> Value
- defaultEncoderOptions :: Registry _ _
- defaultConstructorEncoder :: ConstructorEncoder
- makeEncoderFromConstructor :: Options -> FromConstructor -> (Value, Encoding)
- makeSumEncoding :: Options -> FromConstructor -> (Value, Encoding)
- modifyFromConstructorWithOptions :: Options -> FromConstructor -> FromConstructor
- valuesToObject :: [Text] -> [(Value, Encoding)] -> (Value, Encoding)
- module Data.Registry.Aeson.TH.Encoder
- module Data.Registry.Aeson.TH.ThOptions
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
FromConstructor | |
|
Instances
Show FromConstructor Source # | |
Defined in Data.Registry.Aeson.Encoder showsPrec :: Int -> FromConstructor -> ShowS # show :: FromConstructor -> String # showList :: [FromConstructor] -> ShowS # | |
Eq FromConstructor Source # | |
Defined in Data.Registry.Aeson.Encoder (==) :: FromConstructor -> FromConstructor -> Bool # (/=) :: FromConstructor -> FromConstructor -> Bool # |
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
ConstructorEncoder | |
|
encodeByteString :: Encoder a -> a -> ByteString Source #
encodeValue :: Encoder a -> a -> Value Source #
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)
encodeListOf :: forall a. Typeable a => Typed (Encoder a -> Encoder [a]) Source #
Create an Encoder for a list [a]
listOfEncoder :: Encoder a -> Encoder [a] Source #
encodeNonEmptyOf :: forall a. Typeable a => Typed (Encoder a -> Encoder (NonEmpty a)) Source #
Create an Encoder for a non-empty list (NonEmpty a)
defaultEncoderOptions :: Registry _ _ Source #
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