Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / Block / Drbd / Parser.hs @ 105266b2

History | View | Annotate | Download (17.5 kB)

1 a52f8e72 Michele Tartara
{-# LANGUAGE TemplateHaskell #-}
2 a52f8e72 Michele Tartara
3 a7e0c9b0 Michele Tartara
{-| Unittests for the DRBD Parser -}
4 a52f8e72 Michele Tartara
5 a52f8e72 Michele Tartara
{-
6 a52f8e72 Michele Tartara
7 a52f8e72 Michele Tartara
Copyright (C) 2012 Google Inc.
8 a52f8e72 Michele Tartara
9 a52f8e72 Michele Tartara
This program is free software; you can redistribute it and/or modify
10 a52f8e72 Michele Tartara
it under the terms of the GNU General Public License as published by
11 a52f8e72 Michele Tartara
the Free Software Foundation; either version 2 of the License, or
12 a52f8e72 Michele Tartara
(at your option) any later version.
13 a52f8e72 Michele Tartara
14 a52f8e72 Michele Tartara
This program is distributed in the hope that it will be useful, but
15 a52f8e72 Michele Tartara
WITHOUT ANY WARRANTY; without even the implied warranty of
16 a52f8e72 Michele Tartara
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17 a52f8e72 Michele Tartara
General Public License for more details.
18 a52f8e72 Michele Tartara
19 a52f8e72 Michele Tartara
You should have received a copy of the GNU General Public License
20 a52f8e72 Michele Tartara
along with this program; if not, write to the Free Software
21 a52f8e72 Michele Tartara
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22 a52f8e72 Michele Tartara
02110-1301, USA.
23 a52f8e72 Michele Tartara
24 a52f8e72 Michele Tartara
-}
25 a52f8e72 Michele Tartara
26 fd80be11 Michele Tartara
module Test.Ganeti.Block.Drbd.Parser (testBlock_Drbd_Parser) where
27 a52f8e72 Michele Tartara
28 18837cd8 Michele Tartara
import Test.QuickCheck as QuickCheck hiding (Result)
29 a52f8e72 Michele Tartara
import Test.HUnit
30 a52f8e72 Michele Tartara
31 a52f8e72 Michele Tartara
import Test.Ganeti.TestHelper
32 18837cd8 Michele Tartara
import Test.Ganeti.TestCommon
33 a52f8e72 Michele Tartara
34 a52f8e72 Michele Tartara
import qualified Data.Attoparsec.Text as A
35 18837cd8 Michele Tartara
import Data.List (intercalate)
36 a52f8e72 Michele Tartara
import Data.Text (pack)
37 a52f8e72 Michele Tartara
38 a52f8e72 Michele Tartara
import Ganeti.Block.Drbd.Parser (drbdStatusParser, commaIntParser)
39 a52f8e72 Michele Tartara
import Ganeti.Block.Drbd.Types
40 a52f8e72 Michele Tartara
41 39573352 Iustin Pop
{-# ANN module "HLint: ignore Use camelCase" #-}
42 39573352 Iustin Pop
43 a52f8e72 Michele Tartara
-- | Test a DRBD 8.0 file with an empty line inside.
44 a52f8e72 Michele Tartara
case_drbd80_emptyline :: Assertion
45 105266b2 Michele Tartara
case_drbd80_emptyline = testParser (drbdStatusParser [])
46 105266b2 Michele Tartara
  "proc_drbd80-emptyline.txt" $ DRBDStatus
47 2fe690f1 Thomas Thrainer
    ( VersionInfo (Just "8.0.12") (Just "86") (Just "86") Nothing
48 a52f8e72 Michele Tartara
        (Just "5c9f89594553e32adb87d9638dce591782f947e3")
49 a52f8e72 Michele Tartara
        (Just "root@node1.example.com, 2009-05-22 12:47:52")
50 a52f8e72 Michele Tartara
    )
51 a52f8e72 Michele Tartara
    [ DeviceInfo 0 Connected (LocalRemote Primary Secondary)
52 a52f8e72 Michele Tartara
        (LocalRemote UpToDate UpToDate) 'C' "r---"
53 2188740e Michele Tartara
        (PerfIndicators 78728316 0 77675644 1277039 254 270 0 0 0 0
54 a52f8e72 Michele Tartara
          Nothing Nothing Nothing)
55 a52f8e72 Michele Tartara
        Nothing
56 a52f8e72 Michele Tartara
        (Just $ AdditionalInfo 0 61 65657 135 0 0 135)
57 eb62691c Michele Tartara
        (Just $ AdditionalInfo 0 257 11378843 254 0 0 254)
58 eb62691c Michele Tartara
        Nothing,
59 a52f8e72 Michele Tartara
      UnconfiguredDevice 1,
60 a52f8e72 Michele Tartara
      UnconfiguredDevice 2,
61 a52f8e72 Michele Tartara
      UnconfiguredDevice 5,
62 a52f8e72 Michele Tartara
      UnconfiguredDevice 6
63 a52f8e72 Michele Tartara
    ]
64 a52f8e72 Michele Tartara
65 d41efc42 Thomas Thrainer
-- | Test a DRBD 8.0 file with an empty version.
66 d41efc42 Thomas Thrainer
case_drbd80_emptyversion :: Assertion
67 105266b2 Michele Tartara
case_drbd80_emptyversion = testParser (drbdStatusParser [])
68 105266b2 Michele Tartara
  "proc_drbd80-emptyversion.txt" $ DRBDStatus
69 d41efc42 Thomas Thrainer
    ( VersionInfo Nothing Nothing Nothing Nothing
70 d41efc42 Thomas Thrainer
        (Just "5c9f89594553e32adb87d9638dce591782f947e3")
71 d41efc42 Thomas Thrainer
        (Just "root@node1.example.com, 2009-05-22 12:47:52")
72 d41efc42 Thomas Thrainer
    )
73 d41efc42 Thomas Thrainer
    [ DeviceInfo 0 Connected (LocalRemote Primary Secondary)
74 d41efc42 Thomas Thrainer
        (LocalRemote UpToDate UpToDate) 'C' "r---"
75 d41efc42 Thomas Thrainer
        (PerfIndicators 78728316 0 77675644 1277039 254 270 0 0 0 0
76 d41efc42 Thomas Thrainer
          Nothing Nothing Nothing)
77 d41efc42 Thomas Thrainer
        Nothing
78 d41efc42 Thomas Thrainer
        (Just $ AdditionalInfo 0 61 65657 135 0 0 135)
79 d41efc42 Thomas Thrainer
        (Just $ AdditionalInfo 0 257 11378843 254 0 0 254)
80 d41efc42 Thomas Thrainer
        Nothing,
81 d41efc42 Thomas Thrainer
      UnconfiguredDevice 1,
82 d41efc42 Thomas Thrainer
      UnconfiguredDevice 2,
83 d41efc42 Thomas Thrainer
      UnconfiguredDevice 5,
84 d41efc42 Thomas Thrainer
      UnconfiguredDevice 6
85 d41efc42 Thomas Thrainer
    ]
86 d41efc42 Thomas Thrainer
87 efa6dd08 Thomas Thrainer
-- | Test a DRBD 8.4 file with an ongoing synchronization.
88 efa6dd08 Thomas Thrainer
case_drbd84_sync :: Assertion
89 105266b2 Michele Tartara
case_drbd84_sync = testParser (drbdStatusParser []) "proc_drbd84_sync.txt" $
90 efa6dd08 Thomas Thrainer
  DRBDStatus
91 efa6dd08 Thomas Thrainer
    ( VersionInfo (Just "8.4.2") (Just "1") (Just "86-101") Nothing
92 efa6dd08 Thomas Thrainer
        (Just "7ad5f850d711223713d6dcadc3dd48860321070c")
93 efa6dd08 Thomas Thrainer
        (Just "root@example.com, 2013-04-10 07:45:25")
94 efa6dd08 Thomas Thrainer
    )
95 efa6dd08 Thomas Thrainer
    [ DeviceInfo 0 StandAlone (LocalRemote Primary Unknown)
96 efa6dd08 Thomas Thrainer
        (LocalRemote UpToDate DUnknown) ' ' "r-----"
97 efa6dd08 Thomas Thrainer
        (PerfIndicators 0 0 33318 730 15 0 0 0 0 0 (Just 1)
98 efa6dd08 Thomas Thrainer
          (Just 'd') (Just 1048320))
99 efa6dd08 Thomas Thrainer
        Nothing
100 efa6dd08 Thomas Thrainer
        Nothing
101 efa6dd08 Thomas Thrainer
        Nothing
102 efa6dd08 Thomas Thrainer
        Nothing,
103 efa6dd08 Thomas Thrainer
      UnconfiguredDevice 3,
104 efa6dd08 Thomas Thrainer
      DeviceInfo 5 SyncSource (LocalRemote Secondary Secondary)
105 efa6dd08 Thomas Thrainer
        (LocalRemote UpToDate Inconsistent) 'C' "r---n-"
106 efa6dd08 Thomas Thrainer
        (PerfIndicators 716992 0 0 719432 0 43 0 33 18 0 (Just 1)
107 efa6dd08 Thomas Thrainer
          (Just 'f') (Just 335744))
108 efa6dd08 Thomas Thrainer
        (Just $ SyncStatus 68.5 335744 1048576 KiloByte (Time 0 0 5) 64800
109 efa6dd08 Thomas Thrainer
          Nothing KiloByte Second)
110 efa6dd08 Thomas Thrainer
        Nothing
111 efa6dd08 Thomas Thrainer
        Nothing
112 efa6dd08 Thomas Thrainer
        Nothing
113 efa6dd08 Thomas Thrainer
    ]
114 efa6dd08 Thomas Thrainer
115 efa6dd08 Thomas Thrainer
-- | Test a DRBD 8.4 file.
116 efa6dd08 Thomas Thrainer
case_drbd84 :: Assertion
117 105266b2 Michele Tartara
case_drbd84 = testParser (drbdStatusParser []) "proc_drbd84.txt" $
118 efa6dd08 Thomas Thrainer
  DRBDStatus
119 efa6dd08 Thomas Thrainer
    ( VersionInfo (Just "8.4.2") (Just "1") (Just "86-101") Nothing
120 efa6dd08 Thomas Thrainer
      (Just "7ad5f850d711223713d6dcadc3dd48860321070c")
121 efa6dd08 Thomas Thrainer
      (Just "root@example.com, 2013-04-10 07:45:25")
122 efa6dd08 Thomas Thrainer
    )
123 efa6dd08 Thomas Thrainer
    [ DeviceInfo 0 Connected (LocalRemote Primary Secondary)
124 efa6dd08 Thomas Thrainer
        (LocalRemote UpToDate UpToDate) 'C' "r-----"
125 efa6dd08 Thomas Thrainer
        (PerfIndicators 1048576 0 0 1048776 0 64 0 0 0 0 (Just 1)
126 efa6dd08 Thomas Thrainer
          (Just 'f') (Just 0))
127 efa6dd08 Thomas Thrainer
        Nothing
128 efa6dd08 Thomas Thrainer
        Nothing
129 efa6dd08 Thomas Thrainer
        Nothing
130 efa6dd08 Thomas Thrainer
        Nothing,
131 efa6dd08 Thomas Thrainer
      DeviceInfo 1 Connected (LocalRemote Secondary Primary)
132 efa6dd08 Thomas Thrainer
        (LocalRemote UpToDate UpToDate) 'C' "r-----"
133 efa6dd08 Thomas Thrainer
        (PerfIndicators 0 1048576 1048576 0 0 64 0 0 0 0 (Just 1)
134 efa6dd08 Thomas Thrainer
          (Just 'f') (Just 0))
135 efa6dd08 Thomas Thrainer
        Nothing
136 efa6dd08 Thomas Thrainer
        Nothing
137 efa6dd08 Thomas Thrainer
        Nothing
138 efa6dd08 Thomas Thrainer
        Nothing,
139 efa6dd08 Thomas Thrainer
      UnconfiguredDevice 2,
140 efa6dd08 Thomas Thrainer
      DeviceInfo 4 WFConnection (LocalRemote Primary Unknown)
141 efa6dd08 Thomas Thrainer
        (LocalRemote UpToDate DUnknown) 'C' "r-----"
142 efa6dd08 Thomas Thrainer
        (PerfIndicators 0 0 0 200 0 0 0 0 0 0 (Just 1)
143 efa6dd08 Thomas Thrainer
          (Just 'f') (Just 1048320))
144 efa6dd08 Thomas Thrainer
        Nothing
145 efa6dd08 Thomas Thrainer
        Nothing
146 efa6dd08 Thomas Thrainer
        Nothing
147 efa6dd08 Thomas Thrainer
        Nothing,
148 efa6dd08 Thomas Thrainer
      DeviceInfo 6 Connected (LocalRemote Secondary Primary)
149 efa6dd08 Thomas Thrainer
        (LocalRemote Diskless UpToDate) 'C' "r-----"
150 efa6dd08 Thomas Thrainer
        (PerfIndicators 0 0 0 0 0 0 0 0 0 0 (Just 1) (Just 'b')
151 efa6dd08 Thomas Thrainer
          (Just 0))
152 efa6dd08 Thomas Thrainer
        Nothing
153 efa6dd08 Thomas Thrainer
        Nothing
154 efa6dd08 Thomas Thrainer
        Nothing
155 efa6dd08 Thomas Thrainer
        Nothing,
156 efa6dd08 Thomas Thrainer
      DeviceInfo 8 StandAlone (LocalRemote Secondary Unknown)
157 efa6dd08 Thomas Thrainer
        (LocalRemote UpToDate DUnknown) ' ' "r-----"
158 efa6dd08 Thomas Thrainer
        (PerfIndicators 0 0 0 200 0 0 0 0 0 0 (Just 1)
159 efa6dd08 Thomas Thrainer
          (Just 'f') (Just 1048320))
160 efa6dd08 Thomas Thrainer
        Nothing
161 efa6dd08 Thomas Thrainer
        Nothing
162 efa6dd08 Thomas Thrainer
        Nothing
163 efa6dd08 Thomas Thrainer
        Nothing
164 efa6dd08 Thomas Thrainer
    ]
165 efa6dd08 Thomas Thrainer
166 a52f8e72 Michele Tartara
-- | Test a DRBD 8.3 file with a NULL caracter inside.
167 a52f8e72 Michele Tartara
case_drbd83_sync_krnl2_6_39 :: Assertion
168 105266b2 Michele Tartara
case_drbd83_sync_krnl2_6_39 = testParser (drbdStatusParser [])
169 105266b2 Michele Tartara
  "proc_drbd83_sync_krnl2.6.39.txt" $ DRBDStatus
170 a52f8e72 Michele Tartara
    ( VersionInfo (Just "8.3.1") (Just "88") (Just "86-89") Nothing
171 a52f8e72 Michele Tartara
        (Just "fd40f4a8f9104941537d1afc8521e584a6d3003c")
172 a52f8e72 Michele Tartara
        (Just "phil@fat-tyre, 2009-03-27 12:19:49")
173 a52f8e72 Michele Tartara
    )
174 a52f8e72 Michele Tartara
    [ DeviceInfo 0 Connected (LocalRemote Primary Secondary)
175 a52f8e72 Michele Tartara
        (LocalRemote UpToDate UpToDate) 'C' "r----"
176 2188740e Michele Tartara
        (PerfIndicators 140978 0 9906 131533 27 8 0 0 0 0 (Just 1)
177 a52f8e72 Michele Tartara
          (Just 'b') (Just 0))
178 a52f8e72 Michele Tartara
        Nothing
179 a52f8e72 Michele Tartara
        Nothing
180 eb62691c Michele Tartara
        Nothing
181 a52f8e72 Michele Tartara
        Nothing,
182 a52f8e72 Michele Tartara
      DeviceInfo 1 Connected (LocalRemote Secondary Primary)
183 a52f8e72 Michele Tartara
        (LocalRemote UpToDate UpToDate) 'C' "r---"
184 2188740e Michele Tartara
        (PerfIndicators 0 140980 140980 0 0 8 0 0 0 0 (Just 1) (Just 'f')
185 a52f8e72 Michele Tartara
          (Just 0))
186 a52f8e72 Michele Tartara
        Nothing
187 a52f8e72 Michele Tartara
        Nothing
188 eb62691c Michele Tartara
        Nothing
189 a52f8e72 Michele Tartara
        Nothing,
190 a52f8e72 Michele Tartara
      UnconfiguredDevice 2,
191 a52f8e72 Michele Tartara
      DeviceInfo 3 SyncSource (LocalRemote Primary Secondary)
192 a52f8e72 Michele Tartara
        (LocalRemote UpToDate Inconsistent) 'A' "r-----"
193 2188740e Michele Tartara
        (PerfIndicators 373888 0 0 374088 0 22 7 27 7 0 (Just 1)
194 a52f8e72 Michele Tartara
          (Just 'f') (Just 15358208))
195 a52f8e72 Michele Tartara
        (Just $ SyncStatus 2.4 14996 15360 MegaByte (Time 0 4 8) 61736 Nothing
196 a52f8e72 Michele Tartara
          KiloByte Second)
197 a52f8e72 Michele Tartara
        Nothing
198 eb62691c Michele Tartara
        Nothing
199 a52f8e72 Michele Tartara
        Nothing,
200 a52f8e72 Michele Tartara
      DeviceInfo 4 WFConnection (LocalRemote Primary Unknown)
201 a52f8e72 Michele Tartara
        (LocalRemote UpToDate DUnknown) 'C' "r----"
202 2188740e Michele Tartara
        (PerfIndicators 140978 0 9906 131534 27 8 0 0 0 0 (Just 1)
203 a52f8e72 Michele Tartara
          (Just 'b') (Just 0))
204 a52f8e72 Michele Tartara
        Nothing
205 a52f8e72 Michele Tartara
        Nothing
206 a52f8e72 Michele Tartara
        Nothing
207 eb62691c Michele Tartara
        Nothing
208 a52f8e72 Michele Tartara
    ]
209 a52f8e72 Michele Tartara
210 a52f8e72 Michele Tartara
-- | Test a DRBD 8.3 file with an ongoing synchronization.
211 a52f8e72 Michele Tartara
case_drbd83_sync :: Assertion
212 105266b2 Michele Tartara
case_drbd83_sync = testParser (drbdStatusParser []) "proc_drbd83_sync.txt" $
213 a52f8e72 Michele Tartara
  DRBDStatus
214 a52f8e72 Michele Tartara
    ( VersionInfo (Just "8.3.1") (Just "88") (Just "86-89") Nothing
215 a52f8e72 Michele Tartara
        (Just "fd40f4a8f9104941537d1afc8521e584a6d3003c")
216 a52f8e72 Michele Tartara
        (Just "phil@fat-tyre, 2009-03-27 12:19:49")
217 a52f8e72 Michele Tartara
    )
218 a52f8e72 Michele Tartara
    [ DeviceInfo 0 Connected (LocalRemote Primary Secondary)
219 a52f8e72 Michele Tartara
        (LocalRemote UpToDate UpToDate) 'C' "r----"
220 2188740e Michele Tartara
        (PerfIndicators 140978 0 9906 131533 27 8 0 0 0 0 (Just 1)
221 a52f8e72 Michele Tartara
          (Just 'b') (Just 0))
222 a52f8e72 Michele Tartara
        Nothing
223 a52f8e72 Michele Tartara
        Nothing
224 eb62691c Michele Tartara
        Nothing
225 a52f8e72 Michele Tartara
        Nothing,
226 a52f8e72 Michele Tartara
      DeviceInfo 1 Connected (LocalRemote Secondary Primary)
227 a52f8e72 Michele Tartara
        (LocalRemote UpToDate UpToDate) 'C' "r---"
228 2188740e Michele Tartara
        (PerfIndicators 0 140980 140980 0 0 8 0 0 0 0 (Just 1) (Just 'f')
229 a52f8e72 Michele Tartara
          (Just 0))
230 a52f8e72 Michele Tartara
        Nothing
231 a52f8e72 Michele Tartara
        Nothing
232 eb62691c Michele Tartara
        Nothing
233 a52f8e72 Michele Tartara
        Nothing,
234 a52f8e72 Michele Tartara
      UnconfiguredDevice 2,
235 a52f8e72 Michele Tartara
      DeviceInfo 3 SyncTarget (LocalRemote Primary Secondary)
236 a52f8e72 Michele Tartara
        (LocalRemote Inconsistent UpToDate) 'C' "r----"
237 2188740e Michele Tartara
        (PerfIndicators 0 178176 178176 0 104 42 0 0 0 0 (Just 1)
238 a52f8e72 Michele Tartara
          (Just 'b') (Just 346112))
239 51f2650e Michele Tartara
        (Just $ SyncStatus 34.9 346112 524288 MegaByte (Time 0 0 5) 59392
240 51f2650e Michele Tartara
          Nothing KiloByte Second)
241 a52f8e72 Michele Tartara
        Nothing
242 eb62691c Michele Tartara
        Nothing
243 a52f8e72 Michele Tartara
        Nothing,
244 a52f8e72 Michele Tartara
      DeviceInfo 4 WFConnection (LocalRemote Primary Unknown)
245 a52f8e72 Michele Tartara
        (LocalRemote UpToDate DUnknown) 'C' "r----"
246 2188740e Michele Tartara
        (PerfIndicators 140978 0 9906 131534 27 8 0 0 0 0 (Just 1)
247 a52f8e72 Michele Tartara
          (Just 'b') (Just 0))
248 a52f8e72 Michele Tartara
        Nothing
249 a52f8e72 Michele Tartara
        Nothing
250 a52f8e72 Michele Tartara
        Nothing
251 eb62691c Michele Tartara
        Nothing
252 a52f8e72 Michele Tartara
    ]
253 a52f8e72 Michele Tartara
254 a52f8e72 Michele Tartara
-- | Test a DRBD 8.3 file not from git sources, with an ongoing synchronization
255 a52f8e72 Michele Tartara
-- and the "want" field
256 a52f8e72 Michele Tartara
case_drbd83_sync_want :: Assertion
257 105266b2 Michele Tartara
case_drbd83_sync_want = testParser (drbdStatusParser [])
258 105266b2 Michele Tartara
  "proc_drbd83_sync_want.txt" $ DRBDStatus
259 a52f8e72 Michele Tartara
    ( VersionInfo (Just "8.3.11") (Just "88") (Just "86-96")
260 a52f8e72 Michele Tartara
        (Just "2D876214BAAD53B31ADC1D6")
261 a52f8e72 Michele Tartara
        Nothing Nothing
262 a52f8e72 Michele Tartara
    )
263 a52f8e72 Michele Tartara
    [ DeviceInfo 0 SyncTarget (LocalRemote Secondary Primary)
264 a52f8e72 Michele Tartara
        (LocalRemote Inconsistent UpToDate) 'C' "r-----"
265 2188740e Michele Tartara
        (PerfIndicators 0 460288 460160 0 0 28 2 4 1 0 (Just 1)
266 a52f8e72 Michele Tartara
          (Just 'f') (Just 588416))
267 a52f8e72 Michele Tartara
        (Just $ SyncStatus 44.4 588416 1048576 KiloByte (Time 0 0 8) 65736
268 a52f8e72 Michele Tartara
          (Just 61440) KiloByte Second)
269 a52f8e72 Michele Tartara
        Nothing
270 eb62691c Michele Tartara
        Nothing
271 a52f8e72 Michele Tartara
        Nothing,
272 a52f8e72 Michele Tartara
      UnconfiguredDevice 1,
273 a52f8e72 Michele Tartara
      UnconfiguredDevice 2,
274 a52f8e72 Michele Tartara
      UnconfiguredDevice 3
275 a52f8e72 Michele Tartara
    ]
276 a52f8e72 Michele Tartara
277 a52f8e72 Michele Tartara
-- | Test a DRBD 8.3 file.
278 a52f8e72 Michele Tartara
case_drbd83 :: Assertion
279 105266b2 Michele Tartara
case_drbd83 = testParser (drbdStatusParser []) "proc_drbd83.txt" $
280 a52f8e72 Michele Tartara
  DRBDStatus
281 a52f8e72 Michele Tartara
    ( VersionInfo (Just "8.3.1") (Just "88") (Just "86-89")
282 a52f8e72 Michele Tartara
      Nothing
283 a52f8e72 Michele Tartara
      (Just "fd40f4a8f9104941537d1afc8521e584a6d3003c")
284 a52f8e72 Michele Tartara
      (Just "phil@fat-tyre, 2009-03-27 12:19:49")
285 a52f8e72 Michele Tartara
    )
286 a52f8e72 Michele Tartara
    [ DeviceInfo 0 Connected (LocalRemote Primary Secondary)
287 a52f8e72 Michele Tartara
        (LocalRemote UpToDate UpToDate) 'C' "r----"
288 2188740e Michele Tartara
        (PerfIndicators 140978 0 9906 131533 27 8 0 0 0 0 (Just 1)
289 a52f8e72 Michele Tartara
          (Just 'b') (Just 0))
290 a52f8e72 Michele Tartara
        Nothing
291 a52f8e72 Michele Tartara
        Nothing
292 eb62691c Michele Tartara
        Nothing
293 a52f8e72 Michele Tartara
        Nothing,
294 a52f8e72 Michele Tartara
      DeviceInfo 1 Connected (LocalRemote Secondary Primary)
295 a52f8e72 Michele Tartara
        (LocalRemote UpToDate UpToDate) 'C' "r---"
296 2188740e Michele Tartara
        (PerfIndicators 0 140980 140980 0 0 8 0 0 0 0 (Just 1) (Just 'f')
297 a52f8e72 Michele Tartara
          (Just 0))
298 a52f8e72 Michele Tartara
        Nothing
299 a52f8e72 Michele Tartara
        Nothing
300 eb62691c Michele Tartara
        Nothing
301 a52f8e72 Michele Tartara
        Nothing,
302 a52f8e72 Michele Tartara
      UnconfiguredDevice 2,
303 a52f8e72 Michele Tartara
      DeviceInfo 4 WFConnection (LocalRemote Primary Unknown)
304 a52f8e72 Michele Tartara
        (LocalRemote UpToDate DUnknown) 'C' "r----"
305 2188740e Michele Tartara
        (PerfIndicators 140978 0 9906 131534 27 8 0 0 0 0 (Just 1)
306 a52f8e72 Michele Tartara
          (Just 'b') (Just 0))
307 a52f8e72 Michele Tartara
        Nothing
308 a52f8e72 Michele Tartara
        Nothing
309 eb62691c Michele Tartara
        Nothing
310 a52f8e72 Michele Tartara
        Nothing,
311 a52f8e72 Michele Tartara
      DeviceInfo 5 Connected (LocalRemote Primary Secondary)
312 a52f8e72 Michele Tartara
        (LocalRemote UpToDate Diskless) 'C' "r----"
313 2188740e Michele Tartara
        (PerfIndicators 140978 0 9906 131533 19 8 0 0 0 0 (Just 1)
314 a52f8e72 Michele Tartara
          (Just 'b') (Just 0))
315 a52f8e72 Michele Tartara
        Nothing
316 a52f8e72 Michele Tartara
        Nothing
317 eb62691c Michele Tartara
        Nothing
318 a52f8e72 Michele Tartara
        Nothing,
319 a52f8e72 Michele Tartara
      DeviceInfo 6 Connected (LocalRemote Secondary Primary)
320 a52f8e72 Michele Tartara
        (LocalRemote Diskless UpToDate) 'C' "r---"
321 2188740e Michele Tartara
        (PerfIndicators 0 140978 140978 0 0 8 0 0 0 0 (Just 1) (Just 'f')
322 a52f8e72 Michele Tartara
          (Just 0))
323 a52f8e72 Michele Tartara
        Nothing
324 a52f8e72 Michele Tartara
        Nothing
325 eb62691c Michele Tartara
        Nothing
326 a52f8e72 Michele Tartara
        Nothing,
327 a52f8e72 Michele Tartara
      DeviceInfo 7 WFConnection (LocalRemote Secondary Unknown)
328 a52f8e72 Michele Tartara
        (LocalRemote UpToDate DUnknown) 'C' "r---"
329 2188740e Michele Tartara
        (PerfIndicators 0 140978 140978 0 0 8 0 0 0 0 (Just 1) (Just 'f')
330 a52f8e72 Michele Tartara
          (Just 0))
331 a52f8e72 Michele Tartara
        Nothing
332 a52f8e72 Michele Tartara
        Nothing
333 eb62691c Michele Tartara
        Nothing
334 a52f8e72 Michele Tartara
        Nothing,
335 a52f8e72 Michele Tartara
      DeviceInfo 8 StandAlone (LocalRemote Secondary Unknown)
336 a52f8e72 Michele Tartara
        (LocalRemote UpToDate DUnknown) ' ' "r---"
337 2188740e Michele Tartara
        (PerfIndicators 0 140978 140978 0 0 8 0 0 0 0 (Just 1)
338 a52f8e72 Michele Tartara
          (Just 'f') (Just 0))
339 a52f8e72 Michele Tartara
        Nothing
340 a52f8e72 Michele Tartara
        Nothing
341 a52f8e72 Michele Tartara
        Nothing
342 eb62691c Michele Tartara
        Nothing
343 a52f8e72 Michele Tartara
    ]
344 a52f8e72 Michele Tartara
345 a52f8e72 Michele Tartara
-- | Test a DRBD 8.0 file with a missing device.
346 a52f8e72 Michele Tartara
case_drbd8 :: Assertion
347 105266b2 Michele Tartara
case_drbd8 = testParser (drbdStatusParser []) "proc_drbd8.txt" $
348 a52f8e72 Michele Tartara
  DRBDStatus
349 a52f8e72 Michele Tartara
    ( VersionInfo (Just "8.0.12") (Just "86") (Just "86") Nothing
350 a52f8e72 Michele Tartara
        (Just "5c9f89594553e32adb87d9638dce591782f947e3")
351 a52f8e72 Michele Tartara
        (Just "XXX")
352 a52f8e72 Michele Tartara
    )
353 a52f8e72 Michele Tartara
    [ DeviceInfo 0 Connected (LocalRemote Primary Secondary)
354 a52f8e72 Michele Tartara
        (LocalRemote UpToDate UpToDate) 'C' "r---"
355 2188740e Michele Tartara
        (PerfIndicators 4375577 0 4446279 674 1067 69 0 0 0 0 Nothing
356 a52f8e72 Michele Tartara
          Nothing Nothing)
357 a52f8e72 Michele Tartara
        Nothing
358 a52f8e72 Michele Tartara
        (Just $ AdditionalInfo 0 61 0 0 0 0 0)
359 eb62691c Michele Tartara
        (Just $ AdditionalInfo 0 257 793749 1067 0 0 1067)
360 eb62691c Michele Tartara
        Nothing,
361 a52f8e72 Michele Tartara
      DeviceInfo 1 Connected (LocalRemote Secondary Primary)
362 a52f8e72 Michele Tartara
        (LocalRemote UpToDate UpToDate) 'C' "r---"
363 2188740e Michele Tartara
        (PerfIndicators 738320 0 738320 554400 67 0 0 0 0 0 Nothing
364 a52f8e72 Michele Tartara
          Nothing Nothing)
365 a52f8e72 Michele Tartara
        Nothing
366 a52f8e72 Michele Tartara
        (Just $ AdditionalInfo 0 61 0 0 0 0 0)
367 eb62691c Michele Tartara
        (Just $ AdditionalInfo 0 257 92464 67 0 0 67)
368 eb62691c Michele Tartara
        Nothing,
369 a52f8e72 Michele Tartara
      UnconfiguredDevice 2,
370 a52f8e72 Michele Tartara
      DeviceInfo 4 WFConnection (LocalRemote Primary Unknown)
371 a52f8e72 Michele Tartara
        (LocalRemote UpToDate DUnknown) 'C' "r---"
372 2188740e Michele Tartara
        (PerfIndicators 738320 0 738320 554400 67 0 0 0 0 0 Nothing
373 a52f8e72 Michele Tartara
          Nothing Nothing)
374 a52f8e72 Michele Tartara
        Nothing
375 a52f8e72 Michele Tartara
        (Just $ AdditionalInfo 0 61 0 0 0 0 0)
376 eb62691c Michele Tartara
        (Just $ AdditionalInfo 0 257 92464 67 0 0 67)
377 eb62691c Michele Tartara
        Nothing,
378 a52f8e72 Michele Tartara
      DeviceInfo 5 Connected (LocalRemote Primary Secondary)
379 a52f8e72 Michele Tartara
        (LocalRemote UpToDate Diskless) 'C' "r---"
380 2188740e Michele Tartara
        (PerfIndicators 4375581 0 4446283 674 1069 69 0 0 0 0 Nothing
381 a52f8e72 Michele Tartara
          Nothing Nothing)
382 a52f8e72 Michele Tartara
        Nothing
383 a52f8e72 Michele Tartara
        (Just $ AdditionalInfo 0 61 0 0 0 0 0)
384 eb62691c Michele Tartara
        (Just $ AdditionalInfo 0 257 793750 1069 0 0 1069)
385 eb62691c Michele Tartara
        Nothing,
386 a52f8e72 Michele Tartara
      DeviceInfo 6 Connected (LocalRemote Secondary Primary)
387 a52f8e72 Michele Tartara
        (LocalRemote Diskless UpToDate) 'C'  "r---"
388 2188740e Michele Tartara
        (PerfIndicators 0 4375581 5186925 327 75 214 0 0 0 0 Nothing
389 a52f8e72 Michele Tartara
          Nothing Nothing)
390 a52f8e72 Michele Tartara
        Nothing
391 a52f8e72 Michele Tartara
        Nothing
392 eb62691c Michele Tartara
        Nothing
393 a52f8e72 Michele Tartara
        Nothing,
394 a52f8e72 Michele Tartara
      DeviceInfo 7 WFConnection (LocalRemote Secondary Unknown)
395 a52f8e72 Michele Tartara
        (LocalRemote UpToDate DUnknown) 'C' "r---"
396 2188740e Michele Tartara
        (PerfIndicators 0 0 0 0 0 0 0 0 0 0 Nothing Nothing Nothing)
397 a52f8e72 Michele Tartara
        Nothing
398 a52f8e72 Michele Tartara
        (Just $ AdditionalInfo 0 61 0 0 0 0 0)
399 eb62691c Michele Tartara
        (Just $ AdditionalInfo 0 257 0 0 0 0 0)
400 eb62691c Michele Tartara
        Nothing,
401 a52f8e72 Michele Tartara
      DeviceInfo 8 StandAlone (LocalRemote Secondary Unknown)
402 a52f8e72 Michele Tartara
        (LocalRemote UpToDate DUnknown) ' ' "r---"
403 2188740e Michele Tartara
        (PerfIndicators 0 0 0 0 0 0 0 0 0 0 Nothing Nothing Nothing)
404 a52f8e72 Michele Tartara
        Nothing
405 a52f8e72 Michele Tartara
        (Just $ AdditionalInfo 0 61 0 0 0 0 0)
406 a52f8e72 Michele Tartara
        (Just $ AdditionalInfo 0 257 0 0 0 0 0)
407 eb62691c Michele Tartara
        Nothing
408 a52f8e72 Michele Tartara
    ]
409 a52f8e72 Michele Tartara
410 18837cd8 Michele Tartara
-- | Function for splitting a list in chunks of a given size.
411 18837cd8 Michele Tartara
-- FIXME: an equivalent function exists in Data.List.Split, but it seems
412 18837cd8 Michele Tartara
-- pointless to add this package as a dependence just for this single
413 18837cd8 Michele Tartara
-- use. In case it is ever added, just remove this function definition
414 18837cd8 Michele Tartara
-- and use the one from the package.
415 18837cd8 Michele Tartara
splitEvery :: Int -> [e] -> [[e]]
416 18837cd8 Michele Tartara
splitEvery i l = map (take i) (splitter l (:) []) where
417 18837cd8 Michele Tartara
  splitter [] _ n = n
418 18837cd8 Michele Tartara
  splitter li c n  = li `c` splitter (drop i li) c n
419 18837cd8 Michele Tartara
420 18837cd8 Michele Tartara
-- | Function for testing whether a single comma-separated integer is
421 18837cd8 Michele Tartara
-- parsed correctly.
422 a52f8e72 Michele Tartara
testCommaInt :: String -> Int -> Assertion
423 a52f8e72 Michele Tartara
testCommaInt numString expectedResult =
424 a52f8e72 Michele Tartara
  case A.parseOnly commaIntParser $ pack numString of
425 a52f8e72 Michele Tartara
    Left msg -> assertFailure $ "Parsing failed: " ++ msg
426 a52f8e72 Michele Tartara
    Right obtained -> assertEqual numString expectedResult obtained
427 a52f8e72 Michele Tartara
428 18837cd8 Michele Tartara
-- | Generate a property test for CommaInt numbers in a given range.
429 18837cd8 Michele Tartara
gen_prop_CommaInt :: Int -> Int -> Property
430 18837cd8 Michele Tartara
gen_prop_CommaInt minVal maxVal =
431 18837cd8 Michele Tartara
  forAll (choose (minVal, maxVal)) $ \i ->
432 18837cd8 Michele Tartara
    case A.parseOnly commaIntParser $ pack (generateCommaInt i) of
433 18837cd8 Michele Tartara
      Left msg -> failTest $ "Parsing failed: " ++ msg
434 18837cd8 Michele Tartara
      Right obtained -> i ==? obtained
435 18837cd8 Michele Tartara
  where generateCommaInt x =
436 18837cd8 Michele Tartara
          ((reverse . intercalate ",") . splitEvery 3) . reverse $ show x
437 a52f8e72 Michele Tartara
438 18837cd8 Michele Tartara
-- | Test if <4 digit integers are recognized correctly.
439 18837cd8 Michele Tartara
prop_commaInt_noCommas :: Property
440 18837cd8 Michele Tartara
prop_commaInt_noCommas = gen_prop_CommaInt 0 999
441 a52f8e72 Michele Tartara
442 a52f8e72 Michele Tartara
-- | Test if integers with 1 comma are recognized correctly.
443 18837cd8 Michele Tartara
prop_commaInt_1Comma :: Property
444 18837cd8 Michele Tartara
prop_commaInt_1Comma = gen_prop_CommaInt 1000 999999
445 18837cd8 Michele Tartara
446 18837cd8 Michele Tartara
-- | Test if integers with multiple commas are recognized correctly.
447 18837cd8 Michele Tartara
prop_commaInt_multipleCommas :: Property
448 18837cd8 Michele Tartara
prop_commaInt_multipleCommas = gen_prop_CommaInt 1000000 (maxBound ::
449 18837cd8 Michele Tartara
  Int)
450 a52f8e72 Michele Tartara
451 18837cd8 Michele Tartara
-- | Test whether the parser is actually able to behave as intended with
452 18837cd8 Michele Tartara
-- numbers without commas. That is, if a number with more than 3 digits
453 18837cd8 Michele Tartara
-- is parsed, only up to the first 3 digits are considered (because they
454 18837cd8 Michele Tartara
-- are a valid commaInt), and the rest is ignored.
455 18837cd8 Michele Tartara
-- e.g.: parse "1234" = 123
456 18837cd8 Michele Tartara
prop_commaInt_max3WithoutComma :: Property
457 18837cd8 Michele Tartara
prop_commaInt_max3WithoutComma =
458 18837cd8 Michele Tartara
  forAll (choose (0, maxBound :: Int)) $ \i ->
459 18837cd8 Michele Tartara
    case A.parseOnly commaIntParser $ pack (show i) of
460 18837cd8 Michele Tartara
      Left msg -> failTest $ "Parsing failed: " ++ msg
461 18837cd8 Michele Tartara
      Right obtained ->
462 18837cd8 Michele Tartara
        obtained < 1000 .&&.
463 18837cd8 Michele Tartara
        getFirst3Digits i ==? obtained
464 fd80be11 Michele Tartara
  where getFirst3Digits x =
465 fd80be11 Michele Tartara
          if x >= 1000
466 fd80be11 Michele Tartara
            then getFirst3Digits $ x `div` 10
467 fd80be11 Michele Tartara
            else x
468 a52f8e72 Michele Tartara
469 a52f8e72 Michele Tartara
-- | Test if non-triplets are handled correctly (they are assumed NOT being part
470 a52f8e72 Michele Tartara
-- of the number).
471 a52f8e72 Michele Tartara
case_commaInt_non_triplet :: Assertion
472 a52f8e72 Michele Tartara
case_commaInt_non_triplet = testCommaInt "61,736,12" 61736
473 a52f8e72 Michele Tartara
474 a52f8e72 Michele Tartara
475 fd80be11 Michele Tartara
testSuite "Block/Drbd/Parser"
476 a52f8e72 Michele Tartara
          [ 'case_drbd80_emptyline,
477 d41efc42 Thomas Thrainer
            'case_drbd80_emptyversion,
478 efa6dd08 Thomas Thrainer
            'case_drbd84_sync,
479 efa6dd08 Thomas Thrainer
            'case_drbd84,
480 a52f8e72 Michele Tartara
            'case_drbd83_sync_krnl2_6_39,
481 a52f8e72 Michele Tartara
            'case_drbd83_sync,
482 a52f8e72 Michele Tartara
            'case_drbd83_sync_want,
483 a52f8e72 Michele Tartara
            'case_drbd83,
484 a52f8e72 Michele Tartara
            'case_drbd8,
485 18837cd8 Michele Tartara
            'case_commaInt_non_triplet,
486 18837cd8 Michele Tartara
            'prop_commaInt_noCommas,
487 18837cd8 Michele Tartara
            'prop_commaInt_1Comma,
488 18837cd8 Michele Tartara
            'prop_commaInt_multipleCommas,
489 18837cd8 Michele Tartara
            'prop_commaInt_max3WithoutComma
490 a52f8e72 Michele Tartara
          ]