Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / Block / Drbd / Parser.hs @ efa6dd08

History | View | Annotate | Download (17.7 kB)

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