Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpCodes.hs @ 3039e2dc

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