Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / Locking / Allocation.hs @ 13caa61d

History | View | Annotate | Download (13.1 kB)

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

    
4
{-| Tests for lock allocation.
5

    
6
-}
7

    
8
{-
9

    
10
Copyright (C) 2014 Google Inc.
11

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

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

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

    
27
-}
28

    
29
module Test.Ganeti.Locking.Allocation (testLocking_Allocation) where
30

    
31
import Control.Applicative
32
import qualified Data.Foldable as F
33
import qualified Data.Map as M
34
import qualified Data.Set as S
35

    
36
import Test.QuickCheck
37

    
38
import Test.Ganeti.TestCommon
39
import Test.Ganeti.TestHelper
40

    
41
import Ganeti.BasicTypes
42
import Ganeti.Locking.Allocation
43
import Ganeti.Locking.Types
44

    
45
{-
46

    
47
Ganeti.Locking.Allocation is polymorphic in the types of locks
48
and lock owners. So we can use much simpler types here than Ganeti's
49
real locks and lock owners, knowning at polymorphic functions cannot
50
exploit the simplicity of the types they're deling with.
51

    
52
-}
53

    
54
data TestOwner = TestOwner Int deriving (Ord, Eq, Show)
55

    
56
instance Arbitrary TestOwner where
57
  arbitrary = TestOwner <$> choose (0, 2)
58

    
59
data TestLock = TestBigLock
60
              | TestCollectionLockA
61
              | TestLockA Int
62
              | TestCollectionLockB
63
              | TestLockB Int
64
              deriving (Ord, Eq, Show)
65

    
66
instance Arbitrary TestLock where
67
  arbitrary =  frequency [ (1, elements [ TestBigLock
68
                                        , TestCollectionLockA
69
                                        , TestCollectionLockB
70
                                        ])
71
                         , (2, TestLockA <$> choose (0, 2))
72
                         , (2, TestLockB <$> choose (0, 2))
73
                         ]
74

    
75
instance Lock TestLock where
76
  lockImplications (TestLockA _) = [TestCollectionLockA, TestBigLock]
77
  lockImplications (TestLockB _) = [TestCollectionLockB, TestBigLock]
78
  lockImplications TestBigLock = []
79
  lockImplications _ = [TestBigLock]
80

    
81
{-
82

    
83
All states of a  LockAllocation every available outside the
84
Ganeti.Locking.Allocation module must be constructed by starting
85
with emptyAllocation and applying the exported functions.
86

    
87
-}
88

    
89
instance Arbitrary OwnerState where
90
  arbitrary = elements [OwnShared, OwnExclusive]
91

    
92
instance Arbitrary a => Arbitrary (LockRequest a) where
93
  arbitrary = LockRequest <$> arbitrary <*> genMaybe arbitrary
94

    
95
data UpdateRequest b a = UpdateRequest b [LockRequest a]
96
                       | IntersectRequest b [a]
97
                       | OpportunisticUnion b [(a, OwnerState)]
98
                       | FreeLockRequest b
99
                       deriving Show
100

    
101
instance (Arbitrary a, Arbitrary b) => Arbitrary (UpdateRequest a b) where
102
  arbitrary =
103
    frequency [ (4, UpdateRequest <$> arbitrary <*> (choose (1, 4) >>= vector))
104
              , (2, IntersectRequest <$> arbitrary
105
                                     <*> (choose (1, 4) >>= vector))
106
              , (2, OpportunisticUnion <$> arbitrary
107
                                       <*> (choose (1, 4) >>= vector))
108
              , (1, FreeLockRequest <$> arbitrary)
109
              ]
110

    
111
-- | Transform an UpdateRequest into the corresponding state transformer.
112
asAllocTrans :: (Lock a, Ord b, Show b)
113
              => LockAllocation a b -> UpdateRequest b a -> LockAllocation a b
114
asAllocTrans state (UpdateRequest owner updates) =
115
  fst $ updateLocks owner updates state
116
asAllocTrans state (IntersectRequest owner locks) =
117
  intersectLocks owner locks state
118
asAllocTrans state (OpportunisticUnion owner locks) =
119
  fst $ opportunisticLockUnion owner locks state
120
asAllocTrans state (FreeLockRequest owner) = freeLocks state owner
121

    
122
-- | Fold a sequence of requests to transform a lock allocation onto the empty
123
-- allocation. As we consider all exported LockAllocation transformers, any
124
-- LockAllocation definable is obtained in this way.
125
foldUpdates :: (Lock a, Ord b, Show b)
126
            => [UpdateRequest b a] -> LockAllocation a b
127
foldUpdates = foldl asAllocTrans emptyAllocation
128

    
129
instance (Arbitrary a, Lock a, Arbitrary b, Ord b, Show b)
130
          => Arbitrary (LockAllocation a b) where
131
  arbitrary = foldUpdates <$> (choose (0, 8) >>= vector)
132

    
133
-- | Basic property of locking: the exclusive locks of one user
134
-- are disjoint from any locks of any other user.
135
prop_LocksDisjoint :: Property
136
prop_LocksDisjoint =
137
  forAll (arbitrary :: Gen (LockAllocation TestLock TestOwner)) $ \state ->
