deriving-aeson: Type driven generic aeson instance customisation

[ bsd3, generics, json, library ] [ Propose Tags ]

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]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 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.5, 0.2.6, 0.2.6.1, 0.2.7, 0.2.8, 0.2.9 (info)
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:40Z
Distributions Arch:0.2.9, Fedora:0.2.9, LTSHaskell:0.2.9, NixOS:0.2.9, Stackage:0.2.9, openSUSE:0.2.9
Reverse Dependencies 14 direct, 41 indirect [details]
Downloads 17075 total (194 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2020-04-22 [all 1 reports]

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.

  • 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