Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpCodes.hs @ 11e90588

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