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