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

Data.Registry.Aeson.Decoder

Synopsis

Documentation

type FieldDef = (Text, Text) Source #

Field name + field type

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

data ConstructorDef Source #

Metadata for a given constructor in a data type

Constructors

ConstructorDef 

Fields

newtype KeyDecoder a Source #

Constructors

KeyDecoder 

Fields

Instances

Instances details
Functor KeyDecoder Source # 
Instance details

Defined in Data.Registry.Aeson.Decoder

Methods

fmap :: (a -> b) -> KeyDecoder a -> KeyDecoder b #

(<$) :: a -> KeyDecoder b -> KeyDecoder a #

newtype Decoder a Source #

Constructors

Decoder 

Fields

Instances

Instances details
Applicative Decoder Source # 
Instance details

Defined in Data.Registry.Aeson.Decoder

Methods

pure :: a -> Decoder a #

(<*>) :: Decoder (a -> b) -> Decoder a -> Decoder b #

liftA2 :: (a -> b -> c) -> Decoder a -> Decoder b -> Decoder c #

(*>) :: Decoder a -> Decoder b -> Decoder b #

(<*) :: Decoder a -> Decoder b -> Decoder a #

Functor Decoder Source # 
Instance details

Defined in Data.Registry.Aeson.Decoder

Methods

fmap :: (a -> b) -> Decoder a -> Decoder b #

(<$) :: a -> Decoder b -> Decoder a #

decoderAp :: Decoder a -> Decoder b -> Decoder (a, b) Source #

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

maybeOfDecoder :: forall a. Decoder a -> Decoder (Maybe a) Source #

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 #

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

listOfDecoder :: forall a. Typeable a => Decoder a -> Decoder [a] Source #

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

showType :: forall a. Typeable a => String Source #

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

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

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

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

checkSumEncoding :: Options -> [ConstructorDef] -> Value -> Maybe Text Source #

Check if the sum encoding structure looks correct This requires the whole list of 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

jsonTypeOf :: Value -> Text Source #

Return a textual description of a json value

tryConstructors :: [ConstructorDef] -> (ConstructorDef -> Either Text ToConstructor) -> Either Text ToConstructor Source #

Try to extract a constructor and its values from a list of constructor definitions

foldEither :: [Either Text c] -> Either Text c Source #

Return the first right element if available

encodeAsText :: ToJSON a => a -> Text Source #

Encode a value as Text using its ToJSON instance

plural :: Foldable f => f a -> Text Source #

Return a "s" if there are more than one element