Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / Block / Drbd / Types.hs @ 83846468

History | View | Annotate | Download (5 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2
{-# OPTIONS_GHC -fno-warn-orphans #-}
3

    
4
{-| Unittests for the types representing DRBD status -}
5

    
6
{-
7

    
8
Copyright (C) 2012 Google Inc.
9

    
10
This program is free software; you can redistribute it and/or modify
11
it under the terms of the GNU General Public License as published by
12
the Free Software Foundation; either version 2 of the License, or
13
(at your option) any later version.
14

    
15
This program is distributed in the hope that it will be useful, but
16
WITHOUT ANY WARRANTY; without even the implied warranty of
17
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
18
General Public License for more details.
19

    
20
You should have received a copy of the GNU General Public License
21
along with this program; if not, write to the Free Software
22
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
23
02110-1301, USA.
24

    
25
-}
26

    
27
module Test.Ganeti.Block.Drbd.Types (testBlock_Drbd_Types) where
28

    
29
import Test.QuickCheck
30

    
31
import Test.Ganeti.TestHelper
32
import Test.Ganeti.TestCommon
33

    
34
import Text.JSON
35
import Text.Printf
36

    
37
import Ganeti.JSON
38

    
39
import Ganeti.Block.Drbd.Types
40

    
41
{-# ANN module "HLint: ignore Use camelCase" #-}
42
{-# ANN module "HLint: ignore Use string literal" #-}
43

    
44
-- * Arbitrary instances
45

    
46
$(genArbitrary ''ConnState)
47
$(genArbitrary ''Role)
48
$(genArbitrary ''DiskState)
49
$(genArbitrary ''SizeUnit)
50
$(genArbitrary ''TimeUnit)
51

    
52
-- | Natural numbers generator.
53
natural :: Gen Int
54
natural = choose (0, maxBound :: Int)
55

    
56
-- | Generator of percentages.
57
percent :: Gen Double
58
percent = choose (0 :: Double, 100 :: Double)
59

    
60
-- | Generator of write order flags.
61
wOrderFlag :: Gen Char
62
wOrderFlag = elements ['b', 'f', 'd', 'n']
63

    
64
-- | Property for testing the JSON serialization of a DeviceInfo.
65
prop_DeviceInfo :: Property
66
prop_DeviceInfo = do
67
  minor <- natural
68
  state <- arbitrary
69
  locRole <- arbitrary
70
  remRole <- arbitrary
71
  locState <- arbitrary
72
  remState <- arbitrary
73
  alg <- choose ('A','C')
74
  ns <- natural
75
  nr <- natural
76
  dw <- natural
77
  dr <- natural
78
  al <- natural
79
  bm <- natural
80
  lc <- natural
81
  pe <- natural
82
  ua <- natural
83
  ap <- natural
84
  ep <- genMaybe natural
85
  wo <- genMaybe wOrderFlag
86
  oos <- genMaybe natural
87
  let obtained =
88
          showJSON $
89
            DeviceInfo minor state (LocalRemote locRole remRole)
90
              (LocalRemote locState remState) alg "r----" perfInd
91
              Nothing
92
              Nothing
93
              Nothing
94
      perfInd =
95
        PerfIndicators ns nr dw dr al bm lc pe ua ap ep wo oos
96
      expected =
97
        makeObj
98
          [ ("minor", showJSON minor)
99
          , ("connectionState", showJSON state)
100
          , ("localRole", showJSON locRole)
101
          , ("remoteRole", showJSON remRole)
102
          , ("localState", showJSON locState)
103
          , ("remoteState", showJSON remState)
104
          , ("replicationProtocol", showJSON alg)
105
          , ("ioFlags", showJSON "r----")
106
          , ("perfIndicators", showJSON perfInd)
107
          ]
108
  obtained ==? expected
109

    
110
-- | Property for testing the JSON serialization of a PerfIndicators.
111
prop_PerfIndicators :: Property
112
prop_PerfIndicators = do
113
  ns <- natural
114
  nr <- natural
115
  dw <- natural
116
  dr <- natural
117
  al <- natural
118
  bm <- natural
119
  lc <- natural
120
  pe <- natural
121
  ua <- natural
122
  ap <- natural
123
  ep <- genMaybe natural
124
  wo <- genMaybe wOrderFlag
125
  oos <- genMaybe natural
126
  let expected =
127
        showJSON $
128
          PerfIndicators ns nr dw dr al bm lc pe ua ap ep wo oos
129
      obtained =
130
        optFieldsToObj
131
          [ Just ("networkSend", showJSON ns)
132
          , Just ("networkReceive", showJSON nr)
133
          , Just ("diskWrite", showJSON dw)
134
          , Just ("diskRead", showJSON dr)
135
          , Just ("activityLog", showJSON al)
136
          , Just ("bitMap", showJSON bm)
137
          , Just ("localCount", showJSON lc)
138
          , Just ("pending", showJSON pe)
139
          , Just ("unacknowledged", showJSON ua)
140
          , Just ("applicationPending", showJSON ap)
141
          , optionalJSField "epochs" ep
142
          , optionalJSField "writeOrder" wo
143
          , optionalJSField "outOfSync" oos
144
          ]
145
  obtained ==? expected
146

    
147
-- | Function for testing the JSON serialization of a SyncStatus.
148
prop_SyncStatus :: Property
149
prop_SyncStatus = do
150
  perc <- percent
151
  numer <- natural
152
  denom <- natural
153
  sizeU1 <- arbitrary
154
  h <- choose (0, 23)
155
  m <- choose (0, 59)
156
  s <- choose (0, 59)
157
  sp <- natural
158
  wa <- genMaybe natural
159
  sizeU2 <- arbitrary
160
  timeU <- arbitrary
161
  let obtained = showJSON $
162
        SyncStatus perc numer denom sizeU1 (Time h m s) sp wa sizeU2 timeU
163
      expected = optFieldsToObj
164
        [ Just ("percentage", showJSON perc)
165
        , Just ("progress", showJSON $ show numer ++ "/" ++ show denom)
166
        , Just ("progressUnit", showJSON sizeU1)
167
        , Just ("timeToFinish", showJSON
168
            (printf "%02d:%02d:%02d" h m s :: String))
169
        , Just ("speed", showJSON sp)
170
        , optionalJSField "want" wa
171
        , Just ("speedUnit", showJSON $ show sizeU2 ++ "/" ++ show timeU)
172
        ]
173
  obtained ==? expected
174

    
175
testSuite "Block/Drbd/Types"
176
          [ 'prop_DeviceInfo
177
          , 'prop_PerfIndicators
178
          , 'prop_SyncStatus
179
          ]