Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / Locking / Allocation.hs @ 277c969f

History | View | Annotate | Download (9.8 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 can be obtained by starting from the
84
empty allocation, and sequentially requesting (successfully or not)
85
lock updates. So we first define what arbitrary updates sequences are.
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 a b = UpdateRequest a [LockRequest b] deriving Show
96

    
97
instance (Arbitrary a, Arbitrary b) => Arbitrary (UpdateRequest a b) where
98
  arbitrary = UpdateRequest <$> arbitrary <*> arbitrary
99

    
100
-- | Fold a sequence of update requests; all allocations can be obtained in
101
-- this way, starting from the empty allocation.
102
foldUpdates :: (Lock a, Ord b, Show b)
103
            => LockAllocation a b -> [UpdateRequest b a] -> LockAllocation a b
104
foldUpdates = foldl (\s (UpdateRequest owner updates) ->
105
                      fst $ updateLocks owner updates s)
106

    
107
instance (Arbitrary a, Lock a, Arbitrary b, Ord b, Show b)
108
          => Arbitrary (LockAllocation a b) where
109
  arbitrary = foldUpdates emptyAllocation <$> arbitrary
110

    
111
-- | Basic property of locking: the exclusive locks of one user
112
-- are disjoint from any locks of any other user.
113
prop_LocksDisjoint :: Property
114
prop_LocksDisjoint =
115
  forAll (arbitrary :: Gen (LockAllocation TestLock TestOwner)) $ \state ->
116
  forAll (arbitrary :: Gen TestOwner) $ \a ->
117
  forAll (arbitrary `suchThat` (/= a)) $ \b ->
118
  let aExclusive = M.keysSet . M.filter (== OwnExclusive) $ listLocks  a state
119
      bAll = M.keysSet $ listLocks b state
120
  in printTestCase
121
     (show a ++ "'s exclusive lock" ++ " is not respected by " ++ show b)
122
     (S.null $ S.intersection aExclusive bAll)
123

    
124
-- | Verify that exclusive group locks are honored, i.e., verify that if someone
125
-- holds a lock, then no one else can hold a lock on an exclusive lock on an
126
-- implied lock.
127
prop_LockImplicationX :: Property
128
prop_LockImplicationX =
129
  forAll (arbitrary :: Gen (LockAllocation TestLock TestOwner)) $ \state ->
130
  forAll (arbitrary :: Gen TestOwner) $ \a ->
131
  forAll (arbitrary `suchThat` (/= a)) $ \b ->
132
  let bExclusive = M.keysSet . M.filter (== OwnExclusive) $ listLocks  b state
133
  in printTestCase "Others cannot have an exclusive lock on an implied lock" .
134
     flip all (M.keys $ listLocks a state) $ \lock ->
135
     flip all (lockImplications lock) $ \impliedlock ->
136
     not $ S.member impliedlock bExclusive
137

    
138
-- | Verify that shared group locks are honored, i.e., verify that if someone
139
-- holds an exclusive lock, then no one else can hold any form on lock on an
140
-- implied lock.
141
prop_LockImplicationS :: Property
142
prop_LockImplicationS =
143
  forAll (arbitrary :: Gen (LockAllocation TestLock TestOwner)) $ \state ->
144
  forAll (arbitrary :: Gen TestOwner) $ \a ->
145
  forAll (arbitrary `suchThat` (/= a)) $ \b ->
146
  let aExclusive = M.keys . M.filter (== OwnExclusive) $ listLocks  a state
147
      bAll = M.keysSet $ listLocks b state
148
  in printTestCase "Others cannot hold locks implied by an exclusive lock" .
149
     flip all aExclusive $ \lock ->
150
     flip all (lockImplications lock) $ \impliedlock ->
151
     not $ S.member impliedlock bAll
152

    
153
-- | Verify that locks can only be modified by updates of the owner.
154
prop_LocksStable :: Property
155
prop_LocksStable =
156
  forAll (arbitrary :: Gen (LockAllocation TestLock TestOwner)) $ \state ->
157
  forAll (arbitrary :: Gen TestOwner) $ \a ->
158
  forAll (arbitrary `suchThat` (/= a)) $ \b ->
159
  forAll (arbitrary :: Gen [LockRequest TestLock]) $ \request ->
160
  let (state', _) = updateLocks b request state
161
  in (listLocks a state ==? listLocks a state')
162

    
163
-- | Verify that a given request is statisfied in list of owned locks
164
requestSucceeded :: Ord a => M.Map a  OwnerState -> LockRequest a -> Bool
165
requestSucceeded owned (LockRequest lock status) = M.lookup lock owned == status
166

    
167
-- | Verify that lock updates are atomic, i.e., either we get all the required
168
-- locks, or the state is completely unchanged.
169
prop_LockupdateAtomic :: Property
170
prop_LockupdateAtomic =
171
  forAll (arbitrary :: Gen (LockAllocation TestLock TestOwner)) $ \state ->
172
  forAll (arbitrary :: Gen TestOwner) $ \a ->
173
  forAll (arbitrary :: Gen [LockRequest TestLock]) $ \request ->
174
  let (state', result) = updateLocks a request state
175
  in if result == Ok S.empty
176
       then printTestCase
177
            ("Update succeeded, but in final state " ++ show state'
178
              ++ "not all locks are as requested")
179
            $ let owned = listLocks a state'
180
              in all (requestSucceeded owned) request
181
       else printTestCase
182
            ("Update failed, but state changed to " ++ show state')
183
            (state == state')
184

    
185
-- | Verify that releasing a lock always succeeds.
186
prop_LockReleaseSucceeds :: Property
187
prop_LockReleaseSucceeds =
188
  forAll (arbitrary :: Gen (LockAllocation TestLock TestOwner)) $ \state ->
189
  forAll (arbitrary :: Gen TestOwner) $ \a ->
190
  forAll (arbitrary :: Gen TestLock) $ \lock ->
191
  let (_, result) = updateLocks a [requestRelease lock] state
192
  in printTestCase
193
     ("Releasing a lock has to suceed uncondiationally, but got "
194
       ++ show result)
195
     (isOk result)
196

    
197
-- | Verify the property that only the blocking owners prevent
198
-- lock allocation. We deliberatly go for the expensive variant
199
-- restraining by suchThat, as otherwise the number of cases actually
200
-- covered is too small.
201
prop_BlockSufficient :: Property
202
prop_BlockSufficient =
203
  forAll (arbitrary :: Gen TestOwner) $ \a ->
204
  forAll (arbitrary :: Gen TestLock) $ \lock ->
205
  forAll (elements [ [requestShared lock]
206
                   , [requestExclusive lock]]) $ \request ->
207
  forAll ((arbitrary :: Gen (LockAllocation TestLock TestOwner))
208
           `suchThat` (genericResult (const False) (not . S.null)
209
                        . snd . updateLocks a request)) $ \state ->
210
  let (_, result) = updateLocks a request state
211
      blockedOn = genericResult (const S.empty) id result
212
  in  printTestCase "After all blockers release, a request must succeed"
213
      . isOk . snd . updateLocks a request $ F.foldl freeLocks state blockedOn
214

    
215
-- | Verify the property that every blocking owner is necessary, i.e., even
216
-- if we only keep the locks of one of the blocking owners, the request still
217
-- will be blocked. We deliberatly use the expensive variant of restraining
218
-- to ensure good coverage. To make sure the request can always be blocked
219
-- by two owners, for a shared request we request two different locks.
220
prop_BlockNecessary :: Property
221
prop_BlockNecessary =
222
  forAll (arbitrary :: Gen TestOwner) $ \a ->
223
  forAll (arbitrary :: Gen TestLock) $ \lock ->
224
  forAll (arbitrary `suchThat` (/= lock)) $ \lock' ->
225
  forAll (elements [ [requestShared lock, requestShared lock']
226
                   , [requestExclusive lock]]) $ \request ->
227
  forAll ((arbitrary :: Gen (LockAllocation TestLock TestOwner))
228
           `suchThat` (genericResult (const False) ((>= 2) . S.size)
229
                        . snd . updateLocks a request)) $ \state ->
230
  let (_, result) = updateLocks a request state
231
      blockers = genericResult (const S.empty) id result
232
  in  printTestCase "Each blocker alone must block the request"
233
      . flip all (S.elems blockers) $ \blocker ->
234
        (==) (Ok $ S.singleton blocker) . snd . updateLocks a request
235
        . F.foldl freeLocks state
236
        $ S.filter (/= blocker) blockers
237

    
238
testSuite "Locking/Allocation"
239
 [ 'prop_LocksDisjoint
240
 , 'prop_LockImplicationX
241
 , 'prop_LockImplicationS
242
 , 'prop_LocksStable
243
 , 'prop_LockupdateAtomic
244
 , 'prop_LockReleaseSucceeds
245
 , 'prop_BlockSufficient
246
 , 'prop_BlockNecessary
247
 ]