Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / Utils.hs @ 1de58759

History | View | Annotate | Download (13.6 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
  assertEqual "hostnames"
173
    ["host1.example.com", "host2.example.com", "host03.example.com",
174
     "host11.example.com", "host255.example.com"] $
175
    niceSort ["host2.example.com", "host11.example.com", "host03.example.com",
176
     "host1.example.com", "host255.example.com"]
177

    
178
-- | Tests single-string behaviour of 'niceSort'.
179
prop_niceSort_single :: Property
180
prop_niceSort_single =
181
  forAll genName $ \name ->
182
  conjoin
183
  [ printTestCase "single string" $ [name] ==? niceSort [name]
184
  , printTestCase "single plus empty" $ ["", name] ==? niceSort [name, ""]
185
  ]
186

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

    
200
-- | Tests that niceSorting numbers is identical to actual sorting
201
-- them (in numeric form).
202
prop_niceSort_numbers :: Property
203
prop_niceSort_numbers =
204
  forAll (listOf (arbitrary::Gen (NonNegative Int))) $ \numbers ->
205
  map show (sort numbers) ==? niceSort (map show numbers)
206

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

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

    
237
#ifndef NO_REGEX_PCRE
238
{-# ANN case_new_uuid "HLint: ignore Use camelCase" #-}
239

    
240
-- | Tests that the newUUID function produces valid UUIDs.
241
case_new_uuid :: Assertion
242
case_new_uuid = do
243
  uuid <- newUUID
244
  assertBool "newUUID" $ uuid =~ C.uuidRegex
245
#endif
246

    
247
prop_clockTimeToString :: Integer -> Integer -> Property
248
prop_clockTimeToString ts pico =
249
  clockTimeToString (TOD ts pico) ==? show ts
250

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

    
260
-- | Test that 'chompPrefix' correctly allows the last char (the separator) to
261
-- be absent if the string terminates there.
262
prop_chompPrefix_last :: Property
263
prop_chompPrefix_last =
264
  forAll (choose (1, 20)) $ \len ->
265
  forAll (vectorOf len arbitrary) $ \pfx ->
266
  chompPrefix pfx pfx ==? Just "" .&&.
267
  chompPrefix pfx (init pfx) ==? Just ""
268

    
269
-- | Test that chompPrefix on the empty string always returns Nothing for
270
-- prefixes of length 2 or more.
271
prop_chompPrefix_empty_string :: Property
272
prop_chompPrefix_empty_string =
273
  forAll (choose (2, 20)) $ \len ->
274
  forAll (vectorOf len arbitrary) $ \pfx ->
275
  chompPrefix pfx "" ==? Nothing
276

    
277
-- | Test 'chompPrefix' returns Nothing when the prefix doesn't match.
278
prop_chompPrefix_nothing :: Property
279
prop_chompPrefix_nothing =
280
  forAll (choose (1, 20)) $ \len ->
281
  forAll (vectorOf len arbitrary) $ \pfx ->
282
  forAll (arbitrary `suchThat`
283
          (\s -> not (pfx `isPrefixOf` s) && s /= init pfx)) $ \str ->
284
  chompPrefix pfx str ==? Nothing
285

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

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

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