Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / Storage / Drbd / Parser.hs @ c5f6cba2

History | View | Annotate | Download (17.5 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.Storage.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.Storage.Drbd.Parser (drbdStatusParser, commaIntParser)
39
import Ganeti.Storage.Drbd.Types
40

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

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

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

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

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

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

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

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

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

    
345
-- | Test a DRBD 8.0 file with a missing device.
346
case_drbd8 :: Assertion
347
case_drbd8 = testParser (drbdStatusParser []) "proc_drbd8.txt" $
348
  DRBDStatus
349
    ( VersionInfo (Just "8.0.12") (Just "86") (Just "86") Nothing
350
        (Just "5c9f89594553e32adb87d9638dce591782f947e3")
351
        (Just "XXX")
352
    )
353
    [ DeviceInfo 0 Connected (LocalRemote Primary Secondary)
354
        (LocalRemote UpToDate UpToDate) 'C' "r---"
355
        (PerfIndicators 4375577 0 4446279 674 1067 69 0 0 0 0 Nothing
356
          Nothing Nothing)
357
        Nothing
358
        (Just $ AdditionalInfo 0 61 0 0 0 0 0)
359
        (Just $ AdditionalInfo 0 257 793749 1067 0 0 1067)
360
        Nothing,
361
      DeviceInfo 1 Connected (LocalRemote Secondary Primary)
362
        (LocalRemote UpToDate UpToDate) 'C' "r---"
363
        (PerfIndicators 738320 0 738320 554400 67 0 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 92464 67 0 0 67)
368
        Nothing,
369
      UnconfiguredDevice 2,
370
      DeviceInfo 4 WFConnection (LocalRemote Primary Unknown)
371
        (LocalRemote UpToDate DUnknown) 'C' "r---"
372
        (PerfIndicators 738320 0 738320 554400 67 0 0 0 0 0 Nothing
373
          Nothing Nothing)
374
        Nothing
375
        (Just $ AdditionalInfo 0 61 0 0 0 0 0)
376
        (Just $ AdditionalInfo 0 257 92464 67 0 0 67)
377
        Nothing,
378
      DeviceInfo 5 Connected (LocalRemote Primary Secondary)
379
        (LocalRemote UpToDate Diskless) 'C' "r---"
380
        (PerfIndicators 4375581 0 4446283 674 1069 69 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 793750 1069 0 0 1069)
385
        Nothing,
386
      DeviceInfo 6 Connected (LocalRemote Secondary Primary)
387
        (LocalRemote Diskless UpToDate) 'C'  "r---"
388
        (PerfIndicators 0 4375581 5186925 327 75 214 0 0 0 0 Nothing
389
          Nothing Nothing)
390
        Nothing
391
        Nothing
392
        Nothing
393
        Nothing,
394
      DeviceInfo 7 WFConnection (LocalRemote Secondary Unknown)
395
        (LocalRemote UpToDate DUnknown) 'C' "r---"
396
        (PerfIndicators 0 0 0 0 0 0 0 0 0 0 Nothing Nothing Nothing)
397
        Nothing
398
        (Just $ AdditionalInfo 0 61 0 0 0 0 0)
399
        (Just $ AdditionalInfo 0 257 0 0 0 0 0)
400
        Nothing,
401
      DeviceInfo 8 StandAlone (LocalRemote Secondary Unknown)
402
        (LocalRemote UpToDate DUnknown) ' ' "r---"
403
        (PerfIndicators 0 0 0 0 0 0 0 0 0 0 Nothing Nothing Nothing)
404
        Nothing
405
        (Just $ AdditionalInfo 0 61 0 0 0 0 0)
406
        (Just $ AdditionalInfo 0 257 0 0 0 0 0)
407
        Nothing
408
    ]
409

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

    
420
-- | Function for testing whether a single comma-separated integer is
421
-- parsed correctly.
422
testCommaInt :: String -> Int -> Assertion
423
testCommaInt numString expectedResult =
424
  case A.parseOnly commaIntParser $ pack numString of
425
    Left msg -> assertFailure $ "Parsing failed: " ++ msg
426
    Right obtained -> assertEqual numString expectedResult obtained
427

    
428
-- | Generate a property test for CommaInt numbers in a given range.
429
gen_prop_CommaInt :: Int -> Int -> Property
430
gen_prop_CommaInt minVal maxVal =
431
  forAll (choose (minVal, maxVal)) $ \i ->
432
    case A.parseOnly commaIntParser $ pack (generateCommaInt i) of
433
      Left msg -> failTest $ "Parsing failed: " ++ msg
434
      Right obtained -> i ==? obtained
435
  where generateCommaInt x =
436
          ((reverse . intercalate ",") . splitEvery 3) . reverse $ show x
437

    
438
-- | Test if <4 digit integers are recognized correctly.
439
prop_commaInt_noCommas :: Property
440
prop_commaInt_noCommas = gen_prop_CommaInt 0 999
441

    
442
-- | Test if integers with 1 comma are recognized correctly.
443
prop_commaInt_1Comma :: Property
444
prop_commaInt_1Comma = gen_prop_CommaInt 1000 999999
445

    
446
-- | Test if integers with multiple commas are recognized correctly.
447
prop_commaInt_multipleCommas :: Property
448
prop_commaInt_multipleCommas = gen_prop_CommaInt 1000000 (maxBound ::
449
  Int)
450

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

    
469
-- | Test if non-triplets are handled correctly (they are assumed NOT being part
470
-- of the number).
471
case_commaInt_non_triplet :: Assertion
472
case_commaInt_non_triplet = testCommaInt "61,736,12" 61736
473

    
474

    
475
testSuite "Block/Drbd/Parser"
476
          [ 'case_drbd80_emptyline,
477
            'case_drbd80_emptyversion,
478
            'case_drbd84_sync,
479
            'case_drbd84,
480
            'case_drbd83_sync_krnl2_6_39,
481
            'case_drbd83_sync,
482
            'case_drbd83_sync_want,
483
            'case_drbd83,
484
            'case_drbd8,
485
            'case_commaInt_non_triplet,
486
            'prop_commaInt_noCommas,
487
            'prop_commaInt_1Comma,
488
            'prop_commaInt_multipleCommas,
489
            'prop_commaInt_max3WithoutComma
490
          ]