138
  forAll (arbitrary :: Gen TestOwner) $ \a ->
139
  forAll (arbitrary `suchThat` (/= a)) $ \b ->
140
  let aExclusive = M.keysSet . M.filter (== OwnExclusive) $ listLocks  a state
141
      bAll = M.keysSet $ listLocks b state
142
  in printTestCase
143
     (show a ++ "'s exclusive lock" ++ " is not respected by " ++ show b)
144
     (S.null $ S.intersection aExclusive bAll)
145

    
146
-- | Verify that exclusive group locks are honored, i.e., verify that if someone
147
-- holds a lock, then no one else can hold a lock on an exclusive lock on an
148
-- implied lock.
149
prop_LockImplicationX :: Property
150
prop_LockImplicationX =
151
  forAll (arbitrary :: Gen (LockAllocation TestLock TestOwner)) $ \state ->
152
  forAll (arbitrary :: Gen TestOwner) $ \a ->
153
  forAll (arbitrary `suchThat` (/= a)) $ \b ->
154
  let bExclusive = M.keysSet . M.filter (== OwnExclusive) $ listLocks  b state
155
  in printTestCase "Others cannot have an exclusive lock on an implied lock" .
156
     flip all (M.keys $ listLocks a state) $ \lock ->
157
     flip all (lockImplications lock) $ \impliedlock ->
158
     not $ S.member impliedlock bExclusive
159

    
160
-- | Verify that shared group locks are honored, i.e., verify that if someone
161
-- holds an exclusive lock, then no one else can hold any form on lock on an
162
-- implied lock.
163
prop_LockImplicationS :: Property
164
prop_LockImplicationS =
165
  forAll (arbitrary :: Gen (LockAllocation TestLock TestOwner)) $ \state ->
166
  forAll (arbitrary :: Gen TestOwner) $ \a ->
167
  forAll (arbitrary `suchThat` (/= a)) $ \b ->
168
  let aExclusive = M.keys . M.filter (== OwnExclusive) $ listLocks  a state
169
      bAll = M.keysSet $ listLocks b state
170
  in printTestCase "Others cannot hold locks implied by an exclusive lock" .
171
     flip all aExclusive $ \lock ->
172
     flip all (lockImplications lock) $ \impliedlock ->
173
     not $ S.member impliedlock bAll
174

    
175
-- | Verify that locks can only be modified by updates of the owner.
176
prop_LocksStable :: Property
177
prop_LocksStable =
178
  forAll (arbitrary :: Gen (LockAllocation TestLock TestOwner)) $ \state ->
179
  forAll (arbitrary :: Gen TestOwner) $ \a ->
180
  forAll (arbitrary `suchThat` (/= a)) $ \b ->
181
  forAll (arbitrary :: Gen [LockRequest TestLock]) $ \request ->
