Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / Block / Drbd / Parser.hs @ a7e0c9b0

History | View | Annotate | Download (17.7 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

    
3
{-| Unittests for the DRBD Parser -}
4

    
5
{-
6

    
7
Copyright (C) 2012 Google Inc.
8

    
9
This program is free software; you can redistribute it and/or modify
10
it under the terms of the GNU General Public License as published by
11
the Free Software Foundation; either version 2 of the License, or
12
(at your option) any later version.
13

    
14
This program is distributed in the hope that it will be useful, but
15
WITHOUT ANY WARRANTY; without even the implied warranty of
16
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17
General Public License for more details.
18

    
19
You should have received a copy of the GNU General Public License
20
along with this program; if not, write to the Free Software
21
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22
02110-1301, USA.
23

    
24
-}
25

    
26
module Test.Ganeti.Block.Drbd.Parser (testBlock_Drbd_Parser) where
27

    
28
import Test.QuickCheck as QuickCheck hiding (Result)
29
import Test.HUnit
30

    
31
import Test.Ganeti.TestHelper
32
import Test.Ganeti.TestCommon
33

    
34
import qualified Data.Attoparsec.Text as A
35
import Data.List (intercalate)
36
import Data.Text (pack)
37

    
38
import Ganeti.Block.Drbd.Parser (drbdStatusParser, commaIntParser)
39
import Ganeti.Block.Drbd.Types
40

    
41
{-# ANN module "HLint: ignore Use camelCase" #-}
42

    
43
-- | Function for testing whether a file is parsed correctly.
44
testFile :: String -> DRBDStatus -> Assertion
45
testFile fileName expectedContent = do
46
    fileContent <- readTestData fileName
47
    case A.parseOnly (drbdStatusParser []) $ pack fileContent of
48
        Left msg -> assertFailure $ "Parsing failed: " ++ msg
49
        Right obtained -> assertEqual fileName expectedContent obtained
50

    
51
-- | Test a DRBD 8.0 file with an empty line inside.
52
case_drbd80_emptyline :: Assertion
53
case_drbd80_emptyline = testFile "proc_drbd80-emptyline.txt" $
54
  DRBDStatus
55
    ( VersionInfo (Just "8.0.12") (Just "86") (Just "86") Nothing
56
        (Just "5c9f89594553e32adb87d9638dce591782f947e3")
57
        (Just "root@node1.example.com, 2009-05-22 12:47:52")
58
    )
59
    [ DeviceInfo 0 Connected (LocalRemote Primary Secondary)
60
        (LocalRemote UpToDate UpToDate) 'C' "r---"
61
        (PerfIndicators 78728316 0 77675644 1277039 254 270 0 0 0 0
62
          Nothing Nothing Nothing)
63
        Nothing
64
        (Just $ AdditionalInfo 0 61 65657 135 0 0 135)
65
        (Just $ AdditionalInfo 0 257 11378843 254 0 0 254)
66
        Nothing,
67
      UnconfiguredDevice 1,
68
      UnconfiguredDevice 2,
69
      UnconfiguredDevice 5,
70
      UnconfiguredDevice 6
71
    ]
72

    
73
-- | Test a DRBD 8.0 file with an empty version.
74
case_drbd80_emptyversion :: Assertion
75
case_drbd80_emptyversion = testFile "proc_drbd80-emptyversion.txt" $
76
  DRBDStatus
77
    ( VersionInfo Nothing Nothing Nothing Nothing
78
        (Just "5c9f89594553e32adb87d9638dce591782f947e3")
79
        (Just "root@node1.example.com, 2009-05-22 12:47:52")
80
    )
81
    [ DeviceInfo 0 Connected (LocalRemote Primary Secondary)
82
        (LocalRemote UpToDate UpToDate) 'C' "r---"
83
        (PerfIndicators 78728316 0 77675644 1277039 254 270 0 0 0 0
84
          Nothing Nothing Nothing)
85
        Nothing
86
        (Just $ AdditionalInfo 0 61 65657 135 0 0 135)
87
        (Just $ AdditionalInfo 0 257 11378843 254 0 0 254)
88
        Nothing,
89
      UnconfiguredDevice 1,
90
      UnconfiguredDevice 2,
91
      UnconfiguredDevice 5,
92
      UnconfiguredDevice 6
93
    ]
94

    
95
-- | Test a DRBD 8.4 file with an ongoing synchronization.
96
case_drbd84_sync :: Assertion
97
case_drbd84_sync = testFile "proc_drbd84_sync.txt" $
98
  DRBDStatus
99
    ( VersionInfo (Just "8.4.2") (Just "1") (Just "86-101") Nothing
100
        (Just "7ad5f850d711223713d6dcadc3dd48860321070c")
101
        (Just "root@example.com, 2013-04-10 07:45:25")
102
    )
103
    [ DeviceInfo 0 StandAlone (LocalRemote Primary Unknown)
104
        (LocalRemote UpToDate DUnknown) ' ' "r-----"
105
        (PerfIndicators 0 0 33318 730 15 0 0 0 0 0 (Just 1)
106
          (Just 'd') (Just 1048320))
107
        Nothing
108
        Nothing
109
        Nothing
110
        Nothing,
111
      UnconfiguredDevice 3,
112
      DeviceInfo 5 SyncSource (LocalRemote Secondary Secondary)
113
        (LocalRemote UpToDate Inconsistent) 'C' "r---n-"
114
        (PerfIndicators 716992 0 0 719432 0 43 0 33 18 0 (Just 1)
115
          (Just 'f') (Just 335744))
116
        (Just $ SyncStatus 68.5 335744 1048576 KiloByte (Time 0 0 5) 64800
117
          Nothing KiloByte Second)
118
        Nothing
119
        Nothing
120
        Nothing
121
    ]
122

    
123
-- | Test a DRBD 8.4 file.
124
case_drbd84 :: Assertion
125
case_drbd84 = testFile "proc_drbd84.txt" $
126
  DRBDStatus
127
    ( VersionInfo (Just "8.4.2") (Just "1") (Just "86-101") Nothing
128
      (Just "7ad5f850d711223713d6dcadc3dd48860321070c")
129
      (Just "root@example.com, 2013-04-10 07:45:25")
130
    )
131
    [ DeviceInfo 0 Connected (LocalRemote Primary Secondary)
132
        (LocalRemote UpToDate UpToDate) 'C' "r-----"
133
        (PerfIndicators 1048576 0 0 1048776 0 64 0 0 0 0 (Just 1)
134
          (Just 'f') (Just 0))
135
        Nothing
136
        Nothing
137
        Nothing
138
        Nothing,
139
      DeviceInfo 1 Connected (LocalRemote Secondary Primary)
140
        (LocalRemote UpToDate UpToDate) 'C' "r-----"
141
        (PerfIndicators 0 1048576 1048576 0 0 64 0 0 0 0 (Just 1)
142
          (Just 'f') (Just 0))
143
        Nothing
144
        Nothing
145
        Nothing
146
        Nothing,
147
      UnconfiguredDevice 2,
148
      DeviceInfo 4 WFConnection (LocalRemote Primary Unknown)
149
        (LocalRemote UpToDate DUnknown) 'C' "r-----"
150
        (PerfIndicators 0 0 0 200 0 0 0 0 0 0 (Just 1)
151
          (Just 'f') (Just 1048320))
152
        Nothing
153
        Nothing
154
        Nothing
155
        Nothing,
156
      DeviceInfo 6 Connected (LocalRemote Secondary Primary)
157
        (LocalRemote Diskless UpToDate) 'C' "r-----"
158
        (PerfIndicators 0 0 0 0 0 0 0 0 0 0 (Just 1) (Just 'b')
159
          (Just 0))
160
        Nothing
161
        Nothing
162
        Nothing
163
        Nothing,
164
      DeviceInfo 8 StandAlone (LocalRemote Secondary Unknown)
165
        (LocalRemote UpToDate DUnknown) ' ' "r-----"
166
        (PerfIndicators 0 0 0 200 0 0 0 0 0 0 (Just 1)
167
          (Just 'f') (Just 1048320))
168
        Nothing
169
        Nothing
170
        Nothing
171
        Nothing
172
    ]
173

    
174
-- | Test a DRBD 8.3 file with a NULL caracter inside.
175
case_drbd83_sync_krnl2_6_39 :: Assertion
176
case_drbd83_sync_krnl2_6_39 = testFile "proc_drbd83_sync_krnl2.6.39.txt" $
177
  DRBDStatus
178
    ( VersionInfo (Just "8.3.1") (Just "88") (Just "86-89") Nothing
179
        (Just "fd40f4a8f9104941537d1afc8521e584a6d3003c")
180
        (Just "phil@fat-tyre, 2009-03-27 12:19:49")
181
    )
182
    [ DeviceInfo 0 Connected (LocalRemote Primary Secondary)
183
        (LocalRemote UpToDate UpToDate) 'C' "r----"
184
        (PerfIndicators 140978 0 9906 131533 27 8 0 0 0 0 (Just 1)
185
          (Just 'b') (Just 0))
186
        Nothing
187
        Nothing
188
        Nothing
189
        Nothing,
190
      DeviceInfo 1 Connected (LocalRemote Secondary Primary)
191
        (LocalRemote UpToDate UpToDate) 'C' "r---"
192
        (PerfIndicators 0 140980 140980 0 0 8 0 0 0 0 (Just 1) (Just 'f')
193
          (Just 0))
194
        Nothing
195
        Nothing
196
        Nothing
197
        Nothing,
198
      UnconfiguredDevice 2,
199
      DeviceInfo 3 SyncSource (LocalRemote Primary Secondary)
200
        (LocalRemote UpToDate Inconsistent) 'A' "r-----"
201
        (PerfIndicators 373888 0 0 374088 0 22 7 27 7 0 (Just 1)
202
          (Just 'f') (Just 15358208))
203
        (Just $ SyncStatus 2.4 14996 15360 MegaByte (Time 0 4 8) 61736 Nothing
204
          KiloByte Second)
205
        Nothing
206
        Nothing
207
        Nothing,
208
      DeviceInfo 4 WFConnection (LocalRemote Primary Unknown)
209
        (LocalRemote UpToDate DUnknown) 'C' "r----"
210
        (PerfIndicators 140978 0 9906 131534 27 8 0 0 0 0 (Just 1)
211
          (Just 'b') (Just 0))
212
        Nothing
213
        Nothing
214
        Nothing
215
        Nothing
216
    ]
217

    
218
-- | Test a DRBD 8.3 file with an ongoing synchronization.
219
case_drbd83_sync :: Assertion
220
case_drbd83_sync = testFile "proc_drbd83_sync.txt" $
221
  DRBDStatus
222
    ( VersionInfo (Just "8.3.1") (Just "88") (Just "86-89") Nothing
223
        (Just "fd40f4a8f9104941537d1afc8521e584a6d3003c")
224
        (Just "phil@fat-tyre, 2009-03-27 12:19:49")
225
    )
226
    [ DeviceInfo 0 Connected (LocalRemote Primary Secondary)
227
        (LocalRemote UpToDate UpToDate) 'C' "r----"
228
        (PerfIndicators 140978 0 9906 131533 27 8 0 0 0 0 (Just 1)
229
          (Just 'b') (Just 0))
230
        Nothing
231
        Nothing
232
        Nothing
233
        Nothing,
234
      DeviceInfo 1 Connected (LocalRemote Secondary Primary)
235
        (LocalRemote UpToDate UpToDate) 'C' "r---"
236
        (PerfIndicators 0 140980 140980 0 0 8 0 0 0 0 (Just 1) (Just 'f')
237
          (Just 0))
238
        Nothing
239
        Nothing
240
        Nothing
241
        Nothing,
242
      UnconfiguredDevice 2,
243
      DeviceInfo 3 SyncTarget (LocalRemote Primary Secondary)
244
        (LocalRemote Inconsistent UpToDate) 'C' "r----"
245
        (PerfIndicators 0 178176 178176 0 104 42 0 0 0 0 (Just 1)
246
          (Just 'b') (Just 346112))
247
        (Just $ SyncStatus 34.9 346112 524288 MegaByte (Time 0 0 5) 59392
248
          Nothing KiloByte Second)
249
        Nothing
250
        Nothing
251
        Nothing,
252
      DeviceInfo 4 WFConnection (LocalRemote Primary Unknown)
253
        (LocalRemote UpToDate DUnknown) 'C' "r----"
254
        (PerfIndicators 140978 0 9906 131534 27 8 0 0 0 0 (Just 1)
255
          (Just 'b') (Just 0))
256
        Nothing
257
        Nothing
258
        Nothing
259
        Nothing
260
    ]
261

    
262
-- | Test a DRBD 8.3 file not from git sources, with an ongoing synchronization
263
-- and the "want" field
264
case_drbd83_sync_want :: Assertion
265
case_drbd83_sync_want = testFile "proc_drbd83_sync_want.txt" $
266
  DRBDStatus
267
    ( VersionInfo (Just "8.3.11") (Just "88") (Just "86-96")
268
        (Just "2D876214BAAD53B31ADC1D6")
269
        Nothing Nothing
270
    )
271
    [ DeviceInfo 0 SyncTarget (LocalRemote Secondary Primary)
272
        (LocalRemote Inconsistent UpToDate) 'C' "r-----"
273
        (PerfIndicators 0 460288 460160 0 0 28 2 4 1 0 (Just 1)
274
          (Just 'f') (Just 588416))
275
        (Just $ SyncStatus 44.4 588416 1048576 KiloByte (Time 0 0 8) 65736
276
          (Just 61440) KiloByte Second)
277
        Nothing
278
        Nothing
279
        Nothing,
280
      UnconfiguredDevice 1,
281
      UnconfiguredDevice 2,
282
      UnconfiguredDevice 3
283
    ]
284

    
285
-- | Test a DRBD 8.3 file.
286
case_drbd83 :: Assertion
287
case_drbd83 = testFile "proc_drbd83.txt" $
288
  DRBDStatus
289
    ( VersionInfo (Just "8.3.1") (Just "88") (Just "86-89")
290
      Nothing
291
      (Just "fd40f4a8f9104941537d1afc8521e584a6d3003c")
292
      (Just "phil@fat-tyre, 2009-03-27 12:19:49")
293
    )
294
    [ DeviceInfo 0 Connected (LocalRemote Primary Secondary)
295
        (LocalRemote UpToDate UpToDate) 'C' "r----"
296
        (PerfIndicators 140978 0 9906 131533 27 8 0 0 0 0 (Just 1)
297
          (Just 'b') (Just 0))
298
        Nothing
299
        Nothing
300
        Nothing
301
        Nothing,
302
      DeviceInfo 1 Connected (LocalRemote Secondary Primary)
303
        (LocalRemote UpToDate UpToDate) 'C' "r---"
304
        (PerfIndicators 0 140980 140980 0 0 8 0 0 0 0 (Just 1) (Just 'f')
305
          (Just 0))
306
        Nothing
307
        Nothing
308
        Nothing
309
        Nothing,
310
      UnconfiguredDevice 2,
311
      DeviceInfo 4 WFConnection (LocalRemote Primary Unknown)
312
        (LocalRemote UpToDate DUnknown) 'C' "r----"
313
        (PerfIndicators 140978 0 9906 131534 27 8 0 0 0 0 (Just 1)
314
          (Just 'b') (Just 0))
315
        Nothing
316
        Nothing
317
        Nothing
318
        Nothing,
319
      DeviceInfo 5 Connected (LocalRemote Primary Secondary)
320
        (LocalRemote UpToDate Diskless) 'C' "r----"
321
        (PerfIndicators 140978 0 9906 131533 19 8 0 0 0 0 (Just 1)
322
          (Just 'b') (Just 0))
323
        Nothing
324
        Nothing
325
        Nothing
326
        Nothing,
327
      DeviceInfo 6 Connected (LocalRemote Secondary Primary)
328
        (LocalRemote Diskless UpToDate) 'C' "r---"
329
        (PerfIndicators 0 140978 140978 0 0 8 0 0 0 0 (Just 1) (Just 'f')
330
          (Just 0))
331
        Nothing
332
        Nothing
333
        Nothing
334
        Nothing,
335
      DeviceInfo 7 WFConnection (LocalRemote Secondary Unknown)
336
        (LocalRemote UpToDate DUnknown) 'C' "r---"
337
        (PerfIndicators 0 140978 140978 0 0 8 0 0 0 0 (Just 1) (Just 'f')
338
          (Just 0))
339
        Nothing
340
        Nothing
341
        Nothing
342
        Nothing,
343
      DeviceInfo 8 StandAlone (LocalRemote Secondary Unknown)
344
        (LocalRemote UpToDate DUnknown) ' ' "r---"
345
        (PerfIndicators 0 140978 140978 0 0 8 0 0 0 0 (Just 1)
346
          (Just 'f') (Just 0))
347
        Nothing
348
        Nothing
349
        Nothing
350
        Nothing
351
    ]
352

    
353
-- | Test a DRBD 8.0 file with a missing device.
354
case_drbd8 :: Assertion
355
case_drbd8 = testFile "proc_drbd8.txt" $
356
  DRBDStatus
357
    ( VersionInfo (Just "8.0.12") (Just "86") (Just "86") Nothing
358
        (Just "5c9f89594553e32adb87d9638dce591782f947e3")
359
        (Just "XXX")
360
    )
361
    [ DeviceInfo 0 Connected (LocalRemote Primary Secondary)
362
        (LocalRemote UpToDate UpToDate) 'C' "r---"
363
        (PerfIndicators 4375577 0 4446279 674 1067 69 0 0 0 0 Nothing
364
          Nothing Nothing)
365
        Nothing
366
        (Just $ AdditionalInfo 0 61 0 0 0 0 0)
367
        (Just $ AdditionalInfo 0 257 793749 1067 0 0 1067)
368
        Nothing,
369
      DeviceInfo 1 Connected (LocalRemote Secondary Primary)
370
        (LocalRemote UpToDate UpToDate) 'C' "r---"
371
        (PerfIndicators 738320 0 738320 554400 67 0 0 0 0 0 Nothing
372
          Nothing Nothing)
373
        Nothing
374
        (Just $ AdditionalInfo 0 61 0 0 0 0 0)
375
        (Just $ AdditionalInfo 0 257 92464 67 0 0 67)
376
        Nothing,
377
      UnconfiguredDevice 2,
378
      DeviceInfo 4 WFConnection (LocalRemote Primary Unknown)
379
        (LocalRemote UpToDate DUnknown) 'C' "r---"
380
        (PerfIndicators 738320 0 738320 554400 67 0 0 0 0 0 Nothing
381
          Nothing Nothing)
382
        Nothing
383
        (Just $ AdditionalInfo 0 61 0 0 0 0 0)
384
        (Just $ AdditionalInfo 0 257 92464 67 0 0 67)
385
        Nothing,
386
      DeviceInfo 5 Connected (LocalRemote Primary Secondary)
387
        (LocalRemote UpToDate Diskless) 'C' "r---"
388
        (PerfIndicators 4375581 0 4446283 674 1069 69 0 0 0 0 Nothing
389
          Nothing Nothing)
390
        Nothing
391
        (Just $ AdditionalInfo 0 61 0 0 0 0 0)
392
        (Just $ AdditionalInfo 0 257 793750 1069 0 0 1069)
393
        Nothing,
394
      DeviceInfo 6 Connected (LocalRemote Secondary Primary)
395
        (LocalRemote Diskless UpToDate) 'C'  "r---"
396
        (PerfIndicators 0 4375581 5186925 327 75 214 0 0 0 0 Nothing
397
          Nothing Nothing)
398
        Nothing
399
        Nothing
400
        Nothing
401
        Nothing,
402
      DeviceInfo 7 WFConnection (LocalRemote Secondary Unknown)
403
        (LocalRemote UpToDate DUnknown) 'C' "r---"
404
        (PerfIndicators 0 0 0 0 0 0 0 0 0 0 Nothing Nothing Nothing)
405
        Nothing
406
        (Just $ AdditionalInfo 0 61 0 0 0 0 0)
407
        (Just $ AdditionalInfo 0 257 0 0 0 0 0)
408
        Nothing,
409
      DeviceInfo 8 StandAlone (LocalRemote Secondary Unknown)
410
        (LocalRemote UpToDate DUnknown) ' ' "r---"
411
        (PerfIndicators 0 0 0 0 0 0 0 0 0 0 Nothing Nothing Nothing)
412
        Nothing
413
        (Just $ AdditionalInfo 0 61 0 0 0 0 0)
414
        (Just $ AdditionalInfo 0 257 0 0 0 0 0)
415
        Nothing
416
    ]
417

    
418
-- | Function for splitting a list in chunks of a given size.
419
-- FIXME: an equivalent function exists in Data.List.Split, but it seems
420
-- pointless to add this package as a dependence just for this single
421
-- use. In case it is ever added, just remove this function definition
422
-- and use the one from the package.
423
splitEvery :: Int -> [e] -> [[e]]
424
splitEvery i l = map (take i) (splitter l (:) []) where
425
  splitter [] _ n = n
426
  splitter li c n  = li `c` splitter (drop i li) c n
427

    
428
-- | Function for testing whether a single comma-separated integer is
429
-- parsed correctly.
430
testCommaInt :: String -> Int -> Assertion
431
testCommaInt numString expectedResult =
432
  case A.parseOnly commaIntParser $ pack numString of
433
    Left msg -> assertFailure $ "Parsing failed: " ++ msg
434
    Right obtained -> assertEqual numString expectedResult obtained
435

    
436
-- | Generate a property test for CommaInt numbers in a given range.
437
gen_prop_CommaInt :: Int -> Int -> Property
438
gen_prop_CommaInt minVal maxVal =
439
  forAll (choose (minVal, maxVal)) $ \i ->
440
    case A.parseOnly commaIntParser $ pack (generateCommaInt i) of
441
      Left msg -> failTest $ "Parsing failed: " ++ msg
442
      Right obtained -> i ==? obtained
443
  where generateCommaInt x =
444
          ((reverse . intercalate ",") . splitEvery 3) . reverse $ show x
445

    
446
-- | Test if <4 digit integers are recognized correctly.
447
prop_commaInt_noCommas :: Property
448
prop_commaInt_noCommas = gen_prop_CommaInt 0 999
449

    
450
-- | Test if integers with 1 comma are recognized correctly.
451
prop_commaInt_1Comma :: Property
452
prop_commaInt_1Comma = gen_prop_CommaInt 1000 999999
453

    
454
-- | Test if integers with multiple commas are recognized correctly.
455
prop_commaInt_multipleCommas :: Property
456
prop_commaInt_multipleCommas = gen_prop_CommaInt 1000000 (maxBound ::
457
  Int)
458

    
459
-- | Test whether the parser is actually able to behave as intended with
460
-- numbers without commas. That is, if a number with more than 3 digits
461
-- is parsed, only up to the first 3 digits are considered (because they
462
-- are a valid commaInt), and the rest is ignored.
463
-- e.g.: parse "1234" = 123
464
prop_commaInt_max3WithoutComma :: Property
465
prop_commaInt_max3WithoutComma =
466
  forAll (choose (0, maxBound :: Int)) $ \i ->
467
    case A.parseOnly commaIntParser $ pack (show i) of
468
      Left msg -> failTest $ "Parsing failed: " ++ msg
469
      Right obtained ->
470
        obtained < 1000 .&&.
471
        getFirst3Digits i ==? obtained
472
  where getFirst3Digits x =
473
          if x >= 1000
474
            then getFirst3Digits $ x `div` 10
475
            else x
476

    
477
-- | Test if non-triplets are handled correctly (they are assumed NOT being part
478
-- of the number).
479
case_commaInt_non_triplet :: Assertion
480
case_commaInt_non_triplet = testCommaInt "61,736,12" 61736
481

    
482

    
483
testSuite "Block/Drbd/Parser"
484
          [ 'case_drbd80_emptyline,
485
            'case_drbd80_emptyversion,
486
            'case_drbd84_sync,
487
            'case_drbd84,
488
            'case_drbd83_sync_krnl2_6_39,
489
            'case_drbd83_sync,
490
            'case_drbd83_sync_want,
491
            'case_drbd83,
492
            'case_drbd8,
493
            'case_commaInt_non_triplet,
494
            'prop_commaInt_noCommas,
495
            'prop_commaInt_1Comma,
496
            'prop_commaInt_multipleCommas,
497
            'prop_commaInt_max3WithoutComma
498
          ]