File: Tests.hs

package info (click to toggle)
haskell-aeson-extra 0.5.1.3-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 120 kB
  • sloc: haskell: 549; makefile: 5
file content (186 lines) | stat: -rw-r--r-- 7,370 bytes parent folder | download | duplicates (2)
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
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
{-# LANGUAGE CPP               #-}
{-# LANGUAGE DataKinds         #-}
{-# LANGUAGE KindSignatures    #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell   #-}
{-# OPTIONS_GHC -fno-warn-deprecations #-}
module Main (main) where

import Prelude ()
import Prelude.Compat

import Data.Aeson
import Data.Aeson.Extra

import Data.Maybe                (isJust)
import Data.Proxy
import Data.Vector               (Vector)
import Test.QuickCheck.Instances ()
import Test.Tasty
import Test.Tasty.HUnit
import Test.Tasty.QuickCheck

import Orphans ()

main :: IO ()
main = defaultMain $ testGroup "Tests"
  [ dotColonMark
  , encodeStrictTests
  , symTests
  , singObjectTests
  , collapsedListTests
  , mergeTests
  , streamTests
  ]

------------------------------------------------------------------------------
-- encodeStrict
------------------------------------------------------------------------------
encodeStrictTests :: TestTree
encodeStrictTests = testGroup "encodeStrict"
  [ testProperty "decodeStrict . encodeStrict" prop
  ]
  where prop :: Int -> Property
        prop i = let lhs = decodeStrict . encodeStrict $ i
                     rhs = Just i
                 in lhs === rhs

------------------------------------------------------------------------------
-- SymTag
------------------------------------------------------------------------------

symTests :: TestTree
symTests = testGroup "SymTag"
  [ testCase "encode" $ encode (SymTag :: SymTag "foobar") @?= "\"foobar\""
  , testCase "decode success" $ (decode "\"foobar\"" :: Maybe (SymTag "foobar")) @?= Just SymTag
  , testCase "decode failure" $ (decode "\"foobar\"" :: Maybe (SymTag "barfoo")) @?= Nothing
  ]

------------------------------------------------------------------------------
-- SingObject
------------------------------------------------------------------------------

-- > λ > decode "{\"value\": 42 }" :: Maybe (SingObject "value" Int)
-- > Just (SingObject 42)

singObjectTests :: TestTree
singObjectTests = testGroup "SingObject"
  [ testCase "decode success" $ (decode "{\"value\": 42 }" :: Maybe (SingObject "value" Int)) @?= Just (SingObject 42)
  , testCase "decode failure" $ (decode "{\"value\": 42 }" :: Maybe (SingObject "key" Int)) @?= Nothing
  , testProperty "decode . encode" $
      let prop :: Int -> Property
          prop n = let rhs = fmap (getSingObject p) . decode . encode . mkSingObject p $ n
                       lhs = Just n
                   in lhs === rhs
          p :: Proxy "value"
          p = Proxy
      in prop
  ]

------------------------------------------------------------------------------
-- parseCollapsedList
------------------------------------------------------------------------------

newtype V = V [Int] deriving (Show, Eq)
instance FromJSON V where parseJSON = withObject "V" $ \obj -> V <$> parseCollapsedList obj "value"

collapsedListTests :: TestTree
collapsedListTests = testGroup "collapsedList"
  [ testCase "empty"     $ (decode "{}" :: Maybe V) @?= Just (V [])
  , testCase "null"      $ (decode "{\"value\": null}" :: Maybe V) @?= Just (V [])
  , testCase "singleton" $ (decode "{\"value\": 42}" :: Maybe V) @?= Just (V [42])
  , testCase "array"     $ (decode "{\"value\": [1, 2, 3, 4]}" :: Maybe V) @?= Just (V [1,2,3,4])
  , testProperty "decode . encode" $
      let prop :: [Int] -> Property
          prop l = let rhs = fmap getCollapsedList . decode . encode . CollapsedList $ l
                       lhs = Just l
                   in lhs === rhs
      in prop
  , testProperty "Vector decode . encode" $
      let prop :: Vector Int -> Property
          prop l = let rhs = fmap getCollapsedList . decode . encode . CollapsedList $ l
                       lhs = Just l
                   in lhs === rhs
      in prop
  ]

-------------------------------------------------------------------------------
-- Stream
-------------------------------------------------------------------------------

streamTests :: TestTree
streamTests = testGroup "stream"
    [ streamDecodeTests
    ]
  where
    streamDecodeTests = testGroup "decode" $
        map (uncurry validTestCase) valids ++
        [ testCase "ws: empty"     $ streamDecode " [ ] "           @?= ([]      :: [Int], Nothing)
        , testCase "ws: singleton" $ streamDecode " [ 1 ]"          @?= ([1]     :: [Int], Nothing)
        , testCase "ws: many"      $ streamDecode " [ 1 , 2, 3 ]  " @?= ([1,2,3] :: [Int], Nothing)
        -- Errors:
        , testCase "error begin"   $ streamDecode' ","         @?= ([]    :: [Int], True)
        , testCase "parses first"  $ streamDecode' "[1,2,3["   @?= ([1,2] :: [Int], True)
        , testCase "error begin"   $ streamDecode' "[1,2,'a']" @?= ([1,2] :: [Int], True)
        ]

    validTestCase name v =
        testCase ("valid " ++ name) $ streamDecode (encode v) @?= (v, Nothing)

    streamDecode' = fmap isJust . streamDecode

    valids :: [(String, [Int])]
    valids =
        [ (,) "empty"     []
        , (,) "singleton" [1]
        , (,) "many"      [1..200]
        ]


------------------------------------------------------------------------------
-- Comparison (.:?) and (.:!)
------------------------------------------------------------------------------

newtype T1 = T1 (Maybe Int) deriving (Eq, Show)
newtype T2 = T2 (Maybe Int) deriving (Eq, Show)
newtype T3 = T3 (Maybe Int) deriving (Eq, Show)

instance FromJSON T1 where parseJSON = fmap T1 . withObject "T1" (.: "value")
instance FromJSON T2 where parseJSON = fmap T2 . withObject "T2" (.:? "value")
instance FromJSON T3 where parseJSON = fmap T3 . withObject "T3" (.:! "value")

dotColonMark :: TestTree
dotColonMark = testGroup "Operators" $ fmap t [
    assertEqual ".:  not-present" Nothing               (decode ex1 :: Maybe T1)
  , assertEqual ".:  42"          (Just (T1 (Just 42))) (decode ex2 :: Maybe T1)
  , assertEqual ".:  null"        (Just (T1 Nothing))   (decode ex3 :: Maybe T1)

  , assertEqual ".:? not-present" (Just (T2 (Nothing))) (decode ex1 :: Maybe T2)
  , assertEqual ".:? 42"          (Just (T2 (Just 42))) (decode ex2 :: Maybe T2)
  , assertEqual ".:? null"        (Just (T2 Nothing))   (decode ex3 :: Maybe T2)

  , assertEqual ".:! not-present" (Just (T3 (Nothing))) (decode ex1 :: Maybe T3)
  , assertEqual ".:! 42"          (Just (T3 (Just 42))) (decode ex2 :: Maybe T3)
  , assertEqual ".:! null"        Nothing               (decode ex3 :: Maybe T3)
  ]
  where ex1 = "{}"
        ex2 = "{\"value\": 42 }"
        ex3 = "{\"value\": null }"
        t   = testCase "-"

------------------------------------------------------------------------------
-- Merge tests
------------------------------------------------------------------------------

mergeTests :: TestTree
mergeTests = testGroup "Lodash merge examples" $ map f examples
  where
    f (x, y, z) = testCase "-" $ assertBool "should be equal" $ lodashMerge x y == z
    examples =
      [ (,,) $(mkValue "[1, 2, 3]") $(mkValue "[4, 5, 6, 7, 8]") $(mkValue "[4, 5, 6, 7, 8]")
      , (,,) $(mkValue' "{'a': 1}") $(mkValue' "{'b': 2}") $(mkValue' "{'a': 1, 'b': 2}")
      , (,,)
        $(mkValue' "{ 'data': [{ 'user': 'barney' }, { 'user': 'fred' }] }")
        $(mkValue' "{ 'data': [{ 'age': 36 }, { 'age': 40 }] }")
        $(mkValue' "{ 'data': [{ 'user': 'barney', 'age': 36 }, { 'user': 'fred', 'age': 40 }] }")
      ]