Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Data.Registry.Aeson.Decoder
Synopsis
- newtype Decoder a = Decoder {
- decodeValue :: Value -> Either Text a
- newtype ConstructorsDecoder = ConstructorsDecoder {
- decodeConstructors :: Options -> [ConstructorDef] -> Value -> Either Text [ToConstructor]
- data ToConstructor = ToConstructor {
- toConstructorName :: Text
- toConstructorValues :: [(Maybe FieldDef, Value)]
- newtype KeyDecoder a = KeyDecoder {
- decodeKeyAs :: Key -> Either Text a
- type FieldDef = (Text, Text)
- data ConstructorDef = ConstructorDef {}
- makeConstructorDef :: Text -> [Text] -> [Text] -> ConstructorDef
- decodeFromDefinitions :: Options -> ConstructorsDecoder -> [ConstructorDef] -> Value -> (ToConstructor -> Either Text a) -> Either Text a
- decodeFieldValue :: Decoder a -> Text -> Text -> (Maybe FieldDef, Value) -> Either Text a
- decoderAp :: Decoder a -> Decoder b -> Decoder (a, b)
- decodeByteString :: forall a. Typeable a => Decoder a -> ByteString -> Either Text a
- showType :: forall a. Typeable a => String
- decodeKey :: forall a. Typeable a => (Text -> Either Text a) -> Typed (KeyDecoder a)
- keyDecoder :: forall a. (Text -> Either Text a) -> KeyDecoder a
- jsonDecoder :: forall a. (FromJSON a, Typeable a) => Typed (Decoder a)
- jsonDecoderOf :: FromJSON a => Decoder a
- decodeMaybeOf :: forall a. Typeable a => Typed (Decoder a -> Decoder (Maybe a))
- maybeOfDecoder :: forall a. Decoder a -> Decoder (Maybe a)
- decodePairOf :: forall a b. (Typeable a, Typeable b) => Typed (Decoder a -> Decoder b -> Decoder (a, b))
- pairOfDecoder :: forall a b. (Typeable a, Typeable b) => Decoder a -> Decoder b -> Decoder (a, b)
- decodeTripleOf :: forall a b c. (Typeable a, Typeable b, Typeable c) => Typed (Decoder a -> Decoder b -> Decoder c -> Decoder (a, b, c))
- tripleOfDecoder :: forall a b c. (Typeable a, Typeable b, Typeable c) => Decoder a -> Decoder b -> Decoder c -> Decoder (a, b, c)
- decodeSetOf :: forall a. (Typeable a, Ord a) => Typed (Decoder a -> Decoder (Set a))
- setOfDecoder :: forall a. (Typeable a, Ord a) => Decoder a -> Decoder (Set a)
- decodeListOf :: forall a. Typeable a => Typed (Decoder a -> Decoder [a])
- listOfDecoder :: forall a. Typeable a => Decoder a -> Decoder [a]
- decodeMapOf :: forall a b. (Typeable a, Ord a, Typeable b) => Typed (KeyDecoder a -> Decoder b -> Decoder (Map a b))
- mapOfDecoder :: forall a b. (Typeable a, Ord a, Typeable b) => KeyDecoder a -> Decoder b -> Decoder (Map a b)
- decodeNonEmptyOf :: forall a. Typeable a => Typed (Decoder a -> Decoder (NonEmpty a))
- nonEmptyOfDecoder :: forall a. Typeable a => Decoder a -> Decoder (NonEmpty a)
- defaultDecoderOptions :: Registry _ _
- defaultConstructorsDecoder :: ConstructorsDecoder
- textKeyDecoder :: KeyDecoder Text
- stringKeyDecoder :: KeyDecoder String
- encodeAsText :: ToJSON a => a -> Text
- foldEither :: [Either Text c] -> Either Text c
- makeToConstructors :: Options -> [ConstructorDef] -> Value -> Either Text [ToConstructor]
- applyOptions :: Options -> ConstructorDef -> ConstructorDef
- makeToConstructorFromValue :: Options -> ConstructorDef -> Value -> Either Text ToConstructor
- checkSumEncoding :: Options -> [ConstructorDef] -> Value -> Maybe Text
- makeTaggedObject :: Options -> Text -> Text -> [ConstructorDef] -> Value -> Either Text ToConstructor
- makeUntaggedValue :: Options -> [ConstructorDef] -> Value -> Either Text [ToConstructor]
- makeObjectWithSingleField :: Options -> [ConstructorDef] -> Value -> Either Text ToConstructor
- makeTwoElemArray :: Options -> [ConstructorDef] -> Value -> Either Text ToConstructor
- tryConstructors :: [ConstructorDef] -> (ConstructorDef -> Either Text ToConstructor) -> Either Text ToConstructor
- plural :: Foldable f => f a -> Text
- jsonTypeOf :: Value -> Text
- module Data.Registry.Aeson.TH.Decoder
- module Data.Registry.Aeson.TH.ThOptions
Documentation
Constructors
Decoder | |
Fields
|
newtype ConstructorsDecoder Source #
This function extracts values for a set of constructor definitions The TemplateHaskell function makeDecoder can then use the constructor name and constructor field value to create an actual constructor instance for a given data type
Constructors
ConstructorsDecoder | |
Fields
|
data ToConstructor Source #
Data parsed from a given Value to be potentially used to create a constructor instance of a type
Constructors
ToConstructor | |
Fields
|
Instances
Show ToConstructor Source # | |
Defined in Data.Registry.Aeson.Decoder Methods showsPrec :: Int -> ToConstructor -> ShowS # show :: ToConstructor -> String # showList :: [ToConstructor] -> ShowS # | |
Eq ToConstructor Source # | |
Defined in Data.Registry.Aeson.Decoder Methods (==) :: ToConstructor -> ToConstructor -> Bool # (/=) :: ToConstructor -> ToConstructor -> Bool # |
newtype KeyDecoder a Source #
Constructors
KeyDecoder | |
Fields
|
Instances
Functor KeyDecoder Source # | |
Defined in Data.Registry.Aeson.Decoder Methods fmap :: (a -> b) -> KeyDecoder a -> KeyDecoder b # (<$) :: a -> KeyDecoder b -> KeyDecoder a # |
data ConstructorDef Source #
Metadata for a given constructor in a data type
Constructors
ConstructorDef | |
Fields
|
Instances
Show ConstructorDef Source # | |
Defined in Data.Registry.Aeson.Decoder Methods showsPrec :: Int -> ConstructorDef -> ShowS # show :: ConstructorDef -> String # showList :: [ConstructorDef] -> ShowS # | |
Eq ConstructorDef Source # | |
Defined in Data.Registry.Aeson.Decoder Methods (==) :: ConstructorDef -> ConstructorDef -> Bool # (/=) :: ConstructorDef -> ConstructorDef -> Bool # |
makeConstructorDef :: Text -> [Text] -> [Text] -> ConstructorDef Source #
decodeFromDefinitions :: Options -> ConstructorsDecoder -> [ConstructorDef] -> Value -> (ToConstructor -> Either Text a) -> Either Text a Source #
Try to find the appropriate constructor definition encoded in the json value then try to decode all its fields with decoding function
decodeFieldValue :: Decoder a -> Text -> Text -> (Maybe FieldDef, Value) -> Either Text a Source #
Use a decoder to decode a field The constructor name, the type where the field is inserted and the field definition are used to provide better error messages
decodeByteString :: forall a. Typeable a => Decoder a -> ByteString -> Either Text a Source #
Use a Decoder to decode a ByteString into the desired type
decodeKey :: forall a. Typeable a => (Text -> Either Text a) -> Typed (KeyDecoder a) Source #
Create a decoder for a key which can be read from text
keyDecoder :: forall a. (Text -> Either Text a) -> KeyDecoder a Source #
jsonDecoder :: forall a. (FromJSON a, Typeable a) => Typed (Decoder a) Source #
Add a Decoder a to a registry of decoders when a Aeson a instance exists usage: decoders = jsonDecoder @a <: otherDecoders
jsonDecoderOf :: FromJSON a => Decoder a Source #
decodeMaybeOf :: forall a. Typeable a => Typed (Decoder a -> Decoder (Maybe a)) Source #
Add a Maybe (Decoder a) to a registry of decoders usage: decoders = decodeMaybeOf @a <: otherDecoders the list of otherDecoders must contain a Decoder a otherwise there will be a compilation error
decodePairOf :: forall a b. (Typeable a, Typeable b) => Typed (Decoder a -> Decoder b -> Decoder (a, b)) Source #
Add a Maybe (a, b) to a registry of decoders
usage: decoders = decodePairOf a
b <: otherDecoders
the list of otherDecoders must contain a Decoder a and a Decoder b
otherwise there will be a compilation error
pairOfDecoder :: forall a b. (Typeable a, Typeable b) => Decoder a -> Decoder b -> Decoder (a, b) Source #
decodeTripleOf :: forall a b c. (Typeable a, Typeable b, Typeable c) => Typed (Decoder a -> Decoder b -> Decoder c -> Decoder (a, b, c)) Source #
Add a Maybe (a, b, c) to a registry of decoders
usage: decoders = decodeTripleOf a
b @c <: otherDecoders
the list of otherDecoders must contain a Decoder a, a Decoder b and a Decoder c
otherwise there will be a compilation error
tripleOfDecoder :: forall a b c. (Typeable a, Typeable b, Typeable c) => Decoder a -> Decoder b -> Decoder c -> Decoder (a, b, c) Source #
decodeSetOf :: forall a. (Typeable a, Ord a) => Typed (Decoder a -> Decoder (Set a)) Source #
Add a Decoder (Set a)
decodeListOf :: forall a. Typeable a => Typed (Decoder a -> Decoder [a]) Source #
Add a Decoder [a] to a registry of decoders usage: decoders = decodeListOf @a <: otherDecoders the list of otherDecoders must contain a Decoder a otherwise there will be a compilation error
decodeMapOf :: forall a b. (Typeable a, Ord a, Typeable b) => Typed (KeyDecoder a -> Decoder b -> Decoder (Map a b)) Source #
mapOfDecoder :: forall a b. (Typeable a, Ord a, Typeable b) => KeyDecoder a -> Decoder b -> Decoder (Map a b) Source #
decodeNonEmptyOf :: forall a. Typeable a => Typed (Decoder a -> Decoder (NonEmpty a)) Source #
Add a Decoder (NonEmpty a) to a registry of decoders usage: decoders = decodeNonEmptyOf @a <: otherDecoders the list of otherDecoders must contain a Decoder a otherwise there will be a compilation error
defaultDecoderOptions :: Registry _ _ Source #
encodeAsText :: ToJSON a => a -> Text Source #
Encode a value as Text using its ToJSON instance
makeToConstructors :: Options -> [ConstructorDef] -> Value -> Either Text [ToConstructor] Source #
Try to extract possible constructor values based on: - the encoding options - the list of constructor definitions - a JSON value Several alternatives can be returned for an Untagged sum encoding when there are several constructor definitions
applyOptions :: Options -> ConstructorDef -> ConstructorDef Source #
Apply at runtime options to a constructor definition in order to be able to match field definitions in the decoded json value
makeToConstructorFromValue :: Options -> ConstructorDef -> Value -> Either Text ToConstructor Source #
For a given constructor definition extract all the required fields from a json value
checkSumEncoding :: Options -> [ConstructorDef] -> Value -> Maybe Text Source #
Check if the sum encoding structure looks correct This requires the whole list of constructor definitions
makeTaggedObject :: Options -> Text -> Text -> [ConstructorDef] -> Value -> Either Text ToConstructor Source #
Try to find which constructor was encoded in a tagged object where the tag field encode the constructor name and the values are either inline in the object or in a contents field
makeUntaggedValue :: Options -> [ConstructorDef] -> Value -> Either Text [ToConstructor] Source #
Try to find which constructor was encoded in an untagged value and extract its possible values
makeObjectWithSingleField :: Options -> [ConstructorDef] -> Value -> Either Text ToConstructor Source #
Try to find which constructor was encoded in an object with a single field where the field name encodes the constructor name and the object values encode the constructor fields
makeTwoElemArray :: Options -> [ConstructorDef] -> Value -> Either Text ToConstructor Source #
Try to find which constructor was encoded in an array with 2 elements where the first element encodes the constructor name and the other element the constructor values
tryConstructors :: [ConstructorDef] -> (ConstructorDef -> Either Text ToConstructor) -> Either Text ToConstructor Source #
Try to extract a constructor and its values from a list of constructor definitions
jsonTypeOf :: Value -> Text Source #
Return a textual description of a json value