Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpCodes.hs @ e89525a8

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