Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / Locking / Allocation.hs @ 619b12df

History | View | Annotate | Download (6.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.Map as M
33
import qualified Data.Set as S
34

    
35
import Test.QuickCheck
36

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

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

    
44
{-
45

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

    
51
-}
52

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

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

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

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

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

    
80
{-
81

    
82
All states of a  LockAllocation can be obtained by starting from the
83
empty allocation, and sequentially requesting (successfully or not)
84
lock updates. So we first define what arbitrary updates sequences are.
85

    
86
-}
87

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

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

    
94
data UpdateRequest a b = UpdateRequest a [LockRequest b] deriving Show
95

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

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

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

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

    
123
-- | Verify that locks can only be modified by updates of the owner.
124
prop_LocksStable :: Property
125
prop_LocksStable =
126
  forAll (arbitrary :: Gen (LockAllocation TestLock TestOwner)) $ \state ->
127
  forAll (arbitrary :: Gen TestOwner) $ \a ->
128
  forAll (arbitrary `suchThat` (/= a)) $ \b ->
129
  forAll (arbitrary :: Gen [LockRequest TestLock]) $ \request ->
130
  let (state', _) = updateLocks b request state
131
  in (listLocks a state ==? listLocks a state')
132

    
133
-- | Verify that a given request is statisfied in list of owned locks
134
requestSucceeded :: Ord a => M.Map a  OwnerState -> LockRequest a -> Bool
135
requestSucceeded owned (LockRequest lock status) = M.lookup lock owned == status
136

    
137
-- | Verify that lock updates are atomic, i.e., either we get all the required
138
-- locks, or the state is completely unchanged.
139
prop_LockupdateAtomic :: Property
140
prop_LockupdateAtomic =
141
  forAll (arbitrary :: Gen (LockAllocation TestLock TestOwner)) $ \state ->
142
  forAll (arbitrary :: Gen TestOwner) $ \a ->
143
  forAll (arbitrary :: Gen [LockRequest TestLock]) $ \request ->
144
  let (state', result) = updateLocks a request state
145
  in if result == Ok S.empty
146
       then printTestCase
147
            ("Update succeeded, but in final state " ++ show state'
148
              ++ "not all locks are as requested")
149
            $ let owned = listLocks a state'
150
              in all (requestSucceeded owned) request
151
       else printTestCase
152
            ("Update failed, but state changed to " ++ show state')
153
            (state == state')
154

    
155
-- | Verify that releasing a lock always succeeds.
156
prop_LockReleaseSucceeds :: Property
157
prop_LockReleaseSucceeds =
158
  forAll (arbitrary :: Gen (LockAllocation TestLock TestOwner)) $ \state ->
159
  forAll (arbitrary :: Gen TestOwner) $ \a ->
160
  forAll (arbitrary :: Gen TestLock) $ \lock ->
161
  let (_, result) = updateLocks a [requestRelease lock] state
162
  in printTestCase
163
     ("Releasing a lock has to suceed uncondiationally, but got "
164
       ++ show result)
165
     (isOk result)
166

    
167
testSuite "Locking/Allocation"
168
 [ 'prop_LocksDisjoint
169
 , 'prop_LocksStable
170
 , 'prop_LockupdateAtomic
171
 , 'prop_LockReleaseSucceeds
172
 ]