aeson-deriving-0.1.0.0: data types for compositional, type-directed serialization

Safe HaskellNone
LanguageHaskell2010

Data.Aeson.Deriving.Known

Synopsis

Documentation

data Null Source #

Represents the null JSON Value.

Instances
KnownJSON Null Source # 
Instance details

Defined in Data.Aeson.Deriving.Known

data field := (value :: k) infix 3 Source #

Phantom data type to make explicit which fields we pass for Aeson options. Polykinded in the second argument so it can take i.e. Booleans or Symbols where needed.

Also used for specifying constant values added to, or required from, an encoding. See Data.Aeson.Deriving.WithConstantFields.

Instances
(All (StringFunction :: k2 -> Constraint) (fieldLabelModifier ': (constructorTagModifier ': ([] :: [k2]))), ToSumEncoding sumEncoding, All KnownBool (allNullaryToStringTag ': (omitNothingFields ': (unwrapUnaryRecords ': (tagSingleConstructors ': ([] :: [Bool])))))) => ToAesonOptions (GenericOptions (FieldLabelModifier := fieldLabelModifier) (ConstructorTagModifier := constructorTagModifier) (AllNullaryToStringTag := allNullaryToStringTag) (OmitNothingFields := omitNothingFields) (SumEncoding := sumEncoding) (UnwrapUnaryRecords := unwrapUnaryRecords) (TagSingleConstructors := tagSingleConstructors) :: Type) Source # 
Instance details

Defined in Data.Aeson.Deriving.Internal.Generic

Methods

toAesonOptions :: Proxy (GenericOptions (FieldLabelModifier := fieldLabelModifier) (ConstructorTagModifier := constructorTagModifier) (AllNullaryToStringTag := allNullaryToStringTag) (OmitNothingFields := omitNothingFields) (SumEncoding := sumEncoding) (UnwrapUnaryRecords := unwrapUnaryRecords) (TagSingleConstructors := tagSingleConstructors)) -> Options Source #

(KnownJSONObject fields, KnownSymbol key, KnownJSON val) => KnownJSONObject ((key := val) ': fields :: [Type]) Source # 
Instance details

Defined in Data.Aeson.Deriving.Known

Methods

objectVal :: Proxy ((key := val) ': fields) -> Object Source #

KnownBool b => ToAesonOptionsField (TagSingleConstructors := b :: Type) Source # 
Instance details

Defined in Data.Aeson.Deriving.Internal.Generic

KnownBool b => ToAesonOptionsField (UnwrapUnaryRecords := b :: Type) Source # 
Instance details

Defined in Data.Aeson.Deriving.Internal.Generic

KnownBool b => ToAesonOptionsField (OmitNothingFields := b :: Type) Source # 
Instance details

Defined in Data.Aeson.Deriving.Internal.Generic

KnownBool b => ToAesonOptionsField (AllNullaryToStringTag := b :: Type) Source # 
Instance details

Defined in Data.Aeson.Deriving.Internal.Generic

StringFunction f => ToAesonOptionsField (ConstructorTagModifier := f :: Type) Source # 
Instance details

Defined in Data.Aeson.Deriving.Internal.Generic

StringFunction f => ToAesonOptionsField (FieldLabelModifier := f :: Type) Source # 
Instance details

Defined in Data.Aeson.Deriving.Internal.Generic

ToSumEncoding se => ToAesonOptionsField (SumEncoding := se :: Type) Source # 
Instance details

Defined in Data.Aeson.Deriving.Internal.Generic

data a ==> b infix 6 Source #

Represents a function that maps the first value to the second, and otherwise does nothing but return the input.

Instances
All KnownSymbol (a ': (b ': ([] :: [Symbol]))) => StringFunction (a ==> b :: Type) Source # 
Instance details

Defined in Data.Aeson.Deriving.Internal.Generic

Methods

stringFunction :: Proxy (a ==> b) -> String -> String Source #

(KnownJSON a, KnownJSON b) => KnownJSONFunction (a ==> b) Source # 
Instance details

Defined in Data.Aeson.Deriving.Known

Methods

functionVal :: Proxy (a ==> b) -> Value -> Value Source #

data WithDefault (val :: k) Source #

Represents the function that turns nulls into the given default value.

Instances
KnownJSON a => KnownJSONFunction (WithDefault a) Source # 
Instance details

Defined in Data.Aeson.Deriving.Known

class KnownJSON (a :: k) where Source #

Constant JSON values

Methods

jsonVal :: Proxy a -> Value Source #

Instances
KnownBool b => KnownJSON (b :: Bool) Source # 
Instance details

Defined in Data.Aeson.Deriving.Known

Methods

jsonVal :: Proxy b -> Value Source #

KnownSymbol str => KnownJSON (str :: Symbol) Source # 
Instance details

Defined in Data.Aeson.Deriving.Known

Methods

jsonVal :: Proxy str -> Value Source #

KnownJSONList xs => KnownJSON (xs :: [k]) Source # 
Instance details

Defined in Data.Aeson.Deriving.Known

Methods

jsonVal :: Proxy xs -> Value Source #

KnownJSON Null Source # 
Instance details

Defined in Data.Aeson.Deriving.Known

class KnownBool (b :: Bool) where Source #

Constant boolean values

Methods

boolVal :: Proxy b -> Bool Source #

Instances
KnownBool False Source # 
Instance details

Defined in Data.Aeson.Deriving.Known

KnownBool True Source # 
Instance details

Defined in Data.Aeson.Deriving.Known

Methods

boolVal :: Proxy True -> Bool Source #

class KnownJSONList (xs :: [k]) where Source #

Constant JSON lists

Methods

listVal :: Proxy xs -> [Value] Source #

Instances
KnownJSONList ([] :: [k]) Source # 
Instance details

Defined in Data.Aeson.Deriving.Known

Methods

listVal :: Proxy [] -> [Value] Source #

(KnownJSON x, KnownJSONList xs) => KnownJSONList (x ': xs :: [k]) Source # 
Instance details

Defined in Data.Aeson.Deriving.Known

Methods

listVal :: Proxy (x ': xs) -> [Value] Source #

class KnownJSONObject (a :: k) where Source #

Constant JSON objects

Methods

objectVal :: Proxy a -> Object Source #

Instances
KnownJSONObject ([] :: [k]) Source # 
Instance details

Defined in Data.Aeson.Deriving.Known

Methods

objectVal :: Proxy [] -> Object Source #

(KnownJSONObject fields, KnownSymbol key, KnownJSON val) => KnownJSONObject ((key := val) ': fields :: [Type]) Source # 
Instance details

Defined in Data.Aeson.Deriving.Known

Methods

objectVal :: Proxy ((key := val) ': fields) -> Object Source #

class KnownJSONFunction (a :: Type) where Source #

JSON (Value) functions

Methods

functionVal :: Proxy a -> Value -> Value Source #

Instances
KnownJSON a => KnownJSONFunction (WithDefault a) Source # 
Instance details

Defined in Data.Aeson.Deriving.Known

(KnownJSON a, KnownJSON b) => KnownJSONFunction (a ==> b) Source # 
Instance details

Defined in Data.Aeson.Deriving.Known

Methods

functionVal :: Proxy (a ==> b) -> Value -> Value Source #