deriving-aeson
This package provides a newtype wrapper where you can customise
aeson’s generic methods using a
type-level interface, which synergises well with DerivingVia.
{-# LANGUAGE DerivingVia, DataKinds, DeriveGeneric #-}
import Data.Aeson
import Deriving.Aeson
import qualified Data.ByteString.Lazy.Char8 as BL
data User = User
{ userId :: Int
, userName :: String
, userAPIToken :: Maybe String
} deriving Generic
deriving (FromJSON, ToJSON)
via CustomJSON '[OmitNothingFields, FieldLabelModifier '[StripPrefix "user", CamelToSnake]] User
testData :: [User]
testData = [User 42 "Alice" Nothing, User 43 "Bob" (Just "xyz")]
main = BL.putStrLn $ encode testData
-- [{"name":"Alice","id":42},{"api_token":"xyz","name":"Bob","id":43}]
Deriving.Aeson.Stock
contains some aliases for even less boilerplates.
Prefixed str
= CustomJSON '[FieldLabelModifier (StripPrefix str)]
PrefixedSnake str
= CustomJSON '[FieldLabelModifier (StripPrefix str, CamelToSnake)]
Snake
= CustomJSON '[FieldLabelModifier '[StripPrefix str, CamelToSnake]]
Vanilla
= CustomJSON '[]
How it works
The wrapper type has a phantom type parameter t
, a type-level builder of an Option.
Type-level primitives are reduced to one Option
by the AesonOptions
class.
newtype CustomJSON t a = CustomJSON { unCustomJSON :: a }
class AesonOptions xs where
aesonOptions :: Options
instance AesonOptions xs => AesonOptions (OmitNothingFields ': xs) where
aesonOptions = (aesonOptions @xs) { omitNothingFields = True }
...
You can use any (static) function for name modification by adding an instance of StringModifier
.
data ToLower
instance StringModifier ToLower where
getStringModifier "" = ""
getStringModifier (c : xs) = toLower c : xs
Previous studies