Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / Locking / Locks.hs @ 60c4dbb9

History | View | Annotate | Download (3.9 kB)

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

    
4
{-| Tests for the lock data structure
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.Locks (testLocking_Locks) where
30

    
31
import Control.Applicative ((<$>), (<*>), liftA2)
32
import Control.Monad (liftM)
33
import System.Posix.Types (CPid)
34

    
35
import Test.QuickCheck
36
import Text.JSON
37

    
38
import Test.Ganeti.TestHelper
39
import Test.Ganeti.TestCommon
40
import Test.Ganeti.Types ()
41

    
42
import Ganeti.Locking.Locks
43
import Ganeti.Locking.Types
44

    
45
instance Arbitrary GanetiLocks where
46
  arbitrary = oneof [ return BGL
47
                    , return ClusterLockSet
48
                    , return InstanceLockSet
49
                    , Instance <$> genUUID
50
                    , return NodeGroupLockSet
51
                    , NodeGroup <$> genUUID
52
                    , return NAL
53
                    , return NodeAllocLockSet
54
                    , return NodeResLockSet
55
                    , NodeRes <$> genUUID
56
                    , return NodeLockSet
57
                    , Node <$> genUUID
58
                    , return NetworkLockSet
59
                    , Network <$> genUUID
60
                    ]
61

    
62
-- | Verify that readJSON . showJSON = Ok
63
prop_ReadShow :: Property
64
prop_ReadShow = forAll (arbitrary :: Gen GanetiLocks) $ \a ->
65
  readJSON (showJSON a) ==? Ok a
66

    
67
-- | Verify the implied locks are earlier in the lock order.
68
prop_ImpliedOrder :: Property
69
prop_ImpliedOrder =
70
  forAll ((arbitrary :: Gen GanetiLocks)
71
          `suchThat` (not . null . lockImplications)) $ \b ->
72
  printTestCase "Implied locks must be earlier in the lock order"
73
  . flip all (lockImplications b) $ \a ->
74
  a < b
75

    
76
-- | Verify the intervall property of the locks.
77
prop_ImpliedIntervall :: Property
78
prop_ImpliedIntervall =
79
  forAll ((arbitrary :: Gen GanetiLocks)
80
          `suchThat` (not . null . lockImplications)) $ \b ->
81
  forAll (elements $ lockImplications b) $ \a ->
82
  forAll (arbitrary `suchThat` liftA2 (&&) (a <) (<= b)) $ \x ->
83
  printTestCase ("Locks between a group and a member of the group"
84
                 ++ " must also belong to the group")
85
  $ a `elem` lockImplications x
86

    
87
instance Arbitrary LockLevel where
88
  arbitrary = elements [LevelCluster ..]
89

    
90
-- | Verify that readJSON . showJSON = Ok for lock levels
91
prop_ReadShowLevel :: Property
92
prop_ReadShowLevel = forAll (arbitrary :: Gen LockLevel) $ \a ->
93
  readJSON (showJSON a) ==? Ok a
94

    
95
instance Arbitrary ClientType where
96
  arbitrary = oneof [ ClientOther <$> arbitrary
97
                    , ClientJob <$> arbitrary
98
                    ]
99

    
100
-- | Verify that readJSON . showJSON = Ok for ClientType
101
prop_ReadShow_ClientType :: Property
102
prop_ReadShow_ClientType = forAll (arbitrary :: Gen ClientType) $ \a ->
103
  readJSON (showJSON a) ==? Ok a
104

    
105
instance Arbitrary CPid where
106
  arbitrary = liftM fromIntegral (arbitrary :: Gen Integer)
107

    
108
instance Arbitrary ClientId where
109
  arbitrary = ClientId <$> arbitrary <*> arbitrary <*> arbitrary
110

    
111
-- | Verify that readJSON . showJSON = Ok for ClientId
112
prop_ReadShow_ClientId :: Property
113
prop_ReadShow_ClientId = forAll (arbitrary :: Gen ClientId) $ \a ->
114
  readJSON (showJSON a) ==? Ok a
115

    
116
testSuite "Locking/Locks"
117
 [ 'prop_ReadShow
118
 , 'prop_ImpliedOrder
119
 , 'prop_ImpliedIntervall
120
 , 'prop_ReadShowLevel
121
 , 'prop_ReadShow_ClientType
122
 , 'prop_ReadShow_ClientId
123
 ]