182
  let (state', _) = updateLocks b request state
183
  in (listLocks a state ==? listLocks a state')
184

    
185
-- | Verify that a given request is statisfied in list of owned locks
186
requestSucceeded :: Ord a => M.Map a  OwnerState -> LockRequest a -> Bool
187
requestSucceeded owned (LockRequest lock status) = M.lookup lock owned == status
188

    
189
-- | Verify that lock updates are atomic, i.e., either we get all the required
190
-- locks, or the state is completely unchanged.
191
prop_LockupdateAtomic :: Property
192
prop_LockupdateAtomic =
193
  forAll (arbitrary :: Gen (LockAllocation TestLock TestOwner)) $ \state ->
194
  forAll (arbitrary :: Gen TestOwner) $ \a ->
195
  forAll (arbitrary :: Gen [LockRequest TestLock]) $ \request ->
196
  let (state', result) = updateLocks a request state
197
  in if result == Ok S.empty
198
       then printTestCase
199
            ("Update succeeded, but in final state " ++ show state'
200
              ++ "not all locks are as requested")
201
            $ let owned = listLocks a state'
202
              in all (requestSucceeded owned) request
203
       else printTestCase
204
            ("Update failed, but state changed to " ++ show state')
205
            (state == state')
206

    
207
-- | Verify that releasing a lock always succeeds.
208
prop_LockReleaseSucceeds :: Property
209
prop_LockReleaseSucceeds =
210
  forAll (arbitrary :: Gen (LockAllocation TestLock TestOwner)) $ \state ->
211
  forAll (arbitrary :: Gen TestOwner) $ \a ->
212
  forAll (arbitrary :: Gen TestLock) $ \lock ->
213
  let (_, result) = updateLocks a [requestRelease lock] state
214
  in printTestCase
215
     ("Releasing a lock has to suceed uncondiationally, but got "
216
       ++ show result)
217
     (isOk result)
218

    
219
-- | Verify the property that only the blocking owners prevent
220
-- lock allocation. We deliberatly go for the expensive variant
221
-- restraining by suchThat, as otherwise the number of cases actually
222
-- covered is too small.
223
prop_BlockSufficient :: Property
224
prop_BlockSufficient =
225
  forAll (arbitrary :: Gen TestOwner) $ \a ->
226
  forAll (arbitrary :: Gen TestLock) $ \lock ->
227
  forAll (elements [ [requestShared lock]
228
                   , [requestExclusive lock]]) $ \request ->
229
  forAll ((arbitrary :: Gen (LockAllocation TestLock TestOwner))
230
           `suchThat` (genericResult (const False) (not . S.null)
231
                        . snd . updateLocks a request)) $ \state ->
232
  let (_, result) = updateLocks a request state
233
      blockedOn = genericResult (const S.empty) id result
234
  in  printTestCase "After all blockers release, a request must succeed"
235
      . isOk . snd . updateLocks a request $ F.foldl freeLocks state blockedOn
236

    
237
-- | Verify the property that every blocking owner is necessary, i.e., even
238
-- if we only keep the locks of one of the blocking owners, the request still
239
-- will be blocked. We deliberatly use the expensive variant of restraining
240
-- to ensure good coverage. To make sure the request can always be blocked
241
-- by two owners, for a shared request we request two different locks.
242
prop_BlockNecessary :: Property
243
prop_BlockNecessary =
244
  forAll (arbitrary :: Gen TestOwner) $ \a ->
245
  forAll (arbitrary :: Gen TestLock) $ \lock ->
246
  forAll (arbitrary `suchThat` (/= lock)) $ \lock' ->
247
  forAll (elements [ [requestShared lock, requestShared lock']
248
                   , [requestExclusive lock]]) $ \request ->
249
  forAll ((arbitrary :: Gen (LockAllocation TestLock TestOwner))
250
           `suchThat` (genericResult (const False) ((>= 2) . S.size)
251
                        . snd . updateLocks a request)) $ \state ->
252
  let (_, result) = updateLocks a request state
253
      blockers = genericResult (const S.empty) id result
254
  in  printTestCase "Each blocker alone must block the request"
255
      . flip all (S.elems blockers) $ \blocker ->
256
        (==) (Ok $ S.singleton blocker) . snd . updateLocks a request
257
        . F.foldl freeLocks state
258
        $ S.filter (/= blocker) blockers
259

    
260
-- | Verify that opportunistic union only increases the locks held.
261
prop_OpportunisticMonotone :: Property
262
prop_OpportunisticMonotone =
263
  forAll (arbitrary :: Gen (LockAllocation TestLock TestOwner)) $ \state ->
264
  forAll (arbitrary :: Gen TestOwner) $ \a ->
265
  forAll ((choose (1,3) >>= vector) :: Gen [(TestLock, OwnerState)]) $ \req ->
266
  let (state', _) = opportunisticLockUnion a req state
267
      oldOwned = listLocks a state
268
      oldLocks = M.keys oldOwned
269
      newOwned = listLocks a state'
270
  in printTestCase "Opportunistic union may only increase the set of locks held"
271
     . flip all oldLocks $ \lock ->
272
       M.lookup lock newOwned >= M.lookup lock oldOwned
273

    
274
-- | Verify the result list of the opportunistic union: if a lock is not in
275
-- the result that, than its state has not changed, and if it is, it is as
276
-- requested. The latter property is tested in that liberal way, so that we
277
-- really can take arbitrary requests, including those that require both, shared
278
-- and exlusive state for the same lock.
279
prop_OpportunisticAnswer :: Property
280
prop_OpportunisticAnswer =
281
  forAll (arbitrary :: Gen (LockAllocation TestLock TestOwner)) $ \state ->
282
  forAll (arbitrary :: Gen TestOwner) $ \a ->
283
  forAll ((choose (1,3) >>= vector) :: Gen [(TestLock, OwnerState)]) $ \req ->
284
  let (state', result) = opportunisticLockUnion a req state
285
      oldOwned = listLocks a state
286
      newOwned = listLocks a state'
287
      involvedLocks = M.keys oldOwned ++ map fst req
288
  in conjoin [ printTestCase ("Locks not in the answer set " ++ show result
289
                                ++ " may not be changed, but found "
290
                                ++ show state')
291
               . flip all involvedLocks $ \lock ->
292
                 (lock `S.member` result)
293
                 || (M.lookup lock oldOwned == M.lookup lock newOwned)
294
             , printTestCase ("Locks not in the answer set " ++ show result
295
                               ++ " must be as requested, but found "
296
                               ++ show state')
297
               . flip all involvedLocks $ \lock ->
298
                 (lock `S.notMember` result)
299
                 || maybe False (flip elem req . (,) lock)
300
                      (M.lookup lock newOwned)
301
             ]
302

    
303

    
304

    
305
testSuite "Locking/Allocation"
306
 [ 'prop_LocksDisjoint
307
 , 'prop_LockImplicationX
308
 , 'prop_LockImplicationS
309
 , 'prop_LocksStable
310
 , 'prop_LockupdateAtomic
311
 , 'prop_LockReleaseSucceeds
312
 , 'prop_BlockSufficient
313
 , 'prop_BlockNecessary
314
 , 'prop_OpportunisticMonotone
315
 , 'prop_OpportunisticAnswer
316
 ]