Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / OpCodes.hs @ 560ef132

History | View | Annotate | Download (26.1 kB)

1 aed2325f Iustin Pop
{-# LANGUAGE TemplateHaskell #-}
2 aed2325f Iustin Pop
{-# OPTIONS_GHC -fno-warn-orphans #-}
3 aed2325f Iustin Pop
4 aed2325f Iustin Pop
{-| Unittests for ganeti-htools.
5 aed2325f Iustin Pop
6 aed2325f Iustin Pop
-}
7 aed2325f Iustin Pop
8 aed2325f Iustin Pop
{-
9 aed2325f Iustin Pop
10 72747d91 Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012, 2013 Google Inc.
11 aed2325f Iustin Pop
12 aed2325f Iustin Pop
This program is free software; you can redistribute it and/or modify
13 aed2325f Iustin Pop
it under the terms of the GNU General Public License as published by
14 aed2325f Iustin Pop
the Free Software Foundation; either version 2 of the License, or
15 aed2325f Iustin Pop
(at your option) any later version.
16 aed2325f Iustin Pop
17 aed2325f Iustin Pop
This program is distributed in the hope that it will be useful, but
18 aed2325f Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
19 aed2325f Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20 aed2325f Iustin Pop
General Public License for more details.
21 aed2325f Iustin Pop
22 aed2325f Iustin Pop
You should have received a copy of the GNU General Public License
23 aed2325f Iustin Pop
along with this program; if not, write to the Free Software
24 aed2325f Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25 aed2325f Iustin Pop
02110-1301, USA.
26 aed2325f Iustin Pop
27 aed2325f Iustin Pop
-}
28 aed2325f Iustin Pop
29 aed2325f Iustin Pop
module Test.Ganeti.OpCodes
30 aed2325f Iustin Pop
  ( testOpCodes
31 aed2325f Iustin Pop
  , OpCodes.OpCode(..)
32 aed2325f Iustin Pop
  ) where
33 aed2325f Iustin Pop
34 f56013fd Iustin Pop
import Test.HUnit as HUnit
35 f56013fd Iustin Pop
import Test.QuickCheck as QuickCheck
36 aed2325f Iustin Pop
37 aed2325f Iustin Pop
import Control.Applicative
38 dc4b5c42 Iustin Pop
import Control.Monad
39 dc4b5c42 Iustin Pop
import Data.Char
40 aed2325f Iustin Pop
import Data.List
41 c66f09f5 Iustin Pop
import qualified Data.Map as Map
42 aed2325f Iustin Pop
import qualified Text.JSON as J
43 8d239fa4 Iustin Pop
import Text.Printf (printf)
44 aed2325f Iustin Pop
45 aed2325f Iustin Pop
import Test.Ganeti.TestHelper
46 aed2325f Iustin Pop
import Test.Ganeti.TestCommon
47 c7d249d0 Iustin Pop
import Test.Ganeti.Types ()
48 6e94b75c Jose A. Lopes
import Test.Ganeti.Query.Language ()
49 aed2325f Iustin Pop
50 f56013fd Iustin Pop
import Ganeti.BasicTypes
51 aed2325f Iustin Pop
import qualified Ganeti.Constants as C
52 aed2325f Iustin Pop
import qualified Ganeti.OpCodes as OpCodes
53 c7d249d0 Iustin Pop
import Ganeti.Types
54 c7d249d0 Iustin Pop
import Ganeti.OpParams
55 c66f09f5 Iustin Pop
import Ganeti.JSON
56 aed2325f Iustin Pop
57 5b11f8db Iustin Pop
{-# ANN module "HLint: ignore Use camelCase" #-}
58 5b11f8db Iustin Pop
59 aed2325f Iustin Pop
-- * Arbitrary instances
60 aed2325f Iustin Pop
61 de36f091 Jose A. Lopes
instance (Ord k, Arbitrary k, Arbitrary a) => Arbitrary (Map.Map k a) where
62 de36f091 Jose A. Lopes
  arbitrary = Map.fromList <$> arbitrary
63 367c4241 Dato Simó
64 6e94b75c Jose A. Lopes
arbitraryOpTagsGet :: Gen OpCodes.OpCode
65 6e94b75c Jose A. Lopes
arbitraryOpTagsGet = do
66 6e94b75c Jose A. Lopes
  kind <- arbitrary
67 6e94b75c Jose A. Lopes
  OpCodes.OpTagsSet kind <$> arbitrary <*> genOpCodesTagName kind
68 6e94b75c Jose A. Lopes
69 6e94b75c Jose A. Lopes
arbitraryOpTagsSet :: Gen OpCodes.OpCode
70 6e94b75c Jose A. Lopes
arbitraryOpTagsSet = do
71 6e94b75c Jose A. Lopes
  kind <- arbitrary
72 6e94b75c Jose A. Lopes
  OpCodes.OpTagsSet kind <$> genTags <*> genOpCodesTagName kind
73 6e94b75c Jose A. Lopes
74 6e94b75c Jose A. Lopes
arbitraryOpTagsDel :: Gen OpCodes.OpCode
75 6e94b75c Jose A. Lopes
arbitraryOpTagsDel = do
76 6e94b75c Jose A. Lopes
  kind <- arbitrary
77 6e94b75c Jose A. Lopes
  OpCodes.OpTagsDel kind <$> genTags <*> genOpCodesTagName kind
78 6e94b75c Jose A. Lopes
79 7022db83 Iustin Pop
$(genArbitrary ''OpCodes.ReplaceDisksMode)
80 aed2325f Iustin Pop
81 6d558717 Iustin Pop
$(genArbitrary ''DiskAccess)
82 6d558717 Iustin Pop
83 f198cf91 Thomas Thrainer
$(genArbitrary ''ImportExportCompression)
84 f198cf91 Thomas Thrainer
85 aed2325f Iustin Pop
instance Arbitrary OpCodes.DiskIndex where
86 aed2325f Iustin Pop
  arbitrary = choose (0, C.maxDisks - 1) >>= OpCodes.mkDiskIndex
87 aed2325f Iustin Pop
88 5ef4fbb1 Iustin Pop
instance Arbitrary INicParams where
89 5006418e Iustin Pop
  arbitrary = INicParams <$> genMaybe genNameNE <*> genMaybe genName <*>
90 6e94b75c Jose A. Lopes
              genMaybe genNameNE <*> genMaybe genNameNE <*>
91 7295a6dc Hrvoje Ribicic
              genMaybe genNameNE <*> genMaybe genName <*>
92 6e94b75c Jose A. Lopes
              genMaybe genNameNE
93 c66f09f5 Iustin Pop
94 6d558717 Iustin Pop
instance Arbitrary IDiskParams where
95 6d558717 Iustin Pop
  arbitrary = IDiskParams <$> arbitrary <*> arbitrary <*>
96 5006418e Iustin Pop
              genMaybe genNameNE <*> genMaybe genNameNE <*>
97 2ca1b52d Klaus Aehlig
              genMaybe genNameNE <*> genMaybe genNameNE <*>
98 2e09344f Klaus Aehlig
              genMaybe genNameNE <*> arbitrary <*> genAndRestArguments
99 6d558717 Iustin Pop
100 c2d3219b Iustin Pop
instance Arbitrary RecreateDisksInfo where
101 c2d3219b Iustin Pop
  arbitrary = oneof [ pure RecreateDisksAll
102 c2d3219b Iustin Pop
                    , RecreateDisksIndices <$> arbitrary
103 c2d3219b Iustin Pop
                    , RecreateDisksParams <$> arbitrary
104 c2d3219b Iustin Pop
                    ]
105 c2d3219b Iustin Pop
106 c2d3219b Iustin Pop
instance Arbitrary DdmOldChanges where
107 c2d3219b Iustin Pop
  arbitrary = oneof [ DdmOldIndex <$> arbitrary
108 c2d3219b Iustin Pop
                    , DdmOldMod   <$> arbitrary
109 c2d3219b Iustin Pop
                    ]
110 c2d3219b Iustin Pop
111 c2d3219b Iustin Pop
instance (Arbitrary a) => Arbitrary (SetParamsMods a) where
112 c2d3219b Iustin Pop
  arbitrary = oneof [ pure SetParamsEmpty
113 c2d3219b Iustin Pop
                    , SetParamsDeprecated <$> arbitrary
114 c2d3219b Iustin Pop
                    , SetParamsNew        <$> arbitrary
115 c2d3219b Iustin Pop
                    ]
116 c2d3219b Iustin Pop
117 398e9066 Iustin Pop
instance Arbitrary ExportTarget where
118 398e9066 Iustin Pop
  arbitrary = oneof [ ExportTargetLocal <$> genNodeNameNE
119 398e9066 Iustin Pop
                    , ExportTargetRemote <$> pure []
120 398e9066 Iustin Pop
                    ]
121 398e9066 Iustin Pop
122 aed2325f Iustin Pop
instance Arbitrary OpCodes.OpCode where
123 aed2325f Iustin Pop
  arbitrary = do
124 aed2325f Iustin Pop
    op_id <- elements OpCodes.allOpIDs
125 aed2325f Iustin Pop
    case op_id of
126 aed2325f Iustin Pop
      "OP_TEST_DELAY" ->
127 7d421386 Iustin Pop
        OpCodes.OpTestDelay <$> arbitrary <*> arbitrary <*>
128 1c3231aa Thomas Thrainer
          genNodeNamesNE <*> return Nothing <*> arbitrary
129 aed2325f Iustin Pop
      "OP_INSTANCE_REPLACE_DISKS" ->
130 da4a52a3 Thomas Thrainer
        OpCodes.OpInstanceReplaceDisks <$> genFQDN <*> return Nothing <*>
131 da4a52a3 Thomas Thrainer
          arbitrary <*> arbitrary <*> arbitrary <*> genDiskIndices <*>
132 1c3231aa Thomas Thrainer
          genMaybe genNodeNameNE <*> return Nothing <*> genMaybe genNameNE
133 aed2325f Iustin Pop
      "OP_INSTANCE_FAILOVER" ->
134 da4a52a3 Thomas Thrainer
        OpCodes.OpInstanceFailover <$> genFQDN <*> return Nothing <*>
135 da4a52a3 Thomas Thrainer
        arbitrary <*> arbitrary <*> genMaybe genNodeNameNE <*>
136 1ca326c8 Thomas Thrainer
        return Nothing <*> arbitrary <*> arbitrary <*> genMaybe genNameNE
137 aed2325f Iustin Pop
      "OP_INSTANCE_MIGRATE" ->
138 da4a52a3 Thomas Thrainer
        OpCodes.OpInstanceMigrate <$> genFQDN <*> return Nothing <*>
139 da4a52a3 Thomas Thrainer
          arbitrary <*> arbitrary <*> genMaybe genNodeNameNE <*>
140 da4a52a3 Thomas Thrainer
          return Nothing <*> arbitrary <*> arbitrary <*> arbitrary <*>
141 da4a52a3 Thomas Thrainer
          genMaybe genNameNE <*> arbitrary
142 a451dae2 Iustin Pop
      "OP_TAGS_GET" ->
143 6e94b75c Jose A. Lopes
        arbitraryOpTagsGet
144 a451dae2 Iustin Pop
      "OP_TAGS_SEARCH" ->
145 a451dae2 Iustin Pop
        OpCodes.OpTagsSearch <$> genNameNE
146 3bebda52 Dato Simó
      "OP_TAGS_SET" ->
147 6e94b75c Jose A. Lopes
        arbitraryOpTagsSet
148 3bebda52 Dato Simó
      "OP_TAGS_DEL" ->
149 6e94b75c Jose A. Lopes
        arbitraryOpTagsDel
150 c66f09f5 Iustin Pop
      "OP_CLUSTER_POST_INIT" -> pure OpCodes.OpClusterPostInit
151 b3cc1646 Helga Velroyen
      "OP_CLUSTER_RENEW_CRYPTO" -> pure OpCodes.OpClusterRenewCrypto
152 c66f09f5 Iustin Pop
      "OP_CLUSTER_DESTROY" -> pure OpCodes.OpClusterDestroy
153 c66f09f5 Iustin Pop
      "OP_CLUSTER_QUERY" -> pure OpCodes.OpClusterQuery
154 c66f09f5 Iustin Pop
      "OP_CLUSTER_VERIFY" ->
155 c66f09f5 Iustin Pop
        OpCodes.OpClusterVerify <$> arbitrary <*> arbitrary <*>
156 4651c69f Jose A. Lopes
          genListSet Nothing <*> genListSet Nothing <*> arbitrary <*>
157 5006418e Iustin Pop
          genMaybe genNameNE
158 c66f09f5 Iustin Pop
      "OP_CLUSTER_VERIFY_CONFIG" ->
159 c66f09f5 Iustin Pop
        OpCodes.OpClusterVerifyConfig <$> arbitrary <*> arbitrary <*>
160 4651c69f Jose A. Lopes
          genListSet Nothing <*> arbitrary
161 c66f09f5 Iustin Pop
      "OP_CLUSTER_VERIFY_GROUP" ->
162 5ef4fbb1 Iustin Pop
        OpCodes.OpClusterVerifyGroup <$> genNameNE <*> arbitrary <*>
163 4651c69f Jose A. Lopes
          arbitrary <*> genListSet Nothing <*> genListSet Nothing <*> arbitrary
164 c66f09f5 Iustin Pop
      "OP_CLUSTER_VERIFY_DISKS" -> pure OpCodes.OpClusterVerifyDisks
165 c66f09f5 Iustin Pop
      "OP_GROUP_VERIFY_DISKS" ->
166 5ef4fbb1 Iustin Pop
        OpCodes.OpGroupVerifyDisks <$> genNameNE
167 c66f09f5 Iustin Pop
      "OP_CLUSTER_REPAIR_DISK_SIZES" ->
168 5006418e Iustin Pop
        OpCodes.OpClusterRepairDiskSizes <$> genNodeNamesNE
169 c66f09f5 Iustin Pop
      "OP_CLUSTER_CONFIG_QUERY" ->
170 5ef4fbb1 Iustin Pop
        OpCodes.OpClusterConfigQuery <$> genFieldsNE
171 c66f09f5 Iustin Pop
      "OP_CLUSTER_RENAME" ->
172 5006418e Iustin Pop
        OpCodes.OpClusterRename <$> genNameNE
173 c66f09f5 Iustin Pop
      "OP_CLUSTER_SET_PARAMS" ->
174 e5c92cfb Klaus Aehlig
        OpCodes.OpClusterSetParams <$> arbitrary <*> emptyMUD <*> emptyMUD <*>
175 6e94b75c Jose A. Lopes
          arbitrary <*> genMaybe arbitrary <*>
176 5006418e Iustin Pop
          genMaybe genEmptyContainer <*> emptyMUD <*>
177 5006418e Iustin Pop
          genMaybe genEmptyContainer <*> genMaybe genEmptyContainer <*>
178 5006418e Iustin Pop
          genMaybe genEmptyContainer <*> genMaybe arbitrary <*>
179 ad756c77 Klaus Aehlig
          genMaybe arbitrary <*>
180 c66f09f5 Iustin Pop
          arbitrary <*> arbitrary <*> arbitrary <*>
181 c66f09f5 Iustin Pop
          arbitrary <*> arbitrary <*> arbitrary <*>
182 c66f09f5 Iustin Pop
          emptyMUD <*> emptyMUD <*> arbitrary <*>
183 0359e5d0 Spyros Trigazis
          arbitrary  <*> emptyMUD <*> arbitrary <*> arbitrary <*> arbitrary <*>
184 3039e2dc Helga Velroyen
          arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*>
185 d3e6fd0e Santi Raffa
          arbitrary <*> genMaybe genName <*> genMaybe genName
186 c66f09f5 Iustin Pop
      "OP_CLUSTER_REDIST_CONF" -> pure OpCodes.OpClusterRedistConf
187 c66f09f5 Iustin Pop
      "OP_CLUSTER_ACTIVATE_MASTER_IP" ->
188 c66f09f5 Iustin Pop
        pure OpCodes.OpClusterActivateMasterIp
189 c66f09f5 Iustin Pop
      "OP_CLUSTER_DEACTIVATE_MASTER_IP" ->
190 c66f09f5 Iustin Pop
        pure OpCodes.OpClusterDeactivateMasterIp
191 c66f09f5 Iustin Pop
      "OP_QUERY" ->
192 6e94b75c Jose A. Lopes
        OpCodes.OpQuery <$> arbitrary <*> arbitrary <*> arbitrary <*>
193 6e94b75c Jose A. Lopes
        pure Nothing
194 c66f09f5 Iustin Pop
      "OP_QUERY_FIELDS" ->
195 c66f09f5 Iustin Pop
        OpCodes.OpQueryFields <$> arbitrary <*> arbitrary
196 c66f09f5 Iustin Pop
      "OP_OOB_COMMAND" ->
197 1c3231aa Thomas Thrainer
        OpCodes.OpOobCommand <$> genNodeNamesNE <*> return Nothing <*>
198 1c3231aa Thomas Thrainer
          arbitrary <*> arbitrary <*> arbitrary <*>
199 1c3231aa Thomas Thrainer
          (arbitrary `suchThat` (>0))
200 1c3231aa Thomas Thrainer
      "OP_NODE_REMOVE" ->
201 1c3231aa Thomas Thrainer
        OpCodes.OpNodeRemove <$> genNodeNameNE <*> return Nothing
202 c66f09f5 Iustin Pop
      "OP_NODE_ADD" ->
203 5ef4fbb1 Iustin Pop
        OpCodes.OpNodeAdd <$> genNodeNameNE <*> emptyMUD <*> emptyMUD <*>
204 5cbf7832 Jose A. Lopes
          genMaybe genNameNE <*> genMaybe genNameNE <*> arbitrary <*>
205 5006418e Iustin Pop
          genMaybe genNameNE <*> arbitrary <*> arbitrary <*> emptyMUD
206 c66f09f5 Iustin Pop
      "OP_NODE_QUERYVOLS" ->
207 c66f09f5 Iustin Pop
        OpCodes.OpNodeQueryvols <$> arbitrary <*> genNodeNamesNE
208 c66f09f5 Iustin Pop
      "OP_NODE_QUERY_STORAGE" ->
209 c66f09f5 Iustin Pop
        OpCodes.OpNodeQueryStorage <$> arbitrary <*> arbitrary <*>
210 6e94b75c Jose A. Lopes
          genNodeNamesNE <*> genMaybe genNameNE
211 c66f09f5 Iustin Pop
      "OP_NODE_MODIFY_STORAGE" ->
212 1c3231aa Thomas Thrainer
        OpCodes.OpNodeModifyStorage <$> genNodeNameNE <*> return Nothing <*>
213 6e94b75c Jose A. Lopes
          arbitrary <*> genMaybe genNameNE <*> pure emptyJSObject
214 c66f09f5 Iustin Pop
      "OP_REPAIR_NODE_STORAGE" ->
215 1c3231aa Thomas Thrainer
        OpCodes.OpRepairNodeStorage <$> genNodeNameNE <*> return Nothing <*>
216 6e94b75c Jose A. Lopes
          arbitrary <*> genMaybe genNameNE <*> arbitrary
217 c66f09f5 Iustin Pop
      "OP_NODE_SET_PARAMS" ->
218 1c3231aa Thomas Thrainer
        OpCodes.OpNodeSetParams <$> genNodeNameNE <*> return Nothing <*>
219 1c3231aa Thomas Thrainer
          arbitrary <*> emptyMUD <*> emptyMUD <*> arbitrary <*> arbitrary <*>
220 1c3231aa Thomas Thrainer
          arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*>
221 1c3231aa Thomas Thrainer
          genMaybe genNameNE <*> emptyMUD <*> arbitrary
222 c66f09f5 Iustin Pop
      "OP_NODE_POWERCYCLE" ->
223 1c3231aa Thomas Thrainer
        OpCodes.OpNodePowercycle <$> genNodeNameNE <*> return Nothing <*>
224 1c3231aa Thomas Thrainer
          arbitrary
225 c66f09f5 Iustin Pop
      "OP_NODE_MIGRATE" ->
226 1c3231aa Thomas Thrainer
        OpCodes.OpNodeMigrate <$> genNodeNameNE <*> return Nothing <*>
227 1c3231aa Thomas Thrainer
          arbitrary <*> arbitrary <*> genMaybe genNodeNameNE <*>
228 1c3231aa Thomas Thrainer
          return Nothing <*> arbitrary <*> arbitrary <*> genMaybe genNameNE
229 c66f09f5 Iustin Pop
      "OP_NODE_EVACUATE" ->
230 c66f09f5 Iustin Pop
        OpCodes.OpNodeEvacuate <$> arbitrary <*> genNodeNameNE <*>
231 1c3231aa Thomas Thrainer
          return Nothing <*> genMaybe genNodeNameNE <*> return Nothing <*>
232 1c3231aa Thomas Thrainer
          genMaybe genNameNE <*> arbitrary
233 6d558717 Iustin Pop
      "OP_INSTANCE_CREATE" ->
234 5006418e Iustin Pop
        OpCodes.OpInstanceCreate <$> genFQDN <*> arbitrary <*>
235 6d558717 Iustin Pop
          arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*>
236 6e94b75c Jose A. Lopes
          pure emptyJSObject <*> arbitrary <*> arbitrary <*> arbitrary <*>
237 6e94b75c Jose A. Lopes
          genMaybe genNameNE <*> pure emptyJSObject <*> arbitrary <*>
238 6e94b75c Jose A. Lopes
          genMaybe genNameNE <*> arbitrary <*> arbitrary <*> arbitrary <*>
239 6e94b75c Jose A. Lopes
          arbitrary <*> arbitrary <*> arbitrary <*> pure emptyJSObject <*>
240 6e94b75c Jose A. Lopes
          genMaybe genNameNE <*> genMaybe genNodeNameNE <*> return Nothing <*>
241 6e94b75c Jose A. Lopes
          genMaybe genNodeNameNE <*> return Nothing <*> genMaybe (pure []) <*>
242 6e94b75c Jose A. Lopes
          genMaybe genNodeNameNE <*> arbitrary <*> genMaybe genNodeNameNE <*>
243 6e94b75c Jose A. Lopes
          return Nothing <*> genMaybe genNodeNameNE <*> genMaybe genNameNE <*>
244 015f1517 Jose A. Lopes
          arbitrary <*> arbitrary <*> (genTags >>= mapM mkNonEmpty) <*>
245 015f1517 Jose A. Lopes
          arbitrary
246 c2d3219b Iustin Pop
      "OP_INSTANCE_MULTI_ALLOC" ->
247 6e94b75c Jose A. Lopes
        OpCodes.OpInstanceMultiAlloc <$> arbitrary <*> genMaybe genNameNE <*>
248 6e94b75c Jose A. Lopes
        pure []
249 c2d3219b Iustin Pop
      "OP_INSTANCE_REINSTALL" ->
250 da4a52a3 Thomas Thrainer
        OpCodes.OpInstanceReinstall <$> genFQDN <*> return Nothing <*>
251 da4a52a3 Thomas Thrainer
          arbitrary <*> genMaybe genNameNE <*> genMaybe (pure emptyJSObject)
252 c2d3219b Iustin Pop
      "OP_INSTANCE_REMOVE" ->
253 da4a52a3 Thomas Thrainer
        OpCodes.OpInstanceRemove <$> genFQDN <*> return Nothing <*>
254 c2d3219b Iustin Pop
          arbitrary <*> arbitrary
255 da4a52a3 Thomas Thrainer
      "OP_INSTANCE_RENAME" ->
256 da4a52a3 Thomas Thrainer
        OpCodes.OpInstanceRename <$> genFQDN <*> return Nothing <*>
257 da4a52a3 Thomas Thrainer
          genNodeNameNE <*> arbitrary <*> arbitrary
258 c2d3219b Iustin Pop
      "OP_INSTANCE_STARTUP" ->
259 da4a52a3 Thomas Thrainer
        OpCodes.OpInstanceStartup <$> genFQDN <*> return Nothing <*>
260 da4a52a3 Thomas Thrainer
          arbitrary <*> arbitrary <*> pure emptyJSObject <*>
261 da4a52a3 Thomas Thrainer
          pure emptyJSObject <*> arbitrary <*> arbitrary
262 c2d3219b Iustin Pop
      "OP_INSTANCE_SHUTDOWN" ->
263 da4a52a3 Thomas Thrainer
        OpCodes.OpInstanceShutdown <$> genFQDN <*> return Nothing <*>
264 da4a52a3 Thomas Thrainer
          arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
265 c2d3219b Iustin Pop
      "OP_INSTANCE_REBOOT" ->
266 da4a52a3 Thomas Thrainer
        OpCodes.OpInstanceReboot <$> genFQDN <*> return Nothing <*>
267 da4a52a3 Thomas Thrainer
          arbitrary <*> arbitrary <*> arbitrary
268 c2d3219b Iustin Pop
      "OP_INSTANCE_MOVE" ->
269 da4a52a3 Thomas Thrainer
        OpCodes.OpInstanceMove <$> genFQDN <*> return Nothing <*>
270 da4a52a3 Thomas Thrainer
          arbitrary <*> arbitrary <*> genNodeNameNE <*> return Nothing <*>
271 f198cf91 Thomas Thrainer
          arbitrary <*> arbitrary
272 da4a52a3 Thomas Thrainer
      "OP_INSTANCE_CONSOLE" -> OpCodes.OpInstanceConsole <$> genFQDN <*>
273 da4a52a3 Thomas Thrainer
          return Nothing
274 c2d3219b Iustin Pop
      "OP_INSTANCE_ACTIVATE_DISKS" ->
275 da4a52a3 Thomas Thrainer
        OpCodes.OpInstanceActivateDisks <$> genFQDN <*> return Nothing <*>
276 c2d3219b Iustin Pop
          arbitrary <*> arbitrary
277 c2d3219b Iustin Pop
      "OP_INSTANCE_DEACTIVATE_DISKS" ->
278 da4a52a3 Thomas Thrainer
        OpCodes.OpInstanceDeactivateDisks <$> genFQDN <*> return Nothing <*>
279 da4a52a3 Thomas Thrainer
          arbitrary
280 c2d3219b Iustin Pop
      "OP_INSTANCE_RECREATE_DISKS" ->
281 da4a52a3 Thomas Thrainer
        OpCodes.OpInstanceRecreateDisks <$> genFQDN <*> return Nothing <*>
282 da4a52a3 Thomas Thrainer
          arbitrary <*> genNodeNamesNE <*> return Nothing <*>
283 da4a52a3 Thomas Thrainer
          genMaybe genNameNE
284 c2d3219b Iustin Pop
      "OP_INSTANCE_QUERY_DATA" ->
285 c2d3219b Iustin Pop
        OpCodes.OpInstanceQueryData <$> arbitrary <*>
286 c2d3219b Iustin Pop
          genNodeNamesNE <*> arbitrary
287 c2d3219b Iustin Pop
      "OP_INSTANCE_SET_PARAMS" ->
288 da4a52a3 Thomas Thrainer
        OpCodes.OpInstanceSetParams <$> genFQDN <*> return Nothing <*>
289 c2d3219b Iustin Pop
          arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*>
290 da4a52a3 Thomas Thrainer
          arbitrary <*> pure emptyJSObject <*> arbitrary <*>
291 da4a52a3 Thomas Thrainer
          pure emptyJSObject <*> arbitrary <*> genMaybe genNodeNameNE <*>
292 da4a52a3 Thomas Thrainer
          return Nothing <*> genMaybe genNodeNameNE <*> return Nothing <*>
293 d2204b1a Klaus Aehlig
          genMaybe genNameNE <*> pure emptyJSObject <*> arbitrary <*>
294 96ed3a3e Dimitris Aragiorgis
          arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
295 c2d3219b Iustin Pop
      "OP_INSTANCE_GROW_DISK" ->
296 da4a52a3 Thomas Thrainer
        OpCodes.OpInstanceGrowDisk <$> genFQDN <*> return Nothing <*>
297 da4a52a3 Thomas Thrainer
          arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
298 c2d3219b Iustin Pop
      "OP_INSTANCE_CHANGE_GROUP" ->
299 da4a52a3 Thomas Thrainer
        OpCodes.OpInstanceChangeGroup <$> genFQDN <*> return Nothing <*>
300 da4a52a3 Thomas Thrainer
          arbitrary <*> genMaybe genNameNE <*>
301 da4a52a3 Thomas Thrainer
          genMaybe (resize maxNodes (listOf genNameNE))
302 398e9066 Iustin Pop
      "OP_GROUP_ADD" ->
303 398e9066 Iustin Pop
        OpCodes.OpGroupAdd <$> genNameNE <*> arbitrary <*>
304 5006418e Iustin Pop
          emptyMUD <*> genMaybe genEmptyContainer <*>
305 398e9066 Iustin Pop
          emptyMUD <*> emptyMUD <*> emptyMUD
306 398e9066 Iustin Pop
      "OP_GROUP_ASSIGN_NODES" ->
307 398e9066 Iustin Pop
        OpCodes.OpGroupAssignNodes <$> genNameNE <*> arbitrary <*>
308 1c3231aa Thomas Thrainer
          genNodeNamesNE <*> return Nothing
309 398e9066 Iustin Pop
      "OP_GROUP_SET_PARAMS" ->
310 398e9066 Iustin Pop
        OpCodes.OpGroupSetParams <$> genNameNE <*> arbitrary <*>
311 5006418e Iustin Pop
          emptyMUD <*> genMaybe genEmptyContainer <*>
312 398e9066 Iustin Pop
          emptyMUD <*> emptyMUD <*> emptyMUD
313 398e9066 Iustin Pop
      "OP_GROUP_REMOVE" ->
314 398e9066 Iustin Pop
        OpCodes.OpGroupRemove <$> genNameNE
315 398e9066 Iustin Pop
      "OP_GROUP_RENAME" ->
316 398e9066 Iustin Pop
        OpCodes.OpGroupRename <$> genNameNE <*> genNameNE
317 398e9066 Iustin Pop
      "OP_GROUP_EVACUATE" ->
318 398e9066 Iustin Pop
        OpCodes.OpGroupEvacuate <$> genNameNE <*> arbitrary <*>
319 5006418e Iustin Pop
          genMaybe genNameNE <*> genMaybe genNamesNE
320 398e9066 Iustin Pop
      "OP_OS_DIAGNOSE" ->
321 398e9066 Iustin Pop
        OpCodes.OpOsDiagnose <$> genFieldsNE <*> genNamesNE
322 b954f097 Constantinos Venetsanopoulos
      "OP_EXT_STORAGE_DIAGNOSE" ->
323 b954f097 Constantinos Venetsanopoulos
        OpCodes.OpOsDiagnose <$> genFieldsNE <*> genNamesNE
324 398e9066 Iustin Pop
      "OP_BACKUP_PREPARE" ->
325 da4a52a3 Thomas Thrainer
        OpCodes.OpBackupPrepare <$> genFQDN <*> return Nothing <*> arbitrary
326 398e9066 Iustin Pop
      "OP_BACKUP_EXPORT" ->
327 da4a52a3 Thomas Thrainer
        OpCodes.OpBackupExport <$> genFQDN <*> return Nothing <*>
328 896cc964 Thomas Thrainer
          arbitrary <*> arbitrary <*> arbitrary <*> return Nothing <*>
329 896cc964 Thomas Thrainer
          arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*>
330 896cc964 Thomas Thrainer
          genMaybe (pure []) <*> genMaybe genNameNE
331 398e9066 Iustin Pop
      "OP_BACKUP_REMOVE" ->
332 da4a52a3 Thomas Thrainer
        OpCodes.OpBackupRemove <$> genFQDN <*> return Nothing
333 a3f02317 Iustin Pop
      "OP_TEST_ALLOCATOR" ->
334 a3f02317 Iustin Pop
        OpCodes.OpTestAllocator <$> arbitrary <*> arbitrary <*>
335 6e94b75c Jose A. Lopes
          genNameNE <*> genMaybe (pure []) <*> genMaybe (pure []) <*>
336 5006418e Iustin Pop
          arbitrary <*> genMaybe genNameNE <*>
337 a3f02317 Iustin Pop
          (genTags >>= mapM mkNonEmpty) <*>
338 5006418e Iustin Pop
          arbitrary <*> arbitrary <*> genMaybe genNameNE <*>
339 5006418e Iustin Pop
          arbitrary <*> genMaybe genNodeNamesNE <*> arbitrary <*>
340 5006418e Iustin Pop
          genMaybe genNamesNE <*> arbitrary <*> arbitrary
341 a3f02317 Iustin Pop
      "OP_TEST_JQUEUE" ->
342 a3f02317 Iustin Pop
        OpCodes.OpTestJqueue <$> arbitrary <*> arbitrary <*>
343 5006418e Iustin Pop
          resize 20 (listOf genFQDN) <*> arbitrary
344 a3f02317 Iustin Pop
      "OP_TEST_DUMMY" ->
345 a3f02317 Iustin Pop
        OpCodes.OpTestDummy <$> pure J.JSNull <*> pure J.JSNull <*>
346 a3f02317 Iustin Pop
          pure J.JSNull <*> pure J.JSNull
347 8d239fa4 Iustin Pop
      "OP_NETWORK_ADD" ->
348 6e94b75c Jose A. Lopes
        OpCodes.OpNetworkAdd <$> genNameNE <*> genIPv4Network <*>
349 6e94b75c Jose A. Lopes
          genMaybe genIPv4Address <*> pure Nothing <*> pure Nothing <*>
350 6e94b75c Jose A. Lopes
          genMaybe genMacPrefix <*> genMaybe (listOf genIPv4Address) <*>
351 1dbceab9 Iustin Pop
          arbitrary <*> (genTags >>= mapM mkNonEmpty)
352 8d239fa4 Iustin Pop
      "OP_NETWORK_REMOVE" ->
353 8d239fa4 Iustin Pop
        OpCodes.OpNetworkRemove <$> genNameNE <*> arbitrary
354 8d239fa4 Iustin Pop
      "OP_NETWORK_SET_PARAMS" ->
355 5cfa6c37 Dimitris Aragiorgis
        OpCodes.OpNetworkSetParams <$> genNameNE <*>
356 6e94b75c Jose A. Lopes
          genMaybe genIPv4Address <*> pure Nothing <*> pure Nothing <*>
357 6e94b75c Jose A. Lopes
          genMaybe genMacPrefix <*> genMaybe (listOf genIPv4Address) <*>
358 6e94b75c Jose A. Lopes
          genMaybe (listOf genIPv4Address)
359 8d239fa4 Iustin Pop
      "OP_NETWORK_CONNECT" ->
360 8d239fa4 Iustin Pop
        OpCodes.OpNetworkConnect <$> genNameNE <*> genNameNE <*>
361 8d239fa4 Iustin Pop
          arbitrary <*> genNameNE <*> arbitrary
362 8d239fa4 Iustin Pop
      "OP_NETWORK_DISCONNECT" ->
363 0ae4b355 Helga Velroyen
        OpCodes.OpNetworkDisconnect <$> genNameNE <*> genNameNE
364 1cd563e2 Iustin Pop
      "OP_RESTRICTED_COMMAND" ->
365 1cd563e2 Iustin Pop
        OpCodes.OpRestrictedCommand <$> arbitrary <*> genNodeNamesNE <*>
366 1c3231aa Thomas Thrainer
          return Nothing <*> genNameNE
367 c66f09f5 Iustin Pop
      _ -> fail $ "Undefined arbitrary for opcode " ++ op_id
368 aed2325f Iustin Pop
369 516a0e94 Michele Tartara
-- | Generates one element of a reason trail
370 516a0e94 Michele Tartara
genReasonElem :: Gen ReasonElem
371 516a0e94 Michele Tartara
genReasonElem = (,,) <$> genFQDN <*> genFQDN <*> arbitrary
372 516a0e94 Michele Tartara
373 516a0e94 Michele Tartara
-- | Generates a reason trail
374 516a0e94 Michele Tartara
genReasonTrail :: Gen ReasonTrail
375 516a0e94 Michele Tartara
genReasonTrail = do
376 516a0e94 Michele Tartara
  size <- choose (0, 10)
377 516a0e94 Michele Tartara
  vectorOf size genReasonElem
378 516a0e94 Michele Tartara
379 4a826364 Iustin Pop
instance Arbitrary OpCodes.CommonOpParams where
380 4a826364 Iustin Pop
  arbitrary = OpCodes.CommonOpParams <$> arbitrary <*> arbitrary <*>
381 516a0e94 Michele Tartara
                arbitrary <*> resize 5 arbitrary <*> genMaybe genName <*>
382 516a0e94 Michele Tartara
                genReasonTrail
383 4a826364 Iustin Pop
384 c7d249d0 Iustin Pop
-- * Helper functions
385 c7d249d0 Iustin Pop
386 c66f09f5 Iustin Pop
-- | Empty JSObject.
387 c66f09f5 Iustin Pop
emptyJSObject :: J.JSObject J.JSValue
388 c66f09f5 Iustin Pop
emptyJSObject = J.toJSObject []
389 c66f09f5 Iustin Pop
390 c66f09f5 Iustin Pop
-- | Empty maybe unchecked dictionary.
391 c66f09f5 Iustin Pop
emptyMUD :: Gen (Maybe (J.JSObject J.JSValue))
392 5006418e Iustin Pop
emptyMUD = genMaybe $ pure emptyJSObject
393 c66f09f5 Iustin Pop
394 c66f09f5 Iustin Pop
-- | Generates an empty container.
395 c66f09f5 Iustin Pop
genEmptyContainer :: (Ord a) => Gen (GenericContainer a b)
396 c66f09f5 Iustin Pop
genEmptyContainer = pure . GenericContainer $ Map.fromList []
397 c66f09f5 Iustin Pop
398 c7d249d0 Iustin Pop
-- | Generates list of disk indices.
399 c7d249d0 Iustin Pop
genDiskIndices :: Gen [DiskIndex]
400 c7d249d0 Iustin Pop
genDiskIndices = do
401 c7d249d0 Iustin Pop
  cnt <- choose (0, C.maxDisks)
402 df8578fb Iustin Pop
  genUniquesList cnt arbitrary
403 c7d249d0 Iustin Pop
404 c7d249d0 Iustin Pop
-- | Generates a list of node names.
405 c7d249d0 Iustin Pop
genNodeNames :: Gen [String]
406 5006418e Iustin Pop
genNodeNames = resize maxNodes (listOf genFQDN)
407 c7d249d0 Iustin Pop
408 c66f09f5 Iustin Pop
-- | Generates a list of node names in non-empty string type.
409 c66f09f5 Iustin Pop
genNodeNamesNE :: Gen [NonEmptyString]
410 417ab39c Iustin Pop
genNodeNamesNE = genNodeNames >>= mapM mkNonEmpty
411 c66f09f5 Iustin Pop
412 c7d249d0 Iustin Pop
-- | Gets a node name in non-empty type.
413 c7d249d0 Iustin Pop
genNodeNameNE :: Gen NonEmptyString
414 5006418e Iustin Pop
genNodeNameNE = genFQDN >>= mkNonEmpty
415 c7d249d0 Iustin Pop
416 5ef4fbb1 Iustin Pop
-- | Gets a name (non-fqdn) in non-empty type.
417 5ef4fbb1 Iustin Pop
genNameNE :: Gen NonEmptyString
418 5006418e Iustin Pop
genNameNE = genName >>= mkNonEmpty
419 5ef4fbb1 Iustin Pop
420 398e9066 Iustin Pop
-- | Gets a list of names (non-fqdn) in non-empty type.
421 398e9066 Iustin Pop
genNamesNE :: Gen [NonEmptyString]
422 398e9066 Iustin Pop
genNamesNE = resize maxNodes (listOf genNameNE)
423 398e9066 Iustin Pop
424 5ef4fbb1 Iustin Pop
-- | Returns a list of non-empty fields.
425 5ef4fbb1 Iustin Pop
genFieldsNE :: Gen [NonEmptyString]
426 5006418e Iustin Pop
genFieldsNE = genFields >>= mapM mkNonEmpty
427 5ef4fbb1 Iustin Pop
428 8d239fa4 Iustin Pop
-- | Generate a 3-byte MAC prefix.
429 8d239fa4 Iustin Pop
genMacPrefix :: Gen NonEmptyString
430 8d239fa4 Iustin Pop
genMacPrefix = do
431 8d239fa4 Iustin Pop
  octets <- vectorOf 3 $ choose (0::Int, 255)
432 8d239fa4 Iustin Pop
  mkNonEmpty . intercalate ":" $ map (printf "%02x") octets
433 8d239fa4 Iustin Pop
434 4884f187 Santi Raffa
-- | JSObject of arbitrary data.
435 4884f187 Santi Raffa
--
436 4884f187 Santi Raffa
-- Since JSValue does not implement Arbitrary, I'll simply generate
437 4884f187 Santi Raffa
-- (String, String) objects.
438 4884f187 Santi Raffa
arbitraryPrivateJSObj :: Gen (J.JSObject (Private J.JSValue))
439 4884f187 Santi Raffa
arbitraryPrivateJSObj =
440 4884f187 Santi Raffa
  constructor <$> (fromNonEmpty <$> genNameNE)
441 4884f187 Santi Raffa
              <*> (fromNonEmpty <$> genNameNE)
442 4884f187 Santi Raffa
    where constructor k v = showPrivateJSObject [(k, v)]
443 4884f187 Santi Raffa
444 4a826364 Iustin Pop
-- | Arbitrary instance for MetaOpCode, defined here due to TH ordering.
445 4a826364 Iustin Pop
$(genArbitrary ''OpCodes.MetaOpCode)
446 4a826364 Iustin Pop
447 f56013fd Iustin Pop
-- | Small helper to check for a failed JSON deserialisation
448 f56013fd Iustin Pop
isJsonError :: J.Result a -> Bool
449 f56013fd Iustin Pop
isJsonError (J.Error _) = True
450 f56013fd Iustin Pop
isJsonError _           = False
451 f56013fd Iustin Pop
452 aed2325f Iustin Pop
-- * Test cases
453 aed2325f Iustin Pop
454 aed2325f Iustin Pop
-- | Check that opcode serialization is idempotent.
455 20bc5360 Iustin Pop
prop_serialization :: OpCodes.OpCode -> Property
456 63b068c1 Iustin Pop
prop_serialization = testSerialisation
457 aed2325f Iustin Pop
458 aed2325f Iustin Pop
-- | Check that Python and Haskell defined the same opcode list.
459 20bc5360 Iustin Pop
case_AllDefined :: HUnit.Assertion
460 20bc5360 Iustin Pop
case_AllDefined = do
461 d31193c3 Jose A. Lopes
  py_stdout <-
462 d31193c3 Jose A. Lopes
     runPython "from ganeti import opcodes\n\
463 d31193c3 Jose A. Lopes
               \from ganeti import serializer\n\
464 d31193c3 Jose A. Lopes
               \import sys\n\
465 6e94b75c Jose A. Lopes
               \print serializer.Dump([opid for opid in opcodes.OP_MAPPING])\n"
466 6e94b75c Jose A. Lopes
               ""
467 d31193c3 Jose A. Lopes
     >>= checkPythonResult
468 d31193c3 Jose A. Lopes
  py_ops <- case J.decode py_stdout::J.Result [String] of
469 d31193c3 Jose A. Lopes
               J.Ok ops -> return ops
470 d31193c3 Jose A. Lopes
               J.Error msg ->
471 d31193c3 Jose A. Lopes
                 HUnit.assertFailure ("Unable to decode opcode names: " ++ msg)
472 d31193c3 Jose A. Lopes
                 -- this already raised an expection, but we need it
473 d31193c3 Jose A. Lopes
                 -- for proper types
474 d31193c3 Jose A. Lopes
                 >> fail "Unable to decode opcode names"
475 d31193c3 Jose A. Lopes
  let hs_ops = sort OpCodes.allOpIDs
476 9b773665 Iustin Pop
      extra_py = py_ops \\ hs_ops
477 aed2325f Iustin Pop
      extra_hs = hs_ops \\ py_ops
478 9b773665 Iustin Pop
  HUnit.assertBool ("Missing OpCodes from the Haskell code:\n" ++
479 9b773665 Iustin Pop
                    unlines extra_py) (null extra_py)
480 aed2325f Iustin Pop
  HUnit.assertBool ("Extra OpCodes in the Haskell code code:\n" ++
481 aed2325f Iustin Pop
                    unlines extra_hs) (null extra_hs)
482 aed2325f Iustin Pop
483 aed2325f Iustin Pop
-- | Custom HUnit test case that forks a Python process and checks
484 aed2325f Iustin Pop
-- correspondence between Haskell-generated OpCodes and their Python
485 aed2325f Iustin Pop
-- decoded, validated and re-encoded version.
486 aed2325f Iustin Pop
--
487 aed2325f Iustin Pop
-- Note that we have a strange beast here: since launching Python is
488 aed2325f Iustin Pop
-- expensive, we don't do this via a usual QuickProperty, since that's
489 aed2325f Iustin Pop
-- slow (I've tested it, and it's indeed quite slow). Rather, we use a
490 aed2325f Iustin Pop
-- single HUnit assertion, and in it we manually use QuickCheck to
491 aed2325f Iustin Pop
-- generate 500 opcodes times the number of defined opcodes, which
492 aed2325f Iustin Pop
-- then we pass in bulk to Python. The drawbacks to this method are
493 aed2325f Iustin Pop
-- two fold: we cannot control the number of generated opcodes, since
494 aed2325f Iustin Pop
-- HUnit assertions don't get access to the test options, and for the
495 aed2325f Iustin Pop
-- same reason we can't run a repeatable seed. We should probably find
496 aed2325f Iustin Pop
-- a better way to do this, for example by having a
497 aed2325f Iustin Pop
-- separately-launched Python process (if not running the tests would
498 aed2325f Iustin Pop
-- be skipped).
499 d1ac695f Iustin Pop
case_py_compat_types :: HUnit.Assertion
500 d1ac695f Iustin Pop
case_py_compat_types = do
501 086ad4cf Iustin Pop
  let num_opcodes = length OpCodes.allOpIDs * 100
502 72747d91 Iustin Pop
  opcodes <- genSample (vectorOf num_opcodes
503 72747d91 Iustin Pop
                                   (arbitrary::Gen OpCodes.MetaOpCode))
504 72747d91 Iustin Pop
  let with_sum = map (\o -> (OpCodes.opSummary $
505 ad1c1e41 Iustin Pop
                             OpCodes.metaOpCode o, o)) opcodes
506 aed2325f Iustin Pop
      serialized = J.encode opcodes
507 dc4b5c42 Iustin Pop
  -- check for non-ASCII fields, usually due to 'arbitrary :: String'
508 dc4b5c42 Iustin Pop
  mapM_ (\op -> when (any (not . isAscii) (J.encode op)) .
509 dc4b5c42 Iustin Pop
                HUnit.assertFailure $
510 dc4b5c42 Iustin Pop
                  "OpCode has non-ASCII fields: " ++ show op
511 dc4b5c42 Iustin Pop
        ) opcodes
512 aed2325f Iustin Pop
  py_stdout <-
513 aed2325f Iustin Pop
     runPython "from ganeti import opcodes\n\
514 aed2325f Iustin Pop
               \from ganeti import serializer\n\
515 6e94b75c Jose A. Lopes
               \import sys\n\
516 aed2325f Iustin Pop
               \op_data = serializer.Load(sys.stdin.read())\n\
517 aed2325f Iustin Pop
               \decoded = [opcodes.OpCode.LoadOpCode(o) for o in op_data]\n\
518 aed2325f Iustin Pop
               \for op in decoded:\n\
519 aed2325f Iustin Pop
               \  op.Validate(True)\n\
520 ad1c1e41 Iustin Pop
               \encoded = [(op.Summary(), op.__getstate__())\n\
521 ad1c1e41 Iustin Pop
               \           for op in decoded]\n\
522 560ef132 Santi Raffa
               \print serializer.Dump(\
523 560ef132 Santi Raffa
               \  encoded,\
524 560ef132 Santi Raffa
               \  private_encoder=serializer.EncodeWithPrivateFields)"
525 560ef132 Santi Raffa
               serialized
526 aed2325f Iustin Pop
     >>= checkPythonResult
527 ad1c1e41 Iustin Pop
  let deserialised =
528 ad1c1e41 Iustin Pop
        J.decode py_stdout::J.Result [(String, OpCodes.MetaOpCode)]
529 aed2325f Iustin Pop
  decoded <- case deserialised of
530 aed2325f Iustin Pop
               J.Ok ops -> return ops
531 aed2325f Iustin Pop
               J.Error msg ->
532 aed2325f Iustin Pop
                 HUnit.assertFailure ("Unable to decode opcodes: " ++ msg)
533 aed2325f Iustin Pop
                 -- this already raised an expection, but we need it
534 aed2325f Iustin Pop
                 -- for proper types
535 aed2325f Iustin Pop
                 >> fail "Unable to decode opcodes"
536 aed2325f Iustin Pop
  HUnit.assertEqual "Mismatch in number of returned opcodes"
537 ad1c1e41 Iustin Pop
    (length decoded) (length with_sum)
538 aed2325f Iustin Pop
  mapM_ (uncurry (HUnit.assertEqual "Different result after encoding/decoding")
539 9d929656 Santi Raffa
        ) $ zip with_sum decoded
540 aed2325f Iustin Pop
541 d1ac695f Iustin Pop
-- | Custom HUnit test case that forks a Python process and checks
542 d1ac695f Iustin Pop
-- correspondence between Haskell OpCodes fields and their Python
543 d1ac695f Iustin Pop
-- equivalent.
544 d1ac695f Iustin Pop
case_py_compat_fields :: HUnit.Assertion
545 d1ac695f Iustin Pop
case_py_compat_fields = do
546 d1ac695f Iustin Pop
  let hs_fields = sort $ map (\op_id -> (op_id, OpCodes.allOpFields op_id))
547 d1ac695f Iustin Pop
                         OpCodes.allOpIDs
548 d1ac695f Iustin Pop
  py_stdout <-
549 d1ac695f Iustin Pop
     runPython "from ganeti import opcodes\n\
550 d1ac695f Iustin Pop
               \import sys\n\
551 d1ac695f Iustin Pop
               \from ganeti import serializer\n\
552 d1ac695f Iustin Pop
               \fields = [(k, sorted([p[0] for p in v.OP_PARAMS]))\n\
553 d1ac695f Iustin Pop
               \           for k, v in opcodes.OP_MAPPING.items()]\n\
554 d1ac695f Iustin Pop
               \print serializer.Dump(fields)" ""
555 d1ac695f Iustin Pop
     >>= checkPythonResult
556 d1ac695f Iustin Pop
  let deserialised = J.decode py_stdout::J.Result [(String, [String])]
557 d1ac695f Iustin Pop
  py_fields <- case deserialised of
558 d1ac695f Iustin Pop
                 J.Ok v -> return $ sort v
559 d1ac695f Iustin Pop
                 J.Error msg ->
560 d1ac695f Iustin Pop
                   HUnit.assertFailure ("Unable to decode op fields: " ++ msg)
561 d1ac695f Iustin Pop
                   -- this already raised an expection, but we need it
562 d1ac695f Iustin Pop
                   -- for proper types
563 d1ac695f Iustin Pop
                   >> fail "Unable to decode op fields"
564 d1ac695f Iustin Pop
  HUnit.assertEqual "Mismatch in number of returned opcodes"
565 d1ac695f Iustin Pop
    (length hs_fields) (length py_fields)
566 d1ac695f Iustin Pop
  HUnit.assertEqual "Mismatch in defined OP_IDs"
567 d1ac695f Iustin Pop
    (map fst hs_fields) (map fst py_fields)
568 d1ac695f Iustin Pop
  mapM_ (\((py_id, py_flds), (hs_id, hs_flds)) -> do
569 d1ac695f Iustin Pop
           HUnit.assertEqual "Mismatch in OP_ID" py_id hs_id
570 d1ac695f Iustin Pop
           HUnit.assertEqual ("Mismatch in fields for " ++ hs_id)
571 d1ac695f Iustin Pop
             py_flds hs_flds
572 9d929656 Santi Raffa
        ) $ zip hs_fields py_fields
573 d1ac695f Iustin Pop
574 4a826364 Iustin Pop
-- | Checks that setOpComment works correctly.
575 4a826364 Iustin Pop
prop_setOpComment :: OpCodes.MetaOpCode -> String -> Property
576 4a826364 Iustin Pop
prop_setOpComment op comment =
577 4a826364 Iustin Pop
  let (OpCodes.MetaOpCode common _) = OpCodes.setOpComment comment op
578 4a826364 Iustin Pop
  in OpCodes.opComment common ==? Just comment
579 4a826364 Iustin Pop
580 f56013fd Iustin Pop
-- | Tests wrong (negative) disk index.
581 f56013fd Iustin Pop
prop_mkDiskIndex_fail :: QuickCheck.Positive Int -> Property
582 f56013fd Iustin Pop
prop_mkDiskIndex_fail (Positive i) =
583 f56013fd Iustin Pop
  case mkDiskIndex (negate i) of
584 f56013fd Iustin Pop
    Bad msg -> printTestCase "error message " $
585 f56013fd Iustin Pop
               "Invalid value" `isPrefixOf` msg
586 f56013fd Iustin Pop
    Ok v -> failTest $ "Succeeded to build disk index '" ++ show v ++
587 f56013fd Iustin Pop
                       "' from negative value " ++ show (negate i)
588 f56013fd Iustin Pop
589 f56013fd Iustin Pop
-- | Tests a few invalid 'readRecreateDisks' cases.
590 f56013fd Iustin Pop
case_readRecreateDisks_fail :: Assertion
591 f56013fd Iustin Pop
case_readRecreateDisks_fail = do
592 f56013fd Iustin Pop
  assertBool "null" $
593 f56013fd Iustin Pop
    isJsonError (J.readJSON J.JSNull::J.Result RecreateDisksInfo)
594 f56013fd Iustin Pop
  assertBool "string" $
595 f56013fd Iustin Pop
    isJsonError (J.readJSON (J.showJSON "abc")::J.Result RecreateDisksInfo)
596 f56013fd Iustin Pop
597 f56013fd Iustin Pop
-- | Tests a few invalid 'readDdmOldChanges' cases.
598 f56013fd Iustin Pop
case_readDdmOldChanges_fail :: Assertion
599 f56013fd Iustin Pop
case_readDdmOldChanges_fail = do
600 f56013fd Iustin Pop
  assertBool "null" $
601 f56013fd Iustin Pop
    isJsonError (J.readJSON J.JSNull::J.Result DdmOldChanges)
602 f56013fd Iustin Pop
  assertBool "string" $
603 f56013fd Iustin Pop
    isJsonError (J.readJSON (J.showJSON "abc")::J.Result DdmOldChanges)
604 f56013fd Iustin Pop
605 f56013fd Iustin Pop
-- | Tests a few invalid 'readExportTarget' cases.
606 f56013fd Iustin Pop
case_readExportTarget_fail :: Assertion
607 f56013fd Iustin Pop
case_readExportTarget_fail = do
608 f56013fd Iustin Pop
  assertBool "null" $
609 f56013fd Iustin Pop
    isJsonError (J.readJSON J.JSNull::J.Result ExportTarget)
610 f56013fd Iustin Pop
  assertBool "int" $
611 f56013fd Iustin Pop
    isJsonError (J.readJSON (J.showJSON (5::Int))::J.Result ExportTarget)
612 f56013fd Iustin Pop
613 aed2325f Iustin Pop
testSuite "OpCodes"
614 20bc5360 Iustin Pop
            [ 'prop_serialization
615 20bc5360 Iustin Pop
            , 'case_AllDefined
616 d1ac695f Iustin Pop
            , 'case_py_compat_types
617 d1ac695f Iustin Pop
            , 'case_py_compat_fields
618 4a826364 Iustin Pop
            , 'prop_setOpComment
619 f56013fd Iustin Pop
            , 'prop_mkDiskIndex_fail
620 f56013fd Iustin Pop
            , 'case_readRecreateDisks_fail
621 f56013fd Iustin Pop
            , 'case_readDdmOldChanges_fail
622 f56013fd Iustin Pop
            , 'case_readExportTarget_fail
623 aed2325f Iustin Pop
            ]