Skip to content

Instantly share code, notes, and snippets.

@ejconlon
Created March 6, 2019 19:40
Show Gist options
  • Save ejconlon/a017e2dc7f0482c26b0d26b0efd9e22d to your computer and use it in GitHub Desktop.
Save ejconlon/a017e2dc7f0482c26b0d26b0efd9e22d to your computer and use it in GitHub Desktop.
Fixed repro
#!/usr/bin/env stack
-- stack --resolver lts-13.9 --install-ghc runghc --package aeson --package tasty --package text
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE UndecidableInstances #-}
import Data.Aeson
import Data.Aeson.Encoding (encodingToLazyByteString)
import Data.Text (Text)
import Data.Text.Lazy (toStrict)
import Data.Text.Lazy.Encoding (decodeUtf8)
import GHC.Generics (Generic, Rep)
import Test.Tasty
import Test.Tasty.HUnit
-- Wrapper utils
options :: Options
options = defaultOptions
{ omitNothingFields = True
}
newtype AesonWrapper a = AesonWrapper { unAesonWrapper :: a }
instance (Generic a, GToJSON Zero (Rep a), GToEncoding Zero (Rep a)) => ToJSON (AesonWrapper a) where
toJSON = genericToJSON options . unAesonWrapper
toEncoding = genericToEncoding options . unAesonWrapper
-- Now using them
data B = B { required :: Int, optional :: Maybe Int }
deriving (Eq, Show, Generic)
deriving (ToJSON) via (AesonWrapper B)
data C a = C { required :: Int, optional :: Maybe a }
deriving (Eq, Show, Generic)
deriving via (AesonWrapper (C a)) instance ToJSON a => ToJSON (C a)
newtype D = D { unD :: C D }
deriving (Eq, Show)
deriving (ToJSON) via (AesonWrapper (C D))
expectedWithOptional, expectedWithoutOptional :: Text
expectedWithOptional = "{\"required\":1,\"optional\":2}"
expectedWithoutOptional = "{\"required\":1}"
bWithOptional, bWithoutOptional :: B
bWithOptional = B 1 (Just 2)
bWithoutOptional = B 1 Nothing
cWithOptional, cWithoutOptional :: C Int
cWithOptional = C 1 (Just 2)
cWithoutOptional = C 1 Nothing
recursiveWithOptional, recursiveWithoutOptional :: Text
recursiveWithOptional = "{\"required\":1,\"optional\":{\"required\":3}}"
recursiveWithoutOptional = "{\"required\":1}"
dWithOptional, dWithoutOptional :: D
dWithOptional = D (C 1 (Just (D (C 3 Nothing))))
dWithoutOptional = D (C 1 Nothing)
encodingToText :: Encoding -> Text
encodingToText = toStrict . decodeUtf8 . encodingToLazyByteString
encodeToText :: ToJSON a => a -> Text
encodeToText = encodingToText . toEncoding
main :: IO ()
main = defaultMain $
testCase "Example test case" $ do
encodeToText bWithOptional @?= expectedWithOptional
encodeToText bWithoutOptional @?= expectedWithoutOptional
encodeToText cWithOptional @?= expectedWithOptional
encodeToText cWithoutOptional @?= expectedWithoutOptional
encodeToText dWithOptional @?= recursiveWithOptional
encodeToText dWithoutOptional @?= recursiveWithoutOptional
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment