Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / QC.hs @ 685f5bc6

History | View | Annotate | Download (8.6 kB)

1 9b1e1cc9 Iustin Pop
{-| Unittests for ganeti-htools
2 e2fa2baf Iustin Pop
3 e2fa2baf Iustin Pop
-}
4 e2fa2baf Iustin Pop
5 e2fa2baf Iustin Pop
{-
6 e2fa2baf Iustin Pop
7 e2fa2baf Iustin Pop
Copyright (C) 2009 Google Inc.
8 e2fa2baf Iustin Pop
9 e2fa2baf Iustin Pop
This program is free software; you can redistribute it and/or modify
10 e2fa2baf Iustin Pop
it under the terms of the GNU General Public License as published by
11 e2fa2baf Iustin Pop
the Free Software Foundation; either version 2 of the License, or
12 e2fa2baf Iustin Pop
(at your option) any later version.
13 e2fa2baf Iustin Pop
14 e2fa2baf Iustin Pop
This program is distributed in the hope that it will be useful, but
15 e2fa2baf Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
16 e2fa2baf Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17 e2fa2baf Iustin Pop
General Public License for more details.
18 e2fa2baf Iustin Pop
19 e2fa2baf Iustin Pop
You should have received a copy of the GNU General Public License
20 e2fa2baf Iustin Pop
along with this program; if not, write to the Free Software
21 e2fa2baf Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22 e2fa2baf Iustin Pop
02110-1301, USA.
23 e2fa2baf Iustin Pop
24 e2fa2baf Iustin Pop
-}
25 e2fa2baf Iustin Pop
26 15f4c8ca Iustin Pop
module Ganeti.HTools.QC
27 7dd5ee6c Iustin Pop
    ( test_PeerMap
28 7dd5ee6c Iustin Pop
    , test_Container
29 7dd5ee6c Iustin Pop
    , test_Instance
30 7dd5ee6c Iustin Pop
    , test_Node
31 1ae7a904 Iustin Pop
    , test_Text
32 cf35a869 Iustin Pop
    , test_Cluster
33 7dd5ee6c Iustin Pop
    ) where
34 15f4c8ca Iustin Pop
35 15f4c8ca Iustin Pop
import Test.QuickCheck
36 7dd5ee6c Iustin Pop
import Test.QuickCheck.Batch
37 15f4c8ca Iustin Pop
import Data.Maybe
38 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.CLI as CLI
39 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.Cluster as Cluster
40 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.Container as Container
41 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.IAlloc as IAlloc
42 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
43 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.Loader as Loader
44 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.Node as Node
45 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.PeerMap as PeerMap
46 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.Text as Text
47 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.Types as Types
48 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.Utils as Utils
49 15f4c8ca Iustin Pop
50 79a72ce7 Iustin Pop
-- | Simple checker for whether OpResult is fail or pass
51 79a72ce7 Iustin Pop
isFailure :: Types.OpResult a -> Bool
52 79a72ce7 Iustin Pop
isFailure (Types.OpFail _) = True
53 79a72ce7 Iustin Pop
isFailure _ = False
54 79a72ce7 Iustin Pop
55 15f4c8ca Iustin Pop
-- copied from the introduction to quickcheck
56 15f4c8ca Iustin Pop
instance Arbitrary Char where
57 095d7ac0 Iustin Pop
    arbitrary = choose ('\32', '\128')
58 15f4c8ca Iustin Pop
59 15f4c8ca Iustin Pop
-- let's generate a random instance
60 15f4c8ca Iustin Pop
instance Arbitrary Instance.Instance where
61 15f4c8ca Iustin Pop
    arbitrary = do
62 15f4c8ca Iustin Pop
      name <- arbitrary
63 15f4c8ca Iustin Pop
      mem <- choose(0, 100)
64 15f4c8ca Iustin Pop
      dsk <- choose(0, 100)
