Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / Utils.hs @ da1dcce1

History | View | Annotate | Download (8.6 kB)

1 e1ee7d5a Iustin Pop
{-# LANGUAGE TemplateHaskell #-}
2 e1ee7d5a Iustin Pop
{-# OPTIONS_GHC -fno-warn-orphans #-}
3 e1ee7d5a Iustin Pop
4 e1ee7d5a Iustin Pop
{-| Unittests for ganeti-htools.
5 e1ee7d5a Iustin Pop
6 e1ee7d5a Iustin Pop
-}
7 e1ee7d5a Iustin Pop
8 e1ee7d5a Iustin Pop
{-
9 e1ee7d5a Iustin Pop
10 e1ee7d5a Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012 Google Inc.
11 e1ee7d5a Iustin Pop
12 e1ee7d5a Iustin Pop
This program is free software; you can redistribute it and/or modify
13 e1ee7d5a Iustin Pop
it under the terms of the GNU General Public License as published by
14 e1ee7d5a Iustin Pop
the Free Software Foundation; either version 2 of the License, or
15 e1ee7d5a Iustin Pop
(at your option) any later version.
16 e1ee7d5a Iustin Pop
17 e1ee7d5a Iustin Pop
This program is distributed in the hope that it will be useful, but
18 e1ee7d5a Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
19 e1ee7d5a Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20 e1ee7d5a Iustin Pop
General Public License for more details.
21 e1ee7d5a Iustin Pop
22 e1ee7d5a Iustin Pop
You should have received a copy of the GNU General Public License
23 e1ee7d5a Iustin Pop
along with this program; if not, write to the Free Software
24 e1ee7d5a Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25 e1ee7d5a Iustin Pop
02110-1301, USA.
26 e1ee7d5a Iustin Pop
27 e1ee7d5a Iustin Pop
-}
28 e1ee7d5a Iustin Pop
29 26d62e4c Iustin Pop
module Test.Ganeti.Utils (testUtils) where
30 e1ee7d5a Iustin Pop
31 01e52493 Iustin Pop
import Test.QuickCheck hiding (Result)
32 04edfc99 Iustin Pop
import Test.HUnit
33 e1ee7d5a Iustin Pop
34 04edfc99 Iustin Pop
import Data.List
35 e1ee7d5a Iustin Pop
import qualified Text.JSON as J
36 e1ee7d5a Iustin Pop
37 e1ee7d5a Iustin Pop
import Test.Ganeti.TestHelper
38 e1ee7d5a Iustin Pop
import Test.Ganeti.TestCommon
39 e1ee7d5a Iustin Pop
40 01e52493 Iustin Pop
import Ganeti.BasicTypes
41 f3baf5ef Iustin Pop
import qualified Ganeti.JSON as JSON
42 a5b270c5 Iustin Pop
import Ganeti.Utils
43 e1ee7d5a Iustin Pop
44 e1ee7d5a Iustin Pop
-- | Helper to generate a small string that doesn't contain commas.
45 5b11f8db Iustin Pop
genNonCommaString :: Gen String
46 e1ee7d5a Iustin Pop
genNonCommaString = do
47 e1ee7d5a Iustin Pop
  size <- choose (0, 20) -- arbitrary max size
48 5b11f8db Iustin Pop
  vectorOf size (arbitrary `suchThat` (/=) ',')
49 e1ee7d5a Iustin Pop
50 e1ee7d5a Iustin Pop
-- | If the list is not just an empty element, and if the elements do
51 e1ee7d5a Iustin Pop
-- not contain commas, then join+split should be idempotent.
52 20bc5360 Iustin Pop
prop_commaJoinSplit :: Property
53 20bc5360 Iustin Pop
prop_commaJoinSplit =
54 e1ee7d5a Iustin Pop
  forAll (choose (0, 20)) $ \llen ->
55 5b11f8db Iustin Pop
  forAll (vectorOf llen genNonCommaString `suchThat` (/=) [""]) $ \lst ->
56 a5b270c5 Iustin Pop
  sepSplit ',' (commaJoin lst) ==? lst
57 e1ee7d5a Iustin Pop
58 e1ee7d5a Iustin Pop
-- | Split and join should always be idempotent.
59 5b11f8db Iustin Pop
prop_commaSplitJoin :: String -> Property
60 20bc5360 Iustin Pop
prop_commaSplitJoin s =
61 a5b270c5 Iustin Pop
  commaJoin (sepSplit ',' s) ==? s
62 e1ee7d5a Iustin Pop
63 e1ee7d5a Iustin Pop
-- | fromObjWithDefault, we test using the Maybe monad and an integer
64 e1ee7d5a Iustin Pop
-- value.
65 20bc5360 Iustin Pop
prop_fromObjWithDefault :: Integer -> String -> Bool
66 20bc5360 Iustin Pop
prop_fromObjWithDefault def_value random_key =
67 e1ee7d5a Iustin Pop
  -- a missing key will be returned with the default
68 e1ee7d5a Iustin Pop
  JSON.fromObjWithDefault [] random_key def_value == Just def_value &&
69 e1ee7d5a Iustin Pop
  -- a found key will be returned as is, not with default
70 e1ee7d5a Iustin Pop
  JSON.fromObjWithDefault [(random_key, J.showJSON def_value)]
71 e1ee7d5a Iustin Pop
       random_key (def_value+1) == Just def_value
72 e1ee7d5a Iustin Pop
73 e1ee7d5a Iustin Pop
-- | Test that functional if' behaves like the syntactic sugar if.
74 20bc5360 Iustin Pop
prop_if'if :: Bool -> Int -> Int -> Gen Prop
75 20bc5360 Iustin Pop
prop_if'if cnd a b =
76 a5b270c5 Iustin Pop
  if' cnd a b ==? if cnd then a else b
77 e1ee7d5a Iustin Pop
78 e1ee7d5a Iustin Pop
-- | Test basic select functionality
79 20bc5360 Iustin Pop
prop_select :: Int      -- ^ Default result
80 20bc5360 Iustin Pop
            -> [Int]    -- ^ List of False values
81 20bc5360 Iustin Pop
            -> [Int]    -- ^ List of True values
82 20bc5360 Iustin Pop
            -> Gen Prop -- ^ Test result
83 20bc5360 Iustin Pop
prop_select def lst1 lst2 =
84 a5b270c5 Iustin Pop
  select def (flist ++ tlist) ==? expectedresult
85 a5b270c5 Iustin Pop
    where expectedresult = if' (null lst2) def (head lst2)
86 e1ee7d5a Iustin Pop
          flist = zip (repeat False) lst1
87 e1ee7d5a Iustin Pop
          tlist = zip (repeat True)  lst2
88 e1ee7d5a Iustin Pop
89 e1ee7d5a Iustin Pop
-- | Test basic select functionality with undefined default
90 20bc5360 Iustin Pop
prop_select_undefd :: [Int]            -- ^ List of False values
91 20bc5360 Iustin Pop
                   -> NonEmptyList Int -- ^ List of True values
92 20bc5360 Iustin Pop
                   -> Gen Prop         -- ^ Test result
93 20bc5360 Iustin Pop
prop_select_undefd lst1 (NonEmpty lst2) =
94 a5b270c5 Iustin Pop
  select undefined (flist ++ tlist) ==? head lst2
95 e1ee7d5a Iustin Pop
    where flist = zip (repeat False) lst1
96 e1ee7d5a Iustin Pop
          tlist = zip (repeat True)  lst2
97 e1ee7d5a Iustin Pop
98 e1ee7d5a Iustin Pop
-- | Test basic select functionality with undefined list values
99 20bc5360 Iustin Pop
prop_select_undefv :: [Int]            -- ^ List of False values
100 20bc5360 Iustin Pop
                   -> NonEmptyList Int -- ^ List of True values
101 20bc5360 Iustin Pop
                   -> Gen Prop         -- ^ Test result
102 20bc5360 Iustin Pop
prop_select_undefv lst1 (NonEmpty lst2) =
103 a5b270c5 Iustin Pop
  select undefined cndlist ==? head lst2
104 e1ee7d5a Iustin Pop
    where flist = zip (repeat False) lst1
105 e1ee7d5a Iustin Pop
          tlist = zip (repeat True)  lst2
106 e1ee7d5a Iustin Pop
          cndlist = flist ++ tlist ++ [undefined]
107 e1ee7d5a Iustin Pop
108 20bc5360 Iustin Pop
prop_parseUnit :: NonNegative Int -> Property
109 20bc5360 Iustin Pop
prop_parseUnit (NonNegative n) =
110 01e52493 Iustin Pop
  conjoin
111 01e52493 Iustin Pop
  [ parseUnit (show n) ==? (Ok n::Result Int)
112 01e52493 Iustin Pop
  , parseUnit (show n ++ "m") ==? (Ok n::Result Int)
113 01e52493 Iustin Pop
  , parseUnit (show n ++ "M") ==? (Ok (truncate n_mb)::Result Int)
114 01e52493 Iustin Pop
  , parseUnit (show n ++ "g") ==? (Ok (n*1024)::Result Int)
115 01e52493 Iustin Pop
  , parseUnit (show n ++ "G") ==? (Ok (truncate n_gb)::Result Int)
116 01e52493 Iustin Pop
  , parseUnit (show n ++ "t") ==? (Ok (n*1048576)::Result Int)
117 01e52493 Iustin Pop
  , parseUnit (show n ++ "T") ==? (Ok (truncate n_tb)::Result Int)
118 01e52493 Iustin Pop
  , printTestCase "Internal error/overflow?"
119 01e52493 Iustin Pop
    (n_mb >=0 && n_gb >= 0 && n_tb >= 0)
120 01e52493 Iustin Pop
  , property (isBad (parseUnit (show n ++ "x")::Result Int))
121 01e52493 Iustin Pop
  ]
122 e1ee7d5a Iustin Pop
  where n_mb = (fromIntegral n::Rational) * 1000 * 1000 / 1024 / 1024
123 e1ee7d5a Iustin Pop
        n_gb = n_mb * 1000
124 e1ee7d5a Iustin Pop
        n_tb = n_gb * 1000
125 e1ee7d5a Iustin Pop
126 04edfc99 Iustin Pop
{-# ANN case_niceSort_static "HLint: ignore Use camelCase" #-}
127 04edfc99 Iustin Pop
128 04edfc99 Iustin Pop
case_niceSort_static :: Assertion
129 04edfc99 Iustin Pop
case_niceSort_static = do
130 04edfc99 Iustin Pop
  assertEqual "empty list" [] $ niceSort []
131 04edfc99 Iustin Pop
  assertEqual "punctuation" [",", "."] $ niceSort [",", "."]
132 04edfc99 Iustin Pop
  assertEqual "decimal numbers" ["0.1", "0.2"] $ niceSort ["0.1", "0.2"]
133 04edfc99 Iustin Pop
  assertEqual "various numbers" ["0,099", "0.1", "0.2", "0;099"] $
134 04edfc99 Iustin Pop
              niceSort ["0;099", "0,099", "0.1", "0.2"]
135 04edfc99 Iustin Pop
136 04edfc99 Iustin Pop
  assertEqual "simple concat" ["0000", "a0", "a1", "a2", "a20", "a99",
137 04edfc99 Iustin Pop
                               "b00", "b10", "b70"] $
138 04edfc99 Iustin Pop
    niceSort ["a0", "a1", "a99", "a20", "a2", "b10", "b70", "b00", "0000"]
139 04edfc99 Iustin Pop
140 04edfc99 Iustin Pop
  assertEqual "ranges" ["A", "Z", "a0-0", "a0-4", "a1-0", "a9-1", "a09-2",
141 04edfc99 Iustin Pop
                      "a20-3", "a99-3", "a99-10", "b"] $
142 04edfc99 Iustin Pop
    niceSort ["a0-0", "a1-0", "a99-10", "a20-3", "a0-4", "a99-3", "a09-2",
143 04edfc99 Iustin Pop
              "Z", "a9-1", "A", "b"]
144 04edfc99 Iustin Pop
145 04edfc99 Iustin Pop
  assertEqual "large"
146 04edfc99 Iustin Pop
    ["3jTwJPtrXOY22bwL2YoW", "Eegah9ei", "KOt7vn1dWXi",
147 04edfc99 Iustin Pop
     "KVQqLPDjcPjf8T3oyzjcOsfkb", "WvNJd91OoXvLzdEiEXa6",
148 04edfc99 Iustin Pop
     "Z8Ljf1Pf5eBfNg171wJR", "a07h8feON165N67PIE", "bH4Q7aCu3PUPjK3JtH",
149 04edfc99 Iustin Pop
     "cPRi0lM7HLnSuWA2G9", "guKJkXnkULealVC8CyF1xefym",
150 04edfc99 Iustin Pop
     "pqF8dkU5B1cMnyZuREaSOADYx", "uHXAyYYftCSG1o7qcCqe",
151 04edfc99 Iustin Pop
     "xij88brTulHYAv8IEOyU", "xpIUJeVT1Rp"] $
152 04edfc99 Iustin Pop
    niceSort ["Eegah9ei", "xij88brTulHYAv8IEOyU", "3jTwJPtrXOY22bwL2YoW",
153 04edfc99 Iustin Pop
             "Z8Ljf1Pf5eBfNg171wJR", "WvNJd91OoXvLzdEiEXa6",
154 04edfc99 Iustin Pop
             "uHXAyYYftCSG1o7qcCqe", "xpIUJeVT1Rp", "KOt7vn1dWXi",
155 04edfc99 Iustin Pop
             "a07h8feON165N67PIE", "bH4Q7aCu3PUPjK3JtH",
156 04edfc99 Iustin Pop
             "cPRi0lM7HLnSuWA2G9", "KVQqLPDjcPjf8T3oyzjcOsfkb",
157 04edfc99 Iustin Pop
             "guKJkXnkULealVC8CyF1xefym", "pqF8dkU5B1cMnyZuREaSOADYx"]
158 04edfc99 Iustin Pop
159 04edfc99 Iustin Pop
-- | Tests single-string behaviour of 'niceSort'. Last test is special
160 04edfc99 Iustin Pop
-- in the sense that /0/ is before any other non-empty string (except
161 04edfc99 Iustin Pop
-- itself, etc.).
162 04edfc99 Iustin Pop
prop_niceSort_single :: Property
163 04edfc99 Iustin Pop
prop_niceSort_single =
164 5006418e Iustin Pop
  forAll genName $ \name ->
165 04edfc99 Iustin Pop
  conjoin
166 04edfc99 Iustin Pop
  [ printTestCase "single string" $ [name] ==? niceSort [name]
167 04edfc99 Iustin Pop
  , printTestCase "single plus empty" $ ["", name] ==? niceSort [name, ""]
168 04edfc99 Iustin Pop
  , printTestCase "single plus 0-digit" $ ["0", name] ==? niceSort [name, "0"]
169 04edfc99 Iustin Pop
  ]
170 04edfc99 Iustin Pop
171 04edfc99 Iustin Pop
-- | Tests some generic 'niceSort' properties. Note that the last test
172 04edfc99 Iustin Pop
-- must add a non-digit prefix; a digit one might change ordering.
173 04edfc99 Iustin Pop
prop_niceSort_generic :: Property
174 04edfc99 Iustin Pop
prop_niceSort_generic =
175 04edfc99 Iustin Pop
  forAll (resize 20 arbitrary) $ \names ->
176 04edfc99 Iustin Pop
  let n_sorted = niceSort names in
177 04edfc99 Iustin Pop
  conjoin [ printTestCase "length" $ length names ==? length n_sorted
178 04edfc99 Iustin Pop
          , printTestCase "same strings" $ sort names ==? sort n_sorted
179 04edfc99 Iustin Pop
          , printTestCase "idempotence" $ n_sorted ==? niceSort n_sorted
180 04edfc99 Iustin Pop
          , printTestCase "static prefix" $ n_sorted ==?
181 04edfc99 Iustin Pop
              map tail (niceSort $ map (" "++) names)
182 04edfc99 Iustin Pop
          ]
183 04edfc99 Iustin Pop
184 04edfc99 Iustin Pop
-- | Tests that niceSorting numbers is identical to actual sorting
185 04edfc99 Iustin Pop
-- them (in numeric form).
186 04edfc99 Iustin Pop
prop_niceSort_numbers :: Property
187 04edfc99 Iustin Pop
prop_niceSort_numbers =
188 04edfc99 Iustin Pop
  forAll (listOf (arbitrary::Gen (NonNegative Int))) $ \numbers ->
189 04edfc99 Iustin Pop
  map show (sort numbers) ==? niceSort (map show numbers)
190 04edfc99 Iustin Pop
191 04edfc99 Iustin Pop
-- | Tests that 'niceSort' and 'niceSortKey' are equivalent.
192 04edfc99 Iustin Pop
prop_niceSortKey_equiv :: Property
193 04edfc99 Iustin Pop
prop_niceSortKey_equiv =
194 04edfc99 Iustin Pop
  forAll (resize 20 arbitrary) $ \names ->
195 04edfc99 Iustin Pop
  forAll (vectorOf (length names) (arbitrary::Gen Int)) $ \numbers ->
196 04edfc99 Iustin Pop
  let n_sorted = niceSort names in
197 04edfc99 Iustin Pop
  conjoin
198 04edfc99 Iustin Pop
  [ printTestCase "key id" $ n_sorted ==? niceSortKey id names
199 04edfc99 Iustin Pop
  , printTestCase "key rev" $ niceSort (map reverse names) ==?
200 04edfc99 Iustin Pop
                              map reverse (niceSortKey reverse names)
201 04edfc99 Iustin Pop
  , printTestCase "key snd" $ n_sorted ==? map snd (niceSortKey snd $
202 04edfc99 Iustin Pop
                                                    zip numbers names)
203 04edfc99 Iustin Pop
  ]
204 04edfc99 Iustin Pop
205 e1ee7d5a Iustin Pop
-- | Test list for the Utils module.
206 26d62e4c Iustin Pop
testSuite "Utils"
207 20bc5360 Iustin Pop
            [ 'prop_commaJoinSplit
208 20bc5360 Iustin Pop
            , 'prop_commaSplitJoin
209 20bc5360 Iustin Pop
            , 'prop_fromObjWithDefault
210 20bc5360 Iustin Pop
            , 'prop_if'if
211 20bc5360 Iustin Pop
            , 'prop_select
212 20bc5360 Iustin Pop
            , 'prop_select_undefd
213 20bc5360 Iustin Pop
            , 'prop_select_undefv
214 20bc5360 Iustin Pop
            , 'prop_parseUnit
215 04edfc99 Iustin Pop
            , 'case_niceSort_static
216 04edfc99 Iustin Pop
            , 'prop_niceSort_single
217 04edfc99 Iustin Pop
            , 'prop_niceSort_generic
218 04edfc99 Iustin Pop
            , 'prop_niceSort_numbers
219 04edfc99 Iustin Pop
            , 'prop_niceSortKey_equiv
220 e1ee7d5a Iustin Pop
            ]