Search code examples
jsonhaskellhaskell-lensaeson

Aeson and Lens with DeriveGeneric and makeLenses - names don't line up


Let's say I have a type Person

import GHC.Generics
import Data.Text
import Data.Aeson
import Control.Lens

data Person = Person {
    _firstName :: Text,
    _lastName  :: Text,
    _age       :: Int
} deriving (Show, Generic)

And I want to automatically derive Lenses and JSON typeclasses for it

makeLenses ''Person
instance FromJSON Person
instance ToJSON Person

This works correctly, however DeriveGeneric sees my field names as having an underscore and expects my JSON to be formatted accordingly.

{ "_firstName": "James" ... etc} -- The underscore doesn't belong here.

Obviously I could remove the underscore from the data definition itself, but then makeLenses wouldn't be able to derive the required getters and setters.

Ideally what I want to be able to do is something like this

let person = decode blob
let name = person ^. firstName

i.e. I want to be able to derive lenses and JSON instances with all field names lining up correctly with the values in the JSON-REST Api I'm consuming, without having to write much boilerplate.

This seems like such a straight forward thing that I feel I'm missing something obvious?


Solution

  • Both lens and aeson have functions to allow customizable handling of field and constructor names. Since aeson's default is not what you want, and wouldn't work anyway if you want the lens names to be the same as the JSON field names, let's change the aeson configuration:

    {-# LANGUAGE DeriveGeneric #-}
    {-# LANGUAGE TemplateHaskell #-}
    
    import GHC.Generics
    import Data.Text hiding (drop)
    import Data.Aeson
    import Data.Aeson.TH
    import Data.Aeson.Types
    import Control.Lens
    
    data Person = Person {
        _firstName :: Text,
        _lastName  :: Text,
        _age       :: Int
    } deriving (Show, Generic)
    
    makeLenses ''Person
    
    deriveJSON defaultOptions{fieldLabelModifier = drop 1} ''Person
    
    {- alternative Generic version
    instance FromJSON Person where
        parseJSON = genericParseJSON defaultOptions{fieldLabelModifier = drop 1}
    instance ToJSON Person where
        toJSON = genericToJSON defaultOptions{fieldLabelModifier = drop 1}
    -}
    

    For lens, the corresponding configurable function would be makeLensesWith.