Revision a52f8e72

b/Makefile.am
67 67
	htest \
68 68
	htest/Test \
69 69
	htest/Test/Ganeti \
70
	htest/Test/Ganeti/Block \
71
	htest/Test/Ganeti/Block/Drbd \
70 72
	htest/Test/Ganeti/Confd \
71 73
	htest/Test/Ganeti/HTools \
72 74
	htest/Test/Ganeti/HTools/Backend \
......
490 492
HS_TEST_SRCS = \
491 493
	htest/Test/Ganeti/Attoparsec.hs \
492 494
	htest/Test/Ganeti/BasicTypes.hs \
495
	htest/Test/Ganeti/Block/Drbd/Parser.hs \
493 496
	htest/Test/Ganeti/Common.hs \
494 497
	htest/Test/Ganeti/Confd/Utils.hs \
495 498
	htest/Test/Ganeti/Daemon.hs \
......
887 890
	test/data/proc_drbd80-emptyline.txt \
888 891
	test/data/proc_drbd83.txt \
889 892
	test/data/proc_drbd83_sync.txt \
893
	test/data/proc_drbd83_sync_want.txt \
890 894
	test/data/proc_drbd83_sync_krnl2.6.39.txt \
891 895
	test/data/sys_drbd_usermode_helper.txt \
892 896
	test/data/vgreduce-removemissing-2.02.02.txt \
b/htest/Test/Ganeti/Block/Drbd/Parser.hs
1
{-# LANGUAGE TemplateHaskell #-}
2

  
3
{-| Unittests for Attoparsec support for unicode -}
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_DRBDParser) where
27

  
28
import Test.HUnit
29

  
30
import Test.Ganeti.TestHelper
31
import Test.Ganeti.TestCommon (readPythonTestData)
32

  
33
import qualified Data.Attoparsec.Text as A
34
import Data.Text (pack)
35

  
36
import Ganeti.Block.Drbd.Parser (drbdStatusParser, commaIntParser)
37
import Ganeti.Block.Drbd.Types
38

  
39
-- | Function for testing whether a file is parsed correctly.
40
testFile :: String -> DRBDStatus -> Assertion
41
testFile fileName expectedContent = do
42
    fileContent <- readPythonTestData fileName
43
    case A.parseOnly drbdStatusParser $ pack fileContent of
44
        Left msg -> assertFailure $ "Parsing failed: " ++ msg
45
        Right obtained -> assertEqual fileName expectedContent obtained
46

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

  
68
-- | Test a DRBD 8.3 file with a NULL caracter inside.
69
case_drbd83_sync_krnl2_6_39 :: Assertion
70
case_drbd83_sync_krnl2_6_39 = testFile "proc_drbd83_sync_krnl2.6.39.txt" $
71
  DRBDStatus
72
    ( VersionInfo (Just "8.3.1") (Just "88") (Just "86-89") Nothing
73
        (Just "fd40f4a8f9104941537d1afc8521e584a6d3003c")
74
        (Just "phil@fat-tyre, 2009-03-27 12:19:49")
75
    )
76
    [ DeviceInfo 0 Connected (LocalRemote Primary Secondary)
77
        (LocalRemote UpToDate UpToDate) 'C' "r----"
78
        (PerformanceIndicators 140978 0 9906 131533 27 8 0 0 0 0 (Just 1)
79
          (Just 'b') (Just 0))
80
        Nothing
81
        Nothing
82
        Nothing,
83
      DeviceInfo 1 Connected (LocalRemote Secondary Primary)
84
        (LocalRemote UpToDate UpToDate) 'C' "r---"
85
        (PerformanceIndicators 0 140980 140980 0 0 8 0 0 0 0 (Just 1) (Just 'f')
86
          (Just 0))
87
        Nothing
88
        Nothing
89
        Nothing,
90
      UnconfiguredDevice 2,
91
      DeviceInfo 3 SyncSource (LocalRemote Primary Secondary)
92
        (LocalRemote UpToDate Inconsistent) 'A' "r-----"
93
        (PerformanceIndicators 373888 0 0 374088 0 22 7 27 7 0 (Just 1)
94
          (Just 'f') (Just 15358208))
95
        (Just $ SyncStatus 2.4 14996 15360 MegaByte (Time 0 4 8) 61736 Nothing
96
          KiloByte Second)
97
        Nothing
98
        Nothing,
99
      DeviceInfo 4 WFConnection (LocalRemote Primary Unknown)
100
        (LocalRemote UpToDate DUnknown) 'C' "r----"
101
        (PerformanceIndicators 140978 0 9906 131534 27 8 0 0 0 0 (Just 1)
102
          (Just 'b') (Just 0))
103
        Nothing
104
        Nothing
105
        Nothing
106
    ]
