Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (13.3 kB)

1
{-# LANGUAGE TemplateHaskell, CPP #-}
2
{-# OPTIONS_GHC -fno-warn-orphans #-}
3

    
4
{-| Unittests for ganeti-htools.
5

    
6
-}
7

    
8
{-
9

    
10
Copyright (C) 2009, 2010, 2011, 2012, 2013 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.Utils (testUtils) where
30

    
31
import Test.QuickCheck hiding (Result)
32
import Test.HUnit
33

    
34
import Data.Char (isSpace)
35
import qualified Data.Either as Either
36
import Data.List
37
import System.Time
38
import qualified Text.JSON as J
39
#ifndef NO_REGEX_PCRE
40
import Text.Regex.PCRE
41
#endif
42

    
43
import Test.Ganeti.TestHelper
44
import Test.Ganeti.TestCommon
45

    
46
import Ganeti.BasicTypes
47
import qualified Ganeti.Constants as C
48
import qualified Ganeti.JSON as JSON
49
import Ganeti.Utils
50

    
51
-- | Helper to generate a small string that doesn't contain commas.
52
genNonCommaString :: Gen String
53
genNonCommaString = do
54
  size <- choose (0, 20) -- arbitrary max size
55
  vectorOf size (arbitrary `suchThat` (/=) ',')
56

    
57
-- | If the list is not just an empty element, and if the elements do
58
-- not contain commas, then join+split should be idempotent.
59
prop_commaJoinSplit :: Property
60
prop_commaJoinSplit =
61
  forAll (choose (0, 20)) $ \llen ->
62
  forAll (vectorOf llen genNonCommaString `suchThat` (/=) [""]) $ \lst ->
63
  sepSplit ',' (commaJoin lst) ==? lst
64

    
65
-- | Split and join should always be idempotent.
66
prop_commaSplitJoin :: String -> Property
67
prop_commaSplitJoin s =
68
  commaJoin (sepSplit ',' s) ==? s
69

    
70
-- | fromObjWithDefault, we test using the Maybe monad and an integer
71
-- value.
72
prop_fromObjWithDefault :: Integer -> String -> Bool
73
prop_fromObjWithDefault def_value random_key =
74
  -- a missing key will be returned with the default
75
  JSON.fromObjWithDefault [] random_key def_value == Just def_value &&
76
  -- a found key will be returned as is, not with default
77
  JSON.fromObjWithDefault [(random_key, J.showJSON def_value)]
78
       random_key (def_value+1) == Just def_value
79

    
80
-- | Test that functional if' behaves like the syntactic sugar if.
81
prop_if'if :: Bool -> Int -> Int -> Gen Prop
82
prop_if'if cnd a b =
83
  if' cnd a b ==? if cnd then a else b
84

    
85
-- | Test basic select functionality
86
prop_select :: Int      -- ^ Default result
87
            -> [Int]    -- ^ List of False values
88
            -> [Int]    -- ^ List of True values
89
            -> Gen Prop -- ^ Test result
90
prop_select def lst1 lst2 =
91
  select def (flist ++ tlist) ==? expectedresult
92
    where expectedresult = defaultHead def lst2
93
          flist = zip (repeat False) lst1
94
          tlist = zip (repeat True)  lst2
95

    
96
{-# ANN prop_select_undefd "HLint: ignore Use alternative" #-}
97
-- | Test basic select functionality with undefined default
98
prop_select_undefd :: [Int]            -- ^ List of False values
99
                   -> NonEmptyList Int -- ^ List of True values
100
                   -> Gen Prop         -- ^ Test result
101
prop_select_undefd lst1 (NonEmpty lst2) =
102
  -- head is fine as NonEmpty "guarantees" a non-empty list, but not
103
  -- via types
104
  select undefined (flist ++ tlist) ==? head lst2
105
    where flist = zip (repeat False) lst1
106
          tlist = zip (repeat True)  lst2
107

    
108
{-# ANN prop_select_undefv "HLint: ignore Use alternative" #-}
109
-- | Test basic select functionality with undefined list values
110
prop_select_undefv :: [Int]            -- ^ List of False values
111
                   -> NonEmptyList Int -- ^ List of True values
112
                   -> Gen Prop         -- ^ Test result
113
prop_select_undefv lst1 (NonEmpty lst2) =
114
  -- head is fine as NonEmpty "guarantees" a non-empty list, but not
115
  -- via types
116
  select undefined cndlist ==? head lst2
117
    where flist = zip (repeat False) lst1
118
          tlist = zip (repeat True)  lst2
119
          cndlist = flist ++ tlist ++ [undefined]
120

    
121
prop_parseUnit :: NonNegative Int -> Property
122
prop_parseUnit (NonNegative n) =
123
  conjoin
124
  [ parseUnit (show n) ==? (Ok n::Result Int)
125
  , parseUnit (show n ++ "m") ==? (Ok n::Result Int)
126
  , parseUnit (show n ++ "M") ==? (Ok (truncate n_mb)::Result Int)
127
  , parseUnit (show n ++ "g") ==? (Ok (n*1024)::Result Int)
128
  , parseUnit (show n ++ "G") ==? (Ok (truncate n_gb)::Result Int)
129
  , parseUnit (show n ++ "t") ==? (Ok (n*1048576)::Result Int)
130
  , parseUnit (show n ++ "T") ==? (Ok (truncate n_tb)::Result Int)
131
  , printTestCase "Internal error/overflow?"
132
    (n_mb >=0 && n_gb >= 0 && n_tb >= 0)
133
  , property (isBad (parseUnit (show n ++ "x")::Result Int))
134
  ]
135
  where n_mb = (fromIntegral n::Rational) * 1000 * 1000 / 1024 / 1024
136
        n_gb = n_mb * 1000
137
        n_tb = n_gb * 1000
138

    
139
{-# ANN case_niceSort_static "HLint: ignore Use camelCase" #-}
140

    
141
case_niceSort_static :: Assertion
142
case_niceSort_static = do
143
  assertEqual "empty list" [] $ niceSort []
144
  assertEqual "punctuation" [",", "."] $ niceSort [",", "."]
145
  assertEqual "decimal numbers" ["0.1", "0.2"] $ niceSort ["0.1", "0.2"]
146
  assertEqual "various numbers" ["0,099", "0.1", "0.2", "0;099"] $
147
              niceSort ["0;099", "0,099", "0.1", "0.2"]
148

    
149
  assertEqual "simple concat" ["0000", "a0", "a1", "a2", "a20", "a99",
150
                               "b00", "b10", "b70"] $
151
    niceSort ["a0", "a1", "a99", "a20", "a2", "b10", "b70", "b00", "0000"]
152

    
153
  assertEqual "ranges" ["A", "Z", "a0-0", "a0-4", "a1-0", "a9-1", "a09-2",
154
                      "a20-3", "a99-3", "a99-10", "b"] $
155
    niceSort ["a0-0", "a1-0", "a99-10", "a20-3", "a0-4", "a99-3", "a09-2",
156
              "Z", "a9-1", "A", "b"]
157

    
158
  assertEqual "large"
159
    ["3jTwJPtrXOY22bwL2YoW", "Eegah9ei", "KOt7vn1dWXi",
160
     "KVQqLPDjcPjf8T3oyzjcOsfkb", "WvNJd91OoXvLzdEiEXa6",
161
     "Z8Ljf1Pf5eBfNg171wJR", "a07h8feON165N67PIE", "bH4Q7aCu3PUPjK3JtH",
162
     "cPRi0lM7HLnSuWA2G9", "guKJkXnkULealVC8CyF1xefym",
163
     "pqF8dkU5B1cMnyZuREaSOADYx", "uHXAyYYftCSG1o7qcCqe",
164
     "xij88brTulHYAv8IEOyU", "xpIUJeVT1Rp"] $
165
    niceSort ["Eegah9ei", "xij88brTulHYAv8IEOyU", "3jTwJPtrXOY22bwL2YoW",
166
             "Z8Ljf1Pf5eBfNg171wJR", "WvNJd91OoXvLzdEiEXa6",
167
             "uHXAyYYftCSG1o7qcCqe", "xpIUJeVT1Rp", "KOt7vn1dWXi",
168
             "a07h8feON165N67PIE", "bH4Q7aCu3PUPjK3JtH",
169
             "cPRi0lM7HLnSuWA2G9", "KVQqLPDjcPjf8T3oyzjcOsfkb",
170
             "guKJkXnkULealVC8CyF1xefym", "pqF8dkU5B1cMnyZuREaSOADYx"]
171

    
172
-- | Tests single-string behaviour of 'niceSort'.
173
prop_niceSort_single :: Property
174
prop_niceSort_single =
175
  forAll genName $ \name ->
176
  conjoin
177
  [ printTestCase "single string" $ [name] ==? niceSort [name]
178
  , printTestCase "single plus empty" $ ["", name] ==? niceSort [name, ""]
179
  ]
180

    
181
-- | Tests some generic 'niceSort' properties. Note that the last test
182
-- must add a non-digit prefix; a digit one might change ordering.
183
prop_niceSort_generic :: Property
184
prop_niceSort_generic =
185
  forAll (resize 20 arbitrary) $ \names ->
186
  let n_sorted = niceSort names in
187
  conjoin [ printTestCase "length" $ length names ==? length n_sorted
188
          , printTestCase "same strings" $ sort names ==? sort n_sorted
189
          , printTestCase "idempotence" $ n_sorted ==? niceSort n_sorted
190
          , printTestCase "static prefix" $ n_sorted ==?
191
              map tail (niceSort $ map (" "++) names)
192
          ]
193

    
194
-- | Tests that niceSorting numbers is identical to actual sorting
195
-- them (in numeric form).
196
prop_niceSort_numbers :: Property
197
prop_niceSort_numbers =
198
  forAll (listOf (arbitrary::Gen (NonNegative Int))) $ \numbers ->
199
  map show (sort numbers) ==? niceSort (map show numbers)
200

    
201
-- | Tests that 'niceSort' and 'niceSortKey' are equivalent.
202
prop_niceSortKey_equiv :: Property
203
prop_niceSortKey_equiv =
204
  forAll (resize 20 arbitrary) $ \names ->
205
  forAll (vectorOf (length names) (arbitrary::Gen Int)) $ \numbers ->
206
  let n_sorted = niceSort names in
207
  conjoin
208
  [ printTestCase "key id" $ n_sorted ==? niceSortKey id names
209
  , printTestCase "key rev" $ niceSort (map reverse names) ==?
210
                              map reverse (niceSortKey reverse names)
211
  , printTestCase "key snd" $ n_sorted ==? map snd (niceSortKey snd $
212
                                                    zip numbers names)
213
  ]
214

    
215
-- | Tests 'rStripSpace'.
216
prop_rStripSpace :: NonEmptyList Char -> Property
217
prop_rStripSpace (NonEmpty str) =
218
  forAll (resize 50 $ listOf1 (arbitrary `suchThat` isSpace)) $ \whitespace ->
219
  conjoin [ printTestCase "arb. string last char is not space" $
220
              case rStripSpace str of
221
                [] -> True
222
                xs -> not . isSpace $ last xs
223
          , printTestCase "whitespace suffix is stripped" $
224
              rStripSpace str ==? rStripSpace (str ++ whitespace)
225
          , printTestCase "whitespace reduced to null" $
226
              rStripSpace whitespace ==? ""
227
          , printTestCase "idempotent on empty strings" $
228
              rStripSpace "" ==? ""
229
          ]
230

    
231
#ifndef NO_REGEX_PCRE
232
{-# ANN case_new_uuid "HLint: ignore Use camelCase" #-}
233

    
234
-- | Tests that the newUUID function produces valid UUIDs.
235
case_new_uuid :: Assertion
236
case_new_uuid = do
237
  uuid <- newUUID
238
  assertBool "newUUID" $ uuid =~ C.uuidRegex
239
#endif
240

    
241
prop_clockTimeToString :: Integer -> Integer -> Property
242
prop_clockTimeToString ts pico =
243
  clockTimeToString (TOD ts pico) ==? show ts
244

    
245
-- | Test normal operation for 'chompPrefix'.
246
--
247
-- Any random prefix of a string must be stripped correctly, including the empty
248
-- prefix, and the whole string.
249
prop_chompPrefix_normal :: String -> Property
250
prop_chompPrefix_normal str =
251
  forAll (choose (0, length str)) $ \size ->
252
  chompPrefix (take size str) str ==? (Just $ drop size str)
253

    
254
-- | Test that 'chompPrefix' correctly allows the last char (the separator) to
255
-- be absent if the string terminates there.
256
prop_chompPrefix_last :: Property
257
prop_chompPrefix_last =
258
  forAll (choose (1, 20)) $ \len ->
259
  forAll (vectorOf len arbitrary) $ \pfx ->
260
  chompPrefix pfx pfx ==? Just "" .&&.
261
  chompPrefix pfx (init pfx) ==? Just ""
262

    
263
-- | Test that chompPrefix on the empty string always returns Nothing for
264
-- prefixes of length 2 or more.
265
prop_chompPrefix_empty_string :: Property
266
prop_chompPrefix_empty_string =
267
  forAll (choose (2, 20)) $ \len ->
268
  forAll (vectorOf len arbitrary) $ \pfx ->
269
  chompPrefix pfx "" ==? Nothing
270

    
271
-- | Test 'chompPrefix' returns Nothing when the prefix doesn't match.
272
prop_chompPrefix_nothing :: Property
273
prop_chompPrefix_nothing =
274
  forAll (choose (1, 20)) $ \len ->
275
  forAll (vectorOf len arbitrary) $ \pfx ->
276
  forAll (arbitrary `suchThat`
277
          (\s -> not (pfx `isPrefixOf` s) && s /= init pfx)) $ \str ->
278
  chompPrefix pfx str ==? Nothing
279

    
280
-- | Tests 'trim'.
281
prop_trim :: NonEmptyList Char -> Property
282
prop_trim (NonEmpty str) =
283
  forAll (listOf1 $ elements " \t\n\r\f") $ \whitespace ->
284
  forAll (choose (0, length whitespace)) $ \n ->
285
  let (preWS, postWS) = splitAt n whitespace in
286
  conjoin [ printTestCase "arb. string first and last char are not space" $
287
              case trim str of
288
                [] -> True
289
                xs -> (not . isSpace . head) xs && (not . isSpace . last) xs
290
          , printTestCase "whitespace is striped" $
291
              trim str ==? trim (preWS ++ str ++ postWS)
292
          , printTestCase "whitespace reduced to null" $
293
              trim whitespace ==? ""
294
          , printTestCase "idempotent on empty strings" $
295
              trim "" ==? ""
296
          ]
297

    
298
-- | Tests 'splitEithers' and 'recombineEithers'.
299
prop_splitRecombineEithers :: [Either Int Int] -> Property
300
prop_splitRecombineEithers es =
301
  conjoin
302
  [ printTestCase "only lefts are mapped correctly" $
303
    splitEithers (map Left lefts) ==? (reverse lefts, emptylist, falses)
304
  , printTestCase "only rights are mapped correctly" $
305
    splitEithers (map Right rights) ==? (emptylist, reverse rights, trues)
306
  , printTestCase "recombination is no-op" $
307
    recombineEithers splitleft splitright trail ==? Ok es
308
  , printTestCase "fail on too long lefts" $
309
    isBad (recombineEithers (0:splitleft) splitright trail)
310
  , printTestCase "fail on too long rights" $
311
    isBad (recombineEithers splitleft (0:splitright) trail)
312
  , printTestCase "fail on too long trail" $
313
    isBad (recombineEithers splitleft splitright (True:trail))
314
  ]
315
  where (lefts, rights) = Either.partitionEithers es
316
        falses = map (const False) lefts
317
        trues = map (const True) rights
318
        (splitleft, splitright, trail) = splitEithers es
319
        emptylist = []::[Int]
320

    
321
-- | Test list for the Utils module.
322
testSuite "Utils"
323
            [ 'prop_commaJoinSplit
324
            , 'prop_commaSplitJoin
325
            , 'prop_fromObjWithDefault
326
            , 'prop_if'if
327
            , 'prop_select
328
            , 'prop_select_undefd
329
            , 'prop_select_undefv
330
            , 'prop_parseUnit
331
            , 'case_niceSort_static
332
            , 'prop_niceSort_single
333
            , 'prop_niceSort_generic
334
            , 'prop_niceSort_numbers
335
            , 'prop_niceSortKey_equiv
336
            , 'prop_rStripSpace
337
            , 'prop_trim
338
#ifndef NO_REGEX_PCRE
339
            , 'case_new_uuid
340
#endif
341
            , 'prop_clockTimeToString
342
            , 'prop_chompPrefix_normal
343
            , 'prop_chompPrefix_last
344
            , 'prop_chompPrefix_empty_string
345
            , 'prop_chompPrefix_nothing
346
            , 'prop_splitRecombineEithers
347
            ]