65 1ae7a904 Iustin Pop
      run_st <- elements ["ERROR_up", "ERROR_down", "ADMIN_down"
66 1ae7a904 Iustin Pop
                         , "ERROR_nodedown", "ERROR_nodeoffline"
67 1ae7a904 Iustin Pop
                         , "running"
68 1ae7a904 Iustin Pop
                         , "no_such_status1", "no_such_status2"]
69 15f4c8ca Iustin Pop
      pn <- arbitrary
70 15f4c8ca Iustin Pop
      sn <- arbitrary
71 79a72ce7 Iustin Pop
      vcpus <- arbitrary
72 79a72ce7 Iustin Pop
      return $ Instance.create name mem dsk vcpus run_st pn sn
73 15f4c8ca Iustin Pop
74 15f4c8ca Iustin Pop
-- and a random node
75 15f4c8ca Iustin Pop
instance Arbitrary Node.Node where
76 15f4c8ca Iustin Pop
    arbitrary = do
77 15f4c8ca Iustin Pop
      name <- arbitrary
78 15f4c8ca Iustin Pop
      mem_t <- arbitrary
79 15f4c8ca Iustin Pop
      mem_f <- choose (0, mem_t)
80 15f4c8ca Iustin Pop
      mem_n <- choose (0, mem_t - mem_f)
81 15f4c8ca Iustin Pop
      dsk_t <- arbitrary
82 15f4c8ca Iustin Pop
      dsk_f <- choose (0, dsk_t)
83 79a72ce7 Iustin Pop
      cpu_t <- arbitrary
84 15f4c8ca Iustin Pop
      offl <- arbitrary
85 15f4c8ca Iustin Pop
      let n = Node.create name (fromIntegral mem_t) mem_n mem_f
86 79a72ce7 Iustin Pop
              (fromIntegral dsk_t) dsk_f cpu_t offl
87 9cf4267a Iustin Pop
          n' = Node.buildPeers n Container.empty
88 15f4c8ca Iustin Pop
      return n'
89 15f4c8ca Iustin Pop
90 15f4c8ca Iustin Pop
-- | Make sure add is idempotent
91 15f4c8ca Iustin Pop
prop_PeerMap_addIdempotent pmap key elem =
92 15f4c8ca Iustin Pop
    fn puniq == fn (fn puniq)
93 7bc82927 Iustin Pop
    where _types = (pmap::PeerMap.PeerMap,
94 15f4c8ca Iustin Pop
                    key::PeerMap.Key, elem::PeerMap.Elem)
95 7bc82927 Iustin Pop
          fn = PeerMap.add key elem
96 7bc82927 Iustin Pop
          puniq = PeerMap.accumArray const pmap
97 15f4c8ca Iustin Pop
98 15f4c8ca Iustin Pop
-- | Make sure remove is idempotent
99 15f4c8ca Iustin Pop
prop_PeerMap_removeIdempotent pmap key =
100 15f4c8ca Iustin Pop
    fn puniq == fn (fn puniq)
101 7bc82927 Iustin Pop
    where _types = (pmap::PeerMap.PeerMap, key::PeerMap.Key)
102 7bc82927 Iustin Pop
          fn = PeerMap.remove key
103 15f4c8ca Iustin Pop
          puniq = PeerMap.accumArray const pmap
104 15f4c8ca Iustin Pop
105 15f4c8ca Iustin Pop
-- | Make sure a missing item returns 0
106 15f4c8ca Iustin Pop
prop_PeerMap_findMissing pmap key =
107 15f4c8ca Iustin Pop
    PeerMap.find key (PeerMap.remove key puniq) == 0
108 7bc82927 Iustin Pop
    where _types = (pmap::PeerMap.PeerMap, key::PeerMap.Key)
109 15f4c8ca Iustin Pop
          puniq = PeerMap.accumArray const pmap
110 15f4c8ca Iustin Pop
111 15f4c8ca Iustin Pop
-- | Make sure an added item is found
112 15f4c8ca Iustin Pop
prop_PeerMap_addFind pmap key elem =
113 15f4c8ca Iustin Pop
    PeerMap.find key (PeerMap.add key elem puniq) == elem