107

  
108
-- | Test a DRBD 8.3 file with an ongoing synchronization.
109
case_drbd83_sync :: Assertion
110
case_drbd83_sync = testFile "proc_drbd83_sync.txt" $
111
  DRBDStatus
112
    ( VersionInfo (Just "8.3.1") (Just "88") (Just "86-89") Nothing
113
        (Just "fd40f4a8f9104941537d1afc8521e584a6d3003c")
114
        (Just "phil@fat-tyre, 2009-03-27 12:19:49")
115
    )
116
    [ DeviceInfo 0 Connected (LocalRemote Primary Secondary)
117
        (LocalRemote UpToDate UpToDate) 'C' "r----"
118
        (PerformanceIndicators 140978 0 9906 131533 27 8 0 0 0 0 (Just 1)
119
          (Just 'b') (Just 0))
120
        Nothing
121
        Nothing
122
        Nothing,
123
      DeviceInfo 1 Connected (LocalRemote Secondary Primary)
124
        (LocalRemote UpToDate UpToDate) 'C' "r---"
125
        (PerformanceIndicators 0 140980 140980 0 0 8 0 0 0 0 (Just 1) (Just 'f')
126
          (Just 0))
127
        Nothing
128
        Nothing
129
        Nothing,
130
      UnconfiguredDevice 2,
131
      DeviceInfo 3 SyncTarget (LocalRemote Primary Secondary)
132
        (LocalRemote Inconsistent UpToDate) 'C' "r----"
133
        (PerformanceIndicators 0 178176 178176 0 104 42 0 0 0 0 (Just 1)
134
          (Just 'b') (Just 346112))
135
        (Just $ SyncStatus 34.9 346112 524288 MegaByte (Time 0 0 5) 59392 Nothing
136
          KiloByte Second)
137
        Nothing
138
        Nothing,
139
      DeviceInfo 4 WFConnection (LocalRemote Primary Unknown)
140
        (LocalRemote UpToDate DUnknown) 'C' "r----"
141
        (PerformanceIndicators 140978 0 9906 131534 27 8 0 0 0 0 (Just 1)
142
          (Just 'b') (Just 0))
143
        Nothing
144
        Nothing
145
        Nothing
146
    ]
147

  
148
-- | Test a DRBD 8.3 file not from git sources, with an ongoing synchronization
149
-- and the "want" field
150
case_drbd83_sync_want :: Assertion
151
case_drbd83_sync_want = testFile "proc_drbd83_sync_want.txt" $
152
  DRBDStatus
153
    ( VersionInfo (Just "8.3.11") (Just "88") (Just "86-96")
154
        (Just "2D876214BAAD53B31ADC1D6")
155
        Nothing Nothing
156
    )
157
    [ DeviceInfo 0 SyncTarget (LocalRemote Secondary Primary)
158
        (LocalRemote Inconsistent UpToDate) 'C' "r-----"
159
        (PerformanceIndicators 0 460288 460160 0 0 28 2 4 1 0 (Just 1)
160
          (Just 'f') (Just 588416))
161
        (Just $ SyncStatus 44.4 588416 1048576 KiloByte (Time 0 0 8) 65736
162
          (Just 61440) KiloByte Second)
163
        Nothing
164
        Nothing,
165
      UnconfiguredDevice 1,
166
      UnconfiguredDevice 2,
167
      UnconfiguredDevice 3
168
    ]
169

  
170
-- | Test a DRBD 8.3 file.
171
case_drbd83 :: Assertion
172
case_drbd83 = testFile "proc_drbd83.txt" $
173
  DRBDStatus
174
    ( VersionInfo (Just "8.3.1") (Just "88") (Just "86-89")
175
      Nothing
176
      (Just "fd40f4a8f9104941537d1afc8521e584a6d3003c")
177
      (Just "phil@fat-tyre, 2009-03-27 12:19:49")
178
    )
