deriving-aeson: Type driven generic aeson instance customisation

This is a package candidate release! Here you can preview how this package release will appear once published to the main package index (which can be accomplished via the 'maintain' link below). Please note that once a package has been published to the main package index it cannot be undone! Please consult the package uploading documentation for more information.

[maintain] [Publish]

This package provides a newtype wrapper with FromJSON/ToJSON instances customisable via a phantom type parameter. The instances can be rendered to the original type using DerivingVia.


[Skip to Readme]

Properties

Versions 0, 0.1, 0.1.1, 0.1.2, 0.2, 0.2.1, 0.2.2, 0.2.3, 0.2.4, 0.2.4, 0.2.5, 0.2.6, 0.2.6.1, 0.2.7, 0.2.8, 0.2.9
Change log CHANGELOG.md
Dependencies aeson (>=1.4.7.0 && <1.5), base (>=4.12 && <5) [details]
License BSD-3-Clause
Copyright Copyright (c) 2020 Fumiaki Kinoshita
Author Fumiaki Kinoshita
Maintainer fumiexcel@gmail.com
Category JSON, Generics
Bug tracker https://github.com/fumieval/deriving-aeson
Source repo head: git clone https://github.com/fumieval/deriving-aeson.git
Uploaded by FumiakiKinoshita at 2020-04-22T06:22:36Z

Modules

[Index] [Quick Jump]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees


Readme for deriving-aeson-0.2.4

[back to package description]

deriving-aeson

Hackage Haskell CI Discord

logo

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.

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