114 7bc82927 Iustin Pop
    where _types = (pmap::PeerMap.PeerMap,
115 15f4c8ca Iustin Pop
                    key::PeerMap.Key, elem::PeerMap.Elem)
116 7bc82927 Iustin Pop
          puniq = PeerMap.accumArray const pmap
117 15f4c8ca Iustin Pop
118 15f4c8ca Iustin Pop
-- | Manual check that maxElem returns the maximum indeed, or 0 for null
119 15f4c8ca Iustin Pop
prop_PeerMap_maxElem pmap =
120 15f4c8ca Iustin Pop
    PeerMap.maxElem puniq == if null puniq then 0
121 15f4c8ca Iustin Pop
                             else (maximum . snd . unzip) puniq
122 7bc82927 Iustin Pop
    where _types = pmap::PeerMap.PeerMap
123 15f4c8ca Iustin Pop
          puniq = PeerMap.accumArray const pmap
124 15f4c8ca Iustin Pop
125 7dd5ee6c Iustin Pop
test_PeerMap =
126 7dd5ee6c Iustin Pop
    [ run prop_PeerMap_addIdempotent
127 7dd5ee6c Iustin Pop
    , run prop_PeerMap_removeIdempotent
128 7dd5ee6c Iustin Pop
    , run prop_PeerMap_maxElem
129 7dd5ee6c Iustin Pop
    , run prop_PeerMap_addFind
130 7dd5ee6c Iustin Pop
    , run prop_PeerMap_findMissing
131 7dd5ee6c Iustin Pop
    ]
132 7dd5ee6c Iustin Pop
133 095d7ac0 Iustin Pop
-- Container tests
134 095d7ac0 Iustin Pop
135 095d7ac0 Iustin Pop
prop_Container_addTwo cdata i1 i2 =
136 095d7ac0 Iustin Pop
    fn i1 i2 cont == fn i2 i1 cont &&
137 095d7ac0 Iustin Pop
       fn i1 i2 cont == fn i1 i2 (fn i1 i2 cont)
138 095d7ac0 Iustin Pop
    where _types = (cdata::[Int],
139 095d7ac0 Iustin Pop
                    i1::Int, i2::Int)
140 095d7ac0 Iustin Pop
          cont = foldl (\c x -> Container.add x x c) Container.empty cdata
141 095d7ac0 Iustin Pop
          fn x1 x2 = Container.addTwo x1 x1 x2 x2
142 095d7ac0 Iustin Pop
143 7dd5ee6c Iustin Pop
test_Container =
144 7dd5ee6c Iustin Pop
    [ run prop_Container_addTwo ]
145 095d7ac0 Iustin Pop
146 7bc82927 Iustin Pop
-- Simple instance tests, we only have setter/getters
147 7bc82927 Iustin Pop
148 7bc82927 Iustin Pop
prop_Instance_setIdx inst idx =
149 7bc82927 Iustin Pop
    Instance.idx (Instance.setIdx inst idx) == idx
150 7bc82927 Iustin Pop
    where _types = (inst::Instance.Instance, idx::Types.Idx)
151 7bc82927 Iustin Pop
152 7bc82927 Iustin Pop
prop_Instance_setName inst name =
153 7bc82927 Iustin Pop
    Instance.name (Instance.setName inst name) == name
154 7bc82927 Iustin Pop
    where _types = (inst::Instance.Instance, name::String)
155 7bc82927 Iustin Pop
156 7bc82927 Iustin Pop
prop_Instance_setPri inst pdx =
157 7bc82927 Iustin Pop
    Instance.pnode (Instance.setPri inst pdx) == pdx
158 7bc82927 Iustin Pop
    where _types = (inst::Instance.Instance, pdx::Types.Ndx)
159 7bc82927 Iustin Pop
160 7bc82927 Iustin Pop
prop_Instance_setSec inst sdx =
161 7bc82927 Iustin Pop
    Instance.snode (Instance.setSec inst sdx) == sdx
162 7bc82927 Iustin Pop
    where _types = (inst::Instance.Instance, sdx::Types.Ndx)