179
    [ DeviceInfo 0 Connected (LocalRemote Primary Secondary)
180
        (LocalRemote UpToDate UpToDate) 'C' "r----"
181
        (PerformanceIndicators 140978 0 9906 131533 27 8 0 0 0 0 (Just 1)
182
          (Just 'b') (Just 0))
183
        Nothing
184
        Nothing
185
        Nothing,
186
      DeviceInfo 1 Connected (LocalRemote Secondary Primary)
187
        (LocalRemote UpToDate UpToDate) 'C' "r---"
188
        (PerformanceIndicators 0 140980 140980 0 0 8 0 0 0 0 (Just 1) (Just 'f')
189
          (Just 0))
190
        Nothing
191
        Nothing
192
        Nothing,
193
      UnconfiguredDevice 2,
194
      DeviceInfo 4 WFConnection (LocalRemote Primary Unknown)
195
        (LocalRemote UpToDate DUnknown) 'C' "r----"
196
        (PerformanceIndicators 140978 0 9906 131534 27 8 0 0 0 0 (Just 1)
197
          (Just 'b') (Just 0))
198
        Nothing
199
        Nothing
200
        Nothing,
201
      DeviceInfo 5 Connected (LocalRemote Primary Secondary)
202
        (LocalRemote UpToDate Diskless) 'C' "r----"
203
        (PerformanceIndicators 140978 0 9906 131533 19 8 0 0 0 0 (Just 1)
204
          (Just 'b') (Just 0))
205
        Nothing
206
        Nothing
207
        Nothing,
208
      DeviceInfo 6 Connected (LocalRemote Secondary Primary)
209
        (LocalRemote Diskless UpToDate) 'C' "r---"
210
        (PerformanceIndicators 0 140978 140978 0 0 8 0 0 0 0 (Just 1) (Just 'f')
211
          (Just 0))
212
        Nothing
213
        Nothing
214
        Nothing,
215
      DeviceInfo 7 WFConnection (LocalRemote Secondary Unknown)
216
        (LocalRemote UpToDate DUnknown) 'C' "r---"
217
        (PerformanceIndicators 0 140978 140978 0 0 8 0 0 0 0 (Just 1) (Just 'f')
218
          (Just 0))
219
        Nothing
220
        Nothing
221
        Nothing,
222
      DeviceInfo 8 StandAlone (LocalRemote Secondary Unknown)
223
        (LocalRemote UpToDate DUnknown) ' ' "r---"
224
        (PerformanceIndicators 0 140978 140978 0 0 8 0 0 0 0 (Just 1)
225
          (Just 'f') (Just 0))
226
        Nothing
227
        Nothing
228
        Nothing
229
    ]
230

  
231
-- | Test a DRBD 8.0 file with a missing device.
232
case_drbd8 :: Assertion
233
case_drbd8 = testFile "proc_drbd8.txt" $
234
  DRBDStatus
235
    ( VersionInfo (Just "8.0.12") (Just "86") (Just "86") Nothing
236
        (Just "5c9f89594553e32adb87d9638dce591782f947e3")
237
        (Just "XXX")
238
    )
239
    [ DeviceInfo 0 Connected (LocalRemote Primary Secondary)
240
        (LocalRemote UpToDate UpToDate) 'C' "r---"
241
        (PerformanceIndicators 4375577 0 4446279 674 1067 69 0 0 0 0 Nothing
242
          Nothing Nothing)
243
        Nothing
244
        (Just $ AdditionalInfo 0 61 0 0 0 0 0)
245
        (Just $ AdditionalInfo 0 257 793749 1067 0 0 1067),
246
      DeviceInfo 1 Connected (LocalRemote Secondary Primary)
247
        (LocalRemote UpToDate UpToDate) 'C' "r---"
248
        (PerformanceIndicators 738320 0 738320 554400 67 0 0 0 0 0 Nothing
249
          Nothing Nothing)
250
        Nothing
251
        (Just $ AdditionalInfo 0 61 0 0 0 0 0)
252
        (Just $ AdditionalInfo 0 257 92464 67 0 0 67),
253
      UnconfiguredDevice 2,
254
      DeviceInfo 4 WFConnection (LocalRemote Primary Unknown)
255
        (LocalRemote UpToDate DUnknown) 'C' "r---"
256
        (PerformanceIndicators 738320 0 738320 554400 67 0 0 0 0 0 Nothing
257
          Nothing Nothing)
258
        Nothing
259
        (Just $ AdditionalInfo 0 61 0 0 0 0 0)
260
        (Just $ AdditionalInfo 0 257 92464 67 0 0 67),
261
      DeviceInfo 5 Connected (LocalRemote Primary Secondary)
262
        (LocalRemote UpToDate Diskless) 'C' "r---"
263
        (PerformanceIndicators 4375581 0 4446283 674 1069 69 0 0 0 0 Nothing
264
          Nothing Nothing)
265
        Nothing
266
        (Just $ AdditionalInfo 0 61 0 0 0 0 0)
267
        (Just $ AdditionalInfo 0 257 793750 1069 0 0 1069),
268
      DeviceInfo 6 Connected (LocalRemote Secondary Primary)
269
        (LocalRemote Diskless UpToDate) 'C'  "r---"
270
        (PerformanceIndicators 0 4375581 5186925 327 75 214 0 0 0 0 Nothing
271
          Nothing Nothing)
272
        Nothing
273
        Nothing
274
        Nothing,
275
      DeviceInfo 7 WFConnection (LocalRemote Secondary Unknown)
276
        (LocalRemote UpToDate DUnknown) 'C' "r---"
277
        (PerformanceIndicators 0 0 0 0 0 0 0 0 0 0 Nothing Nothing Nothing)
278
        Nothing
279
        (Just $ AdditionalInfo 0 61 0 0 0 0 0)
280
        (Just $ AdditionalInfo 0 257 0 0 0 0 0),
281
      DeviceInfo 8 StandAlone (LocalRemote Secondary Unknown)
282
        (LocalRemote UpToDate DUnknown) ' ' "r---"
283
        (PerformanceIndicators 0 0 0 0 0 0 0 0 0 0 Nothing Nothing Nothing)
284
        Nothing
285
        (Just $ AdditionalInfo 0 61 0 0 0 0 0)
286
        (Just $ AdditionalInfo 0 257 0 0 0 0 0)
287
    ]
