Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / JSON.hs @ 896cc964

History | View | Annotate | Download (2.7 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 a4f35477 Bernardo Dal Seno
import Data.List
32 2d87bd0a Iustin Pop
import Test.QuickCheck
33 2d87bd0a Iustin Pop
34 2d87bd0a Iustin Pop
import qualified Text.JSON as J
35 2d87bd0a Iustin Pop
36 2d87bd0a Iustin Pop
import Test.Ganeti.TestHelper
37 2d87bd0a Iustin Pop
import Test.Ganeti.TestCommon
38 2d87bd0a Iustin Pop
39 2d87bd0a Iustin Pop
import qualified Ganeti.BasicTypes as BasicTypes
40 2d87bd0a Iustin Pop
import qualified Ganeti.JSON as JSON
41 2d87bd0a Iustin Pop
42 20bc5360 Iustin Pop
prop_toArray :: [Int] -> Property
43 20bc5360 Iustin Pop
prop_toArray intarr =
44 2d87bd0a Iustin Pop
  let arr = map J.showJSON intarr in
45 2d87bd0a Iustin Pop
  case JSON.toArray (J.JSArray arr) of
46 2d87bd0a Iustin Pop
    BasicTypes.Ok arr' -> arr ==? arr'
47 2d87bd0a Iustin Pop
    BasicTypes.Bad err -> failTest $ "Failed to parse array: " ++ err
48 2d87bd0a Iustin Pop
49 20bc5360 Iustin Pop
prop_toArrayFail :: Int -> String -> Bool -> Property
50 20bc5360 Iustin Pop
prop_toArrayFail i s b =
51 2d87bd0a Iustin Pop
  -- poor man's instance Arbitrary JSValue
52 2d87bd0a Iustin Pop
  forAll (elements [J.showJSON i, J.showJSON s, J.showJSON b]) $ \item ->
53 93be1ced Iustin Pop
  case JSON.toArray item::BasicTypes.Result [J.JSValue] of
54 2e0bb81d Iustin Pop
    BasicTypes.Bad _ -> passTest
55 2d87bd0a Iustin Pop
    BasicTypes.Ok result -> failTest $ "Unexpected parse, got " ++ show result
56 2d87bd0a Iustin Pop
57 a4f35477 Bernardo Dal Seno
arrayMaybeToJson :: (J.JSON a) => [Maybe a] -> String -> JSON.JSRecord
58 a4f35477 Bernardo Dal Seno
arrayMaybeToJson xs k = [(k, J.JSArray $ map sh xs)]
59 a4f35477 Bernardo Dal Seno
  where
60 a4f35477 Bernardo Dal Seno
    sh x = case x of
61 a4f35477 Bernardo Dal Seno
      Just v -> J.showJSON v
62 a4f35477 Bernardo Dal Seno
      Nothing -> J.JSNull
63 a4f35477 Bernardo Dal Seno
64 a4f35477 Bernardo Dal Seno
prop_arrayMaybeFromObj :: String -> [Maybe Int] -> String -> Property
65 a4f35477 Bernardo Dal Seno
prop_arrayMaybeFromObj t xs k =
66 a4f35477 Bernardo Dal Seno
  case JSON.tryArrayMaybeFromObj t (arrayMaybeToJson xs k) k of
67 a4f35477 Bernardo Dal Seno
    BasicTypes.Ok xs' -> xs' ==? xs
68 a4f35477 Bernardo Dal Seno
    BasicTypes.Bad e -> failTest $ "Parsing failing, got: " ++ show e
69 a4f35477 Bernardo Dal Seno
70 a4f35477 Bernardo Dal Seno
prop_arrayMaybeFromObjFail :: String -> String -> Property
71 a4f35477 Bernardo Dal Seno
prop_arrayMaybeFromObjFail t k =
72 a4f35477 Bernardo Dal Seno
  case JSON.tryArrayMaybeFromObj t [] k of
73 a4f35477 Bernardo Dal Seno
    BasicTypes.Ok r -> fail $
74 a4f35477 Bernardo Dal Seno
                       "Unexpected result, got: " ++ show (r::[Maybe Int])
75 a4f35477 Bernardo Dal Seno
    BasicTypes.Bad e -> conjoin [ Data.List.isInfixOf t e ==? True
76 a4f35477 Bernardo Dal Seno
                                , Data.List.isInfixOf k e ==? True
77 a4f35477 Bernardo Dal Seno
                                ]
78 a4f35477 Bernardo Dal Seno
79 2d87bd0a Iustin Pop
testSuite "JSON"
80 20bc5360 Iustin Pop
          [ 'prop_toArray
81 20bc5360 Iustin Pop
          , 'prop_toArrayFail
82 a4f35477 Bernardo Dal Seno
          , 'prop_arrayMaybeFromObj
83 a4f35477 Bernardo Dal Seno
          , 'prop_arrayMaybeFromObjFail
84 2d87bd0a Iustin Pop
          ]