reddit-pub/reddit_pub/src/Data/Deriving/Aeson.hs

42 lines
1.3 KiB
Haskell

{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Data.Deriving.Aeson
( AesonCodec(..)
, type (<<<)
, Field
, CamelCase
, DropPrefix
)
where
import Control.Lens
import Data.Aeson
import qualified Data.Text.Strict.Lens as T
import Dhall.Deriving
import GHC.Generics (Generic, Rep)
newtype AesonCodec codec a = AesonCodec a
class ModifyAesonOptions a where
modifyAesonOptions :: Options -> Options
instance (ModifyAesonOptions f, ModifyAesonOptions g) => ModifyAesonOptions (f <<< g) where
modifyAesonOptions = modifyAesonOptions @f . modifyAesonOptions @g
instance TextFunction f => ModifyAesonOptions (Field f) where
modifyAesonOptions opts = opts{fieldLabelModifier = over T.packed (textFunction @f) }
instance (Generic a, ModifyAesonOptions codec, GToJSON' Value Zero (Rep a))
=> ToJSON (AesonCodec codec a) where
toJSON (AesonCodec a) =
genericToJSON (modifyAesonOptions @codec defaultOptions) a
instance (ModifyAesonOptions codec, Generic a, GFromJSON Zero (Rep a))
=> FromJSON (AesonCodec codec a) where
parseJSON va =
AesonCodec <$> genericParseJSON (modifyAesonOptions @codec defaultOptions) va