Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / JSON.hs @ 93f1e606

History | View | Annotate | Download (3.3 kB)

1 2d87bd0a Iustin Pop
{-# LANGUAGE TemplateHaskell #-}
2 2d87bd0a Iustin Pop
{-# OPTIONS_GHC -fno-warn-orphans #-}
3 2d87bd0a Iustin Pop
4 2d87bd0a Iustin Pop
{-| Unittests for ganeti-htools.
5 2d87bd0a Iustin Pop
6 2d87bd0a Iustin Pop
-}
7 2d87bd0a Iustin Pop
8 2d87bd0a Iustin Pop
{-
9 2d87bd0a Iustin Pop
10 2d87bd0a Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012 Google Inc.
11 2d87bd0a Iustin Pop
12 2d87bd0a Iustin Pop
This program is free software; you can redistribute it and/or modify
13 2d87bd0a Iustin Pop
it under the terms of the GNU General Public License as published by
14 2d87bd0a Iustin Pop
the Free Software Foundation; either version 2 of the License, or
15 2d87bd0a Iustin Pop
(at your option) any later version.
16 2d87bd0a Iustin Pop
17 2d87bd0a Iustin Pop
This program is distributed in the hope that it will be useful, but
18 2d87bd0a Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
19 2d87bd0a Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20 2d87bd0a Iustin Pop
General Public License for more details.
21 2d87bd0a Iustin Pop
22 2d87bd0a Iustin Pop
You should have received a copy of the GNU General Public License
23 2d87bd0a Iustin Pop
along with this program; if not, write to the Free Software
24 2d87bd0a Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25 2d87bd0a Iustin Pop
02110-1301, USA.
26 2d87bd0a Iustin Pop
27 2d87bd0a Iustin Pop
-}
28 2d87bd0a Iustin Pop
29 2d87bd0a Iustin Pop
module Test.Ganeti.JSON (testJSON) where
30 2d87bd0a Iustin Pop
31 dde8b625 Petr Pudlak
import Control.Monad
32 a4f35477 Bernardo Dal Seno
import Data.List
33 2d87bd0a Iustin Pop
import Test.QuickCheck
34 2d87bd0a Iustin Pop
35 2d87bd0a Iustin Pop
import qualified Text.JSON as J
36 2d87bd0a Iustin Pop
37 2d87bd0a Iustin Pop
import Test.Ganeti.TestHelper
38 2d87bd0a Iustin Pop
import Test.Ganeti.TestCommon
39 dde8b625 Petr Pudlak
import Test.Ganeti.Types ()
40 2d87bd0a Iustin Pop
41 2d87bd0a Iustin Pop
import qualified Ganeti.BasicTypes as BasicTypes
42 2d87bd0a Iustin Pop
import qualified Ganeti.JSON as JSON
43 2d87bd0a Iustin Pop
44 6879dfd2 Petr Pudlak
instance (Arbitrary a) => Arbitrary (JSON.MaybeForJSON a) where
45 6879dfd2 Petr Pudlak
  arbitrary = liftM JSON.MaybeForJSON arbitrary
46 6879dfd2 Petr Pudlak
47 dde8b625 Petr Pudlak
instance Arbitrary JSON.TimeAsDoubleJSON where
48 dde8b625 Petr Pudlak
  arbitrary = liftM JSON.TimeAsDoubleJSON arbitrary
49 dde8b625 Petr Pudlak
50 20bc5360 Iustin Pop
prop_toArray :: [Int] -> Property
51 20bc5360 Iustin Pop
prop_toArray intarr =
52 2d87bd0a Iustin Pop
  let arr = map J.showJSON intarr in
53 2d87bd0a Iustin Pop
  case JSON.toArray (J.JSArray arr) of
54 2d87bd0a Iustin Pop
    BasicTypes.Ok arr' -> arr ==? arr'
55 2d87bd0a Iustin Pop
    BasicTypes.Bad err -> failTest $ "Failed to parse array: " ++ err
56 2d87bd0a Iustin Pop
57 20bc5360 Iustin Pop
prop_toArrayFail :: Int -> String -> Bool -> Property
58 20bc5360 Iustin Pop
prop_toArrayFail i s b =
59 2d87bd0a Iustin Pop
  -- poor man's instance Arbitrary JSValue
60 2d87bd0a Iustin Pop
  forAll (elements [J.showJSON i, J.showJSON s, J.showJSON b]) $ \item ->
61 93be1ced Iustin Pop
  case JSON.toArray item::BasicTypes.Result [J.JSValue] of
62 2e0bb81d Iustin Pop
    BasicTypes.Bad _ -> passTest
63 2d87bd0a Iustin Pop
    BasicTypes.Ok result -> failTest $ "Unexpected parse, got " ++ show result
64 2d87bd0a Iustin Pop
65 a4f35477 Bernardo Dal Seno
arrayMaybeToJson :: (J.JSON a) => [Maybe a] -> String -> JSON.JSRecord
66 a4f35477 Bernardo Dal Seno
arrayMaybeToJson xs k = [(k, J.JSArray $ map sh xs)]
67 a4f35477 Bernardo Dal Seno
  where
68 a4f35477 Bernardo Dal Seno
    sh x = case x of
69 a4f35477 Bernardo Dal Seno
      Just v -> J.showJSON v
70 a4f35477 Bernardo Dal Seno
      Nothing -> J.JSNull
71 a4f35477 Bernardo Dal Seno
72 a4f35477 Bernardo Dal Seno
prop_arrayMaybeFromObj :: String -> [Maybe Int] -> String -> Property
73 a4f35477 Bernardo Dal Seno
prop_arrayMaybeFromObj t xs k =
74 a4f35477 Bernardo Dal Seno
  case JSON.tryArrayMaybeFromObj t (arrayMaybeToJson xs k) k of
75 a4f35477 Bernardo Dal Seno
    BasicTypes.Ok xs' -> xs' ==? xs
76 a4f35477 Bernardo Dal Seno
    BasicTypes.Bad e -> failTest $ "Parsing failing, got: " ++ show e
77 a4f35477 Bernardo Dal Seno
78 a4f35477 Bernardo Dal Seno
prop_arrayMaybeFromObjFail :: String -> String -> Property
79 a4f35477 Bernardo Dal Seno
prop_arrayMaybeFromObjFail t k =
80 a4f35477 Bernardo Dal Seno
  case JSON.tryArrayMaybeFromObj t [] k of
81 a4f35477 Bernardo Dal Seno
    BasicTypes.Ok r -> fail $
82 a4f35477 Bernardo Dal Seno
                       "Unexpected result, got: " ++ show (r::[Maybe Int])
83 a4f35477 Bernardo Dal Seno
    BasicTypes.Bad e -> conjoin [ Data.List.isInfixOf t e ==? True
84 a4f35477 Bernardo Dal Seno
                                , Data.List.isInfixOf k e ==? True
85 a4f35477 Bernardo Dal Seno
                                ]
86 a4f35477 Bernardo Dal Seno
87 6879dfd2 Petr Pudlak
prop_MaybeForJSON_serialisation :: JSON.MaybeForJSON String -> Property
88 6879dfd2 Petr Pudlak
prop_MaybeForJSON_serialisation = testSerialisation
89 6879dfd2 Petr Pudlak
90 dde8b625 Petr Pudlak
prop_TimeAsDoubleJSON_serialisation :: JSON.TimeAsDoubleJSON -> Property
91 dde8b625 Petr Pudlak
prop_TimeAsDoubleJSON_serialisation = testSerialisation
92 dde8b625 Petr Pudlak
93 2d87bd0a Iustin Pop
testSuite "JSON"
94 20bc5360 Iustin Pop
          [ 'prop_toArray
95 20bc5360 Iustin Pop
          , 'prop_toArrayFail
96 a4f35477 Bernardo Dal Seno
          , 'prop_arrayMaybeFromObj
97 a4f35477 Bernardo Dal Seno
          , 'prop_arrayMaybeFromObjFail
98 6879dfd2 Petr Pudlak
          , 'prop_MaybeForJSON_serialisation
99 dde8b625 Petr Pudlak
          , 'prop_TimeAsDoubleJSON_serialisation
100 2d87bd0a Iustin Pop
          ]