Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / OpCodes.hs @ 363f43eb

History | View | Annotate | Download (30.2 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 2868f3f7 Hrvoje Ribicic
          genNodeNamesNE <*> return Nothing <*> arbitrary <*> 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 07e3c124 Santi Raffa
        OpCodes.OpClusterSetParams
175 07e3c124 Santi Raffa
          <$> arbitrary                    -- force
176 07e3c124 Santi Raffa
          <*> emptyMUD                     -- hv_state
177 07e3c124 Santi Raffa
          <*> emptyMUD                     -- disk_state
178 07e3c124 Santi Raffa
          <*> arbitrary                    -- vg_name
179 07e3c124 Santi Raffa
          <*> genMaybe arbitrary           -- enabled_hypervisors
180 07e3c124 Santi Raffa
          <*> genMaybe genEmptyContainer   -- hvparams
181 07e3c124 Santi Raffa
          <*> emptyMUD                     -- beparams
182 07e3c124 Santi Raffa
          <*> genMaybe genEmptyContainer   -- os_hvp
183 07e3c124 Santi Raffa
          <*> genMaybe genEmptyContainer   -- osparams
184 07e3c124 Santi Raffa
          <*> genMaybe genEmptyContainer   -- osparams_private_cluster
185 07e3c124 Santi Raffa
          <*> genMaybe genEmptyContainer   -- diskparams
186 07e3c124 Santi Raffa
          <*> genMaybe arbitrary           -- candidate_pool_size
187 07e3c124 Santi Raffa
          <*> genMaybe arbitrary           -- max_running_jobs
188 07e3c124 Santi Raffa
          <*> arbitrary                    -- uid_pool
189 07e3c124 Santi Raffa
          <*> arbitrary                    -- add_uids
190 07e3c124 Santi Raffa
          <*> arbitrary                    -- remove_uids
191 07e3c124 Santi Raffa
          <*> arbitrary                    -- maintain_node_health
192 07e3c124 Santi Raffa
          <*> arbitrary                    -- prealloc_wipe_disks
193 07e3c124 Santi Raffa
          <*> arbitrary                    -- nicparams
194 07e3c124 Santi Raffa
          <*> emptyMUD                     -- ndparams
195 07e3c124 Santi Raffa
          <*> emptyMUD                     -- ipolicy
196 07e3c124 Santi Raffa
          <*> arbitrary                    -- drbd_helper
197 07e3c124 Santi Raffa
          <*> arbitrary                    -- default_iallocator
198 07e3c124 Santi Raffa
          <*> emptyMUD                     -- default_iallocator_params
199 0cffcdb1 Dimitris Bliablias
          <*> genMaybe genMacPrefix        -- mac_prefix
200 07e3c124 Santi Raffa
          <*> arbitrary                    -- master_netdev
201 07e3c124 Santi Raffa
          <*> arbitrary                    -- master_netmask
202 07e3c124 Santi Raffa
          <*> arbitrary                    -- reserved_lvs
203 07e3c124 Santi Raffa
          <*> arbitrary                    -- hidden_os
204 07e3c124 Santi Raffa
          <*> arbitrary                    -- blacklisted_os
205 07e3c124 Santi Raffa
          <*> arbitrary                    -- use_external_mip_script
206 07e3c124 Santi Raffa
          <*> arbitrary                    -- enabled_disk_templates
207 07e3c124 Santi Raffa
          <*> arbitrary                    -- modify_etc_hosts
208 07e3c124 Santi Raffa
          <*> genMaybe genName             -- file_storage_dir
209 07e3c124 Santi Raffa
          <*> genMaybe genName             -- shared_file_storage_dir
210 07e3c124 Santi Raffa
          <*> genMaybe genName             -- gluster_file_storage_dir
211 42fda604 Jose A. Lopes
          <*> arbitrary                    -- instance_communication_network
212 c66f09f5 Iustin Pop
      "OP_CLUSTER_REDIST_CONF" -> pure OpCodes.OpClusterRedistConf
213 c66f09f5 Iustin Pop
      "OP_CLUSTER_ACTIVATE_MASTER_IP" ->
214 c66f09f5 Iustin Pop
        pure OpCodes.OpClusterActivateMasterIp
215 c66f09f5 Iustin Pop
      "OP_CLUSTER_DEACTIVATE_MASTER_IP" ->
216 c66f09f5 Iustin Pop
        pure OpCodes.OpClusterDeactivateMasterIp
217 c66f09f5 Iustin Pop
      "OP_QUERY" ->
218 6e94b75c Jose A. Lopes
        OpCodes.OpQuery <$> arbitrary <*> arbitrary <*> arbitrary <*>
219 6e94b75c Jose A. Lopes
        pure Nothing
220 c66f09f5 Iustin Pop
      "OP_QUERY_FIELDS" ->
221 c66f09f5 Iustin Pop
        OpCodes.OpQueryFields <$> arbitrary <*> arbitrary
222 c66f09f5 Iustin Pop
      "OP_OOB_COMMAND" ->
223 1c3231aa Thomas Thrainer
        OpCodes.OpOobCommand <$> genNodeNamesNE <*> return Nothing <*>
224 1c3231aa Thomas Thrainer
          arbitrary <*> arbitrary <*> arbitrary <*>
225 1c3231aa Thomas Thrainer
          (arbitrary `suchThat` (>0))
226 1c3231aa Thomas Thrainer
      "OP_NODE_REMOVE" ->
227 1c3231aa Thomas Thrainer
        OpCodes.OpNodeRemove <$> genNodeNameNE <*> return Nothing
228 c66f09f5 Iustin Pop
      "OP_NODE_ADD" ->
229 5ef4fbb1 Iustin Pop
        OpCodes.OpNodeAdd <$> genNodeNameNE <*> emptyMUD <*> emptyMUD <*>
230 5cbf7832 Jose A. Lopes
          genMaybe genNameNE <*> genMaybe genNameNE <*> arbitrary <*>
231 5006418e Iustin Pop
          genMaybe genNameNE <*> arbitrary <*> arbitrary <*> emptyMUD
232 c66f09f5 Iustin Pop
      "OP_NODE_QUERYVOLS" ->
233 c66f09f5 Iustin Pop
        OpCodes.OpNodeQueryvols <$> arbitrary <*> genNodeNamesNE
234 c66f09f5 Iustin Pop
      "OP_NODE_QUERY_STORAGE" ->
235 c66f09f5 Iustin Pop
        OpCodes.OpNodeQueryStorage <$> arbitrary <*> arbitrary <*>
236 6e94b75c Jose A. Lopes
          genNodeNamesNE <*> genMaybe genNameNE
237 c66f09f5 Iustin Pop
      "OP_NODE_MODIFY_STORAGE" ->
238 1c3231aa Thomas Thrainer
        OpCodes.OpNodeModifyStorage <$> genNodeNameNE <*> return Nothing <*>
239 6e94b75c Jose A. Lopes
          arbitrary <*> genMaybe genNameNE <*> pure emptyJSObject
240 c66f09f5 Iustin Pop
      "OP_REPAIR_NODE_STORAGE" ->
241 1c3231aa Thomas Thrainer
        OpCodes.OpRepairNodeStorage <$> genNodeNameNE <*> return Nothing <*>
242 6e94b75c Jose A. Lopes
          arbitrary <*> genMaybe genNameNE <*> arbitrary
243 c66f09f5 Iustin Pop
      "OP_NODE_SET_PARAMS" ->
244 1c3231aa Thomas Thrainer
        OpCodes.OpNodeSetParams <$> genNodeNameNE <*> return Nothing <*>
245 1c3231aa Thomas Thrainer
          arbitrary <*> emptyMUD <*> emptyMUD <*> arbitrary <*> arbitrary <*>
246 1c3231aa Thomas Thrainer
          arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*>
247 1c3231aa Thomas Thrainer
          genMaybe genNameNE <*> emptyMUD <*> arbitrary
248 c66f09f5 Iustin Pop
      "OP_NODE_POWERCYCLE" ->
249 1c3231aa Thomas Thrainer
        OpCodes.OpNodePowercycle <$> genNodeNameNE <*> return Nothing <*>
250 1c3231aa Thomas Thrainer
          arbitrary
251 c66f09f5 Iustin Pop
      "OP_NODE_MIGRATE" ->
252 1c3231aa Thomas Thrainer
        OpCodes.OpNodeMigrate <$> genNodeNameNE <*> return Nothing <*>
253 1c3231aa Thomas Thrainer
          arbitrary <*> arbitrary <*> genMaybe genNodeNameNE <*>
254 1c3231aa Thomas Thrainer
          return Nothing <*> arbitrary <*> arbitrary <*> genMaybe genNameNE
255 c66f09f5 Iustin Pop
      "OP_NODE_EVACUATE" ->
256 c66f09f5 Iustin Pop
        OpCodes.OpNodeEvacuate <$> arbitrary <*> genNodeNameNE <*>
257 1c3231aa Thomas Thrainer
          return Nothing <*> genMaybe genNodeNameNE <*> return Nothing <*>
258 1c3231aa Thomas Thrainer
          genMaybe genNameNE <*> arbitrary
259 6d558717 Iustin Pop
      "OP_INSTANCE_CREATE" ->
260 6bce7ba2 Santi Raffa
        OpCodes.OpInstanceCreate
261 6bce7ba2 Santi Raffa
          <$> genFQDN                         -- instance_name
262 6bce7ba2 Santi Raffa
          <*> arbitrary                       -- force_variant
263 6bce7ba2 Santi Raffa
          <*> arbitrary                       -- wait_for_sync
264 6bce7ba2 Santi Raffa
          <*> arbitrary                       -- name_check
265 6bce7ba2 Santi Raffa
          <*> arbitrary                       -- ignore_ipolicy
266 6bce7ba2 Santi Raffa
          <*> arbitrary                       -- opportunistic_locking
267 6bce7ba2 Santi Raffa
          <*> pure emptyJSObject              -- beparams
268 6bce7ba2 Santi Raffa
          <*> arbitrary                       -- disks
269 6bce7ba2 Santi Raffa
          <*> arbitrary                       -- disk_template
270 6bce7ba2 Santi Raffa
          <*> arbitrary                       -- file_driver
271 6bce7ba2 Santi Raffa
          <*> genMaybe genNameNE              -- file_storage_dir
272 6bce7ba2 Santi Raffa
          <*> pure emptyJSObject              -- hvparams
273 6bce7ba2 Santi Raffa
          <*> arbitrary                       -- hypervisor
274 6bce7ba2 Santi Raffa
          <*> genMaybe genNameNE              -- iallocator
275 6bce7ba2 Santi Raffa
          <*> arbitrary                       -- identify_defaults
276 6bce7ba2 Santi Raffa
          <*> arbitrary                       -- ip_check
277 6bce7ba2 Santi Raffa
          <*> arbitrary                       -- conflicts_check
278 6bce7ba2 Santi Raffa
          <*> arbitrary                       -- mode
279 6bce7ba2 Santi Raffa
          <*> arbitrary                       -- nics
280 6bce7ba2 Santi Raffa
          <*> arbitrary                       -- no_install
281 6bce7ba2 Santi Raffa
          <*> pure emptyJSObject              -- osparams
282 6bce7ba2 Santi Raffa
          <*> genMaybe arbitraryPrivateJSObj  -- osparams_private
283 6bce7ba2 Santi Raffa
          <*> genMaybe arbitraryPrivateJSObj  -- osparams_secret
284 6bce7ba2 Santi Raffa
          <*> genMaybe genNameNE              -- os_type
285 6bce7ba2 Santi Raffa
          <*> genMaybe genNodeNameNE          -- pnode
286 6bce7ba2 Santi Raffa
          <*> return Nothing                  -- pnode_uuid
287 6bce7ba2 Santi Raffa
          <*> genMaybe genNodeNameNE          -- snode
288 6bce7ba2 Santi Raffa
          <*> return Nothing                  -- snode_uuid
289 6bce7ba2 Santi Raffa
          <*> genMaybe (pure [])              -- source_handshake
290 6bce7ba2 Santi Raffa
          <*> genMaybe genNodeNameNE          -- source_instance_name
291 6bce7ba2 Santi Raffa
          <*> arbitrary                       -- source_shutdown_timeout
292 6bce7ba2 Santi Raffa
          <*> genMaybe genNodeNameNE          -- source_x509_ca
293 6bce7ba2 Santi Raffa
          <*> return Nothing                  -- src_node
294 6bce7ba2 Santi Raffa
          <*> genMaybe genNodeNameNE          -- src_node_uuid
295 6bce7ba2 Santi Raffa
          <*> genMaybe genNameNE              -- src_path
296 6bce7ba2 Santi Raffa
          <*> arbitrary                       -- compress
297 6bce7ba2 Santi Raffa
          <*> arbitrary                       -- start
298 6bce7ba2 Santi Raffa
          <*> (genTags >>= mapM mkNonEmpty)   -- tags
299 6bce7ba2 Santi Raffa
          <*> arbitrary                       -- instance_communication
300 c2d3219b Iustin Pop
      "OP_INSTANCE_MULTI_ALLOC" ->
301 6e94b75c Jose A. Lopes
        OpCodes.OpInstanceMultiAlloc <$> arbitrary <*> genMaybe genNameNE <*>
302 6e94b75c Jose A. Lopes
        pure []
303 c2d3219b Iustin Pop
      "OP_INSTANCE_REINSTALL" ->
304 da4a52a3 Thomas Thrainer
        OpCodes.OpInstanceReinstall <$> genFQDN <*> return Nothing <*>
305 da4a52a3 Thomas Thrainer
          arbitrary <*> genMaybe genNameNE <*> genMaybe (pure emptyJSObject)
306 da0aa302 Santi Raffa
          <*> genMaybe arbitraryPrivateJSObj <*> genMaybe arbitraryPrivateJSObj
307 c2d3219b Iustin Pop
      "OP_INSTANCE_REMOVE" ->
308 da4a52a3 Thomas Thrainer
        OpCodes.OpInstanceRemove <$> genFQDN <*> return Nothing <*>
309 c2d3219b Iustin Pop
          arbitrary <*> arbitrary
310 da4a52a3 Thomas Thrainer
      "OP_INSTANCE_RENAME" ->
311 da4a52a3 Thomas Thrainer
        OpCodes.OpInstanceRename <$> genFQDN <*> return Nothing <*>
312 da4a52a3 Thomas Thrainer
          genNodeNameNE <*> arbitrary <*> arbitrary
313 c2d3219b Iustin Pop
      "OP_INSTANCE_STARTUP" ->
314 da4a52a3 Thomas Thrainer
        OpCodes.OpInstanceStartup <$> genFQDN <*> return Nothing <*>
315 da4a52a3 Thomas Thrainer
          arbitrary <*> arbitrary <*> pure emptyJSObject <*>
316 da4a52a3 Thomas Thrainer
          pure emptyJSObject <*> arbitrary <*> arbitrary
317 c2d3219b Iustin Pop
      "OP_INSTANCE_SHUTDOWN" ->
318 da4a52a3 Thomas Thrainer
        OpCodes.OpInstanceShutdown <$> genFQDN <*> return Nothing <*>
319 da4a52a3 Thomas Thrainer
          arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
320 c2d3219b Iustin Pop
      "OP_INSTANCE_REBOOT" ->
321 da4a52a3 Thomas Thrainer
        OpCodes.OpInstanceReboot <$> genFQDN <*> return Nothing <*>
322 da4a52a3 Thomas Thrainer
          arbitrary <*> arbitrary <*> arbitrary
323 c2d3219b Iustin Pop
      "OP_INSTANCE_MOVE" ->
324 da4a52a3 Thomas Thrainer
        OpCodes.OpInstanceMove <$> genFQDN <*> return Nothing <*>
325 da4a52a3 Thomas Thrainer
          arbitrary <*> arbitrary <*> genNodeNameNE <*> return Nothing <*>
326 f198cf91 Thomas Thrainer
          arbitrary <*> arbitrary
327 da4a52a3 Thomas Thrainer
      "OP_INSTANCE_CONSOLE" -> OpCodes.OpInstanceConsole <$> genFQDN <*>
328 da4a52a3 Thomas Thrainer
          return Nothing
329 c2d3219b Iustin Pop
      "OP_INSTANCE_ACTIVATE_DISKS" ->
330 da4a52a3 Thomas Thrainer
        OpCodes.OpInstanceActivateDisks <$> genFQDN <*> return Nothing <*>
331 c2d3219b Iustin Pop
          arbitrary <*> arbitrary
332 c2d3219b Iustin Pop
      "OP_INSTANCE_DEACTIVATE_DISKS" ->
333 da4a52a3 Thomas Thrainer
        OpCodes.OpInstanceDeactivateDisks <$> genFQDN <*> return Nothing <*>
334 da4a52a3 Thomas Thrainer
          arbitrary
335 c2d3219b Iustin Pop
      "OP_INSTANCE_RECREATE_DISKS" ->
336 da4a52a3 Thomas Thrainer
        OpCodes.OpInstanceRecreateDisks <$> genFQDN <*> return Nothing <*>
337 da4a52a3 Thomas Thrainer
          arbitrary <*> genNodeNamesNE <*> return Nothing <*>
338 da4a52a3 Thomas Thrainer
          genMaybe genNameNE
339 c2d3219b Iustin Pop
      "OP_INSTANCE_QUERY_DATA" ->
340 c2d3219b Iustin Pop
        OpCodes.OpInstanceQueryData <$> arbitrary <*>
341 c2d3219b Iustin Pop
          genNodeNamesNE <*> arbitrary
342 c2d3219b Iustin Pop
      "OP_INSTANCE_SET_PARAMS" ->
343 1a182390 Santi Raffa
        OpCodes.OpInstanceSetParams
344 1a182390 Santi Raffa
          <$> genFQDN                         -- instance_name
345 1a182390 Santi Raffa
          <*> return Nothing                  -- instance_uuid
346 1a182390 Santi Raffa
          <*> arbitrary                       -- force
347 1a182390 Santi Raffa
          <*> arbitrary                       -- force_variant
348 1a182390 Santi Raffa
          <*> arbitrary                       -- ignore_ipolicy
349 1a182390 Santi Raffa
          <*> arbitrary                       -- nics
350 1a182390 Santi Raffa
          <*> arbitrary                       -- disks
351 1a182390 Santi Raffa
          <*> pure emptyJSObject              -- beparams
352 1a182390 Santi Raffa
          <*> arbitrary                       -- runtime_mem
353 1a182390 Santi Raffa
          <*> pure emptyJSObject              -- hvparams
354 1a182390 Santi Raffa
          <*> arbitrary                       -- disk_template
355 1a182390 Santi Raffa
          <*> genMaybe genNodeNameNE          -- pnode
356 1a182390 Santi Raffa
          <*> return Nothing                  -- pnode_uuid
357 1a182390 Santi Raffa
          <*> genMaybe genNodeNameNE          -- remote_node
358 1a182390 Santi Raffa
          <*> return Nothing                  -- remote_node_uuid
359 1a182390 Santi Raffa
          <*> genMaybe genNameNE              -- os_name
360 1a182390 Santi Raffa
          <*> pure emptyJSObject              -- osparams
361 1a182390 Santi Raffa
          <*> genMaybe arbitraryPrivateJSObj  -- osparams_private
362 1a182390 Santi Raffa
          <*> arbitrary                       -- wait_for_sync
363 1a182390 Santi Raffa
          <*> arbitrary                       -- offline
364 1a182390 Santi Raffa
          <*> arbitrary                       -- conflicts_check
365 1a182390 Santi Raffa
          <*> arbitrary                       -- hotplug
366 1a182390 Santi Raffa
          <*> arbitrary                       -- hotplug_if_possible
367 93f1e606 Jose A. Lopes
          <*> arbitrary                       -- instance_communication
368 c2d3219b Iustin Pop
      "OP_INSTANCE_GROW_DISK" ->
369 da4a52a3 Thomas Thrainer
        OpCodes.OpInstanceGrowDisk <$> genFQDN <*> return Nothing <*>
370 da4a52a3 Thomas Thrainer
          arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
371 c2d3219b Iustin Pop
      "OP_INSTANCE_CHANGE_GROUP" ->
372 da4a52a3 Thomas Thrainer
        OpCodes.OpInstanceChangeGroup <$> genFQDN <*> return Nothing <*>
373 da4a52a3 Thomas Thrainer
          arbitrary <*> genMaybe genNameNE <*>
374 da4a52a3 Thomas Thrainer
          genMaybe (resize maxNodes (listOf genNameNE))
375 398e9066 Iustin Pop
      "OP_GROUP_ADD" ->
376 398e9066 Iustin Pop
        OpCodes.OpGroupAdd <$> genNameNE <*> arbitrary <*>
377 5006418e Iustin Pop
          emptyMUD <*> genMaybe genEmptyContainer <*>
378 398e9066 Iustin Pop
          emptyMUD <*> emptyMUD <*> emptyMUD
379 398e9066 Iustin Pop
      "OP_GROUP_ASSIGN_NODES" ->
380 398e9066 Iustin Pop
        OpCodes.OpGroupAssignNodes <$> genNameNE <*> arbitrary <*>
381 1c3231aa Thomas Thrainer
          genNodeNamesNE <*> return Nothing
382 398e9066 Iustin Pop
      "OP_GROUP_SET_PARAMS" ->
383 398e9066 Iustin Pop
        OpCodes.OpGroupSetParams <$> genNameNE <*> arbitrary <*>
384 5006418e Iustin Pop
          emptyMUD <*> genMaybe genEmptyContainer <*>
385 398e9066 Iustin Pop
          emptyMUD <*> emptyMUD <*> emptyMUD
386 398e9066 Iustin Pop
      "OP_GROUP_REMOVE" ->
387 398e9066 Iustin Pop
        OpCodes.OpGroupRemove <$> genNameNE
388 398e9066 Iustin Pop
      "OP_GROUP_RENAME" ->
389 398e9066 Iustin Pop
        OpCodes.OpGroupRename <$> genNameNE <*> genNameNE
390 398e9066 Iustin Pop
      "OP_GROUP_EVACUATE" ->
391 398e9066 Iustin Pop
        OpCodes.OpGroupEvacuate <$> genNameNE <*> arbitrary <*>
392 5006418e Iustin Pop
          genMaybe genNameNE <*> genMaybe genNamesNE
393 398e9066 Iustin Pop
      "OP_OS_DIAGNOSE" ->
394 398e9066 Iustin Pop
        OpCodes.OpOsDiagnose <$> genFieldsNE <*> genNamesNE
395 b954f097 Constantinos Venetsanopoulos
      "OP_EXT_STORAGE_DIAGNOSE" ->
396 b954f097 Constantinos Venetsanopoulos
        OpCodes.OpOsDiagnose <$> genFieldsNE <*> genNamesNE
397 398e9066 Iustin Pop
      "OP_BACKUP_PREPARE" ->
398 da4a52a3 Thomas Thrainer
        OpCodes.OpBackupPrepare <$> genFQDN <*> return Nothing <*> arbitrary
399 398e9066 Iustin Pop
      "OP_BACKUP_EXPORT" ->
400 da4a52a3 Thomas Thrainer
        OpCodes.OpBackupExport <$> genFQDN <*> return Nothing <*>
401 896cc964 Thomas Thrainer
          arbitrary <*> arbitrary <*> arbitrary <*> return Nothing <*>
402 896cc964 Thomas Thrainer
          arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*>
403 363f43eb Hrvoje Ribicic
          genMaybe (pure []) <*> genMaybe genNameNE <*> arbitrary
404 398e9066 Iustin Pop
      "OP_BACKUP_REMOVE" ->
405 da4a52a3 Thomas Thrainer
        OpCodes.OpBackupRemove <$> genFQDN <*> return Nothing
406 a3f02317 Iustin Pop
      "OP_TEST_ALLOCATOR" ->
407 a3f02317 Iustin Pop
        OpCodes.OpTestAllocator <$> arbitrary <*> arbitrary <*>
408 6e94b75c Jose A. Lopes
          genNameNE <*> genMaybe (pure []) <*> genMaybe (pure []) <*>
409 5006418e Iustin Pop
          arbitrary <*> genMaybe genNameNE <*>
410 a3f02317 Iustin Pop
          (genTags >>= mapM mkNonEmpty) <*>
411 5006418e Iustin Pop
          arbitrary <*> arbitrary <*> genMaybe genNameNE <*>
412 5006418e Iustin Pop
          arbitrary <*> genMaybe genNodeNamesNE <*> arbitrary <*>
413 5006418e Iustin Pop
          genMaybe genNamesNE <*> arbitrary <*> arbitrary
414 a3f02317 Iustin Pop
      "OP_TEST_JQUEUE" ->
415 a3f02317 Iustin Pop
        OpCodes.OpTestJqueue <$> arbitrary <*> arbitrary <*>
416 5006418e Iustin Pop
          resize 20 (listOf genFQDN) <*> arbitrary
417 a3f02317 Iustin Pop
      "OP_TEST_DUMMY" ->
418 a3f02317 Iustin Pop
        OpCodes.OpTestDummy <$> pure J.JSNull <*> pure J.JSNull <*>
419 a3f02317 Iustin Pop
          pure J.JSNull <*> pure J.JSNull
420 8d239fa4 Iustin Pop
      "OP_NETWORK_ADD" ->
421 6e94b75c Jose A. Lopes
        OpCodes.OpNetworkAdd <$> genNameNE <*> genIPv4Network <*>
422 6e94b75c Jose A. Lopes
          genMaybe genIPv4Address <*> pure Nothing <*> pure Nothing <*>
423 6e94b75c Jose A. Lopes
          genMaybe genMacPrefix <*> genMaybe (listOf genIPv4Address) <*>
424 1dbceab9 Iustin Pop
          arbitrary <*> (genTags >>= mapM mkNonEmpty)
425 8d239fa4 Iustin Pop
      "OP_NETWORK_REMOVE" ->
426 8d239fa4 Iustin Pop
        OpCodes.OpNetworkRemove <$> genNameNE <*> arbitrary
427 8d239fa4 Iustin Pop
      "OP_NETWORK_SET_PARAMS" ->
428 5cfa6c37 Dimitris Aragiorgis
        OpCodes.OpNetworkSetParams <$> genNameNE <*>
429 6e94b75c Jose A. Lopes
          genMaybe genIPv4Address <*> pure Nothing <*> pure Nothing <*>
430 6e94b75c Jose A. Lopes
          genMaybe genMacPrefix <*> genMaybe (listOf genIPv4Address) <*>
431 6e94b75c Jose A. Lopes
          genMaybe (listOf genIPv4Address)
432 8d239fa4 Iustin Pop
      "OP_NETWORK_CONNECT" ->
433 8d239fa4 Iustin Pop
        OpCodes.OpNetworkConnect <$> genNameNE <*> genNameNE <*>
434 8d239fa4 Iustin Pop
          arbitrary <*> genNameNE <*> arbitrary
435 8d239fa4 Iustin Pop
      "OP_NETWORK_DISCONNECT" ->
436 0ae4b355 Helga Velroyen
        OpCodes.OpNetworkDisconnect <$> genNameNE <*> genNameNE
437 1cd563e2 Iustin Pop
      "OP_RESTRICTED_COMMAND" ->
438 1cd563e2 Iustin Pop
        OpCodes.OpRestrictedCommand <$> arbitrary <*> genNodeNamesNE <*>
439 1c3231aa Thomas Thrainer
          return Nothing <*> genNameNE
440 c66f09f5 Iustin Pop
      _ -> fail $ "Undefined arbitrary for opcode " ++ op_id
441 aed2325f Iustin Pop
442 516a0e94 Michele Tartara
-- | Generates one element of a reason trail
443 516a0e94 Michele Tartara
genReasonElem :: Gen ReasonElem
444 516a0e94 Michele Tartara
genReasonElem = (,,) <$> genFQDN <*> genFQDN <*> arbitrary
445 516a0e94 Michele Tartara
446 516a0e94 Michele Tartara
-- | Generates a reason trail
447 516a0e94 Michele Tartara
genReasonTrail :: Gen ReasonTrail
448 516a0e94 Michele Tartara
genReasonTrail = do
449 516a0e94 Michele Tartara
  size <- choose (0, 10)
450 516a0e94 Michele Tartara
  vectorOf size genReasonElem
451 516a0e94 Michele Tartara
452 4a826364 Iustin Pop
instance Arbitrary OpCodes.CommonOpParams where
453 4a826364 Iustin Pop
  arbitrary = OpCodes.CommonOpParams <$> arbitrary <*> arbitrary <*>
454 516a0e94 Michele Tartara
                arbitrary <*> resize 5 arbitrary <*> genMaybe genName <*>
455 516a0e94 Michele Tartara
                genReasonTrail
456 4a826364 Iustin Pop
457 c7d249d0 Iustin Pop
-- * Helper functions
458 c7d249d0 Iustin Pop
459 c66f09f5 Iustin Pop
-- | Empty JSObject.
460 c66f09f5 Iustin Pop
emptyJSObject :: J.JSObject J.JSValue
461 c66f09f5 Iustin Pop
emptyJSObject = J.toJSObject []
462 c66f09f5 Iustin Pop
463 c66f09f5 Iustin Pop
-- | Empty maybe unchecked dictionary.
464 c66f09f5 Iustin Pop
emptyMUD :: Gen (Maybe (J.JSObject J.JSValue))
465 5006418e Iustin Pop
emptyMUD = genMaybe $ pure emptyJSObject
466 c66f09f5 Iustin Pop
467 c66f09f5 Iustin Pop
-- | Generates an empty container.
468 c66f09f5 Iustin Pop
genEmptyContainer :: (Ord a) => Gen (GenericContainer a b)
469 c66f09f5 Iustin Pop
genEmptyContainer = pure . GenericContainer $ Map.fromList []
470 c66f09f5 Iustin Pop
471 c7d249d0 Iustin Pop
-- | Generates list of disk indices.
472 c7d249d0 Iustin Pop
genDiskIndices :: Gen [DiskIndex]
473 c7d249d0 Iustin Pop
genDiskIndices = do
474 c7d249d0 Iustin Pop
  cnt <- choose (0, C.maxDisks)
475 df8578fb Iustin Pop
  genUniquesList cnt arbitrary
476 c7d249d0 Iustin Pop
477 c7d249d0 Iustin Pop
-- | Generates a list of node names.
478 c7d249d0 Iustin Pop
genNodeNames :: Gen [String]
479 5006418e Iustin Pop
genNodeNames = resize maxNodes (listOf genFQDN)
480 c7d249d0 Iustin Pop
481 c66f09f5 Iustin Pop
-- | Generates a list of node names in non-empty string type.
482 c66f09f5 Iustin Pop
genNodeNamesNE :: Gen [NonEmptyString]
483 417ab39c Iustin Pop
genNodeNamesNE = genNodeNames >>= mapM mkNonEmpty
484 c66f09f5 Iustin Pop
485 c7d249d0 Iustin Pop
-- | Gets a node name in non-empty type.
486 c7d249d0 Iustin Pop
genNodeNameNE :: Gen NonEmptyString
487 5006418e Iustin Pop
genNodeNameNE = genFQDN >>= mkNonEmpty
488 c7d249d0 Iustin Pop
489 5ef4fbb1 Iustin Pop
-- | Gets a name (non-fqdn) in non-empty type.
490 5ef4fbb1 Iustin Pop
genNameNE :: Gen NonEmptyString
491 5006418e Iustin Pop
genNameNE = genName >>= mkNonEmpty
492 5ef4fbb1 Iustin Pop
493 398e9066 Iustin Pop
-- | Gets a list of names (non-fqdn) in non-empty type.
494 398e9066 Iustin Pop
genNamesNE :: Gen [NonEmptyString]
495 398e9066 Iustin Pop
genNamesNE = resize maxNodes (listOf genNameNE)
496 398e9066 Iustin Pop
497 5ef4fbb1 Iustin Pop
-- | Returns a list of non-empty fields.
498 5ef4fbb1 Iustin Pop
genFieldsNE :: Gen [NonEmptyString]
499 5006418e Iustin Pop
genFieldsNE = genFields >>= mapM mkNonEmpty
500 5ef4fbb1 Iustin Pop
501 8d239fa4 Iustin Pop
-- | Generate a 3-byte MAC prefix.
502 8d239fa4 Iustin Pop
genMacPrefix :: Gen NonEmptyString
503 8d239fa4 Iustin Pop
genMacPrefix = do
504 8d239fa4 Iustin Pop
  octets <- vectorOf 3 $ choose (0::Int, 255)
505 8d239fa4 Iustin Pop
  mkNonEmpty . intercalate ":" $ map (printf "%02x") octets
506 8d239fa4 Iustin Pop
507 4884f187 Santi Raffa
-- | JSObject of arbitrary data.
508 4884f187 Santi Raffa
--
509 4884f187 Santi Raffa
-- Since JSValue does not implement Arbitrary, I'll simply generate
510 4884f187 Santi Raffa
-- (String, String) objects.
511 4884f187 Santi Raffa
arbitraryPrivateJSObj :: Gen (J.JSObject (Private J.JSValue))
512 4884f187 Santi Raffa
arbitraryPrivateJSObj =
513 4884f187 Santi Raffa
  constructor <$> (fromNonEmpty <$> genNameNE)
514 4884f187 Santi Raffa
              <*> (fromNonEmpty <$> genNameNE)
515 4884f187 Santi Raffa
    where constructor k v = showPrivateJSObject [(k, v)]
516 4884f187 Santi Raffa
517 4a826364 Iustin Pop
-- | Arbitrary instance for MetaOpCode, defined here due to TH ordering.
518 4a826364 Iustin Pop
$(genArbitrary ''OpCodes.MetaOpCode)
519 4a826364 Iustin Pop
520 f56013fd Iustin Pop
-- | Small helper to check for a failed JSON deserialisation
521 f56013fd Iustin Pop
isJsonError :: J.Result a -> Bool
522 f56013fd Iustin Pop
isJsonError (J.Error _) = True
523 f56013fd Iustin Pop
isJsonError _           = False
524 f56013fd Iustin Pop
525 aed2325f Iustin Pop
-- * Test cases
526 aed2325f Iustin Pop
527 aed2325f Iustin Pop
-- | Check that opcode serialization is idempotent.
528 20bc5360 Iustin Pop
prop_serialization :: OpCodes.OpCode -> Property
529 63b068c1 Iustin Pop
prop_serialization = testSerialisation
530 aed2325f Iustin Pop
531 aed2325f Iustin Pop
-- | Check that Python and Haskell defined the same opcode list.
532 20bc5360 Iustin Pop
case_AllDefined :: HUnit.Assertion
533 20bc5360 Iustin Pop
case_AllDefined = do
534 d31193c3 Jose A. Lopes
  py_stdout <-
535 d31193c3 Jose A. Lopes
     runPython "from ganeti import opcodes\n\
536 d31193c3 Jose A. Lopes
               \from ganeti import serializer\n\
537 d31193c3 Jose A. Lopes
               \import sys\n\
538 6e94b75c Jose A. Lopes
               \print serializer.Dump([opid for opid in opcodes.OP_MAPPING])\n"
539 6e94b75c Jose A. Lopes
               ""
540 d31193c3 Jose A. Lopes
     >>= checkPythonResult
541 d31193c3 Jose A. Lopes
  py_ops <- case J.decode py_stdout::J.Result [String] of
542 d31193c3 Jose A. Lopes
               J.Ok ops -> return ops
543 d31193c3 Jose A. Lopes
               J.Error msg ->
544 d31193c3 Jose A. Lopes
                 HUnit.assertFailure ("Unable to decode opcode names: " ++ msg)
545 d31193c3 Jose A. Lopes
                 -- this already raised an expection, but we need it
546 d31193c3 Jose A. Lopes
                 -- for proper types
547 d31193c3 Jose A. Lopes
                 >> fail "Unable to decode opcode names"
548 d31193c3 Jose A. Lopes
  let hs_ops = sort OpCodes.allOpIDs
549 9b773665 Iustin Pop
      extra_py = py_ops \\ hs_ops
550 aed2325f Iustin Pop
      extra_hs = hs_ops \\ py_ops
551 9b773665 Iustin Pop
  HUnit.assertBool ("Missing OpCodes from the Haskell code:\n" ++
552 9b773665 Iustin Pop
                    unlines extra_py) (null extra_py)
553 aed2325f Iustin Pop
  HUnit.assertBool ("Extra OpCodes in the Haskell code code:\n" ++
554 aed2325f Iustin Pop
                    unlines extra_hs) (null extra_hs)
555 aed2325f Iustin Pop
556 aed2325f Iustin Pop
-- | Custom HUnit test case that forks a Python process and checks
557 aed2325f Iustin Pop
-- correspondence between Haskell-generated OpCodes and their Python
558 aed2325f Iustin Pop
-- decoded, validated and re-encoded version.
559 aed2325f Iustin Pop
--
560 aed2325f Iustin Pop
-- Note that we have a strange beast here: since launching Python is
561 aed2325f Iustin Pop
-- expensive, we don't do this via a usual QuickProperty, since that's
562 aed2325f Iustin Pop
-- slow (I've tested it, and it's indeed quite slow). Rather, we use a
563 aed2325f Iustin Pop
-- single HUnit assertion, and in it we manually use QuickCheck to
564 aed2325f Iustin Pop
-- generate 500 opcodes times the number of defined opcodes, which
565 aed2325f Iustin Pop
-- then we pass in bulk to Python. The drawbacks to this method are
566 aed2325f Iustin Pop
-- two fold: we cannot control the number of generated opcodes, since
567 aed2325f Iustin Pop
-- HUnit assertions don't get access to the test options, and for the
568 aed2325f Iustin Pop
-- same reason we can't run a repeatable seed. We should probably find
569 aed2325f Iustin Pop
-- a better way to do this, for example by having a
570 aed2325f Iustin Pop
-- separately-launched Python process (if not running the tests would
571 aed2325f Iustin Pop
-- be skipped).
572 d1ac695f Iustin Pop
case_py_compat_types :: HUnit.Assertion
573 d1ac695f Iustin Pop
case_py_compat_types = do
574 086ad4cf Iustin Pop
  let num_opcodes = length OpCodes.allOpIDs * 100
575 72747d91 Iustin Pop
  opcodes <- genSample (vectorOf num_opcodes
576 72747d91 Iustin Pop
                                   (arbitrary::Gen OpCodes.MetaOpCode))
577 72747d91 Iustin Pop
  let with_sum = map (\o -> (OpCodes.opSummary $
578 ad1c1e41 Iustin Pop
                             OpCodes.metaOpCode o, o)) opcodes
579 aed2325f Iustin Pop
      serialized = J.encode opcodes
580 dc4b5c42 Iustin Pop
  -- check for non-ASCII fields, usually due to 'arbitrary :: String'
581 dc4b5c42 Iustin Pop
  mapM_ (\op -> when (any (not . isAscii) (J.encode op)) .
582 dc4b5c42 Iustin Pop
                HUnit.assertFailure $
583 dc4b5c42 Iustin Pop
                  "OpCode has non-ASCII fields: " ++ show op
584 dc4b5c42 Iustin Pop
        ) opcodes
585 aed2325f Iustin Pop
  py_stdout <-
586 aed2325f Iustin Pop
     runPython "from ganeti import opcodes\n\
587 aed2325f Iustin Pop
               \from ganeti import serializer\n\
588 6e94b75c Jose A. Lopes
               \import sys\n\
589 aed2325f Iustin Pop
               \op_data = serializer.Load(sys.stdin.read())\n\
590 aed2325f Iustin Pop
               \decoded = [opcodes.OpCode.LoadOpCode(o) for o in op_data]\n\
591 aed2325f Iustin Pop
               \for op in decoded:\n\
592 aed2325f Iustin Pop
               \  op.Validate(True)\n\
593 ad1c1e41 Iustin Pop
               \encoded = [(op.Summary(), op.__getstate__())\n\
594 ad1c1e41 Iustin Pop
               \           for op in decoded]\n\
595 560ef132 Santi Raffa
               \print serializer.Dump(\
596 560ef132 Santi Raffa
               \  encoded,\
597 560ef132 Santi Raffa
               \  private_encoder=serializer.EncodeWithPrivateFields)"
598 560ef132 Santi Raffa
               serialized
599 aed2325f Iustin Pop
     >>= checkPythonResult
600 ad1c1e41 Iustin Pop
  let deserialised =
601 ad1c1e41 Iustin Pop
        J.decode py_stdout::J.Result [(String, OpCodes.MetaOpCode)]
602 aed2325f Iustin Pop
  decoded <- case deserialised of
603 aed2325f Iustin Pop
               J.Ok ops -> return ops
604 aed2325f Iustin Pop
               J.Error msg ->
605 aed2325f Iustin Pop
                 HUnit.assertFailure ("Unable to decode opcodes: " ++ msg)
606 aed2325f Iustin Pop
                 -- this already raised an expection, but we need it
607 aed2325f Iustin Pop
                 -- for proper types
608 aed2325f Iustin Pop
                 >> fail "Unable to decode opcodes"
609 aed2325f Iustin Pop
  HUnit.assertEqual "Mismatch in number of returned opcodes"
610 ad1c1e41 Iustin Pop
    (length decoded) (length with_sum)
611 aed2325f Iustin Pop
  mapM_ (uncurry (HUnit.assertEqual "Different result after encoding/decoding")
612 9d929656 Santi Raffa
        ) $ zip with_sum decoded
613 aed2325f Iustin Pop
614 d1ac695f Iustin Pop
-- | Custom HUnit test case that forks a Python process and checks
615 d1ac695f Iustin Pop
-- correspondence between Haskell OpCodes fields and their Python
616 d1ac695f Iustin Pop
-- equivalent.
617 d1ac695f Iustin Pop
case_py_compat_fields :: HUnit.Assertion
618 d1ac695f Iustin Pop
case_py_compat_fields = do
619 d1ac695f Iustin Pop
  let hs_fields = sort $ map (\op_id -> (op_id, OpCodes.allOpFields op_id))
620 d1ac695f Iustin Pop
                         OpCodes.allOpIDs
621 d1ac695f Iustin Pop
  py_stdout <-
622 d1ac695f Iustin Pop
     runPython "from ganeti import opcodes\n\
623 d1ac695f Iustin Pop
               \import sys\n\
624 d1ac695f Iustin Pop
               \from ganeti import serializer\n\
625 d1ac695f Iustin Pop
               \fields = [(k, sorted([p[0] for p in v.OP_PARAMS]))\n\
626 d1ac695f Iustin Pop
               \           for k, v in opcodes.OP_MAPPING.items()]\n\
627 d1ac695f Iustin Pop
               \print serializer.Dump(fields)" ""
628 d1ac695f Iustin Pop
     >>= checkPythonResult
629 d1ac695f Iustin Pop
  let deserialised = J.decode py_stdout::J.Result [(String, [String])]
630 d1ac695f Iustin Pop
  py_fields <- case deserialised of
631 d1ac695f Iustin Pop
                 J.Ok v -> return $ sort v
632 d1ac695f Iustin Pop
                 J.Error msg ->
633 d1ac695f Iustin Pop
                   HUnit.assertFailure ("Unable to decode op fields: " ++ msg)
634 d1ac695f Iustin Pop
                   -- this already raised an expection, but we need it
635 d1ac695f Iustin Pop
                   -- for proper types
636 d1ac695f Iustin Pop
                   >> fail "Unable to decode op fields"
637 d1ac695f Iustin Pop
  HUnit.assertEqual "Mismatch in number of returned opcodes"
638 d1ac695f Iustin Pop
    (length hs_fields) (length py_fields)
639 d1ac695f Iustin Pop
  HUnit.assertEqual "Mismatch in defined OP_IDs"
640 d1ac695f Iustin Pop
    (map fst hs_fields) (map fst py_fields)
641 d1ac695f Iustin Pop
  mapM_ (\((py_id, py_flds), (hs_id, hs_flds)) -> do
642 d1ac695f Iustin Pop
           HUnit.assertEqual "Mismatch in OP_ID" py_id hs_id
643 d1ac695f Iustin Pop
           HUnit.assertEqual ("Mismatch in fields for " ++ hs_id)
644 d1ac695f Iustin Pop
             py_flds hs_flds
645 9d929656 Santi Raffa
        ) $ zip hs_fields py_fields
646 d1ac695f Iustin Pop
647 4a826364 Iustin Pop
-- | Checks that setOpComment works correctly.
648 4a826364 Iustin Pop
prop_setOpComment :: OpCodes.MetaOpCode -> String -> Property
649 4a826364 Iustin Pop
prop_setOpComment op comment =
650 4a826364 Iustin Pop
  let (OpCodes.MetaOpCode common _) = OpCodes.setOpComment comment op
651 4a826364 Iustin Pop
  in OpCodes.opComment common ==? Just comment
652 4a826364 Iustin Pop
653 f56013fd Iustin Pop
-- | Tests wrong (negative) disk index.
654 f56013fd Iustin Pop
prop_mkDiskIndex_fail :: QuickCheck.Positive Int -> Property
655 f56013fd Iustin Pop
prop_mkDiskIndex_fail (Positive i) =
656 f56013fd Iustin Pop
  case mkDiskIndex (negate i) of
657 f56013fd Iustin Pop
    Bad msg -> printTestCase "error message " $
658 f56013fd Iustin Pop
               "Invalid value" `isPrefixOf` msg
659 f56013fd Iustin Pop
    Ok v -> failTest $ "Succeeded to build disk index '" ++ show v ++
660 f56013fd Iustin Pop
                       "' from negative value " ++ show (negate i)
661 f56013fd Iustin Pop
662 f56013fd Iustin Pop
-- | Tests a few invalid 'readRecreateDisks' cases.
663 f56013fd Iustin Pop
case_readRecreateDisks_fail :: Assertion
664 f56013fd Iustin Pop
case_readRecreateDisks_fail = do
665 f56013fd Iustin Pop
  assertBool "null" $
666 f56013fd Iustin Pop
    isJsonError (J.readJSON J.JSNull::J.Result RecreateDisksInfo)
667 f56013fd Iustin Pop
  assertBool "string" $
668 f56013fd Iustin Pop
    isJsonError (J.readJSON (J.showJSON "abc")::J.Result RecreateDisksInfo)
669 f56013fd Iustin Pop
670 f56013fd Iustin Pop
-- | Tests a few invalid 'readDdmOldChanges' cases.
671 f56013fd Iustin Pop
case_readDdmOldChanges_fail :: Assertion
672 f56013fd Iustin Pop
case_readDdmOldChanges_fail = do
673 f56013fd Iustin Pop
  assertBool "null" $
674 f56013fd Iustin Pop
    isJsonError (J.readJSON J.JSNull::J.Result DdmOldChanges)
675 f56013fd Iustin Pop
  assertBool "string" $
676 f56013fd Iustin Pop
    isJsonError (J.readJSON (J.showJSON "abc")::J.Result DdmOldChanges)
677 f56013fd Iustin Pop
678 f56013fd Iustin Pop
-- | Tests a few invalid 'readExportTarget' cases.
679 f56013fd Iustin Pop
case_readExportTarget_fail :: Assertion
680 f56013fd Iustin Pop
case_readExportTarget_fail = do
681 f56013fd Iustin Pop
  assertBool "null" $
682 f56013fd Iustin Pop
    isJsonError (J.readJSON J.JSNull::J.Result ExportTarget)
683 f56013fd Iustin Pop
  assertBool "int" $
684 f56013fd Iustin Pop
    isJsonError (J.readJSON (J.showJSON (5::Int))::J.Result ExportTarget)
685 f56013fd Iustin Pop
686 aed2325f Iustin Pop
testSuite "OpCodes"
687 20bc5360 Iustin Pop
            [ 'prop_serialization
688 20bc5360 Iustin Pop
            , 'case_AllDefined
689 d1ac695f Iustin Pop
            , 'case_py_compat_types
690 d1ac695f Iustin Pop
            , 'case_py_compat_fields
691 4a826364 Iustin Pop
            , 'prop_setOpComment
692 f56013fd Iustin Pop
            , 'prop_mkDiskIndex_fail
693 f56013fd Iustin Pop
            , 'case_readRecreateDisks_fail
694 f56013fd Iustin Pop
            , 'case_readDdmOldChanges_fail
695 f56013fd Iustin Pop
            , 'case_readExportTarget_fail
696 aed2325f Iustin Pop
            ]