288

  
289
-- | Function for testing whether a comma-separated integer is parsed correctly.
290
testCommaInt :: String -> Int -> Assertion
291
testCommaInt numString expectedResult =
292
  case A.parseOnly commaIntParser $ pack numString of
293
    Left msg -> assertFailure $ "Parsing failed: " ++ msg
294
    Right obtained -> assertEqual numString expectedResult obtained
295

  
296
-- | Test if 1 digit integers are recognized correctly.
297
case_commaInt_1digit :: Assertion
298
case_commaInt_1digit = testCommaInt "1" 1
299

  
300
-- | Test if 3 digits integers are recognized correctly.
301
case_commaInt_3digits :: Assertion
302
case_commaInt_3digits = testCommaInt "123" 123
303

  
304
-- | Test if integers with 1 comma are recognized correctly.
305
case_commaInt_1comma :: Assertion
306
case_commaInt_1comma = testCommaInt "61,736" 61736
307

  
308
-- | Test if integers with 2 commas are recognized correctly.
309
case_commaInt_2commas :: Assertion
310
case_commaInt_2commas = testCommaInt "61,736,123" 61736123
311

  
312
-- | Test if non-triplets are handled correctly (they are assumed NOT being part
313
-- of the number).
314
case_commaInt_non_triplet :: Assertion
315
case_commaInt_non_triplet = testCommaInt "61,736,12" 61736
316

  
317

  
318
testSuite "Block_DRBDParser"
319
          [ 'case_drbd80_emptyline,
320
            'case_drbd83_sync_krnl2_6_39,
321
            'case_drbd83_sync,
322
            'case_drbd83_sync_want,
323
            'case_drbd83,
324
            'case_drbd8,
325
            'case_commaInt_1digit,
326
            'case_commaInt_3digits,
327
            'case_commaInt_1comma,
328
            'case_commaInt_2commas,
329
            'case_commaInt_non_triplet
330
          ]
b/htest/test.hs
32 32
import Test.Ganeti.TestImports ()
33 33
import Test.Ganeti.Attoparsec
34 34
import Test.Ganeti.BasicTypes
35
import Test.Ganeti.Block.Drbd.Parser
35 36
import Test.Ganeti.Common
36 37
import Test.Ganeti.Confd.Utils
37 38
import Test.Ganeti.Daemon
......
80 81
  , testCommon
81 82
  , testConfd_Utils
82 83
  , testDaemon
84
  , testBlock_DRBDParser
83 85
  , testErrors
84 86
  , testHTools_Backend_Simu
85 87
  , testHTools_Backend_Text
b/test/data/proc_drbd83_sync_want.txt
1
version: 8.3.11 (api:88/proto:86-96)
2
srcversion: 2D876214BAAD53B31ADC1D6
3
 0: cs:SyncTarget ro:Secondary/Primary ds:Inconsistent/UpToDate C r-----
4
    ns:0 nr:460288 dw:460160 dr:0 al:0 bm:28 lo:2 pe:4 ua:1 ap:0 ep:1 wo:f oos:588416 
5
        [=======>............] sync'ed: 44.4% (588416/1048576)K
6
        finish: 0:00:08 speed: 65,736 (65,736) want: 61,440 K/sec
7
 1: cs:Unconfigured
8
 2: cs:Unconfigured
9
 3: cs:Unconfigured

Also available in: Unified diff