aeson-default-0.9.1.0: Apply default value to FromJSON instacnes' Maybe fields

Safe HaskellNone
LanguageHaskell2010

Data.Aeson.Default

Description

This library provides a solution for applying a default value to Maybe fields of FromJSON instances. You should know a little bit about the higher-kinded data(HKD), here is an article on this topic.

Examples

See Logging.Config.Type in log4hs package for more information on how to use this library in a real project.

>>> :set -XDeriveGeneric
>>> :set -XFlexibleInstances
>>> :set -XFlexibleContexts
>>> :set -XStandaloneDeriving
>>> import           Data.Functor.Identity
>>> import           GHC.Generics
>>> import           Data.Aeson
>>> import           Data.Aeson.Default
>>> :{
data NameH f = Name { first  :: String
                    , middle :: f String
                    , last_  :: String
                    } deriving Generic
instance FromJSON (NameH Maybe)
instance Default NameH where
  constrDef _ = Name "Jorah" (Identity ".") "Gao"
deriving instance Show (NameH Identity)
data PersonH f = Person { name :: NameH f
                        , age  :: f Int
                        } deriving Generic
instance FromJSON (PersonH Maybe)
instance Default PersonH where
  constrDef _ = Person (constrDef "Name") (Identity 28)
deriving instance Show (PersonH Identity)
:}
>>> decode "{\"first\":\"jorah\", \"last_\": \"gao\"}" :: Maybe (NameH Identity)
Just (Name {first = "jorah", middle = Identity ".", last_ = "gao"})
>>> decode "{\"first\":\"jorah\", \"middle\": \"*\", \"last_\": \"gao\"}" :: Maybe (NameH Identity)
Just (Name {first = "jorah", middle = Identity "*", last_ = "gao"})
>>> :set -XDeriveGeneric
>>> :set -XFlexibleInstances
>>> :set -XFlexibleContexts
>>> :set -XStandaloneDeriving
>>> :set -XTypeFamilies
>>> import           Data.Functor.Identity
>>> import           GHC.Generics
>>> import           Data.Aeson
>>> import           Data.Aeson.Default
>>> import           Data.Aeson.Default.HKD
>>> :{
data ShapeH f = Square { side :: HKD Double f }
              | Circle { redius :: HKD Double f }
              deriving Generic
instance FromJSON (ShapeH Maybe)
instance Default ShapeH where
  constrDef "Square" = Square 1.0
  constrDef "Circle" = Circle 1.0
deriving instance Show (ShapeH Identity)
data BoxH f = Box { base   :: HKD (ShapeH f) f
                  , height :: HKD Double f
                  } deriving Generic
instance FromJSON (BoxH Maybe)
instance Default BoxH where
  constrDef _ = Box (constrDef "Square") 1.0
deriving instance Show (BoxH Identity)
:}
>>> decode "{}" :: Maybe (BoxH Identity)
Just (Box {base = Square {side = 1.0}, height = 1.0})
>>> decode "{\"base\": {\"tag\": \"Square\"}}" :: Maybe (BoxH Identity)
Just (Box {base = Square {side = 1.0}, height = 1.0})
>>> decode "{\"base\": {\"tag\": \"Circle\"}}" :: Maybe (BoxH Identity)
Just (Box {base = Circle {redius = 1.0}, height = 1.0})
>>> decode "{\"base\": {\"tag\": \"Square\", \"side\": 10.0}}" :: Maybe (BoxH Identity)
Just (Box {base = Square {side = 10.0}, height = 1.0})
>>> decode "{\"height\": 10.0}" :: Maybe (BoxH Identity)
Just (Box {base = Square {side = 1.0}, height = 10.0})
Synopsis

Documentation

class FromJSON (t Maybe) => Default (t :: (Type -> Type) -> Type) where Source #

In most cases, use the default implementation for Generic instances.

Since Default instances have implemented FromJSON (t Maybe), all Default instances will automatically implement FromJSON (t Identity).

Minimal complete definition

constrDef

Methods

constrDef :: String -> t Identity Source #

Get default value by the data constructor name.

applyDef :: t Identity -> t Maybe -> t Identity Source #

Apply the given default value, if the data constructor does not match, call constrDef to get the correct value and then apply it again, if it does not match either, raise an error.

There is a default implementation for Generic instances.

applyDef :: (Generic (t Identity), Generic (t Maybe), GDefault (Rep (t Identity)) (Rep (t Maybe)), GConsName (Rep (t Identity)), GConsName (Rep (t Maybe))) => t Identity -> t Maybe -> t Identity Source #

Apply the given default value, if the data constructor does not match, call constrDef to get the correct value and then apply it again, if it does not match either, raise an error.

There is a default implementation for Generic instances.

applyDefs :: t Maybe -> t Identity Source #

Call constrDef to get the default value, then call applyDef to apply it.

applyDefs :: (Generic (t Maybe), GConsName (Rep (t Maybe))) => t Maybe -> t Identity Source #

Call constrDef to get the default value, then call applyDef to apply it.

Instances
(Default t, FromJSON (ListH t Maybe)) => Default (ListH t) Source # 
Instance details

Defined in Data.Aeson.Default.List

(Ord k, Default t, FromJSON (MapH k t Maybe)) => Default (MapH k t) Source # 
Instance details

Defined in Data.Aeson.Default.Map.Lazy

(Ord k, Default t, FromJSON (MapH k t Maybe)) => Default (MapH k t) Source # 
Instance details

Defined in Data.Aeson.Default.Map.Strict