Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (3.9 kB)

1 e3b02e1f Klaus Aehlig
{-# LANGUAGE TemplateHaskell #-}
2 e3b02e1f Klaus Aehlig
{-# OPTIONS_GHC -fno-warn-orphans #-}
3 e3b02e1f Klaus Aehlig
4 e3b02e1f Klaus Aehlig
{-| Tests for the lock data structure
5 e3b02e1f Klaus Aehlig
6 e3b02e1f Klaus Aehlig
-}
7 e3b02e1f Klaus Aehlig
8 e3b02e1f Klaus Aehlig
{-
9 e3b02e1f Klaus Aehlig
10 e3b02e1f Klaus Aehlig
Copyright (C) 2014 Google Inc.
11 e3b02e1f Klaus Aehlig
12 e3b02e1f Klaus Aehlig
This program is free software; you can redistribute it and/or modify
13 e3b02e1f Klaus Aehlig
it under the terms of the GNU General Public License as published by
14 e3b02e1f Klaus Aehlig
the Free Software Foundation; either version 2 of the License, or
15 e3b02e1f Klaus Aehlig
(at your option) any later version.
16 e3b02e1f Klaus Aehlig
17 e3b02e1f Klaus Aehlig
This program is distributed in the hope that it will be useful, but
18 e3b02e1f Klaus Aehlig
WITHOUT ANY WARRANTY; without even the implied warranty of
19 e3b02e1f Klaus Aehlig
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20 e3b02e1f Klaus Aehlig
General Public License for more details.
21 e3b02e1f Klaus Aehlig
22 e3b02e1f Klaus Aehlig
You should have received a copy of the GNU General Public License
23 e3b02e1f Klaus Aehlig
along with this program; if not, write to the Free Software
24 e3b02e1f Klaus Aehlig
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25 e3b02e1f Klaus Aehlig
02110-1301, USA.
26 e3b02e1f Klaus Aehlig
27 e3b02e1f Klaus Aehlig
-}
28 e3b02e1f Klaus Aehlig
29 e3b02e1f Klaus Aehlig
module Test.Ganeti.Locking.Locks (testLocking_Locks) where
30 e3b02e1f Klaus Aehlig
31 c211dcc4 Petr Pudlak
import Control.Applicative ((<$>), (<*>), liftA2)
32 60c4dbb9 Klaus Aehlig
import Control.Monad (liftM)
33 60c4dbb9 Klaus Aehlig
import System.Posix.Types (CPid)
34 2e1399da Klaus Aehlig
35 e3b02e1f Klaus Aehlig
import Test.QuickCheck
36 e3b02e1f Klaus Aehlig
import Text.JSON
37 e3b02e1f Klaus Aehlig
38 e3b02e1f Klaus Aehlig
import Test.Ganeti.TestHelper
39 e3b02e1f Klaus Aehlig
import Test.Ganeti.TestCommon
40 c211dcc4 Petr Pudlak
import Test.Ganeti.Types ()
41 e3b02e1f Klaus Aehlig
42 e3b02e1f Klaus Aehlig
import Ganeti.Locking.Locks
43 cf7f8e51 Klaus Aehlig
import Ganeti.Locking.Types
44 e3b02e1f Klaus Aehlig
45 e3b02e1f Klaus Aehlig
instance Arbitrary GanetiLocks where
46 2e1399da Klaus Aehlig
  arbitrary = oneof [ return BGL
47 2e1399da Klaus Aehlig
                    , return ClusterLockSet
48 2e1399da Klaus Aehlig
                    , return InstanceLockSet
49 2e1399da Klaus Aehlig
                    , Instance <$> genUUID
50 2e1399da Klaus Aehlig
                    , return NodeGroupLockSet
51 2e1399da Klaus Aehlig
                    , NodeGroup <$> genUUID
52 2e1399da Klaus Aehlig
                    , return NAL
53 2e1399da Klaus Aehlig
                    , return NodeAllocLockSet
54 2e1399da Klaus Aehlig
                    , return NodeResLockSet
55 2e1399da Klaus Aehlig
                    , NodeRes <$> genUUID
56 2e1399da Klaus Aehlig
                    , return NodeLockSet
57 2e1399da Klaus Aehlig
                    , Node <$> genUUID
58 1835fd75 Klaus Aehlig
                    , return NetworkLockSet
59 1835fd75 Klaus Aehlig
                    , Network <$> genUUID
60 2e1399da Klaus Aehlig
                    ]
61 e3b02e1f Klaus Aehlig
62 e3b02e1f Klaus Aehlig
-- | Verify that readJSON . showJSON = Ok
63 e3b02e1f Klaus Aehlig
prop_ReadShow :: Property
64 e3b02e1f Klaus Aehlig
prop_ReadShow = forAll (arbitrary :: Gen GanetiLocks) $ \a ->
65 e3b02e1f Klaus Aehlig
  readJSON (showJSON a) ==? Ok a
66 e3b02e1f Klaus Aehlig
67 cf7f8e51 Klaus Aehlig
-- | Verify the implied locks are earlier in the lock order.
68 cf7f8e51 Klaus Aehlig
prop_ImpliedOrder :: Property
69 cf7f8e51 Klaus Aehlig
prop_ImpliedOrder =
70 cf7f8e51 Klaus Aehlig
  forAll ((arbitrary :: Gen GanetiLocks)
71 cf7f8e51 Klaus Aehlig
          `suchThat` (not . null . lockImplications)) $ \b ->
72 cf7f8e51 Klaus Aehlig
  printTestCase "Implied locks must be earlier in the lock order"
73 cf7f8e51 Klaus Aehlig
  . flip all (lockImplications b) $ \a ->
74 cf7f8e51 Klaus Aehlig
  a < b
75 e3b02e1f Klaus Aehlig
76 69809ae3 Klaus Aehlig
-- | Verify the intervall property of the locks.
77 69809ae3 Klaus Aehlig
prop_ImpliedIntervall :: Property
78 69809ae3 Klaus Aehlig
prop_ImpliedIntervall =
79 69809ae3 Klaus Aehlig
  forAll ((arbitrary :: Gen GanetiLocks)
80 69809ae3 Klaus Aehlig
          `suchThat` (not . null . lockImplications)) $ \b ->
81 69809ae3 Klaus Aehlig
  forAll (elements $ lockImplications b) $ \a ->
82 69809ae3 Klaus Aehlig
  forAll (arbitrary `suchThat` liftA2 (&&) (a <) (<= b)) $ \x ->
83 69809ae3 Klaus Aehlig
  printTestCase ("Locks between a group and a member of the group"
84 69809ae3 Klaus Aehlig
                 ++ " must also belong to the group")
85 69809ae3 Klaus Aehlig
  $ a `elem` lockImplications x
86 69809ae3 Klaus Aehlig
87 0108d385 Klaus Aehlig
instance Arbitrary LockLevel where
88 0108d385 Klaus Aehlig
  arbitrary = elements [LevelCluster ..]
89 0108d385 Klaus Aehlig
90 0108d385 Klaus Aehlig
-- | Verify that readJSON . showJSON = Ok for lock levels
91 0108d385 Klaus Aehlig
prop_ReadShowLevel :: Property
92 0108d385 Klaus Aehlig
prop_ReadShowLevel = forAll (arbitrary :: Gen LockLevel) $ \a ->
93 0108d385 Klaus Aehlig
  readJSON (showJSON a) ==? Ok a
94 0108d385 Klaus Aehlig
95 d32fe318 Klaus Aehlig
instance Arbitrary ClientType where
96 d32fe318 Klaus Aehlig
  arbitrary = oneof [ ClientOther <$> arbitrary
97 d32fe318 Klaus Aehlig
                    , ClientJob <$> arbitrary
98 d32fe318 Klaus Aehlig
                    ]
99 d32fe318 Klaus Aehlig
100 d32fe318 Klaus Aehlig
-- | Verify that readJSON . showJSON = Ok for ClientType
101 d32fe318 Klaus Aehlig
prop_ReadShow_ClientType :: Property
102 d32fe318 Klaus Aehlig
prop_ReadShow_ClientType = forAll (arbitrary :: Gen ClientType) $ \a ->
103 d32fe318 Klaus Aehlig
  readJSON (showJSON a) ==? Ok a
104 d32fe318 Klaus Aehlig
105 60c4dbb9 Klaus Aehlig
instance Arbitrary CPid where
106 60c4dbb9 Klaus Aehlig
  arbitrary = liftM fromIntegral (arbitrary :: Gen Integer)
107 60c4dbb9 Klaus Aehlig
108 c211dcc4 Petr Pudlak
instance Arbitrary ClientId where
109 60c4dbb9 Klaus Aehlig
  arbitrary = ClientId <$> arbitrary <*> arbitrary <*> arbitrary
110 c211dcc4 Petr Pudlak
111 c211dcc4 Petr Pudlak
-- | Verify that readJSON . showJSON = Ok for ClientId
112 c211dcc4 Petr Pudlak
prop_ReadShow_ClientId :: Property
113 c211dcc4 Petr Pudlak
prop_ReadShow_ClientId = forAll (arbitrary :: Gen ClientId) $ \a ->
114 c211dcc4 Petr Pudlak
  readJSON (showJSON a) ==? Ok a
115 c211dcc4 Petr Pudlak
116 e3b02e1f Klaus Aehlig
testSuite "Locking/Locks"
117 e3b02e1f Klaus Aehlig
 [ 'prop_ReadShow
118 cf7f8e51 Klaus Aehlig
 , 'prop_ImpliedOrder
119 69809ae3 Klaus Aehlig
 , 'prop_ImpliedIntervall
120 0108d385 Klaus Aehlig
 , 'prop_ReadShowLevel
121 d32fe318 Klaus Aehlig
 , 'prop_ReadShow_ClientType
122 c211dcc4 Petr Pudlak
 , 'prop_ReadShow_ClientId
123 e3b02e1f Klaus Aehlig
 ]