Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpCodes.hs @ 9c8c69bc

History | View | Annotate | Download (16.6 kB)

1 e9aaa3c6 Iustin Pop
{-# LANGUAGE TemplateHaskell #-}
2 e9aaa3c6 Iustin Pop
3 702a4ee0 Iustin Pop
{-| Implementation of the opcodes.
4 702a4ee0 Iustin Pop
5 702a4ee0 Iustin Pop
-}
6 702a4ee0 Iustin Pop
7 702a4ee0 Iustin Pop
{-
8 702a4ee0 Iustin Pop
9 551b44e2 Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012, 2013 Google Inc.
10 702a4ee0 Iustin Pop
11 702a4ee0 Iustin Pop
This program is free software; you can redistribute it and/or modify
12 702a4ee0 Iustin Pop
it under the terms of the GNU General Public License as published by
13 702a4ee0 Iustin Pop
the Free Software Foundation; either version 2 of the License, or
14 702a4ee0 Iustin Pop
(at your option) any later version.
15 702a4ee0 Iustin Pop
16 702a4ee0 Iustin Pop
This program is distributed in the hope that it will be useful, but
17 702a4ee0 Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
18 702a4ee0 Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19 702a4ee0 Iustin Pop
General Public License for more details.
20 702a4ee0 Iustin Pop
21 702a4ee0 Iustin Pop
You should have received a copy of the GNU General Public License
22 702a4ee0 Iustin Pop
along with this program; if not, write to the Free Software
23 702a4ee0 Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
24 702a4ee0 Iustin Pop
02110-1301, USA.
25 702a4ee0 Iustin Pop
26 702a4ee0 Iustin Pop
-}
27 702a4ee0 Iustin Pop
28 702a4ee0 Iustin Pop
module Ganeti.OpCodes
29 ebf38064 Iustin Pop
  ( OpCode(..)
30 367c4241 Dato Simó
  , TagObject(..)
31 d8e7c45e Iustin Pop
  , tagObjectFrom
32 d8e7c45e Iustin Pop
  , encodeTagObject
33 d8e7c45e Iustin Pop
  , decodeTagObject
34 ebf38064 Iustin Pop
  , ReplaceDisksMode(..)
35 4a1dc2bf Iustin Pop
  , DiskIndex
36 4a1dc2bf Iustin Pop
  , mkDiskIndex
37 4a1dc2bf Iustin Pop
  , unDiskIndex
38 ebf38064 Iustin Pop
  , opID
39 a583ec5d Iustin Pop
  , allOpIDs
40 3929e782 Iustin Pop
  , allOpFields
41 ad1c1e41 Iustin Pop
  , opSummary
42 4a826364 Iustin Pop
  , CommonOpParams(..)
43 4a826364 Iustin Pop
  , defOpParams
44 4a826364 Iustin Pop
  , MetaOpCode(..)
45 4a826364 Iustin Pop
  , wrapOpCode
46 4a826364 Iustin Pop
  , setOpComment
47 551b44e2 Iustin Pop
  , setOpPriority
48 ebf38064 Iustin Pop
  ) where
49 702a4ee0 Iustin Pop
50 ad1c1e41 Iustin Pop
import Data.Maybe (fromMaybe)
51 4a826364 Iustin Pop
import Text.JSON (readJSON, showJSON, JSON, JSValue, makeObj)
52 4a826364 Iustin Pop
import qualified Text.JSON
53 702a4ee0 Iustin Pop
54 12c19659 Iustin Pop
import Ganeti.THH
55 e9aaa3c6 Iustin Pop
56 92f51573 Iustin Pop
import Ganeti.OpParams
57 ad1c1e41 Iustin Pop
import Ganeti.Types (OpSubmitPriority(..), fromNonEmpty)
58 ad1c1e41 Iustin Pop
import Ganeti.Query.Language (queryTypeOpToRaw)
59 4a1dc2bf Iustin Pop
60 525bfb36 Iustin Pop
-- | OpCode representation.
61 525bfb36 Iustin Pop
--
62 3bebda52 Dato Simó
-- We only implement a subset of Ganeti opcodes: those which are actually used
63 3bebda52 Dato Simó
-- in the htools codebase.
64 12c19659 Iustin Pop
$(genOpCode "OpCode"
65 ebf38064 Iustin Pop
  [ ("OpTestDelay",
66 7d421386 Iustin Pop
     [ pDelayDuration
67 7d421386 Iustin Pop
     , pDelayOnMaster
68 7d421386 Iustin Pop
     , pDelayOnNodes
69 a451dae2 Iustin Pop
     , pDelayRepeat
70 ebf38064 Iustin Pop
     ])
71 ebf38064 Iustin Pop
  , ("OpInstanceReplaceDisks",
72 92f51573 Iustin Pop
     [ pInstanceName
73 3d7e87b8 Iustin Pop
     , pEarlyRelease
74 3d7e87b8 Iustin Pop
     , pIgnoreIpolicy
75 7d421386 Iustin Pop
     , pReplaceDisksMode
76 7d421386 Iustin Pop
     , pReplaceDisksList
77 3d7e87b8 Iustin Pop
     , pRemoteNode
78 c7d249d0 Iustin Pop
     , pIallocator
79 ebf38064 Iustin Pop
     ])
80 ebf38064 Iustin Pop
  , ("OpInstanceFailover",
81 92f51573 Iustin Pop
     [ pInstanceName
82 3d7e87b8 Iustin Pop
     , pShutdownTimeout
83 7d421386 Iustin Pop
     , pIgnoreConsistency
84 c7d249d0 Iustin Pop
     , pMigrationTargetNode
85 3d7e87b8 Iustin Pop
     , pIgnoreIpolicy
86 3d7e87b8 Iustin Pop
     , pIallocator
87 ebf38064 Iustin Pop
     ])
88 ebf38064 Iustin Pop
  , ("OpInstanceMigrate",
89 92f51573 Iustin Pop
     [ pInstanceName
90 3d7e87b8 Iustin Pop
     , pMigrationMode
91 f9556d33 Iustin Pop
     , pMigrationLive
92 3d7e87b8 Iustin Pop
     , pMigrationTargetNode
93 3d7e87b8 Iustin Pop
     , pAllowRuntimeChgs
94 3d7e87b8 Iustin Pop
     , pIgnoreIpolicy
95 7d421386 Iustin Pop
     , pMigrationCleanup
96 3d7e87b8 Iustin Pop
     , pIallocator
97 7d421386 Iustin Pop
     , pAllowFailover
98 ebf38064 Iustin Pop
     ])
99 a451dae2 Iustin Pop
  , ("OpTagsGet",
100 a451dae2 Iustin Pop
     [ pTagsObject
101 a451dae2 Iustin Pop
     , pUseLocking
102 a451dae2 Iustin Pop
     ])
103 a451dae2 Iustin Pop
  , ("OpTagsSearch",
104 a451dae2 Iustin Pop
     [ pTagSearchPattern ])
105 3bebda52 Dato Simó
  , ("OpTagsSet",
106 92f51573 Iustin Pop
     [ pTagsObject
107 92f51573 Iustin Pop
     , pTagsList
108 3bebda52 Dato Simó
     ])
109 3bebda52 Dato Simó
  , ("OpTagsDel",
110 92f51573 Iustin Pop
     [ pTagsObject
111 92f51573 Iustin Pop
     , pTagsList
112 3bebda52 Dato Simó
     ])
113 c66f09f5 Iustin Pop
  , ("OpClusterPostInit", [])
114 c66f09f5 Iustin Pop
  , ("OpClusterDestroy", [])
115 c66f09f5 Iustin Pop
  , ("OpClusterQuery", [])
116 c66f09f5 Iustin Pop
  , ("OpClusterVerify",
117 c66f09f5 Iustin Pop
     [ pDebugSimulateErrors
118 c66f09f5 Iustin Pop
     , pErrorCodes
119 c66f09f5 Iustin Pop
     , pSkipChecks
120 c66f09f5 Iustin Pop
     , pIgnoreErrors
121 c66f09f5 Iustin Pop
     , pVerbose
122 c66f09f5 Iustin Pop
     , pOptGroupName
123 c66f09f5 Iustin Pop
     ])
124 c66f09f5 Iustin Pop
  , ("OpClusterVerifyConfig",
125 c66f09f5 Iustin Pop
     [ pDebugSimulateErrors
126 c66f09f5 Iustin Pop
     , pErrorCodes
127 c66f09f5 Iustin Pop
     , pIgnoreErrors
128 c66f09f5 Iustin Pop
     , pVerbose
129 c66f09f5 Iustin Pop
     ])
130 c66f09f5 Iustin Pop
  , ("OpClusterVerifyGroup",
131 c66f09f5 Iustin Pop
     [ pGroupName
132 c66f09f5 Iustin Pop
     , pDebugSimulateErrors
133 c66f09f5 Iustin Pop
     , pErrorCodes
134 c66f09f5 Iustin Pop
     , pSkipChecks
135 c66f09f5 Iustin Pop
     , pIgnoreErrors
136 c66f09f5 Iustin Pop
     , pVerbose
137 c66f09f5 Iustin Pop
     ])
138 c66f09f5 Iustin Pop
  , ("OpClusterVerifyDisks", [])
139 c66f09f5 Iustin Pop
  , ("OpGroupVerifyDisks",
140 c66f09f5 Iustin Pop
     [ pGroupName
141 c66f09f5 Iustin Pop
     ])
142 c66f09f5 Iustin Pop
  , ("OpClusterRepairDiskSizes",
143 c66f09f5 Iustin Pop
     [ pInstances
144 c66f09f5 Iustin Pop
     ])
145 c66f09f5 Iustin Pop
  , ("OpClusterConfigQuery",
146 c66f09f5 Iustin Pop
     [ pOutputFields
147 c66f09f5 Iustin Pop
     ])
148 c66f09f5 Iustin Pop
  , ("OpClusterRename",
149 c66f09f5 Iustin Pop
     [ pName
150 c66f09f5 Iustin Pop
     ])
151 c66f09f5 Iustin Pop
  , ("OpClusterSetParams",
152 c66f09f5 Iustin Pop
     [ pHvState
153 c66f09f5 Iustin Pop
     , pDiskState
154 c66f09f5 Iustin Pop
     , pVgName
155 c66f09f5 Iustin Pop
     , pEnabledHypervisors
156 c66f09f5 Iustin Pop
     , pClusterHvParams
157 c66f09f5 Iustin Pop
     , pClusterBeParams
158 c66f09f5 Iustin Pop
     , pOsHvp
159 6d558717 Iustin Pop
     , pClusterOsParams
160 c66f09f5 Iustin Pop
     , pDiskParams
161 c66f09f5 Iustin Pop
     , pCandidatePoolSize
162 c66f09f5 Iustin Pop
     , pUidPool
163 c66f09f5 Iustin Pop
     , pAddUids
164 c66f09f5 Iustin Pop
     , pRemoveUids
165 c66f09f5 Iustin Pop
     , pMaintainNodeHealth
166 c66f09f5 Iustin Pop
     , pPreallocWipeDisks
167 c66f09f5 Iustin Pop
     , pNicParams
168 c66f09f5 Iustin Pop
     , pNdParams
169 c66f09f5 Iustin Pop
     , pIpolicy
170 c66f09f5 Iustin Pop
     , pDrbdHelper
171 c66f09f5 Iustin Pop
     , pDefaultIAllocator
172 c66f09f5 Iustin Pop
     , pMasterNetdev
173 67fc4de7 Iustin Pop
     , pMasterNetmask
174 c66f09f5 Iustin Pop
     , pReservedLvs
175 c66f09f5 Iustin Pop
     , pHiddenOs
176 c66f09f5 Iustin Pop
     , pBlacklistedOs
177 c66f09f5 Iustin Pop
     , pUseExternalMipScript
178 66af5ec5 Helga Velroyen
     , pEnabledDiskTemplates
179 c66f09f5 Iustin Pop
     ])
180 c66f09f5 Iustin Pop
  , ("OpClusterRedistConf", [])
181 c66f09f5 Iustin Pop
  , ("OpClusterActivateMasterIp", [])
182 c66f09f5 Iustin Pop
  , ("OpClusterDeactivateMasterIp", [])
183 c66f09f5 Iustin Pop
  , ("OpQuery",
184 c66f09f5 Iustin Pop
     [ pQueryWhat
185 c66f09f5 Iustin Pop
     , pUseLocking
186 c66f09f5 Iustin Pop
     , pQueryFields
187 c66f09f5 Iustin Pop
     , pQueryFilter
188 c66f09f5 Iustin Pop
     ])
189 c66f09f5 Iustin Pop
  , ("OpQueryFields",
190 c66f09f5 Iustin Pop
     [ pQueryWhat
191 c66f09f5 Iustin Pop
     , pQueryFields
192 c66f09f5 Iustin Pop
     ])
193 c66f09f5 Iustin Pop
  , ("OpOobCommand",
194 c66f09f5 Iustin Pop
     [ pNodeNames
195 c66f09f5 Iustin Pop
     , pOobCommand
196 c66f09f5 Iustin Pop
     , pOobTimeout
197 c66f09f5 Iustin Pop
     , pIgnoreStatus
198 c66f09f5 Iustin Pop
     , pPowerDelay
199 c66f09f5 Iustin Pop
     ])
200 c66f09f5 Iustin Pop
  , ("OpNodeRemove", [ pNodeName ])
201 c66f09f5 Iustin Pop
  , ("OpNodeAdd",
202 c66f09f5 Iustin Pop
     [ pNodeName
203 c66f09f5 Iustin Pop
     , pHvState
204 c66f09f5 Iustin Pop
     , pDiskState
205 c66f09f5 Iustin Pop
     , pPrimaryIp
206 c66f09f5 Iustin Pop
     , pSecondaryIp
207 c66f09f5 Iustin Pop
     , pReadd
208 c66f09f5 Iustin Pop
     , pNodeGroup
209 c66f09f5 Iustin Pop
     , pMasterCapable
210 c66f09f5 Iustin Pop
     , pVmCapable
211 c66f09f5 Iustin Pop
     , pNdParams
212 c66f09f5 Iustin Pop
    ])
213 3131adc7 Iustin Pop
  , ("OpNodeQuery", dOldQuery)
214 c66f09f5 Iustin Pop
  , ("OpNodeQueryvols",
215 c66f09f5 Iustin Pop
     [ pOutputFields
216 c66f09f5 Iustin Pop
     , pNodes
217 c66f09f5 Iustin Pop
     ])
218 c66f09f5 Iustin Pop
  , ("OpNodeQueryStorage",
219 c66f09f5 Iustin Pop
     [ pOutputFields
220 c66f09f5 Iustin Pop
     , pStorageType
221 c66f09f5 Iustin Pop
     , pNodes
222 c66f09f5 Iustin Pop
     , pStorageName
223 c66f09f5 Iustin Pop
     ])
224 c66f09f5 Iustin Pop
  , ("OpNodeModifyStorage",
225 c66f09f5 Iustin Pop
     [ pNodeName
226 c66f09f5 Iustin Pop
     , pStorageType
227 c66f09f5 Iustin Pop
     , pStorageName
228 c66f09f5 Iustin Pop
     , pStorageChanges
229 c66f09f5 Iustin Pop
     ])
230 c66f09f5 Iustin Pop
  , ("OpRepairNodeStorage",
231 c66f09f5 Iustin Pop
     [ pNodeName
232 c66f09f5 Iustin Pop
     , pStorageType
233 c66f09f5 Iustin Pop
     , pStorageName
234 c66f09f5 Iustin Pop
     , pIgnoreConsistency
235 c66f09f5 Iustin Pop
     ])
236 c66f09f5 Iustin Pop
  , ("OpNodeSetParams",
237 c66f09f5 Iustin Pop
     [ pNodeName
238 c66f09f5 Iustin Pop
     , pForce
239 c66f09f5 Iustin Pop
     , pHvState
240 c66f09f5 Iustin Pop
     , pDiskState
241 c66f09f5 Iustin Pop
     , pMasterCandidate
242 c66f09f5 Iustin Pop
     , pOffline
243 c66f09f5 Iustin Pop
     , pDrained
244 c66f09f5 Iustin Pop
     , pAutoPromote
245 c66f09f5 Iustin Pop
     , pMasterCapable
246 c66f09f5 Iustin Pop
     , pVmCapable
247 c66f09f5 Iustin Pop
     , pSecondaryIp
248 c66f09f5 Iustin Pop
     , pNdParams
249 67fc4de7 Iustin Pop
     , pPowered
250 c66f09f5 Iustin Pop
     ])
251 c66f09f5 Iustin Pop
  , ("OpNodePowercycle",
252 c66f09f5 Iustin Pop
     [ pNodeName
253 c66f09f5 Iustin Pop
     , pForce
254 c66f09f5 Iustin Pop
     ])
255 c66f09f5 Iustin Pop
  , ("OpNodeMigrate",
256 c66f09f5 Iustin Pop
     [ pNodeName
257 c66f09f5 Iustin Pop
     , pMigrationMode
258 c66f09f5 Iustin Pop
     , pMigrationLive
259 c66f09f5 Iustin Pop
     , pMigrationTargetNode
260 c66f09f5 Iustin Pop
     , pAllowRuntimeChgs
261 c66f09f5 Iustin Pop
     , pIgnoreIpolicy
262 c66f09f5 Iustin Pop
     , pIallocator
263 c66f09f5 Iustin Pop
     ])
264 c66f09f5 Iustin Pop
  , ("OpNodeEvacuate",
265 c66f09f5 Iustin Pop
     [ pEarlyRelease
266 c66f09f5 Iustin Pop
     , pNodeName
267 c66f09f5 Iustin Pop
     , pRemoteNode
268 c66f09f5 Iustin Pop
     , pIallocator
269 c66f09f5 Iustin Pop
     , pEvacMode
270 c66f09f5 Iustin Pop
     ])
271 6d558717 Iustin Pop
  , ("OpInstanceCreate",
272 6d558717 Iustin Pop
     [ pInstanceName
273 6d558717 Iustin Pop
     , pForceVariant
274 6d558717 Iustin Pop
     , pWaitForSync
275 6d558717 Iustin Pop
     , pNameCheck
276 6d558717 Iustin Pop
     , pIgnoreIpolicy
277 6d558717 Iustin Pop
     , pInstBeParams
278 6d558717 Iustin Pop
     , pInstDisks
279 6d558717 Iustin Pop
     , pDiskTemplate
280 6d558717 Iustin Pop
     , pFileDriver
281 6d558717 Iustin Pop
     , pFileStorageDir
282 6d558717 Iustin Pop
     , pInstHvParams
283 6d558717 Iustin Pop
     , pHypervisor
284 6d558717 Iustin Pop
     , pIallocator
285 6d558717 Iustin Pop
     , pResetDefaults
286 6d558717 Iustin Pop
     , pIpCheck
287 6d558717 Iustin Pop
     , pIpConflictsCheck
288 6d558717 Iustin Pop
     , pInstCreateMode
289 6d558717 Iustin Pop
     , pInstNics
290 6d558717 Iustin Pop
     , pNoInstall
291 6d558717 Iustin Pop
     , pInstOsParams
292 6d558717 Iustin Pop
     , pInstOs
293 6d558717 Iustin Pop
     , pPrimaryNode
294 6d558717 Iustin Pop
     , pSecondaryNode
295 6d558717 Iustin Pop
     , pSourceHandshake
296 6d558717 Iustin Pop
     , pSourceInstance
297 6d558717 Iustin Pop
     , pSourceShutdownTimeout
298 6d558717 Iustin Pop
     , pSourceX509Ca
299 6d558717 Iustin Pop
     , pSrcNode
300 6d558717 Iustin Pop
     , pSrcPath
301 6d558717 Iustin Pop
     , pStartInstance
302 1f1188c3 Michael Hanselmann
     , pOpportunisticLocking
303 6d558717 Iustin Pop
     , pInstTags
304 6d558717 Iustin Pop
     ])
305 c2d3219b Iustin Pop
  , ("OpInstanceMultiAlloc",
306 c2d3219b Iustin Pop
     [ pIallocator
307 c2d3219b Iustin Pop
     , pMultiAllocInstances
308 c298ed02 Michael Hanselmann
     , pOpportunisticLocking
309 c2d3219b Iustin Pop
     ])
310 c2d3219b Iustin Pop
  , ("OpInstanceReinstall",
311 c2d3219b Iustin Pop
     [ pInstanceName
312 c2d3219b Iustin Pop
     , pForceVariant
313 c2d3219b Iustin Pop
     , pInstOs
314 c2d3219b Iustin Pop
     , pTempOsParams
315 c2d3219b Iustin Pop
     ])
316 c2d3219b Iustin Pop
  , ("OpInstanceRemove",
317 c2d3219b Iustin Pop
     [ pInstanceName
318 c2d3219b Iustin Pop
     , pShutdownTimeout
319 c2d3219b Iustin Pop
     , pIgnoreFailures
320 c2d3219b Iustin Pop
     ])
321 c2d3219b Iustin Pop
  , ("OpInstanceRename",
322 c2d3219b Iustin Pop
     [ pInstanceName
323 c2d3219b Iustin Pop
     , pNewName
324 c2d3219b Iustin Pop
     , pNameCheck
325 c2d3219b Iustin Pop
     , pIpCheck
326 c2d3219b Iustin Pop
     ])
327 c2d3219b Iustin Pop
  , ("OpInstanceStartup",
328 c2d3219b Iustin Pop
     [ pInstanceName
329 c2d3219b Iustin Pop
     , pForce
330 c2d3219b Iustin Pop
     , pIgnoreOfflineNodes
331 c2d3219b Iustin Pop
     , pTempHvParams
332 c2d3219b Iustin Pop
     , pTempBeParams
333 c2d3219b Iustin Pop
     , pNoRemember
334 c2d3219b Iustin Pop
     , pStartupPaused
335 c2d3219b Iustin Pop
     ])
336 c2d3219b Iustin Pop
  , ("OpInstanceShutdown",
337 c2d3219b Iustin Pop
     [ pInstanceName
338 0d57ce24 Guido Trotter
     , pForce
339 c2d3219b Iustin Pop
     , pIgnoreOfflineNodes
340 c2d3219b Iustin Pop
     , pShutdownTimeout'
341 c2d3219b Iustin Pop
     , pNoRemember
342 c2d3219b Iustin Pop
     ])
343 c2d3219b Iustin Pop
  , ("OpInstanceReboot",
344 c2d3219b Iustin Pop
     [ pInstanceName
345 c2d3219b Iustin Pop
     , pShutdownTimeout
346 c2d3219b Iustin Pop
     , pIgnoreSecondaries
347 c2d3219b Iustin Pop
     , pRebootType
348 4a90bd4f Michele Tartara
     , pReason
349 c2d3219b Iustin Pop
     ])
350 c2d3219b Iustin Pop
  , ("OpInstanceMove",
351 c2d3219b Iustin Pop
     [ pInstanceName
352 c2d3219b Iustin Pop
     , pShutdownTimeout
353 c2d3219b Iustin Pop
     , pIgnoreIpolicy
354 c2d3219b Iustin Pop
     , pMoveTargetNode
355 c2d3219b Iustin Pop
     , pIgnoreConsistency
356 c2d3219b Iustin Pop
     ])
357 c2d3219b Iustin Pop
  , ("OpInstanceConsole",
358 c2d3219b Iustin Pop
     [ pInstanceName ])
359 c2d3219b Iustin Pop
  , ("OpInstanceActivateDisks",
360 c2d3219b Iustin Pop
     [ pInstanceName
361 c2d3219b Iustin Pop
     , pIgnoreDiskSize
362 c2d3219b Iustin Pop
     , pWaitForSyncFalse
363 c2d3219b Iustin Pop
     ])
364 c2d3219b Iustin Pop
  , ("OpInstanceDeactivateDisks",
365 c2d3219b Iustin Pop
     [ pInstanceName
366 c2d3219b Iustin Pop
     , pForce
367 c2d3219b Iustin Pop
     ])
368 c2d3219b Iustin Pop
  , ("OpInstanceRecreateDisks",
369 c2d3219b Iustin Pop
     [ pInstanceName
370 c2d3219b Iustin Pop
     , pRecreateDisksInfo
371 c2d3219b Iustin Pop
     , pNodes
372 c2d3219b Iustin Pop
     , pIallocator
373 c2d3219b Iustin Pop
     ])
374 3131adc7 Iustin Pop
  , ("OpInstanceQuery", dOldQuery)
375 c2d3219b Iustin Pop
  , ("OpInstanceQueryData",
376 c2d3219b Iustin Pop
     [ pUseLocking
377 c2d3219b Iustin Pop
     , pInstances
378 c2d3219b Iustin Pop
     , pStatic
379 c2d3219b Iustin Pop
     ])
380 c2d3219b Iustin Pop
  , ("OpInstanceSetParams",
381 c2d3219b Iustin Pop
     [ pInstanceName
382 c2d3219b Iustin Pop
     , pForce
383 c2d3219b Iustin Pop
     , pForceVariant
384 c2d3219b Iustin Pop
     , pIgnoreIpolicy
385 c2d3219b Iustin Pop
     , pInstParamsNicChanges
386 c2d3219b Iustin Pop
     , pInstParamsDiskChanges
387 c2d3219b Iustin Pop
     , pInstBeParams
388 c2d3219b Iustin Pop
     , pRuntimeMem
389 c2d3219b Iustin Pop
     , pInstHvParams
390 88127c47 Iustin Pop
     , pOptDiskTemplate
391 d2204b1a Klaus Aehlig
     , pPrimaryNode
392 c2d3219b Iustin Pop
     , pRemoteNode
393 c2d3219b Iustin Pop
     , pOsNameChange
394 c2d3219b Iustin Pop
     , pInstOsParams
395 c2d3219b Iustin Pop
     , pWaitForSync
396 c2d3219b Iustin Pop
     , pOffline
397 c2d3219b Iustin Pop
     , pIpConflictsCheck
398 c2d3219b Iustin Pop
     ])
399 c2d3219b Iustin Pop
  , ("OpInstanceGrowDisk",
400 c2d3219b Iustin Pop
     [ pInstanceName
401 c2d3219b Iustin Pop
     , pWaitForSync
402 c2d3219b Iustin Pop
     , pDiskIndex
403 c2d3219b Iustin Pop
     , pDiskChgAmount
404 c2d3219b Iustin Pop
     , pDiskChgAbsolute
405 c2d3219b Iustin Pop
     ])
406 c2d3219b Iustin Pop
  , ("OpInstanceChangeGroup",
407 c2d3219b Iustin Pop
     [ pInstanceName
408 c2d3219b Iustin Pop
     , pEarlyRelease
409 c2d3219b Iustin Pop
     , pIallocator
410 c2d3219b Iustin Pop
     , pTargetGroups
411 c2d3219b Iustin Pop
     ])
412 398e9066 Iustin Pop
  , ("OpGroupAdd",
413 398e9066 Iustin Pop
     [ pGroupName
414 398e9066 Iustin Pop
     , pNodeGroupAllocPolicy
415 398e9066 Iustin Pop
     , pGroupNodeParams
416 398e9066 Iustin Pop
     , pDiskParams
417 398e9066 Iustin Pop
     , pHvState
418 398e9066 Iustin Pop
     , pDiskState
419 398e9066 Iustin Pop
     , pIpolicy
420 398e9066 Iustin Pop
     ])
421 398e9066 Iustin Pop
  , ("OpGroupAssignNodes",
422 398e9066 Iustin Pop
     [ pGroupName
423 398e9066 Iustin Pop
     , pForce
424 398e9066 Iustin Pop
     , pRequiredNodes
425 398e9066 Iustin Pop
     ])
426 3131adc7 Iustin Pop
  , ("OpGroupQuery", dOldQueryNoLocking)
427 398e9066 Iustin Pop
  , ("OpGroupSetParams",
428 398e9066 Iustin Pop
     [ pGroupName
429 398e9066 Iustin Pop
     , pNodeGroupAllocPolicy
430 398e9066 Iustin Pop
     , pGroupNodeParams
431 398e9066 Iustin Pop
     , pDiskParams
432 398e9066 Iustin Pop
     , pHvState
433 398e9066 Iustin Pop
     , pDiskState
434 398e9066 Iustin Pop
     , pIpolicy
435 398e9066 Iustin Pop
     ])
436 398e9066 Iustin Pop
  , ("OpGroupRemove",
437 398e9066 Iustin Pop
     [ pGroupName ])
438 398e9066 Iustin Pop
  , ("OpGroupRename",
439 398e9066 Iustin Pop
     [ pGroupName
440 398e9066 Iustin Pop
     , pNewName
441 398e9066 Iustin Pop
     ])
442 398e9066 Iustin Pop
  , ("OpGroupEvacuate",
443 398e9066 Iustin Pop
     [ pGroupName
444 398e9066 Iustin Pop
     , pEarlyRelease
445 398e9066 Iustin Pop
     , pIallocator
446 398e9066 Iustin Pop
     , pTargetGroups
447 398e9066 Iustin Pop
     ])
448 398e9066 Iustin Pop
  , ("OpOsDiagnose",
449 398e9066 Iustin Pop
     [ pOutputFields
450 398e9066 Iustin Pop
     , pNames ])
451 b954f097 Constantinos Venetsanopoulos
  , ("OpExtStorageDiagnose",
452 b954f097 Constantinos Venetsanopoulos
     [ pOutputFields
453 b954f097 Constantinos Venetsanopoulos
     , pNames ])
454 398e9066 Iustin Pop
  , ("OpBackupQuery",
455 398e9066 Iustin Pop
     [ pUseLocking
456 398e9066 Iustin Pop
     , pNodes
457 398e9066 Iustin Pop
     ])
458 398e9066 Iustin Pop
  , ("OpBackupPrepare",
459 398e9066 Iustin Pop
     [ pInstanceName
460 398e9066 Iustin Pop
     , pExportMode
461 398e9066 Iustin Pop
     ])
462 398e9066 Iustin Pop
  , ("OpBackupExport",
463 398e9066 Iustin Pop
     [ pInstanceName
464 398e9066 Iustin Pop
     , pShutdownTimeout
465 398e9066 Iustin Pop
     , pExportTargetNode
466 67fc4de7 Iustin Pop
     , pShutdownInstance
467 398e9066 Iustin Pop
     , pRemoveInstance
468 398e9066 Iustin Pop
     , pIgnoreRemoveFailures
469 398e9066 Iustin Pop
     , pExportMode
470 398e9066 Iustin Pop
     , pX509KeyName
471 398e9066 Iustin Pop
     , pX509DestCA
472 398e9066 Iustin Pop
     ])
473 398e9066 Iustin Pop
  , ("OpBackupRemove",
474 398e9066 Iustin Pop
     [ pInstanceName ])
475 a3f02317 Iustin Pop
  , ("OpTestAllocator",
476 a3f02317 Iustin Pop
     [ pIAllocatorDirection
477 a3f02317 Iustin Pop
     , pIAllocatorMode
478 a3f02317 Iustin Pop
     , pIAllocatorReqName
479 a3f02317 Iustin Pop
     , pIAllocatorNics
480 a3f02317 Iustin Pop
     , pIAllocatorDisks
481 a3f02317 Iustin Pop
     , pHypervisor
482 a3f02317 Iustin Pop
     , pIallocator
483 a3f02317 Iustin Pop
     , pInstTags
484 a3f02317 Iustin Pop
     , pIAllocatorMemory
485 a3f02317 Iustin Pop
     , pIAllocatorVCpus
486 a3f02317 Iustin Pop
     , pIAllocatorOs
487 a3f02317 Iustin Pop
     , pDiskTemplate
488 a3f02317 Iustin Pop
     , pIAllocatorInstances
489 a3f02317 Iustin Pop
     , pIAllocatorEvacMode
490 a3f02317 Iustin Pop
     , pTargetGroups
491 a3f02317 Iustin Pop
     , pIAllocatorSpindleUse
492 a3f02317 Iustin Pop
     , pIAllocatorCount
493 a3f02317 Iustin Pop
     ])
494 a3f02317 Iustin Pop
  , ("OpTestJqueue",
495 a3f02317 Iustin Pop
     [ pJQueueNotifyWaitLock
496 a3f02317 Iustin Pop
     , pJQueueNotifyExec
497 a3f02317 Iustin Pop
     , pJQueueLogMessages
498 a3f02317 Iustin Pop
     , pJQueueFail
499 a3f02317 Iustin Pop
     ])
500 a3f02317 Iustin Pop
  , ("OpTestDummy",
501 a3f02317 Iustin Pop
     [ pTestDummyResult
502 a3f02317 Iustin Pop
     , pTestDummyMessages
503 a3f02317 Iustin Pop
     , pTestDummyFail
504 a3f02317 Iustin Pop
     , pTestDummySubmitJobs
505 a3f02317 Iustin Pop
     ])
506 8d239fa4 Iustin Pop
  , ("OpNetworkAdd",
507 8d239fa4 Iustin Pop
     [ pNetworkName
508 8d239fa4 Iustin Pop
     , pNetworkAddress4
509 8d239fa4 Iustin Pop
     , pNetworkGateway4
510 8d239fa4 Iustin Pop
     , pNetworkAddress6
511 8d239fa4 Iustin Pop
     , pNetworkGateway6
512 8d239fa4 Iustin Pop
     , pNetworkMacPrefix
513 8d239fa4 Iustin Pop
     , pNetworkAddRsvdIps
514 1dbceab9 Iustin Pop
     , pIpConflictsCheck
515 8d239fa4 Iustin Pop
     , pInstTags
516 8d239fa4 Iustin Pop
     ])
517 8d239fa4 Iustin Pop
  , ("OpNetworkRemove",
518 8d239fa4 Iustin Pop
     [ pNetworkName
519 8d239fa4 Iustin Pop
     , pForce
520 8d239fa4 Iustin Pop
     ])
521 8d239fa4 Iustin Pop
  , ("OpNetworkSetParams",
522 8d239fa4 Iustin Pop
     [ pNetworkName
523 8d239fa4 Iustin Pop
     , pNetworkGateway4
524 8d239fa4 Iustin Pop
     , pNetworkAddress6
525 8d239fa4 Iustin Pop
     , pNetworkGateway6
526 8d239fa4 Iustin Pop
     , pNetworkMacPrefix
527 8d239fa4 Iustin Pop
     , pNetworkAddRsvdIps
528 8d239fa4 Iustin Pop
     , pNetworkRemoveRsvdIps
529 8d239fa4 Iustin Pop
     ])
530 8d239fa4 Iustin Pop
  , ("OpNetworkConnect",
531 8d239fa4 Iustin Pop
     [ pGroupName
532 8d239fa4 Iustin Pop
     , pNetworkName
533 8d239fa4 Iustin Pop
     , pNetworkMode
534 8d239fa4 Iustin Pop
     , pNetworkLink
535 8d239fa4 Iustin Pop
     , pIpConflictsCheck
536 8d239fa4 Iustin Pop
     ])
537 8d239fa4 Iustin Pop
  , ("OpNetworkDisconnect",
538 8d239fa4 Iustin Pop
     [ pGroupName
539 8d239fa4 Iustin Pop
     , pNetworkName
540 8d239fa4 Iustin Pop
     ])
541 8d459129 Michael Hanselmann
  , ("OpNetworkQuery", dOldQuery)
542 1cd563e2 Iustin Pop
  , ("OpRestrictedCommand",
543 1cd563e2 Iustin Pop
     [ pUseLocking
544 1cd563e2 Iustin Pop
     , pRequiredNodes
545 1cd563e2 Iustin Pop
     , pRestrictedCommand
546 1cd563e2 Iustin Pop
     ])
547 ebf38064 Iustin Pop
  ])
548 12c19659 Iustin Pop
549 a583ec5d Iustin Pop
-- | Returns the OP_ID for a given opcode value.
550 12c19659 Iustin Pop
$(genOpID ''OpCode "opID")
551 702a4ee0 Iustin Pop
552 a583ec5d Iustin Pop
-- | A list of all defined/supported opcode IDs.
553 a583ec5d Iustin Pop
$(genAllOpIDs ''OpCode "allOpIDs")
554 a583ec5d Iustin Pop
555 702a4ee0 Iustin Pop
instance JSON OpCode where
556 ebf38064 Iustin Pop
  readJSON = loadOpCode
557 ebf38064 Iustin Pop
  showJSON = saveOpCode
558 4a826364 Iustin Pop
559 ad1c1e41 Iustin Pop
-- | Generates the summary value for an opcode.
560 ad1c1e41 Iustin Pop
opSummaryVal :: OpCode -> Maybe String
561 ad1c1e41 Iustin Pop
opSummaryVal OpClusterVerifyGroup { opGroupName = s } = Just (fromNonEmpty s)
562 ad1c1e41 Iustin Pop
opSummaryVal OpGroupVerifyDisks { opGroupName = s } = Just (fromNonEmpty s)
563 ad1c1e41 Iustin Pop
opSummaryVal OpClusterRename { opName = s } = Just (fromNonEmpty s)
564 ad1c1e41 Iustin Pop
opSummaryVal OpQuery { opWhat = s } = Just (queryTypeOpToRaw s)
565 ad1c1e41 Iustin Pop
opSummaryVal OpQueryFields { opWhat = s } = Just (queryTypeOpToRaw s)
566 ad1c1e41 Iustin Pop
opSummaryVal OpNodeRemove { opNodeName = s } = Just (fromNonEmpty s)
567 ad1c1e41 Iustin Pop
opSummaryVal OpNodeAdd { opNodeName = s } = Just (fromNonEmpty s)
568 ad1c1e41 Iustin Pop
opSummaryVal OpNodeModifyStorage { opNodeName = s } = Just (fromNonEmpty s)
569 ad1c1e41 Iustin Pop
opSummaryVal OpRepairNodeStorage  { opNodeName = s } = Just (fromNonEmpty s)
570 ad1c1e41 Iustin Pop
opSummaryVal OpNodeSetParams { opNodeName = s } = Just (fromNonEmpty s)
571 ad1c1e41 Iustin Pop
opSummaryVal OpNodePowercycle { opNodeName = s } = Just (fromNonEmpty s)
572 ad1c1e41 Iustin Pop
opSummaryVal OpNodeMigrate { opNodeName = s } = Just (fromNonEmpty s)
573 ad1c1e41 Iustin Pop
opSummaryVal OpNodeEvacuate { opNodeName = s } = Just (fromNonEmpty s)
574 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceCreate { opInstanceName = s } = Just s
575 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceReinstall { opInstanceName = s } = Just s
576 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceRemove { opInstanceName = s } = Just s
577 ad1c1e41 Iustin Pop
-- FIXME: instance rename should show both names; currently it shows none
578 ad1c1e41 Iustin Pop
-- opSummaryVal OpInstanceRename { opInstanceName = s } = Just s
579 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceStartup { opInstanceName = s } = Just s
580 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceShutdown { opInstanceName = s } = Just s
581 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceReboot { opInstanceName = s } = Just s
582 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceReplaceDisks { opInstanceName = s } = Just s
583 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceFailover { opInstanceName = s } = Just s
584 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceMigrate { opInstanceName = s } = Just s
585 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceMove { opInstanceName = s } = Just s
586 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceConsole { opInstanceName = s } = Just s
587 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceActivateDisks { opInstanceName = s } = Just s
588 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceDeactivateDisks { opInstanceName = s } = Just s
589 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceRecreateDisks { opInstanceName = s } = Just s
590 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceSetParams { opInstanceName = s } = Just s
591 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceGrowDisk { opInstanceName = s } = Just s
592 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceChangeGroup { opInstanceName = s } = Just s
593 ad1c1e41 Iustin Pop
opSummaryVal OpGroupAdd { opGroupName = s } = Just (fromNonEmpty s)
594 ad1c1e41 Iustin Pop
opSummaryVal OpGroupAssignNodes { opGroupName = s } = Just (fromNonEmpty s)
595 ad1c1e41 Iustin Pop
opSummaryVal OpGroupSetParams { opGroupName = s } = Just (fromNonEmpty s)
596 ad1c1e41 Iustin Pop
opSummaryVal OpGroupRemove { opGroupName = s } = Just (fromNonEmpty s)
597 ad1c1e41 Iustin Pop
opSummaryVal OpGroupEvacuate { opGroupName = s } = Just (fromNonEmpty s)
598 ad1c1e41 Iustin Pop
opSummaryVal OpBackupPrepare { opInstanceName = s } = Just s
599 ad1c1e41 Iustin Pop
opSummaryVal OpBackupExport { opInstanceName = s } = Just s
600 ad1c1e41 Iustin Pop
opSummaryVal OpBackupRemove { opInstanceName = s } = Just s
601 ad1c1e41 Iustin Pop
opSummaryVal OpTagsGet { opKind = k } =
602 ad1c1e41 Iustin Pop
  Just . fromMaybe "None" $ tagNameOf k
603 ad1c1e41 Iustin Pop
opSummaryVal OpTagsSearch { opTagSearchPattern = s } = Just (fromNonEmpty s)
604 ad1c1e41 Iustin Pop
opSummaryVal OpTestDelay { opDelayDuration = d } = Just (show d)
605 ad1c1e41 Iustin Pop
opSummaryVal OpTestAllocator { opIallocator = s } =
606 ad1c1e41 Iustin Pop
  -- FIXME: Python doesn't handle None fields well, so we have behave the same
607 ad1c1e41 Iustin Pop
  Just $ maybe "None" fromNonEmpty s
608 ad1c1e41 Iustin Pop
opSummaryVal OpNetworkAdd { opNetworkName = s} = Just (fromNonEmpty s)
609 ad1c1e41 Iustin Pop
opSummaryVal OpNetworkRemove { opNetworkName = s} = Just (fromNonEmpty s)
610 ad1c1e41 Iustin Pop
opSummaryVal OpNetworkSetParams { opNetworkName = s} = Just (fromNonEmpty s)
611 ad1c1e41 Iustin Pop
opSummaryVal OpNetworkConnect { opNetworkName = s} = Just (fromNonEmpty s)
612 ad1c1e41 Iustin Pop
opSummaryVal OpNetworkDisconnect { opNetworkName = s} = Just (fromNonEmpty s)
613 ad1c1e41 Iustin Pop
opSummaryVal _ = Nothing
614 ad1c1e41 Iustin Pop
615 ad1c1e41 Iustin Pop
-- | Computes the summary of the opcode.
616 ad1c1e41 Iustin Pop
opSummary :: OpCode -> String
617 ad1c1e41 Iustin Pop
opSummary op =
618 ad1c1e41 Iustin Pop
  case opSummaryVal op of
619 ad1c1e41 Iustin Pop
    Nothing -> op_suffix
620 ad1c1e41 Iustin Pop
    Just s -> op_suffix ++ "(" ++ s ++ ")"
621 ad1c1e41 Iustin Pop
  where op_suffix = drop 3 $ opID op
622 ad1c1e41 Iustin Pop
623 4a826364 Iustin Pop
-- | Generic\/common opcode parameters.
624 4a826364 Iustin Pop
$(buildObject "CommonOpParams" "op"
625 4a826364 Iustin Pop
  [ pDryRun
626 4a826364 Iustin Pop
  , pDebugLevel
627 4a826364 Iustin Pop
  , pOpPriority
628 4a826364 Iustin Pop
  , pDependencies
629 4a826364 Iustin Pop
  , pComment
630 4a826364 Iustin Pop
  ])
631 4a826364 Iustin Pop
632 4a826364 Iustin Pop
-- | Default common parameter values.
633 4a826364 Iustin Pop
defOpParams :: CommonOpParams
634 4a826364 Iustin Pop
defOpParams =
635 4a826364 Iustin Pop
  CommonOpParams { opDryRun     = Nothing
636 4a826364 Iustin Pop
                 , opDebugLevel = Nothing
637 4a826364 Iustin Pop
                 , opPriority   = OpPrioNormal
638 4a826364 Iustin Pop
                 , opDepends    = Nothing
639 4a826364 Iustin Pop
                 , opComment    = Nothing
640 4a826364 Iustin Pop
                 }
641 4a826364 Iustin Pop
642 4a826364 Iustin Pop
-- | The top-level opcode type.
643 ad1c1e41 Iustin Pop
data MetaOpCode = MetaOpCode { metaParams :: CommonOpParams
644 ad1c1e41 Iustin Pop
                             , metaOpCode :: OpCode
645 ad1c1e41 Iustin Pop
                             } deriving (Show, Eq)
646 4a826364 Iustin Pop
647 4a826364 Iustin Pop
-- | JSON serialisation for 'MetaOpCode'.
648 4a826364 Iustin Pop
showMeta :: MetaOpCode -> JSValue
649 4a826364 Iustin Pop
showMeta (MetaOpCode params op) =
650 4a826364 Iustin Pop
  let objparams = toDictCommonOpParams params
651 4a826364 Iustin Pop
      objop = toDictOpCode op
652 4a826364 Iustin Pop
  in makeObj (objparams ++ objop)
653 4a826364 Iustin Pop
654 4a826364 Iustin Pop
-- | JSON deserialisation for 'MetaOpCode'
655 4a826364 Iustin Pop
readMeta :: JSValue -> Text.JSON.Result MetaOpCode
656 4a826364 Iustin Pop
readMeta v = do
657 4a826364 Iustin Pop
  meta <- readJSON v
658 4a826364 Iustin Pop
  op <- readJSON v
659 4a826364 Iustin Pop
  return $ MetaOpCode meta op
660 4a826364 Iustin Pop
661 4a826364 Iustin Pop
instance JSON MetaOpCode where
662 4a826364 Iustin Pop
  showJSON = showMeta
663 4a826364 Iustin Pop
  readJSON = readMeta
664 4a826364 Iustin Pop
665 4a826364 Iustin Pop
-- | Wraps an 'OpCode' with the default parameters to build a
666 4a826364 Iustin Pop
-- 'MetaOpCode'.
667 4a826364 Iustin Pop
wrapOpCode :: OpCode -> MetaOpCode
668 4a826364 Iustin Pop
wrapOpCode = MetaOpCode defOpParams
669 4a826364 Iustin Pop
670 4a826364 Iustin Pop
-- | Sets the comment on a meta opcode.
671 4a826364 Iustin Pop
setOpComment :: String -> MetaOpCode -> MetaOpCode
672 4a826364 Iustin Pop
setOpComment comment (MetaOpCode common op) =
673 4a826364 Iustin Pop
  MetaOpCode (common { opComment = Just comment}) op
674 551b44e2 Iustin Pop
675 551b44e2 Iustin Pop
-- | Sets the priority on a meta opcode.
676 551b44e2 Iustin Pop
setOpPriority :: OpSubmitPriority -> MetaOpCode -> MetaOpCode
677 551b44e2 Iustin Pop
setOpPriority prio (MetaOpCode common op) =
678 551b44e2 Iustin Pop
  MetaOpCode (common { opPriority = prio }) op