License | BSD-style |
---|---|
Maintainer | palkovsky.ondrej@gmail.com |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | GHC2021 |
Data.Aeson.DefaultField
Description
Type-level default fields for aeson Generic FromJSON parser
Synopsis
- type family DefaultField (m :: ParseStage) a where ...
- data ParseStage = Final
- parseWithDefaults :: forall (o :: ParseStage -> Type). (GFromJSON Zero (Rep (o InsertDefaults)), Generic (o InsertDefaults), Generic (o Final), Coercible (Rep (o InsertDefaults)) (Rep (o Final))) => Options -> Value -> Parser (o Final)
- newtype DefInt (num :: Nat) = DefInt Int
- newtype DefNegativeInt (num :: Nat) = DefNegativeInt Int
- newtype DefText (x :: Symbol) = DefText Text
- newtype DefString (x :: Symbol) = DefString String
- newtype DefBool (a :: Bool) = DefBool Bool
- newtype DefDefault a = DefDefault a
- class (Generic a, GNewtype (Rep a)) => DefaultConstant a where
- newtype DefDefaultConstant a = DefDefaultConstant (EmbeddedType (Rep a))
How to use this library
import Data.Aeson ( FromJSON(parseJSON), decode ) import Data.Default ( Default(..) ) import GHC.Generics (Generic) import qualified Data.Text as T import qualified Data.Aeson as AE import Data.Aeson.DefaultField -- Define some custom datatype for json data data Color = Red | Green | Blue deriving (Generic,FromJSON
, Show) -- We may want a default instance for later use withDefDefault
instanceDefault
Color where def = Red -- Alternatively, we may create a separate default type that would be coerced back -- to Color withDefDefaultConstant
. This allows for different default values -- with the same type for different fields. newtype BlueDefault = BlueDefault Color deriving Generic instanceDefaultConstant
BlueDefault where defValue _ = Blue -- Simply create the data object we want to parse from the file; add a type parameter -- so that we can use the type family magic to create 2 different type representations. -- Normal fields act normally. UseDefaultField
with the appropriate settings -- to configure the parsing of the missing fields. Null fields are NOT replaced -- with the default value; only missing fields are. data ConfigFileT d = ConfigFile { defaultEnabled ::DefaultField
d (DefBool
True) , defaultDisabled ::DefaultField
d (DefBool
False) , defaultText ::DefaultField
d (DefText
"default text") , defaultInt ::DefaultField
d (DefInt
42) , defaultNegativeInt ::DefaultField
d (DefNegativeInt
42) , defaultRed ::DefaultField
d (DefDefault
Color) , defaultBlue ::DefaultField
d (DefDefaultConstant
BlueDefault) , normalField :: T.Text , normalOptional :: Maybe Int } deriving (Generic) -- Create a type alias so that we can (mostly) handle the type as if nothing special -- was happening under the hood. type ConfigFile = ConfigFileTFinal
deriving instance Show ConfigFile -- Create a custom parsing instance for the data object. instance FromJSON ConfigFile where parseJSON =parseWithDefaults
AE.defaultOptions{AE.rejectUnknownFields=True}
>>>
AE.decode "{\"defaultDisabled\":true,\"normalField\":\"text\"}" :: Maybe ConfigFile
>>>
Just (ConfigFile {
defaultEnabled = True , defaultDisabled = True , defaultText = "default text" , defaultInt = 42 , defaultNegativeInt = -42 , defaultRed = Red , defaultBlue = Blue , normalField = "text" , normalOptional = Nothing} )
How to extend the library
The provided DefText
, DefInt
, etc. newtypes should provide enough flexibility to configure the missing
fields for the objects. If a special type of configuration is needed, a newtype
based on a final type must be created with Generic
and FromJSON
instances.
See the source code for examples.
The default newtypes do not replace null value with the default value. You can create your own types that behave differently.
E.g. a configuration that would use the singletons package is:
newtype DefSing (a :: k) = DefSing (Demote k) deriving Generic instance (SingI a, SingKind k, FromJSON (Demote k)) => FromJSON (DefSing (a :: k)) where omittedField = Just $ DefSing $ fromSing (sing @a) parseJSON v = DefSing <$> parseJSON v
The configuration would then be:
defaultBool :: DefaultField d (DefSing False)
Caveats
The final step in the parsing is coercing the structure with newtypes (e.g. DefBool
) to
a structure with the final types (e.g. Bool). Unfortunately, the type families in Haskell
cause the type not to be directly coercible between the intermediate and the Final
stage.
However, it is possible through the Generic instances.
This solution probably brings some performance degradation in the sense that the structure must be recreated. Benchmark before use in performance-sensitive situations.
Main field types and functions
type family DefaultField (m :: ParseStage) a where ... Source #
Higher-kinded-type that either instantiates the field to a newtype that decodes the default value if not present; or instantiates to the type embedded in the newtype parameter
Equations
DefaultField InsertDefaults a = a | |
DefaultField Final a = EmbeddedType (Rep a) |
data ParseStage Source #
Kind for separating parsing with defaults and the final type
Constructors
Final | Use this type to instantiate the final data type (e.g. using the type alias) |
parseWithDefaults :: forall (o :: ParseStage -> Type). (GFromJSON Zero (Rep (o InsertDefaults)), Generic (o InsertDefaults), Generic (o Final), Coercible (Rep (o InsertDefaults)) (Rep (o Final))) => Options -> Value -> Parser (o Final) Source #
genericParseJSON
drop-in replacement
Different basic types
newtype DefInt (num :: Nat) Source #
Positive Int default field (only positive numbers are supported as type parameters)
newtype DefNegativeInt (num :: Nat) Source #
Negative Int default field
Constructors
DefNegativeInt Int |
Instances
KnownNat num => FromJSON (DefNegativeInt num) Source # | |
Defined in Data.Aeson.DefaultField Methods parseJSON :: Value -> Parser (DefNegativeInt num) # parseJSONList :: Value -> Parser [DefNegativeInt num] # omittedField :: Maybe (DefNegativeInt num) # | |
Generic (DefNegativeInt num) Source # | |
Defined in Data.Aeson.DefaultField Associated Types type Rep (DefNegativeInt num) :: Type -> Type # Methods from :: DefNegativeInt num -> Rep (DefNegativeInt num) x # to :: Rep (DefNegativeInt num) x -> DefNegativeInt num # | |
type Rep (DefNegativeInt num) Source # | |
Defined in Data.Aeson.DefaultField type Rep (DefNegativeInt num) = D1 ('MetaData "DefNegativeInt" "Data.Aeson.DefaultField" "aeson-generic-default-0.1.1.0-IXIMtpeWkpQIucxeKQFqNI" 'True) (C1 ('MetaCons "DefNegativeInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) |
newtype DefText (x :: Symbol) Source #
Text default field
Instances
KnownSymbol sym => FromJSON (DefText sym) Source # | |
Defined in Data.Aeson.DefaultField | |
Generic (DefText x) Source # | |
type Rep (DefText x) Source # | |
Defined in Data.Aeson.DefaultField |
newtype DefString (x :: Symbol) Source #
String default field
Instances
KnownSymbol sym => FromJSON (DefString sym) Source # | |
Defined in Data.Aeson.DefaultField | |
Generic (DefString x) Source # | |
type Rep (DefString x) Source # | |
Defined in Data.Aeson.DefaultField |
newtype DefBool (a :: Bool) Source #
Boolean default field
newtype DefDefault a Source #
Default field using the Default class
Constructors
DefDefault a |
Instances
(FromJSON a, Default a) => FromJSON (DefDefault a) Source # | |
Defined in Data.Aeson.DefaultField Methods parseJSON :: Value -> Parser (DefDefault a) # parseJSONList :: Value -> Parser [DefDefault a] # omittedField :: Maybe (DefDefault a) # | |
Generic (DefDefault a) Source # | |
Defined in Data.Aeson.DefaultField Associated Types type Rep (DefDefault a) :: Type -> Type # | |
type Rep (DefDefault a) Source # | |
Defined in Data.Aeson.DefaultField type Rep (DefDefault a) = D1 ('MetaData "DefDefault" "Data.Aeson.DefaultField" "aeson-generic-default-0.1.1.0-IXIMtpeWkpQIucxeKQFqNI" 'True) (C1 ('MetaCons "DefDefault" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))) |
Support for newtype default constants
class (Generic a, GNewtype (Rep a)) => DefaultConstant a where Source #
Default class for DefDefaultConstant
field configuration
newtype DefDefaultConstant a Source #
Use DefaultConstant
type as a default value for a field.
E.g. you cannot create a direct settings for real numbers; however, you can do this:
newtype Pi = Pi Double deriving Generic instance DefaultConstant Pi where defValue _ = 3.141592654 data MyObjectT d = MyObject { phaseAngle :: DefaultField d (DefDefaultConstant Pi) } deriving Generic
Constructors
DefDefaultConstant (EmbeddedType (Rep a)) |
Instances
(DefaultConstant a, FromJSON (EmbeddedType (Rep a))) => FromJSON (DefDefaultConstant a) Source # | |
Defined in Data.Aeson.DefaultField Methods parseJSON :: Value -> Parser (DefDefaultConstant a) # parseJSONList :: Value -> Parser [DefDefaultConstant a] # omittedField :: Maybe (DefDefaultConstant a) # | |
Generic (DefDefaultConstant a) Source # | |
Defined in Data.Aeson.DefaultField Associated Types type Rep (DefDefaultConstant a) :: Type -> Type # Methods from :: DefDefaultConstant a -> Rep (DefDefaultConstant a) x # to :: Rep (DefDefaultConstant a) x -> DefDefaultConstant a # | |
type Rep (DefDefaultConstant a) Source # | |
Defined in Data.Aeson.DefaultField |