163 7bc82927 Iustin Pop
164 7bc82927 Iustin Pop
prop_Instance_setBoth inst pdx sdx =
165 7bc82927 Iustin Pop
    Instance.pnode si == pdx && Instance.snode si == sdx
166 7bc82927 Iustin Pop
    where _types = (inst::Instance.Instance, pdx::Types.Ndx, sdx::Types.Ndx)
167 7bc82927 Iustin Pop
          si = Instance.setBoth inst pdx sdx
168 7bc82927 Iustin Pop
169 1ae7a904 Iustin Pop
prop_Instance_runStatus_True inst =
170 1ae7a904 Iustin Pop
    let run_st = Instance.running inst
171 1ae7a904 Iustin Pop
        run_tx = Instance.run_st inst
172 1ae7a904 Iustin Pop
    in
173 1ae7a904 Iustin Pop
      run_tx == "running" || run_tx == "ERROR_up" ==> run_st == True
174 1ae7a904 Iustin Pop
175 1ae7a904 Iustin Pop
prop_Instance_runStatus_False inst =
176 1ae7a904 Iustin Pop
    let run_st = Instance.running inst
177 1ae7a904 Iustin Pop
        run_tx = Instance.run_st inst
178 1ae7a904 Iustin Pop
    in
179 1ae7a904 Iustin Pop
      run_tx /= "running" && run_tx /= "ERROR_up" ==> run_st == False
180 1ae7a904 Iustin Pop
181 7dd5ee6c Iustin Pop
test_Instance =
182 7dd5ee6c Iustin Pop
    [ run prop_Instance_setIdx
183 7dd5ee6c Iustin Pop
    , run prop_Instance_setName
184 7dd5ee6c Iustin Pop
    , run prop_Instance_setPri
185 7dd5ee6c Iustin Pop
    , run prop_Instance_setSec
186 7dd5ee6c Iustin Pop
    , run prop_Instance_setBoth
187 1ae7a904 Iustin Pop
    , run prop_Instance_runStatus_True
188 1ae7a904 Iustin Pop
    , run prop_Instance_runStatus_False
189 1ae7a904 Iustin Pop
    ]
190 1ae7a904 Iustin Pop
191 1ae7a904 Iustin Pop
-- Instance text loader tests
192 1ae7a904 Iustin Pop
193 1ae7a904 Iustin Pop
prop_Text_Load_Instance name mem dsk vcpus status pnode snode pdx sdx =
194 1ae7a904 Iustin Pop
    let vcpus_s = show vcpus
195 1ae7a904 Iustin Pop
        dsk_s = show dsk
196 1ae7a904 Iustin Pop
        mem_s = show mem
197 1ae7a904 Iustin Pop
        rsnode = snode ++ "a" -- non-empty secondary node
198 1ae7a904 Iustin Pop
        rsdx = if pdx == sdx
199 1ae7a904 Iustin Pop
               then sdx + 1
200 1ae7a904 Iustin Pop
               else sdx
201 1ae7a904 Iustin Pop
        ndx = [(pnode, pdx), (rsnode, rsdx)]
202 1ae7a904 Iustin Pop
        inst = Text.loadInst ndx
203 1ae7a904 Iustin Pop
               (name:mem_s:dsk_s:vcpus_s:status:pnode:rsnode:[])::
204 1ae7a904 Iustin Pop
               Maybe (String, Instance.Instance)
205 1ae7a904 Iustin Pop
        _types = ( name::String, mem::Int, dsk::Int
206 1ae7a904 Iustin Pop
                 , vcpus::Int, status::String
207 1ae7a904 Iustin Pop
                 , pnode::String, snode::String
208 1ae7a904 Iustin Pop
                 , pdx::Types.Ndx, sdx::Types.Ndx)
209 1ae7a904 Iustin Pop
    in
210 1ae7a904 Iustin Pop
      case inst of
211 1ae7a904 Iustin Pop
        Nothing -> False
212 1ae7a904 Iustin Pop
        Just (_, i) ->
