File: test.hs

package info (click to toggle)
haskell-deriving-aeson 0.2.9-2
  • links: PTS
  • area: main
  • in suites: forky, sid, trixie
  • size: 80 kB
  • sloc: haskell: 214; makefile: 6
file content (88 lines) | stat: -rw-r--r-- 2,736 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
{-# LANGUAGE DerivingVia, DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
module Main where

import Data.Aeson
import Deriving.Aeson
import Deriving.Aeson.Stock
import System.Exit (die)
import qualified Data.ByteString.Lazy.Char8 as BL


data User = User
  { userId :: Int
  , userName :: String
  , userAPIToken :: Maybe String
  , userType :: String
  } deriving Generic
  deriving (FromJSON, ToJSON)
  via CustomJSON '[ OmitNothingFields
                  , FieldLabelModifier '[StripPrefix "user", CamelToSnake, Rename "type" "user_type"]
                  ] User

data Foo = Foo { fooFoo :: Int, fooBar :: Int }
  deriving Generic
  deriving (FromJSON, ToJSON)
  via Prefixed "foo" Foo

testData :: [User]
testData = [User 42 "Alice" Nothing "human", User 43 "Bob" (Just "xyz") "bot"]

data MultipleCtorRenames
  = RenamedCtorOptA
  | RenamedCtorOptB (Maybe ())
  | RenamedCtorOptC Char
  deriving (Eq, Generic, Show)
  deriving (ToJSON)
    via CustomJSON
      [ ConstructorTagModifier (Rename "RenamedCtorOptA" "nullary")
      , ConstructorTagModifier (Rename "RenamedCtorOptB" "twisted-bool")
      , ConstructorTagModifier (Rename "RenamedCtorOptC" "wrapped-char")
      ] MultipleCtorRenames

data MultipleFieldRenames = MultipleFieldRenames
  { fooField1 :: Int
  , fooField2 :: Bool
  , fooField3 :: String
  }
  deriving (Eq, Generic, Show)
  deriving (ToJSON)
    via CustomJSON
      [ FieldLabelModifier (Rename "fooField1" "field-1")
      , FieldLabelModifier (Rename "fooField2" "field-2")
      , FieldLabelModifier (Rename "fooField3" "field-3")
      ] MultipleFieldRenames

main = do
  BL.putStrLn $ encode testData
  BL.putStrLn $ encode $ Foo 0 1

  assertEq
    (toJSON RenamedCtorOptA)
    (object [("tag", "nullary")])
    "Support multiple constructor modifiers"

  assertEq
    (toJSON $ RenamedCtorOptB Nothing)
    (object [("tag", String "twisted-bool"), ("contents", Null)])
    "Support multiple constructor modifiers"

  assertEq
    (toJSON $ RenamedCtorOptC '?')
    (object [("tag", String "wrapped-char"), ("contents", String "?")])
    "Support multiple constructor modifiers"

  assertEq
    (toJSON $ MultipleFieldRenames 42 True "meaning of life")
    (object [("field-1", Number 42)
            ,("field-2", Bool True)
            ,("field-3", String "meaning of life")
            ])
    "Support multiple field modifiers"

assertEq :: (Show a, Eq a) => a -> a -> String -> IO ()
assertEq x y expectation | x == y = pure ()
                         | otherwise = die msg
  where
    msg = concat [expectation, " -- not fulfilled:\n\t", show x, "\n\t /= \n\t", show y]