a59a77c55ed5ec5851a213590c49abb28180095a
[ganeti-local] / 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_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 <- readPythonTestData 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 Nothing Nothing Nothing 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         (PerformanceIndicators 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       UnconfiguredDevice 1,
67       UnconfiguredDevice 2,
68       UnconfiguredDevice 5,
69       UnconfiguredDevice 6
70     ]
71
72 -- | Test a DRBD 8.3 file with a NULL caracter inside.
73 case_drbd83_sync_krnl2_6_39 :: Assertion
74 case_drbd83_sync_krnl2_6_39 = testFile "proc_drbd83_sync_krnl2.6.39.txt" $
75   DRBDStatus
76     ( VersionInfo (Just "8.3.1") (Just "88") (Just "86-89") Nothing
77         (Just "fd40f4a8f9104941537d1afc8521e584a6d3003c")
78         (Just "phil@fat-tyre, 2009-03-27 12:19:49")
79     )
80     [ DeviceInfo 0 Connected (LocalRemote Primary Secondary)
81         (LocalRemote UpToDate UpToDate) 'C' "r----"
82         (PerformanceIndicators 140978 0 9906 131533 27 8 0 0 0 0 (Just 1)
83           (Just 'b') (Just 0))
84         Nothing
85         Nothing
86         Nothing,
87       DeviceInfo 1 Connected (LocalRemote Secondary Primary)
88         (LocalRemote UpToDate UpToDate) 'C' "r---"
89         (PerformanceIndicators 0 140980 140980 0 0 8 0 0 0 0 (Just 1) (Just 'f')
90           (Just 0))
91         Nothing
92         Nothing
93         Nothing,
94       UnconfiguredDevice 2,
95       DeviceInfo 3 SyncSource (LocalRemote Primary Secondary)
96         (LocalRemote UpToDate Inconsistent) 'A' "r-----"
97         (PerformanceIndicators 373888 0 0 374088 0 22 7 27 7 0 (Just 1)
98           (Just 'f') (Just 15358208))
99         (Just $ SyncStatus 2.4 14996 15360 MegaByte (Time 0 4 8) 61736 Nothing
100           KiloByte Second)
101         Nothing
102         Nothing,
103       DeviceInfo 4 WFConnection (LocalRemote Primary Unknown)
104         (LocalRemote UpToDate DUnknown) 'C' "r----"
105         (PerformanceIndicators 140978 0 9906 131534 27 8 0 0 0 0 (Just 1)
106           (Just 'b') (Just 0))
107         Nothing
108         Nothing
109         Nothing
110     ]
111
112 -- | Test a DRBD 8.3 file with an ongoing synchronization.
113 case_drbd83_sync :: Assertion
114 case_drbd83_sync = testFile "proc_drbd83_sync.txt" $
115   DRBDStatus
116     ( VersionInfo (Just "8.3.1") (Just "88") (Just "86-89") Nothing
117         (Just "fd40f4a8f9104941537d1afc8521e584a6d3003c")
118         (Just "phil@fat-tyre, 2009-03-27 12:19:49")
119     )
120     [ DeviceInfo 0 Connected (LocalRemote Primary Secondary)
121         (LocalRemote UpToDate UpToDate) 'C' "r----"
122         (PerformanceIndicators 140978 0 9906 131533 27 8 0 0 0 0 (Just 1)
123           (Just 'b') (Just 0))
124         Nothing
125         Nothing
126         Nothing,
127       DeviceInfo 1 Connected (LocalRemote Secondary Primary)
128         (LocalRemote UpToDate UpToDate) 'C' "r---"
129         (PerformanceIndicators 0 140980 140980 0 0 8 0 0 0 0 (Just 1) (Just 'f')
130           (Just 0))
131         Nothing
132         Nothing
133         Nothing,
134       UnconfiguredDevice 2,
135       DeviceInfo 3 SyncTarget (LocalRemote Primary Secondary)
136         (LocalRemote Inconsistent UpToDate) 'C' "r----"
137         (PerformanceIndicators 0 178176 178176 0 104 42 0 0 0 0 (Just 1)
138           (Just 'b') (Just 346112))
139         (Just $ SyncStatus 34.9 346112 524288 MegaByte (Time 0 0 5) 59392
140           Nothing KiloByte Second)
141         Nothing
142         Nothing,
143       DeviceInfo 4 WFConnection (LocalRemote Primary Unknown)
144         (LocalRemote UpToDate DUnknown) 'C' "r----"
145         (PerformanceIndicators 140978 0 9906 131534 27 8 0 0 0 0 (Just 1)
146           (Just 'b') (Just 0))
147         Nothing
148         Nothing
149         Nothing
150     ]
151
152 -- | Test a DRBD 8.3 file not from git sources, with an ongoing synchronization
153 -- and the "want" field
154 case_drbd83_sync_want :: Assertion
155 case_drbd83_sync_want = testFile "proc_drbd83_sync_want.txt" $
156   DRBDStatus
157     ( VersionInfo (Just "8.3.11") (Just "88") (Just "86-96")
158         (Just "2D876214BAAD53B31ADC1D6")
159         Nothing Nothing
160     )
161     [ DeviceInfo 0 SyncTarget (LocalRemote Secondary Primary)
162         (LocalRemote Inconsistent UpToDate) 'C' "r-----"
163         (PerformanceIndicators 0 460288 460160 0 0 28 2 4 1 0 (Just 1)
164           (Just 'f') (Just 588416))
165         (Just $ SyncStatus 44.4 588416 1048576 KiloByte (Time 0 0 8) 65736
166           (Just 61440) KiloByte Second)
167         Nothing
168         Nothing,
169       UnconfiguredDevice 1,
170       UnconfiguredDevice 2,
171       UnconfiguredDevice 3
172     ]
173
174 -- | Test a DRBD 8.3 file.
175 case_drbd83 :: Assertion
176 case_drbd83 = testFile "proc_drbd83.txt" $
177   DRBDStatus
178     ( VersionInfo (Just "8.3.1") (Just "88") (Just "86-89")
179       Nothing
180       (Just "fd40f4a8f9104941537d1afc8521e584a6d3003c")
181       (Just "phil@fat-tyre, 2009-03-27 12:19:49")
182     )
183     [ DeviceInfo 0 Connected (LocalRemote Primary Secondary)
184         (LocalRemote UpToDate UpToDate) 'C' "r----"
185         (PerformanceIndicators 140978 0 9906 131533 27 8 0 0 0 0 (Just 1)
186           (Just 'b') (Just 0))
187         Nothing
188         Nothing
189         Nothing,
190       DeviceInfo 1 Connected (LocalRemote Secondary Primary)
191         (LocalRemote UpToDate UpToDate) 'C' "r---"
192         (PerformanceIndicators 0 140980 140980 0 0 8 0 0 0 0 (Just 1) (Just 'f')
193           (Just 0))
194         Nothing
195         Nothing
196         Nothing,
197       UnconfiguredDevice 2,
198       DeviceInfo 4 WFConnection (LocalRemote Primary Unknown)
199         (LocalRemote UpToDate DUnknown) 'C' "r----"
200         (PerformanceIndicators 140978 0 9906 131534 27 8 0 0 0 0 (Just 1)
201           (Just 'b') (Just 0))
202         Nothing
203         Nothing
204         Nothing,
205       DeviceInfo 5 Connected (LocalRemote Primary Secondary)
206         (LocalRemote UpToDate Diskless) 'C' "r----"
207         (PerformanceIndicators 140978 0 9906 131533 19 8 0 0 0 0 (Just 1)
208           (Just 'b') (Just 0))
209         Nothing
210         Nothing
211         Nothing,
212       DeviceInfo 6 Connected (LocalRemote Secondary Primary)
213         (LocalRemote Diskless UpToDate) 'C' "r---"
214         (PerformanceIndicators 0 140978 140978 0 0 8 0 0 0 0 (Just 1) (Just 'f')
215           (Just 0))
216         Nothing
217         Nothing
218         Nothing,
219       DeviceInfo 7 WFConnection (LocalRemote Secondary Unknown)
220         (LocalRemote UpToDate DUnknown) 'C' "r---"
221         (PerformanceIndicators 0 140978 140978 0 0 8 0 0 0 0 (Just 1) (Just 'f')
222           (Just 0))
223         Nothing
224         Nothing
225         Nothing,
226       DeviceInfo 8 StandAlone (LocalRemote Secondary Unknown)
227         (LocalRemote UpToDate DUnknown) ' ' "r---"
228         (PerformanceIndicators 0 140978 140978 0 0 8 0 0 0 0 (Just 1)
229           (Just 'f') (Just 0))
230         Nothing
231         Nothing
232         Nothing
233     ]
234
235 -- | Test a DRBD 8.0 file with a missing device.
236 case_drbd8 :: Assertion
237 case_drbd8 = testFile "proc_drbd8.txt" $
238   DRBDStatus
239     ( VersionInfo (Just "8.0.12") (Just "86") (Just "86") Nothing
240         (Just "5c9f89594553e32adb87d9638dce591782f947e3")
241         (Just "XXX")
242     )
243     [ DeviceInfo 0 Connected (LocalRemote Primary Secondary)
244         (LocalRemote UpToDate UpToDate) 'C' "r---"
245         (PerformanceIndicators 4375577 0 4446279 674 1067 69 0 0 0 0 Nothing
246           Nothing Nothing)
247         Nothing
248         (Just $ AdditionalInfo 0 61 0 0 0 0 0)
249         (Just $ AdditionalInfo 0 257 793749 1067 0 0 1067),
250       DeviceInfo 1 Connected (LocalRemote Secondary Primary)
251         (LocalRemote UpToDate UpToDate) 'C' "r---"
252         (PerformanceIndicators 738320 0 738320 554400 67 0 0 0 0 0 Nothing
253           Nothing Nothing)
254         Nothing
255         (Just $ AdditionalInfo 0 61 0 0 0 0 0)
256         (Just $ AdditionalInfo 0 257 92464 67 0 0 67),
257       UnconfiguredDevice 2,
258       DeviceInfo 4 WFConnection (LocalRemote Primary Unknown)
259         (LocalRemote UpToDate DUnknown) 'C' "r---"
260         (PerformanceIndicators 738320 0 738320 554400 67 0 0 0 0 0 Nothing
261           Nothing Nothing)
262         Nothing
263         (Just $ AdditionalInfo 0 61 0 0 0 0 0)
264         (Just $ AdditionalInfo 0 257 92464 67 0 0 67),
265       DeviceInfo 5 Connected (LocalRemote Primary Secondary)
266         (LocalRemote UpToDate Diskless) 'C' "r---"
267         (PerformanceIndicators 4375581 0 4446283 674 1069 69 0 0 0 0 Nothing
268           Nothing Nothing)
269         Nothing
270         (Just $ AdditionalInfo 0 61 0 0 0 0 0)
271         (Just $ AdditionalInfo 0 257 793750 1069 0 0 1069),
272       DeviceInfo 6 Connected (LocalRemote Secondary Primary)
273         (LocalRemote Diskless UpToDate) 'C'  "r---"
274         (PerformanceIndicators 0 4375581 5186925 327 75 214 0 0 0 0 Nothing
275           Nothing Nothing)
276         Nothing
277         Nothing
278         Nothing,
279       DeviceInfo 7 WFConnection (LocalRemote Secondary Unknown)
280         (LocalRemote UpToDate DUnknown) 'C' "r---"
281         (PerformanceIndicators 0 0 0 0 0 0 0 0 0 0 Nothing Nothing Nothing)
282         Nothing
283         (Just $ AdditionalInfo 0 61 0 0 0 0 0)
284         (Just $ AdditionalInfo 0 257 0 0 0 0 0),
285       DeviceInfo 8 StandAlone (LocalRemote Secondary Unknown)
286         (LocalRemote UpToDate DUnknown) ' ' "r---"
287         (PerformanceIndicators 0 0 0 0 0 0 0 0 0 0 Nothing Nothing Nothing)
288         Nothing
289         (Just $ AdditionalInfo 0 61 0 0 0 0 0)
290         (Just $ AdditionalInfo 0 257 0 0 0 0 0)
291     ]
292
293 -- | Function for splitting a list in chunks of a given size.
294 -- FIXME: an equivalent function exists in Data.List.Split, but it seems
295 -- pointless to add this package as a dependence just for this single
296 -- use. In case it is ever added, just remove this function definition
297 -- and use the one from the package.
298 splitEvery :: Int -> [e] -> [[e]]
299 splitEvery i l = map (take i) (splitter l (:) []) where
300   splitter [] _ n = n
301   splitter li c n  = li `c` splitter (drop i li) c n
302
303 -- | Function for testing whether a single comma-separated integer is
304 -- parsed correctly.
305 testCommaInt :: String -> Int -> Assertion
306 testCommaInt numString expectedResult =
307   case A.parseOnly commaIntParser $ pack numString of
308     Left msg -> assertFailure $ "Parsing failed: " ++ msg
309     Right obtained -> assertEqual numString expectedResult obtained
310
311 -- | Generate a property test for CommaInt numbers in a given range.
312 gen_prop_CommaInt :: Int -> Int -> Property
313 gen_prop_CommaInt minVal maxVal =
314   forAll (choose (minVal, maxVal)) $ \i ->
315     case A.parseOnly commaIntParser $ pack (generateCommaInt i) of
316       Left msg -> failTest $ "Parsing failed: " ++ msg
317       Right obtained -> i ==? obtained
318   where generateCommaInt x =
319           ((reverse . intercalate ",") . splitEvery 3) . reverse $ show x
320
321 -- | Test if <4 digit integers are recognized correctly.
322 prop_commaInt_noCommas :: Property
323 prop_commaInt_noCommas = gen_prop_CommaInt 0 999
324
325 -- | Test if integers with 1 comma are recognized correctly.
326 prop_commaInt_1Comma :: Property
327 prop_commaInt_1Comma = gen_prop_CommaInt 1000 999999
328
329 -- | Test if integers with multiple commas are recognized correctly.
330 prop_commaInt_multipleCommas :: Property
331 prop_commaInt_multipleCommas = gen_prop_CommaInt 1000000 (maxBound ::
332   Int)
333
334 -- | Test whether the parser is actually able to behave as intended with
335 -- numbers without commas. That is, if a number with more than 3 digits
336 -- is parsed, only up to the first 3 digits are considered (because they
337 -- are a valid commaInt), and the rest is ignored.
338 -- e.g.: parse "1234" = 123
339 prop_commaInt_max3WithoutComma :: Property
340 prop_commaInt_max3WithoutComma =
341   forAll (choose (0, maxBound :: Int)) $ \i ->
342     case A.parseOnly commaIntParser $ pack (show i) of
343       Left msg -> failTest $ "Parsing failed: " ++ msg
344       Right obtained ->
345         obtained < 1000 .&&.
346         getFirst3Digits i ==? obtained
347   where getFirst3Digits x =
348           if x >= 1000
349             then getFirst3Digits $ x `div` 10
350             else x
351
352 -- | Test if non-triplets are handled correctly (they are assumed NOT being part
353 -- of the number).
354 case_commaInt_non_triplet :: Assertion
355 case_commaInt_non_triplet = testCommaInt "61,736,12" 61736
356
357
358 testSuite "Block/Drbd/Parser"
359           [ 'case_drbd80_emptyline,
360             'case_drbd83_sync_krnl2_6_39,
361             'case_drbd83_sync,
362             'case_drbd83_sync_want,
363             'case_drbd83,
364             'case_drbd8,
365             'case_commaInt_non_triplet,
366             'prop_commaInt_noCommas,
367             'prop_commaInt_1Comma,
368             'prop_commaInt_multipleCommas,
369             'prop_commaInt_max3WithoutComma
370           ]