213 1ae7a904 Iustin Pop
            (Instance.name i == name &&
214 1ae7a904 Iustin Pop
             Instance.vcpus i == vcpus &&
215 1ae7a904 Iustin Pop
             Instance.mem i == mem &&
216 1ae7a904 Iustin Pop
             Instance.pnode i == pdx &&
217 1ae7a904 Iustin Pop
             Instance.snode i == rsdx)
218 1ae7a904 Iustin Pop
219 1ae7a904 Iustin Pop
test_Text =
220 1ae7a904 Iustin Pop
    [ run prop_Text_Load_Instance
221 7dd5ee6c Iustin Pop
    ]
222 7dd5ee6c Iustin Pop
223 7dd5ee6c Iustin Pop
-- Node tests
224 7dd5ee6c Iustin Pop
225 7bc82927 Iustin Pop
-- | Check that an instance add with too high memory or disk will be rejected
226 15f4c8ca Iustin Pop
prop_Node_addPri node inst = (Instance.mem inst >= Node.f_mem node ||
227 15f4c8ca Iustin Pop
                              Instance.dsk inst >= Node.f_dsk node) &&
228 9f6dcdea Iustin Pop
                             not (Node.failN1 node)
229 15f4c8ca Iustin Pop
                             ==>
230 79a72ce7 Iustin Pop
                             isFailure (Node.addPri node inst)
231 15f4c8ca Iustin Pop
    where _types = (node::Node.Node, inst::Instance.Instance)
232 15f4c8ca Iustin Pop
233 7bc82927 Iustin Pop
234 7bc82927 Iustin Pop
-- | Check that an instance add with too high memory or disk will be rejected
235 15f4c8ca Iustin Pop
prop_Node_addSec node inst pdx =
236 15f4c8ca Iustin Pop
    (Instance.mem inst >= (Node.f_mem node - Node.r_mem node) ||
237 15f4c8ca Iustin Pop
     Instance.dsk inst >= Node.f_dsk node) &&
238 9f6dcdea Iustin Pop
    not (Node.failN1 node)
239 79a72ce7 Iustin Pop
    ==> isFailure (Node.addSec node inst pdx)
240 15f4c8ca Iustin Pop
        where _types = (node::Node.Node, inst::Instance.Instance, pdx::Int)
241 7dd5ee6c Iustin Pop
242 7dd5ee6c Iustin Pop
test_Node =
243 7dd5ee6c Iustin Pop
    [ run prop_Node_addPri
244 7dd5ee6c Iustin Pop
    , run prop_Node_addSec
245 7dd5ee6c Iustin Pop
    ]
246 cf35a869 Iustin Pop
247 cf35a869 Iustin Pop
248 cf35a869 Iustin Pop
-- Cluster tests
249 cf35a869 Iustin Pop
250 cf35a869 Iustin Pop
-- | Check that the cluster score is close to zero for a homogeneous cluster
251 cf35a869 Iustin Pop
prop_Score_Zero node count =
252 cf35a869 Iustin Pop
    ((not $ Node.offline node) && (not $ Node.failN1 node) && (count > 0) &&
253 cf35a869 Iustin Pop
     (Node.t_dsk node > 0) && (Node.t_mem node > 0)) ==>
254 cf35a869 Iustin Pop
    let fn = Node.buildPeers node Container.empty
255 cf35a869 Iustin Pop
        nlst = (zip [1..] $ replicate count fn)::[(Types.Ndx, Node.Node)]
256 cf35a869 Iustin Pop
        nl = Container.fromAssocList nlst
257 cf35a869 Iustin Pop
        score = Cluster.compCV nl
258 cf35a869 Iustin Pop
    -- we can't say == 0 here as the floating point errors accumulate;
259 cf35a869 Iustin Pop
    -- this should be much lower than the default score in CLI.hs
260 685f5bc6 Iustin Pop
    in score <= 1e-15
261 cf35a869 Iustin Pop
262 cf35a869 Iustin Pop
test_Cluster =
263 cf35a869 Iustin Pop
    [ run prop_Score_Zero
264 cf35a869 Iustin Pop
    ]