Move JSON.hs and Compat.hs out from under HTools/
[ganeti-local] / htest / Test / Ganeti / HTools / Utils.hs
1 {-# LANGUAGE TemplateHaskell #-}
2 {-# OPTIONS_GHC -fno-warn-orphans #-}
3
4 {-| Unittests for ganeti-htools.
5
6 -}
7
8 {-
9
10 Copyright (C) 2009, 2010, 2011, 2012 Google Inc.
11
12 This program is free software; you can redistribute it and/or modify
13 it under the terms of the GNU General Public License as published by
14 the Free Software Foundation; either version 2 of the License, or
15 (at your option) any later version.
16
17 This program is distributed in the hope that it will be useful, but
18 WITHOUT ANY WARRANTY; without even the implied warranty of
19 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20 General Public License for more details.
21
22 You should have received a copy of the GNU General Public License
23 along with this program; if not, write to the Free Software
24 Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25 02110-1301, USA.
26
27 -}
28
29 module Test.Ganeti.HTools.Utils (testUtils) where
30
31 import Test.QuickCheck
32
33 import qualified Text.JSON as J
34
35 import Test.Ganeti.TestHelper
36 import Test.Ganeti.TestCommon
37
38 import qualified Ganeti.JSON as JSON
39 import qualified Ganeti.HTools.Types as Types
40 import qualified Ganeti.HTools.Utils as Utils
41
42 -- | Helper to generate a small string that doesn't contain commas.
43 genNonCommaString :: Gen [Char]
44 genNonCommaString = do
45   size <- choose (0, 20) -- arbitrary max size
46   vectorOf size (arbitrary `suchThat` ((/=) ','))
47
48 -- | If the list is not just an empty element, and if the elements do
49 -- not contain commas, then join+split should be idempotent.
50 prop_Utils_commaJoinSplit :: Property
51 prop_Utils_commaJoinSplit =
52   forAll (choose (0, 20)) $ \llen ->
53   forAll (vectorOf llen genNonCommaString `suchThat` ((/=) [""])) $ \lst ->
54   Utils.sepSplit ',' (Utils.commaJoin lst) ==? lst
55
56 -- | Split and join should always be idempotent.
57 prop_Utils_commaSplitJoin :: [Char] -> Property
58 prop_Utils_commaSplitJoin s =
59   Utils.commaJoin (Utils.sepSplit ',' s) ==? s
60
61 -- | fromObjWithDefault, we test using the Maybe monad and an integer
62 -- value.
63 prop_Utils_fromObjWithDefault :: Integer -> String -> Bool
64 prop_Utils_fromObjWithDefault def_value random_key =
65   -- a missing key will be returned with the default
66   JSON.fromObjWithDefault [] random_key def_value == Just def_value &&
67   -- a found key will be returned as is, not with default
68   JSON.fromObjWithDefault [(random_key, J.showJSON def_value)]
69        random_key (def_value+1) == Just def_value
70
71 -- | Test that functional if' behaves like the syntactic sugar if.
72 prop_Utils_if'if :: Bool -> Int -> Int -> Gen Prop
73 prop_Utils_if'if cnd a b =
74   Utils.if' cnd a b ==? if cnd then a else b
75
76 -- | Test basic select functionality
77 prop_Utils_select :: Int      -- ^ Default result
78                   -> [Int]    -- ^ List of False values
79                   -> [Int]    -- ^ List of True values
80                   -> Gen Prop -- ^ Test result
81 prop_Utils_select def lst1 lst2 =
82   Utils.select def (flist ++ tlist) ==? expectedresult
83     where expectedresult = Utils.if' (null lst2) def (head lst2)
84           flist = zip (repeat False) lst1
85           tlist = zip (repeat True)  lst2
86
87 -- | Test basic select functionality with undefined default
88 prop_Utils_select_undefd :: [Int]            -- ^ List of False values
89                          -> NonEmptyList Int -- ^ List of True values
90                          -> Gen Prop         -- ^ Test result
91 prop_Utils_select_undefd lst1 (NonEmpty lst2) =
92   Utils.select undefined (flist ++ tlist) ==? head lst2
93     where flist = zip (repeat False) lst1
94           tlist = zip (repeat True)  lst2
95
96 -- | Test basic select functionality with undefined list values
97 prop_Utils_select_undefv :: [Int]            -- ^ List of False values
98                          -> NonEmptyList Int -- ^ List of True values
99                          -> Gen Prop         -- ^ Test result
100 prop_Utils_select_undefv lst1 (NonEmpty lst2) =
101   Utils.select undefined cndlist ==? head lst2
102     where flist = zip (repeat False) lst1
103           tlist = zip (repeat True)  lst2
104           cndlist = flist ++ tlist ++ [undefined]
105
106 prop_Utils_parseUnit :: NonNegative Int -> Property
107 prop_Utils_parseUnit (NonNegative n) =
108   Utils.parseUnit (show n) ==? Types.Ok n .&&.
109   Utils.parseUnit (show n ++ "m") ==? Types.Ok n .&&.
110   Utils.parseUnit (show n ++ "M") ==? Types.Ok (truncate n_mb::Int) .&&.
111   Utils.parseUnit (show n ++ "g") ==? Types.Ok (n*1024) .&&.
112   Utils.parseUnit (show n ++ "G") ==? Types.Ok (truncate n_gb::Int) .&&.
113   Utils.parseUnit (show n ++ "t") ==? Types.Ok (n*1048576) .&&.
114   Utils.parseUnit (show n ++ "T") ==? Types.Ok (truncate n_tb::Int) .&&.
115   printTestCase "Internal error/overflow?"
116     (n_mb >=0 && n_gb >= 0 && n_tb >= 0) .&&.
117   property (Types.isBad (Utils.parseUnit (show n ++ "x")::Types.Result Int))
118   where n_mb = (fromIntegral n::Rational) * 1000 * 1000 / 1024 / 1024
119         n_gb = n_mb * 1000
120         n_tb = n_gb * 1000
121
122 -- | Test list for the Utils module.
123 testSuite "Utils"
124             [ 'prop_Utils_commaJoinSplit
125             , 'prop_Utils_commaSplitJoin
126             , 'prop_Utils_fromObjWithDefault
127             , 'prop_Utils_if'if
128             , 'prop_Utils_select
129             , 'prop_Utils_select_undefd
130             , 'prop_Utils_select_undefv
131             , 'prop_Utils_parseUnit
132             ]