Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpCodes.hs @ e713a686

History | View | Annotate | Download (27.1 kB)

1 34af39e8 Jose A. Lopes
{-# LANGUAGE ExistentialQuantification, TemplateHaskell #-}
2 34af39e8 Jose A. Lopes
{-# OPTIONS_GHC -fno-warn-orphans #-}
3 e9aaa3c6 Iustin Pop
4 702a4ee0 Iustin Pop
{-| Implementation of the opcodes.
5 702a4ee0 Iustin Pop
6 702a4ee0 Iustin Pop
-}
7 702a4ee0 Iustin Pop
8 702a4ee0 Iustin Pop
{-
9 702a4ee0 Iustin Pop
10 551b44e2 Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012, 2013 Google Inc.
11 702a4ee0 Iustin Pop
12 702a4ee0 Iustin Pop
This program is free software; you can redistribute it and/or modify
13 702a4ee0 Iustin Pop
it under the terms of the GNU General Public License as published by
14 702a4ee0 Iustin Pop
the Free Software Foundation; either version 2 of the License, or
15 702a4ee0 Iustin Pop
(at your option) any later version.
16 702a4ee0 Iustin Pop
17 702a4ee0 Iustin Pop
This program is distributed in the hope that it will be useful, but
18 702a4ee0 Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
19 702a4ee0 Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20 702a4ee0 Iustin Pop
General Public License for more details.
21 702a4ee0 Iustin Pop
22 702a4ee0 Iustin Pop
You should have received a copy of the GNU General Public License
23 702a4ee0 Iustin Pop
along with this program; if not, write to the Free Software
24 702a4ee0 Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25 702a4ee0 Iustin Pop
02110-1301, USA.
26 702a4ee0 Iustin Pop
27 702a4ee0 Iustin Pop
-}
28 702a4ee0 Iustin Pop
29 702a4ee0 Iustin Pop
module Ganeti.OpCodes
30 34af39e8 Jose A. Lopes
  ( pyClasses
31 34af39e8 Jose A. Lopes
  , OpCode(..)
32 ebf38064 Iustin Pop
  , ReplaceDisksMode(..)
33 4a1dc2bf Iustin Pop
  , DiskIndex
34 4a1dc2bf Iustin Pop
  , mkDiskIndex
35 4a1dc2bf Iustin Pop
  , unDiskIndex
36 ebf38064 Iustin Pop
  , opID
37 e713a686 Petr Pudlak
  , opReasonSrcID
38 a583ec5d Iustin Pop
  , allOpIDs
39 3929e782 Iustin Pop
  , allOpFields
40 ad1c1e41 Iustin Pop
  , opSummary
41 4a826364 Iustin Pop
  , CommonOpParams(..)
42 4a826364 Iustin Pop
  , defOpParams
43 4a826364 Iustin Pop
  , MetaOpCode(..)
44 62933497 Klaus Aehlig
  , resolveDependencies
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 34af39e8 Jose A. Lopes
import Text.JSON (readJSON, JSObject, JSON, JSValue(..), makeObj, fromJSObject)
51 4a826364 Iustin Pop
import qualified Text.JSON
52 702a4ee0 Iustin Pop
53 12c19659 Iustin Pop
import Ganeti.THH
54 e9aaa3c6 Iustin Pop
55 34af39e8 Jose A. Lopes
import qualified Ganeti.Hs2Py.OpDoc as OpDoc
56 92f51573 Iustin Pop
import Ganeti.OpParams
57 b711450c Petr Pudlak
import Ganeti.PyValue ()
58 34af39e8 Jose A. Lopes
import Ganeti.Types
59 ad1c1e41 Iustin Pop
import Ganeti.Query.Language (queryTypeOpToRaw)
60 4a1dc2bf Iustin Pop
61 34af39e8 Jose A. Lopes
import Data.List (intercalate)
62 34af39e8 Jose A. Lopes
import Data.Map (Map)
63 34af39e8 Jose A. Lopes
64 34af39e8 Jose A. Lopes
import qualified Ganeti.Constants as C
65 34af39e8 Jose A. Lopes
66 34af39e8 Jose A. Lopes
instance PyValue DiskIndex where
67 34af39e8 Jose A. Lopes
  showValue = showValue . unDiskIndex
68 34af39e8 Jose A. Lopes
69 34af39e8 Jose A. Lopes
instance PyValue IDiskParams where
70 34af39e8 Jose A. Lopes
  showValue _ = error "OpCodes.showValue(IDiskParams): unhandled case"
71 34af39e8 Jose A. Lopes
72 34af39e8 Jose A. Lopes
instance PyValue RecreateDisksInfo where
73 34af39e8 Jose A. Lopes
  showValue RecreateDisksAll = "[]"
74 34af39e8 Jose A. Lopes
  showValue (RecreateDisksIndices is) = showValue is
75 34af39e8 Jose A. Lopes
  showValue (RecreateDisksParams is) = showValue is
76 34af39e8 Jose A. Lopes
77 34af39e8 Jose A. Lopes
instance PyValue a => PyValue (SetParamsMods a) where
78 34af39e8 Jose A. Lopes
  showValue SetParamsEmpty = "[]"
79 34af39e8 Jose A. Lopes
  showValue _ = error "OpCodes.showValue(SetParamsMods): unhandled case"
80 34af39e8 Jose A. Lopes
81 34af39e8 Jose A. Lopes
instance PyValue a => PyValue (NonNegative a) where
82 34af39e8 Jose A. Lopes
  showValue = showValue . fromNonNegative
83 f048c574 Thomas Thrainer
84 34af39e8 Jose A. Lopes
instance PyValue a => PyValue (NonEmpty a) where
85 34af39e8 Jose A. Lopes
  showValue = showValue . fromNonEmpty
86 f048c574 Thomas Thrainer
87 34af39e8 Jose A. Lopes
-- FIXME: should use the 'toRaw' function instead of being harcoded or
88 34af39e8 Jose A. Lopes
-- perhaps use something similar to the NonNegative type instead of
89 34af39e8 Jose A. Lopes
-- using the declareSADT
90 34af39e8 Jose A. Lopes
instance PyValue ExportMode where
91 34af39e8 Jose A. Lopes
  showValue ExportModeLocal = show C.exportModeLocal
92 661c765b Jose A. Lopes
  showValue ExportModeRemote = show C.exportModeLocal
93 34af39e8 Jose A. Lopes
94 34af39e8 Jose A. Lopes
instance PyValue CVErrorCode where
95 34af39e8 Jose A. Lopes
  showValue = cVErrorCodeToRaw
96 94d8fc5a Jose A. Lopes
97 34af39e8 Jose A. Lopes
instance PyValue VerifyOptionalChecks where
98 34af39e8 Jose A. Lopes
  showValue = verifyOptionalChecksToRaw
99 34af39e8 Jose A. Lopes
100 34af39e8 Jose A. Lopes
instance PyValue INicParams where
101 34af39e8 Jose A. Lopes
  showValue = error "instance PyValue INicParams: not implemented"
102 34af39e8 Jose A. Lopes
103 34af39e8 Jose A. Lopes
instance PyValue a => PyValue (JSObject a) where
104 34af39e8 Jose A. Lopes
  showValue obj =
105 34af39e8 Jose A. Lopes
    "{" ++ intercalate ", " (map showPair (fromJSObject obj)) ++ "}"
106 34af39e8 Jose A. Lopes
    where showPair (k, v) = show k ++ ":" ++ showValue v
107 34af39e8 Jose A. Lopes
108 34af39e8 Jose A. Lopes
instance PyValue JSValue where
109 34af39e8 Jose A. Lopes
  showValue (JSObject obj) = showValue obj
110 34af39e8 Jose A. Lopes
  showValue x = show x
111 34af39e8 Jose A. Lopes
112 b6e31235 Jose A. Lopes
type JobIdListOnly = Map String [(Bool, Either String JobId)]
113 34af39e8 Jose A. Lopes
114 34af39e8 Jose A. Lopes
type InstanceMultiAllocResponse =
115 34af39e8 Jose A. Lopes
  ([(Bool, Either String JobId)], NonEmptyString)
116 34af39e8 Jose A. Lopes
117 34af39e8 Jose A. Lopes
type QueryFieldDef =
118 34af39e8 Jose A. Lopes
  (NonEmptyString, NonEmptyString, TagKind, NonEmptyString)
119 34af39e8 Jose A. Lopes
120 34af39e8 Jose A. Lopes
type QueryResponse =
121 34af39e8 Jose A. Lopes
  ([QueryFieldDef], [[(QueryResultCode, JSValue)]])
122 34af39e8 Jose A. Lopes
123 34af39e8 Jose A. Lopes
type QueryFieldsResponse = [QueryFieldDef]
124 34af39e8 Jose A. Lopes
125 525bfb36 Iustin Pop
-- | OpCode representation.
126 525bfb36 Iustin Pop
--
127 3bebda52 Dato Simรณ
-- We only implement a subset of Ganeti opcodes: those which are actually used
128 3bebda52 Dato Simรณ
-- in the htools codebase.
129 12c19659 Iustin Pop
$(genOpCode "OpCode"
130 34af39e8 Jose A. Lopes
  [ ("OpClusterPostInit",
131 34af39e8 Jose A. Lopes
     [t| Bool |],
132 34af39e8 Jose A. Lopes
     OpDoc.opClusterPostInit,
133 34af39e8 Jose A. Lopes
     [],
134 34af39e8 Jose A. Lopes
     [])
135 34af39e8 Jose A. Lopes
  , ("OpClusterDestroy",
136 34af39e8 Jose A. Lopes
     [t| NonEmptyString |],
137 34af39e8 Jose A. Lopes
     OpDoc.opClusterDestroy,
138 34af39e8 Jose A. Lopes
     [],
139 34af39e8 Jose A. Lopes
     [])
140 34af39e8 Jose A. Lopes
  , ("OpClusterQuery",
141 34af39e8 Jose A. Lopes
     [t| JSObject JSValue |],
142 34af39e8 Jose A. Lopes
     OpDoc.opClusterQuery,
143 34af39e8 Jose A. Lopes
     [],
144 34af39e8 Jose A. Lopes
     [])
145 c66f09f5 Iustin Pop
  , ("OpClusterVerify",
146 34af39e8 Jose A. Lopes
     [t| JobIdListOnly |],
147 34af39e8 Jose A. Lopes
     OpDoc.opClusterVerify,
148 c66f09f5 Iustin Pop
     [ pDebugSimulateErrors
149 c66f09f5 Iustin Pop
     , pErrorCodes
150 c66f09f5 Iustin Pop
     , pSkipChecks
151 c66f09f5 Iustin Pop
     , pIgnoreErrors
152 c66f09f5 Iustin Pop
     , pVerbose
153 c66f09f5 Iustin Pop
     , pOptGroupName
154 34af39e8 Jose A. Lopes
     ],
155 34af39e8 Jose A. Lopes
     [])
156 c66f09f5 Iustin Pop
  , ("OpClusterVerifyConfig",
157 34af39e8 Jose A. Lopes
     [t| Bool |],
158 34af39e8 Jose A. Lopes
     OpDoc.opClusterVerifyConfig,
159 c66f09f5 Iustin Pop
     [ pDebugSimulateErrors
160 c66f09f5 Iustin Pop
     , pErrorCodes
161 c66f09f5 Iustin Pop
     , pIgnoreErrors
162 c66f09f5 Iustin Pop
     , pVerbose
163 34af39e8 Jose A. Lopes
     ],
164 34af39e8 Jose A. Lopes
     [])
165 c66f09f5 Iustin Pop
  , ("OpClusterVerifyGroup",
166 34af39e8 Jose A. Lopes
     [t| Bool |],
167 34af39e8 Jose A. Lopes
     OpDoc.opClusterVerifyGroup,
168 c66f09f5 Iustin Pop
     [ pGroupName
169 c66f09f5 Iustin Pop
     , pDebugSimulateErrors
170 c66f09f5 Iustin Pop
     , pErrorCodes
171 c66f09f5 Iustin Pop
     , pSkipChecks
172 c66f09f5 Iustin Pop
     , pIgnoreErrors
173 c66f09f5 Iustin Pop
     , pVerbose
174 34af39e8 Jose A. Lopes
     ],
175 34af39e8 Jose A. Lopes
     "group_name")
176 34af39e8 Jose A. Lopes
  , ("OpClusterVerifyDisks",
177 34af39e8 Jose A. Lopes
     [t| JobIdListOnly |],
178 34af39e8 Jose A. Lopes
     OpDoc.opClusterVerifyDisks,
179 34af39e8 Jose A. Lopes
     [],
180 34af39e8 Jose A. Lopes
     [])
181 c66f09f5 Iustin Pop
  , ("OpGroupVerifyDisks",
182 34af39e8 Jose A. Lopes
     [t| (Map String String, [String], Map String [[String]]) |],
183 34af39e8 Jose A. Lopes
     OpDoc.opGroupVerifyDisks,
184 c66f09f5 Iustin Pop
     [ pGroupName
185 34af39e8 Jose A. Lopes
     ],
186 34af39e8 Jose A. Lopes
     "group_name")
187 c66f09f5 Iustin Pop
  , ("OpClusterRepairDiskSizes",
188 34af39e8 Jose A. Lopes
     [t| [(NonEmptyString, NonNegative Int, NonEmptyString, NonNegative Int)]|],
189 34af39e8 Jose A. Lopes
     OpDoc.opClusterRepairDiskSizes,
190 c66f09f5 Iustin Pop
     [ pInstances
191 34af39e8 Jose A. Lopes
     ],
192 34af39e8 Jose A. Lopes
     [])
193 c66f09f5 Iustin Pop
  , ("OpClusterConfigQuery",
194 34af39e8 Jose A. Lopes
     [t| [JSValue] |],
195 34af39e8 Jose A. Lopes
     OpDoc.opClusterConfigQuery,
196 c66f09f5 Iustin Pop
     [ pOutputFields
197 34af39e8 Jose A. Lopes
     ],
198 34af39e8 Jose A. Lopes
     [])
199 c66f09f5 Iustin Pop
  , ("OpClusterRename",
200 34af39e8 Jose A. Lopes
      [t| NonEmptyString |],
201 34af39e8 Jose A. Lopes
      OpDoc.opClusterRename,
202 c66f09f5 Iustin Pop
     [ pName
203 34af39e8 Jose A. Lopes
     ],
204 34af39e8 Jose A. Lopes
     "name")
205 c66f09f5 Iustin Pop
  , ("OpClusterSetParams",
206 34af39e8 Jose A. Lopes
     [t| () |],
207 34af39e8 Jose A. Lopes
     OpDoc.opClusterSetParams,
208 e5c92cfb Klaus Aehlig
     [ pForce
209 e5c92cfb Klaus Aehlig
     , pHvState
210 c66f09f5 Iustin Pop
     , pDiskState
211 c66f09f5 Iustin Pop
     , pVgName
212 c66f09f5 Iustin Pop
     , pEnabledHypervisors
213 c66f09f5 Iustin Pop
     , pClusterHvParams
214 c66f09f5 Iustin Pop
     , pClusterBeParams
215 c66f09f5 Iustin Pop
     , pOsHvp
216 6d558717 Iustin Pop
     , pClusterOsParams
217 c66f09f5 Iustin Pop
     , pDiskParams
218 c66f09f5 Iustin Pop
     , pCandidatePoolSize
219 ad756c77 Klaus Aehlig
     , pMaxRunningJobs
220 c66f09f5 Iustin Pop
     , pUidPool
221 c66f09f5 Iustin Pop
     , pAddUids
222 c66f09f5 Iustin Pop
     , pRemoveUids
223 c66f09f5 Iustin Pop
     , pMaintainNodeHealth
224 c66f09f5 Iustin Pop
     , pPreallocWipeDisks
225 c66f09f5 Iustin Pop
     , pNicParams
226 34af39e8 Jose A. Lopes
     , withDoc "Cluster-wide node parameter defaults" pNdParams
227 34af39e8 Jose A. Lopes
     , withDoc "Cluster-wide ipolicy specs" pIpolicy
228 c66f09f5 Iustin Pop
     , pDrbdHelper
229 c66f09f5 Iustin Pop
     , pDefaultIAllocator
230 0359e5d0 Spyros Trigazis
     , pDefaultIAllocatorParams
231 c66f09f5 Iustin Pop
     , pMasterNetdev
232 67fc4de7 Iustin Pop
     , pMasterNetmask
233 c66f09f5 Iustin Pop
     , pReservedLvs
234 c66f09f5 Iustin Pop
     , pHiddenOs
235 c66f09f5 Iustin Pop
     , pBlacklistedOs
236 c66f09f5 Iustin Pop
     , pUseExternalMipScript
237 66af5ec5 Helga Velroyen
     , pEnabledDiskTemplates
238 75f2ff7d Michele Tartara
     , pModifyEtcHosts
239 5ce621ab Helga Velroyen
     , pClusterFileStorageDir
240 5ce621ab Helga Velroyen
     , pClusterSharedFileStorageDir
241 d3e6fd0e Santi Raffa
     , pClusterGlusterStorageDir
242 34af39e8 Jose A. Lopes
     ],
243 34af39e8 Jose A. Lopes
     [])
244 34af39e8 Jose A. Lopes
  , ("OpClusterRedistConf",
245 34af39e8 Jose A. Lopes
     [t| () |],
246 34af39e8 Jose A. Lopes
     OpDoc.opClusterRedistConf,
247 34af39e8 Jose A. Lopes
     [],
248 34af39e8 Jose A. Lopes
     [])
249 34af39e8 Jose A. Lopes
  , ("OpClusterActivateMasterIp",
250 34af39e8 Jose A. Lopes
     [t| () |],
251 34af39e8 Jose A. Lopes
     OpDoc.opClusterActivateMasterIp,
252 34af39e8 Jose A. Lopes
     [],
253 34af39e8 Jose A. Lopes
     [])
254 34af39e8 Jose A. Lopes
  , ("OpClusterDeactivateMasterIp",
255 34af39e8 Jose A. Lopes
     [t| () |],
256 34af39e8 Jose A. Lopes
     OpDoc.opClusterDeactivateMasterIp,
257 34af39e8 Jose A. Lopes
     [],
258 34af39e8 Jose A. Lopes
     [])
259 b3cc1646 Helga Velroyen
  , ("OpClusterRenewCrypto",
260 b3cc1646 Helga Velroyen
     [t| () |],
261 b3cc1646 Helga Velroyen
     OpDoc.opClusterRenewCrypto,
262 b3cc1646 Helga Velroyen
     [],
263 b3cc1646 Helga Velroyen
     [])
264 c66f09f5 Iustin Pop
  , ("OpQuery",
265 34af39e8 Jose A. Lopes
     [t| QueryResponse |],
266 34af39e8 Jose A. Lopes
     OpDoc.opQuery,
267 c66f09f5 Iustin Pop
     [ pQueryWhat
268 c66f09f5 Iustin Pop
     , pUseLocking
269 c66f09f5 Iustin Pop
     , pQueryFields
270 c66f09f5 Iustin Pop
     , pQueryFilter
271 34af39e8 Jose A. Lopes
     ],
272 34af39e8 Jose A. Lopes
     "what")
273 c66f09f5 Iustin Pop
  , ("OpQueryFields",
274 34af39e8 Jose A. Lopes
     [t| QueryFieldsResponse |],
275 34af39e8 Jose A. Lopes
     OpDoc.opQueryFields,
276 c66f09f5 Iustin Pop
     [ pQueryWhat
277 34af39e8 Jose A. Lopes
     , pQueryFieldsFields
278 34af39e8 Jose A. Lopes
     ],
279 34af39e8 Jose A. Lopes
     "what")
280 c66f09f5 Iustin Pop
  , ("OpOobCommand",
281 34af39e8 Jose A. Lopes
     [t| [[(QueryResultCode, JSValue)]] |],
282 34af39e8 Jose A. Lopes
     OpDoc.opOobCommand,
283 c66f09f5 Iustin Pop
     [ pNodeNames
284 34af39e8 Jose A. Lopes
     , withDoc "List of node UUIDs to run the OOB command against" pNodeUuids
285 c66f09f5 Iustin Pop
     , pOobCommand
286 c66f09f5 Iustin Pop
     , pOobTimeout
287 c66f09f5 Iustin Pop
     , pIgnoreStatus
288 c66f09f5 Iustin Pop
     , pPowerDelay
289 34af39e8 Jose A. Lopes
     ],
290 34af39e8 Jose A. Lopes
     [])
291 34af39e8 Jose A. Lopes
  , ("OpRestrictedCommand",
292 34af39e8 Jose A. Lopes
     [t| [(Bool, String)] |],
293 34af39e8 Jose A. Lopes
     OpDoc.opRestrictedCommand,
294 34af39e8 Jose A. Lopes
     [ pUseLocking
295 34af39e8 Jose A. Lopes
     , withDoc
296 34af39e8 Jose A. Lopes
       "Nodes on which the command should be run (at least one)"
297 34af39e8 Jose A. Lopes
       pRequiredNodes
298 34af39e8 Jose A. Lopes
     , withDoc
299 34af39e8 Jose A. Lopes
       "Node UUIDs on which the command should be run (at least one)"
300 34af39e8 Jose A. Lopes
       pRequiredNodeUuids
301 34af39e8 Jose A. Lopes
     , pRestrictedCommand
302 34af39e8 Jose A. Lopes
     ],
303 34af39e8 Jose A. Lopes
     [])
304 1c3231aa Thomas Thrainer
  , ("OpNodeRemove",
305 34af39e8 Jose A. Lopes
     [t| () |],
306 34af39e8 Jose A. Lopes
      OpDoc.opNodeRemove,
307 1c3231aa Thomas Thrainer
     [ pNodeName
308 1c3231aa Thomas Thrainer
     , pNodeUuid
309 34af39e8 Jose A. Lopes
     ],
310 34af39e8 Jose A. Lopes
     "node_name")
311 c66f09f5 Iustin Pop
  , ("OpNodeAdd",
312 34af39e8 Jose A. Lopes
     [t| () |],
313 34af39e8 Jose A. Lopes
      OpDoc.opNodeAdd,
314 c66f09f5 Iustin Pop
     [ pNodeName
315 c66f09f5 Iustin Pop
     , pHvState
316 c66f09f5 Iustin Pop
     , pDiskState
317 c66f09f5 Iustin Pop
     , pPrimaryIp
318 c66f09f5 Iustin Pop
     , pSecondaryIp
319 c66f09f5 Iustin Pop
     , pReadd
320 c66f09f5 Iustin Pop
     , pNodeGroup
321 c66f09f5 Iustin Pop
     , pMasterCapable
322 c66f09f5 Iustin Pop
     , pVmCapable
323 c66f09f5 Iustin Pop
     , pNdParams
324 34af39e8 Jose A. Lopes
     ],
325 34af39e8 Jose A. Lopes
     "node_name")
326 c66f09f5 Iustin Pop
  , ("OpNodeQueryvols",
327 34af39e8 Jose A. Lopes
     [t| [JSValue] |],
328 34af39e8 Jose A. Lopes
     OpDoc.opNodeQueryvols,
329 c66f09f5 Iustin Pop
     [ pOutputFields
330 34af39e8 Jose A. Lopes
     , withDoc "Empty list to query all nodes, node names otherwise" pNodes
331 34af39e8 Jose A. Lopes
     ],
332 34af39e8 Jose A. Lopes
     [])
333 c66f09f5 Iustin Pop
  , ("OpNodeQueryStorage",
334 34af39e8 Jose A. Lopes
     [t| [[JSValue]] |],
335 34af39e8 Jose A. Lopes
     OpDoc.opNodeQueryStorage,
336 c66f09f5 Iustin Pop
     [ pOutputFields
337 4f90370c Helga Velroyen
     , pStorageTypeOptional
338 34af39e8 Jose A. Lopes
     , withDoc
339 34af39e8 Jose A. Lopes
       "Empty list to query all, list of names to query otherwise"
340 34af39e8 Jose A. Lopes
       pNodes
341 c66f09f5 Iustin Pop
     , pStorageName
342 34af39e8 Jose A. Lopes
     ],
343 34af39e8 Jose A. Lopes
     [])
344 c66f09f5 Iustin Pop
  , ("OpNodeModifyStorage",
345 34af39e8 Jose A. Lopes
     [t| () |],
346 34af39e8 Jose A. Lopes
     OpDoc.opNodeModifyStorage,
347 c66f09f5 Iustin Pop
     [ pNodeName
348 1c3231aa Thomas Thrainer
     , pNodeUuid
349 c66f09f5 Iustin Pop
     , pStorageType
350 c66f09f5 Iustin Pop
     , pStorageName
351 c66f09f5 Iustin Pop
     , pStorageChanges
352 34af39e8 Jose A. Lopes
     ],
353 34af39e8 Jose A. Lopes
     "node_name")
354 c66f09f5 Iustin Pop
  , ("OpRepairNodeStorage",
355 34af39e8 Jose A. Lopes
      [t| () |],
356 34af39e8 Jose A. Lopes
      OpDoc.opRepairNodeStorage,
357 c66f09f5 Iustin Pop
     [ pNodeName
358 1c3231aa Thomas Thrainer
     , pNodeUuid
359 c66f09f5 Iustin Pop
     , pStorageType
360 c66f09f5 Iustin Pop
     , pStorageName
361 c66f09f5 Iustin Pop
     , pIgnoreConsistency
362 34af39e8 Jose A. Lopes
     ],
363 34af39e8 Jose A. Lopes
     "node_name")
364 c66f09f5 Iustin Pop
  , ("OpNodeSetParams",
365 34af39e8 Jose A. Lopes
     [t| [(NonEmptyString, JSValue)] |],
366 34af39e8 Jose A. Lopes
     OpDoc.opNodeSetParams,
367 c66f09f5 Iustin Pop
     [ pNodeName
368 1c3231aa Thomas Thrainer
     , pNodeUuid
369 c66f09f5 Iustin Pop
     , pForce
370 c66f09f5 Iustin Pop
     , pHvState
371 c66f09f5 Iustin Pop
     , pDiskState
372 c66f09f5 Iustin Pop
     , pMasterCandidate
373 34af39e8 Jose A. Lopes
     , withDoc "Whether to mark the node offline" pOffline
374 c66f09f5 Iustin Pop
     , pDrained
375 c66f09f5 Iustin Pop
     , pAutoPromote
376 c66f09f5 Iustin Pop
     , pMasterCapable
377 c66f09f5 Iustin Pop
     , pVmCapable
378 c66f09f5 Iustin Pop
     , pSecondaryIp
379 c66f09f5 Iustin Pop
     , pNdParams
380 67fc4de7 Iustin Pop
     , pPowered
381 34af39e8 Jose A. Lopes
     ],
382 34af39e8 Jose A. Lopes
     "node_name")
383 c66f09f5 Iustin Pop
  , ("OpNodePowercycle",
384 34af39e8 Jose A. Lopes
     [t| Maybe NonEmptyString |],
385 34af39e8 Jose A. Lopes
     OpDoc.opNodePowercycle,
386 c66f09f5 Iustin Pop
     [ pNodeName
387 1c3231aa Thomas Thrainer
     , pNodeUuid
388 c66f09f5 Iustin Pop
     , pForce
389 34af39e8 Jose A. Lopes
     ],
390 34af39e8 Jose A. Lopes
     "node_name")
391 c66f09f5 Iustin Pop
  , ("OpNodeMigrate",
392 34af39e8 Jose A. Lopes
     [t| JobIdListOnly |],
393 34af39e8 Jose A. Lopes
     OpDoc.opNodeMigrate,
394 c66f09f5 Iustin Pop
     [ pNodeName
395 1c3231aa Thomas Thrainer
     , pNodeUuid
396 c66f09f5 Iustin Pop
     , pMigrationMode
397 c66f09f5 Iustin Pop
     , pMigrationLive
398 c66f09f5 Iustin Pop
     , pMigrationTargetNode
399 1c3231aa Thomas Thrainer
     , pMigrationTargetNodeUuid
400 c66f09f5 Iustin Pop
     , pAllowRuntimeChgs
401 c66f09f5 Iustin Pop
     , pIgnoreIpolicy
402 c66f09f5 Iustin Pop
     , pIallocator
403 34af39e8 Jose A. Lopes
     ],
404 34af39e8 Jose A. Lopes
     "node_name")
405 c66f09f5 Iustin Pop
  , ("OpNodeEvacuate",
406 34af39e8 Jose A. Lopes
     [t| JobIdListOnly |],
407 34af39e8 Jose A. Lopes
     OpDoc.opNodeEvacuate,
408 c66f09f5 Iustin Pop
     [ pEarlyRelease
409 c66f09f5 Iustin Pop
     , pNodeName
410 1c3231aa Thomas Thrainer
     , pNodeUuid
411 c66f09f5 Iustin Pop
     , pRemoteNode
412 1c3231aa Thomas Thrainer
     , pRemoteNodeUuid
413 c66f09f5 Iustin Pop
     , pIallocator
414 c66f09f5 Iustin Pop
     , pEvacMode
415 34af39e8 Jose A. Lopes
     ],
416 34af39e8 Jose A. Lopes
     "node_name")
417 6d558717 Iustin Pop
  , ("OpInstanceCreate",
418 34af39e8 Jose A. Lopes
     [t| [NonEmptyString] |],
419 34af39e8 Jose A. Lopes
     OpDoc.opInstanceCreate,
420 6d558717 Iustin Pop
     [ pInstanceName
421 6d558717 Iustin Pop
     , pForceVariant
422 6d558717 Iustin Pop
     , pWaitForSync
423 6d558717 Iustin Pop
     , pNameCheck
424 6d558717 Iustin Pop
     , pIgnoreIpolicy
425 34af39e8 Jose A. Lopes
     , pOpportunisticLocking
426 6d558717 Iustin Pop
     , pInstBeParams
427 6d558717 Iustin Pop
     , pInstDisks
428 7b6996a8 Thomas Thrainer
     , pOptDiskTemplate
429 6d558717 Iustin Pop
     , pFileDriver
430 6d558717 Iustin Pop
     , pFileStorageDir
431 6d558717 Iustin Pop
     , pInstHvParams
432 6d558717 Iustin Pop
     , pHypervisor
433 6d558717 Iustin Pop
     , pIallocator
434 6d558717 Iustin Pop
     , pResetDefaults
435 6d558717 Iustin Pop
     , pIpCheck
436 6d558717 Iustin Pop
     , pIpConflictsCheck
437 6d558717 Iustin Pop
     , pInstCreateMode
438 6d558717 Iustin Pop
     , pInstNics
439 6d558717 Iustin Pop
     , pNoInstall
440 6d558717 Iustin Pop
     , pInstOsParams
441 6d558717 Iustin Pop
     , pInstOs
442 6d558717 Iustin Pop
     , pPrimaryNode
443 1c3231aa Thomas Thrainer
     , pPrimaryNodeUuid
444 6d558717 Iustin Pop
     , pSecondaryNode
445 1c3231aa Thomas Thrainer
     , pSecondaryNodeUuid
446 6d558717 Iustin Pop
     , pSourceHandshake
447 6d558717 Iustin Pop
     , pSourceInstance
448 6d558717 Iustin Pop
     , pSourceShutdownTimeout
449 6d558717 Iustin Pop
     , pSourceX509Ca
450 6d558717 Iustin Pop
     , pSrcNode
451 1c3231aa Thomas Thrainer
     , pSrcNodeUuid
452 6d558717 Iustin Pop
     , pSrcPath
453 51d7ac96 Thomas Thrainer
     , pBackupCompress
454 6d558717 Iustin Pop
     , pStartInstance
455 6d558717 Iustin Pop
     , pInstTags
456 34af39e8 Jose A. Lopes
     ],
457 34af39e8 Jose A. Lopes
     "instance_name")
458 c2d3219b Iustin Pop
  , ("OpInstanceMultiAlloc",
459 34af39e8 Jose A. Lopes
     [t| InstanceMultiAllocResponse |],
460 34af39e8 Jose A. Lopes
     OpDoc.opInstanceMultiAlloc,
461 34af39e8 Jose A. Lopes
     [ pOpportunisticLocking
462 34af39e8 Jose A. Lopes
     , pIallocator
463 c2d3219b Iustin Pop
     , pMultiAllocInstances
464 34af39e8 Jose A. Lopes
     ],
465 34af39e8 Jose A. Lopes
     [])
466 c2d3219b Iustin Pop
  , ("OpInstanceReinstall",
467 34af39e8 Jose A. Lopes
     [t| () |],
468 34af39e8 Jose A. Lopes
     OpDoc.opInstanceReinstall,
469 c2d3219b Iustin Pop
     [ pInstanceName
470 da4a52a3 Thomas Thrainer
     , pInstanceUuid
471 c2d3219b Iustin Pop
     , pForceVariant
472 c2d3219b Iustin Pop
     , pInstOs
473 c2d3219b Iustin Pop
     , pTempOsParams
474 34af39e8 Jose A. Lopes
     ],
475 34af39e8 Jose A. Lopes
     "instance_name")
476 c2d3219b Iustin Pop
  , ("OpInstanceRemove",
477 34af39e8 Jose A. Lopes
     [t| () |],
478 34af39e8 Jose A. Lopes
     OpDoc.opInstanceRemove,
479 c2d3219b Iustin Pop
     [ pInstanceName
480 da4a52a3 Thomas Thrainer
     , pInstanceUuid
481 c2d3219b Iustin Pop
     , pShutdownTimeout
482 c2d3219b Iustin Pop
     , pIgnoreFailures
483 34af39e8 Jose A. Lopes
     ],
484 34af39e8 Jose A. Lopes
     "instance_name")
485 c2d3219b Iustin Pop
  , ("OpInstanceRename",
486 34af39e8 Jose A. Lopes
     [t| NonEmptyString |],
487 34af39e8 Jose A. Lopes
     OpDoc.opInstanceRename,
488 c2d3219b Iustin Pop
     [ pInstanceName
489 da4a52a3 Thomas Thrainer
     , pInstanceUuid
490 34af39e8 Jose A. Lopes
     , withDoc "New instance name" pNewName
491 c2d3219b Iustin Pop
     , pNameCheck
492 c2d3219b Iustin Pop
     , pIpCheck
493 34af39e8 Jose A. Lopes
     ],
494 34af39e8 Jose A. Lopes
     [])
495 c2d3219b Iustin Pop
  , ("OpInstanceStartup",
496 34af39e8 Jose A. Lopes
     [t| () |],
497 34af39e8 Jose A. Lopes
     OpDoc.opInstanceStartup,
498 c2d3219b Iustin Pop
     [ pInstanceName
499 da4a52a3 Thomas Thrainer
     , pInstanceUuid
500 c2d3219b Iustin Pop
     , pForce
501 c2d3219b Iustin Pop
     , pIgnoreOfflineNodes
502 c2d3219b Iustin Pop
     , pTempHvParams
503 c2d3219b Iustin Pop
     , pTempBeParams
504 c2d3219b Iustin Pop
     , pNoRemember
505 c2d3219b Iustin Pop
     , pStartupPaused
506 34af39e8 Jose A. Lopes
     ],
507 34af39e8 Jose A. Lopes
     "instance_name")
508 c2d3219b Iustin Pop
  , ("OpInstanceShutdown",
509 34af39e8 Jose A. Lopes
     [t| () |],
510 34af39e8 Jose A. Lopes
     OpDoc.opInstanceShutdown,
511 c2d3219b Iustin Pop
     [ pInstanceName
512 da4a52a3 Thomas Thrainer
     , pInstanceUuid
513 0d57ce24 Guido Trotter
     , pForce
514 c2d3219b Iustin Pop
     , pIgnoreOfflineNodes
515 5cbf7832 Jose A. Lopes
     , pShutdownTimeout'
516 c2d3219b Iustin Pop
     , pNoRemember
517 34af39e8 Jose A. Lopes
     ],
518 34af39e8 Jose A. Lopes
     "instance_name")
519 c2d3219b Iustin Pop
  , ("OpInstanceReboot",
520 34af39e8 Jose A. Lopes
     [t| () |],
521 34af39e8 Jose A. Lopes
     OpDoc.opInstanceReboot,
522 c2d3219b Iustin Pop
     [ pInstanceName
523 da4a52a3 Thomas Thrainer
     , pInstanceUuid
524 c2d3219b Iustin Pop
     , pShutdownTimeout
525 c2d3219b Iustin Pop
     , pIgnoreSecondaries
526 c2d3219b Iustin Pop
     , pRebootType
527 34af39e8 Jose A. Lopes
     ],
528 34af39e8 Jose A. Lopes
     "instance_name")
529 34af39e8 Jose A. Lopes
  , ("OpInstanceReplaceDisks",
530 34af39e8 Jose A. Lopes
     [t| () |],
531 34af39e8 Jose A. Lopes
     OpDoc.opInstanceReplaceDisks,
532 34af39e8 Jose A. Lopes
     [ pInstanceName
533 34af39e8 Jose A. Lopes
     , pInstanceUuid
534 34af39e8 Jose A. Lopes
     , pEarlyRelease
535 34af39e8 Jose A. Lopes
     , pIgnoreIpolicy
536 34af39e8 Jose A. Lopes
     , pReplaceDisksMode
537 34af39e8 Jose A. Lopes
     , pReplaceDisksList
538 34af39e8 Jose A. Lopes
     , pRemoteNode
539 34af39e8 Jose A. Lopes
     , pRemoteNodeUuid
540 34af39e8 Jose A. Lopes
     , pIallocator
541 34af39e8 Jose A. Lopes
     ],
542 34af39e8 Jose A. Lopes
     "instance_name")
543 34af39e8 Jose A. Lopes
  , ("OpInstanceFailover",
544 34af39e8 Jose A. Lopes
     [t| () |],
545 34af39e8 Jose A. Lopes
     OpDoc.opInstanceFailover,
546 34af39e8 Jose A. Lopes
     [ pInstanceName
547 34af39e8 Jose A. Lopes
     , pInstanceUuid
548 34af39e8 Jose A. Lopes
     , pShutdownTimeout
549 34af39e8 Jose A. Lopes
     , pIgnoreConsistency
550 34af39e8 Jose A. Lopes
     , pMigrationTargetNode
551 34af39e8 Jose A. Lopes
     , pMigrationTargetNodeUuid
552 34af39e8 Jose A. Lopes
     , pIgnoreIpolicy
553 1ca326c8 Thomas Thrainer
     , pMigrationCleanup
554 34af39e8 Jose A. Lopes
     , pIallocator
555 34af39e8 Jose A. Lopes
     ],
556 34af39e8 Jose A. Lopes
     "instance_name")
557 34af39e8 Jose A. Lopes
  , ("OpInstanceMigrate",
558 34af39e8 Jose A. Lopes
     [t| () |],
559 34af39e8 Jose A. Lopes
     OpDoc.opInstanceMigrate,
560 34af39e8 Jose A. Lopes
     [ pInstanceName
561 34af39e8 Jose A. Lopes
     , pInstanceUuid
562 34af39e8 Jose A. Lopes
     , pMigrationMode
563 34af39e8 Jose A. Lopes
     , pMigrationLive
564 34af39e8 Jose A. Lopes
     , pMigrationTargetNode
565 34af39e8 Jose A. Lopes
     , pMigrationTargetNodeUuid
566 34af39e8 Jose A. Lopes
     , pAllowRuntimeChgs
567 34af39e8 Jose A. Lopes
     , pIgnoreIpolicy
568 34af39e8 Jose A. Lopes
     , pMigrationCleanup
569 34af39e8 Jose A. Lopes
     , pIallocator
570 34af39e8 Jose A. Lopes
     , pAllowFailover
571 34af39e8 Jose A. Lopes
     ],
572 34af39e8 Jose A. Lopes
     "instance_name")
573 c2d3219b Iustin Pop
  , ("OpInstanceMove",
574 34af39e8 Jose A. Lopes
     [t| () |],
575 34af39e8 Jose A. Lopes
     OpDoc.opInstanceMove,
576 c2d3219b Iustin Pop
     [ pInstanceName
577 da4a52a3 Thomas Thrainer
     , pInstanceUuid
578 c2d3219b Iustin Pop
     , pShutdownTimeout
579 c2d3219b Iustin Pop
     , pIgnoreIpolicy
580 c2d3219b Iustin Pop
     , pMoveTargetNode
581 1c3231aa Thomas Thrainer
     , pMoveTargetNodeUuid
582 f198cf91 Thomas Thrainer
     , pMoveCompress
583 c2d3219b Iustin Pop
     , pIgnoreConsistency
584 34af39e8 Jose A. Lopes
     ],
585 34af39e8 Jose A. Lopes
     "instance_name")
586 c2d3219b Iustin Pop
  , ("OpInstanceConsole",
587 34af39e8 Jose A. Lopes
     [t| JSObject JSValue |],
588 34af39e8 Jose A. Lopes
     OpDoc.opInstanceConsole,
589 da4a52a3 Thomas Thrainer
     [ pInstanceName
590 da4a52a3 Thomas Thrainer
     , pInstanceUuid
591 34af39e8 Jose A. Lopes
     ],
592 34af39e8 Jose A. Lopes
     "instance_name")
593 c2d3219b Iustin Pop
  , ("OpInstanceActivateDisks",
594 34af39e8 Jose A. Lopes
     [t| [(NonEmptyString, NonEmptyString, NonEmptyString)] |],
595 34af39e8 Jose A. Lopes
     OpDoc.opInstanceActivateDisks,
596 c2d3219b Iustin Pop
     [ pInstanceName
597 da4a52a3 Thomas Thrainer
     , pInstanceUuid
598 c2d3219b Iustin Pop
     , pIgnoreDiskSize
599 c2d3219b Iustin Pop
     , pWaitForSyncFalse
600 34af39e8 Jose A. Lopes
     ],
601 34af39e8 Jose A. Lopes
     "instance_name")
602 c2d3219b Iustin Pop
  , ("OpInstanceDeactivateDisks",
603 34af39e8 Jose A. Lopes
     [t| () |],
604 34af39e8 Jose A. Lopes
     OpDoc.opInstanceDeactivateDisks,
605 c2d3219b Iustin Pop
     [ pInstanceName
606 da4a52a3 Thomas Thrainer
     , pInstanceUuid
607 c2d3219b Iustin Pop
     , pForce
608 34af39e8 Jose A. Lopes
     ],
609 34af39e8 Jose A. Lopes
     "instance_name")
610 c2d3219b Iustin Pop
  , ("OpInstanceRecreateDisks",
611 34af39e8 Jose A. Lopes
     [t| () |],
612 34af39e8 Jose A. Lopes
     OpDoc.opInstanceRecreateDisks,
613 c2d3219b Iustin Pop
     [ pInstanceName
614 da4a52a3 Thomas Thrainer
     , pInstanceUuid
615 c2d3219b Iustin Pop
     , pRecreateDisksInfo
616 34af39e8 Jose A. Lopes
     , withDoc "New instance nodes, if relocation is desired" pNodes
617 34af39e8 Jose A. Lopes
     , withDoc "New instance node UUIDs, if relocation is desired" pNodeUuids
618 c2d3219b Iustin Pop
     , pIallocator
619 34af39e8 Jose A. Lopes
     ],
620 34af39e8 Jose A. Lopes
     "instance_name")
621 c2d3219b Iustin Pop
  , ("OpInstanceQueryData",
622 34af39e8 Jose A. Lopes
     [t| JSObject (JSObject JSValue) |],
623 34af39e8 Jose A. Lopes
     OpDoc.opInstanceQueryData,
624 c2d3219b Iustin Pop
     [ pUseLocking
625 c2d3219b Iustin Pop
     , pInstances
626 c2d3219b Iustin Pop
     , pStatic
627 34af39e8 Jose A. Lopes
     ],
628 34af39e8 Jose A. Lopes
     [])
629 c2d3219b Iustin Pop
  , ("OpInstanceSetParams",
630 34af39e8 Jose A. Lopes
      [t| [(NonEmptyString, JSValue)] |],
631 34af39e8 Jose A. Lopes
      OpDoc.opInstanceSetParams,
632 c2d3219b Iustin Pop
     [ pInstanceName
633 da4a52a3 Thomas Thrainer
     , pInstanceUuid
634 c2d3219b Iustin Pop
     , pForce
635 c2d3219b Iustin Pop
     , pForceVariant
636 c2d3219b Iustin Pop
     , pIgnoreIpolicy
637 c2d3219b Iustin Pop
     , pInstParamsNicChanges
638 c2d3219b Iustin Pop
     , pInstParamsDiskChanges
639 c2d3219b Iustin Pop
     , pInstBeParams
640 c2d3219b Iustin Pop
     , pRuntimeMem
641 c2d3219b Iustin Pop
     , pInstHvParams
642 88127c47 Iustin Pop
     , pOptDiskTemplate
643 d2204b1a Klaus Aehlig
     , pPrimaryNode
644 1c3231aa Thomas Thrainer
     , pPrimaryNodeUuid
645 34af39e8 Jose A. Lopes
     , withDoc "Secondary node (used when changing disk template)" pRemoteNode
646 34af39e8 Jose A. Lopes
     , withDoc
647 34af39e8 Jose A. Lopes
       "Secondary node UUID (used when changing disk template)"
648 34af39e8 Jose A. Lopes
       pRemoteNodeUuid
649 c2d3219b Iustin Pop
     , pOsNameChange
650 c2d3219b Iustin Pop
     , pInstOsParams
651 c2d3219b Iustin Pop
     , pWaitForSync
652 34af39e8 Jose A. Lopes
     , withDoc "Whether to mark the instance as offline" pOffline
653 c2d3219b Iustin Pop
     , pIpConflictsCheck
654 df58ca1c Dimitris Aragiorgis
     , pHotplug
655 96ed3a3e Dimitris Aragiorgis
     , pHotplugIfPossible
656 34af39e8 Jose A. Lopes
     ],
657 34af39e8 Jose A. Lopes
     "instance_name")
658 c2d3219b Iustin Pop
  , ("OpInstanceGrowDisk",
659 34af39e8 Jose A. Lopes
     [t| () |],
660 34af39e8 Jose A. Lopes
     OpDoc.opInstanceGrowDisk,
661 c2d3219b Iustin Pop
     [ pInstanceName
662 da4a52a3 Thomas Thrainer
     , pInstanceUuid
663 c2d3219b Iustin Pop
     , pWaitForSync
664 c2d3219b Iustin Pop
     , pDiskIndex
665 c2d3219b Iustin Pop
     , pDiskChgAmount
666 c2d3219b Iustin Pop
     , pDiskChgAbsolute
667 34af39e8 Jose A. Lopes
     ],
668 34af39e8 Jose A. Lopes
     "instance_name")
669 c2d3219b Iustin Pop
  , ("OpInstanceChangeGroup",
670 34af39e8 Jose A. Lopes
     [t| JobIdListOnly |],
671 34af39e8 Jose A. Lopes
     OpDoc.opInstanceChangeGroup,
672 c2d3219b Iustin Pop
     [ pInstanceName
673 da4a52a3 Thomas Thrainer
     , pInstanceUuid
674 c2d3219b Iustin Pop
     , pEarlyRelease
675 c2d3219b Iustin Pop
     , pIallocator
676 c2d3219b Iustin Pop
     , pTargetGroups
677 34af39e8 Jose A. Lopes
     ],
678 34af39e8 Jose A. Lopes
     "instance_name")
679 398e9066 Iustin Pop
  , ("OpGroupAdd",
680 34af39e8 Jose A. Lopes
     [t| () |],
681 34af39e8 Jose A. Lopes
     OpDoc.opGroupAdd,
682 398e9066 Iustin Pop
     [ pGroupName
683 398e9066 Iustin Pop
     , pNodeGroupAllocPolicy
684 398e9066 Iustin Pop
     , pGroupNodeParams
685 398e9066 Iustin Pop
     , pDiskParams
686 398e9066 Iustin Pop
     , pHvState
687 398e9066 Iustin Pop
     , pDiskState
688 34af39e8 Jose A. Lopes
     , withDoc "Group-wide ipolicy specs" pIpolicy
689 34af39e8 Jose A. Lopes
     ],
690 34af39e8 Jose A. Lopes
     "group_name")
691 398e9066 Iustin Pop
  , ("OpGroupAssignNodes",
692 34af39e8 Jose A. Lopes
     [t| () |],
693 34af39e8 Jose A. Lopes
     OpDoc.opGroupAssignNodes,
694 398e9066 Iustin Pop
     [ pGroupName
695 398e9066 Iustin Pop
     , pForce
696 34af39e8 Jose A. Lopes
     , withDoc "List of nodes to assign" pRequiredNodes
697 34af39e8 Jose A. Lopes
     , withDoc "List of node UUIDs to assign" pRequiredNodeUuids
698 34af39e8 Jose A. Lopes
     ],
699 34af39e8 Jose A. Lopes
     "group_name")
700 398e9066 Iustin Pop
  , ("OpGroupSetParams",
701 34af39e8 Jose A. Lopes
     [t| [(NonEmptyString, JSValue)] |],
702 34af39e8 Jose A. Lopes
     OpDoc.opGroupSetParams,
703 398e9066 Iustin Pop
     [ pGroupName
704 398e9066 Iustin Pop
     , pNodeGroupAllocPolicy
705 398e9066 Iustin Pop
     , pGroupNodeParams
706 398e9066 Iustin Pop
     , pDiskParams
707 398e9066 Iustin Pop
     , pHvState
708 398e9066 Iustin Pop
     , pDiskState
709 34af39e8 Jose A. Lopes
     , withDoc "Group-wide ipolicy specs" pIpolicy
710 34af39e8 Jose A. Lopes
     ],
711 34af39e8 Jose A. Lopes
     "group_name")
712 398e9066 Iustin Pop
  , ("OpGroupRemove",
713 34af39e8 Jose A. Lopes
     [t| () |],
714 34af39e8 Jose A. Lopes
     OpDoc.opGroupRemove,
715 34af39e8 Jose A. Lopes
     [ pGroupName
716 34af39e8 Jose A. Lopes
     ],
717 34af39e8 Jose A. Lopes
     "group_name")
718 398e9066 Iustin Pop
  , ("OpGroupRename",
719 34af39e8 Jose A. Lopes
     [t| NonEmptyString |],
720 34af39e8 Jose A. Lopes
     OpDoc.opGroupRename,
721 398e9066 Iustin Pop
     [ pGroupName
722 34af39e8 Jose A. Lopes
     , withDoc "New group name" pNewName
723 34af39e8 Jose A. Lopes
     ],
724 34af39e8 Jose A. Lopes
     [])
725 398e9066 Iustin Pop
  , ("OpGroupEvacuate",
726 34af39e8 Jose A. Lopes
     [t| JobIdListOnly |],
727 34af39e8 Jose A. Lopes
     OpDoc.opGroupEvacuate,
728 398e9066 Iustin Pop
     [ pGroupName
729 398e9066 Iustin Pop
     , pEarlyRelease
730 398e9066 Iustin Pop
     , pIallocator
731 398e9066 Iustin Pop
     , pTargetGroups
732 34af39e8 Jose A. Lopes
     ],
733 34af39e8 Jose A. Lopes
     "group_name")
734 398e9066 Iustin Pop
  , ("OpOsDiagnose",
735 34af39e8 Jose A. Lopes
     [t| [[JSValue]] |],
736 34af39e8 Jose A. Lopes
     OpDoc.opOsDiagnose,
737 398e9066 Iustin Pop
     [ pOutputFields
738 34af39e8 Jose A. Lopes
     , withDoc "Which operating systems to diagnose" pNames
739 34af39e8 Jose A. Lopes
     ],
740 34af39e8 Jose A. Lopes
     [])
741 b954f097 Constantinos Venetsanopoulos
  , ("OpExtStorageDiagnose",
742 34af39e8 Jose A. Lopes
     [t| [[JSValue]] |],
743 34af39e8 Jose A. Lopes
     OpDoc.opExtStorageDiagnose,
744 b954f097 Constantinos Venetsanopoulos
     [ pOutputFields
745 34af39e8 Jose A. Lopes
     , withDoc "Which ExtStorage Provider to diagnose" pNames
746 34af39e8 Jose A. Lopes
     ],
747 34af39e8 Jose A. Lopes
     [])
748 398e9066 Iustin Pop
  , ("OpBackupPrepare",
749 34af39e8 Jose A. Lopes
     [t| Maybe (JSObject JSValue) |],
750 34af39e8 Jose A. Lopes
     OpDoc.opBackupPrepare,
751 398e9066 Iustin Pop
     [ pInstanceName
752 da4a52a3 Thomas Thrainer
     , pInstanceUuid
753 398e9066 Iustin Pop
     , pExportMode
754 34af39e8 Jose A. Lopes
     ],
755 34af39e8 Jose A. Lopes
     "instance_name")
756 398e9066 Iustin Pop
  , ("OpBackupExport",
757 34af39e8 Jose A. Lopes
     [t| (Bool, [Bool]) |],
758 34af39e8 Jose A. Lopes
     OpDoc.opBackupExport,
759 398e9066 Iustin Pop
     [ pInstanceName
760 da4a52a3 Thomas Thrainer
     , pInstanceUuid
761 896cc964 Thomas Thrainer
     , pBackupCompress
762 398e9066 Iustin Pop
     , pShutdownTimeout
763 398e9066 Iustin Pop
     , pExportTargetNode
764 1c3231aa Thomas Thrainer
     , pExportTargetNodeUuid
765 67fc4de7 Iustin Pop
     , pShutdownInstance
766 398e9066 Iustin Pop
     , pRemoveInstance
767 398e9066 Iustin Pop
     , pIgnoreRemoveFailures
768 34af39e8 Jose A. Lopes
     , defaultField [| ExportModeLocal |] pExportMode
769 398e9066 Iustin Pop
     , pX509KeyName
770 398e9066 Iustin Pop
     , pX509DestCA
771 34af39e8 Jose A. Lopes
     ],
772 34af39e8 Jose A. Lopes
     "instance_name")
773 398e9066 Iustin Pop
  , ("OpBackupRemove",
774 34af39e8 Jose A. Lopes
     [t| () |],
775 34af39e8 Jose A. Lopes
     OpDoc.opBackupRemove,
776 da4a52a3 Thomas Thrainer
     [ pInstanceName
777 da4a52a3 Thomas Thrainer
     , pInstanceUuid
778 34af39e8 Jose A. Lopes
     ],
779 34af39e8 Jose A. Lopes
     "instance_name")
780 34af39e8 Jose A. Lopes
  , ("OpTagsGet",
781 34af39e8 Jose A. Lopes
     [t| [NonEmptyString] |],
782 34af39e8 Jose A. Lopes
     OpDoc.opTagsGet,
783 34af39e8 Jose A. Lopes
     [ pTagsObject
784 34af39e8 Jose A. Lopes
     , pUseLocking
785 34af39e8 Jose A. Lopes
     , withDoc "Name of object to retrieve tags from" pTagsName
786 34af39e8 Jose A. Lopes
     ],
787 34af39e8 Jose A. Lopes
     "name")
788 34af39e8 Jose A. Lopes
  , ("OpTagsSearch",
789 34af39e8 Jose A. Lopes
     [t| [(NonEmptyString, NonEmptyString)] |],
790 34af39e8 Jose A. Lopes
     OpDoc.opTagsSearch,
791 34af39e8 Jose A. Lopes
     [ pTagSearchPattern
792 34af39e8 Jose A. Lopes
     ],
793 34af39e8 Jose A. Lopes
     "pattern")
794 34af39e8 Jose A. Lopes
  , ("OpTagsSet",
795 34af39e8 Jose A. Lopes
     [t| () |],
796 34af39e8 Jose A. Lopes
     OpDoc.opTagsSet,
797 34af39e8 Jose A. Lopes
     [ pTagsObject
798 34af39e8 Jose A. Lopes
     , pTagsList
799 34af39e8 Jose A. Lopes
     , withDoc "Name of object where tag(s) should be added" pTagsName
800 34af39e8 Jose A. Lopes
     ],
801 34af39e8 Jose A. Lopes
     [])
802 34af39e8 Jose A. Lopes
  , ("OpTagsDel",
803 34af39e8 Jose A. Lopes
     [t| () |],
804 34af39e8 Jose A. Lopes
     OpDoc.opTagsDel,
805 34af39e8 Jose A. Lopes
     [ pTagsObject
806 34af39e8 Jose A. Lopes
     , pTagsList
807 34af39e8 Jose A. Lopes
     , withDoc "Name of object where tag(s) should be deleted" pTagsName
808 34af39e8 Jose A. Lopes
     ],
809 34af39e8 Jose A. Lopes
     [])
810 34af39e8 Jose A. Lopes
  , ("OpTestDelay",
811 34af39e8 Jose A. Lopes
     [t| () |],
812 34af39e8 Jose A. Lopes
     OpDoc.opTestDelay,
813 34af39e8 Jose A. Lopes
     [ pDelayDuration
814 34af39e8 Jose A. Lopes
     , pDelayOnMaster
815 34af39e8 Jose A. Lopes
     , pDelayOnNodes
816 34af39e8 Jose A. Lopes
     , pDelayOnNodeUuids
817 34af39e8 Jose A. Lopes
     , pDelayRepeat
818 34af39e8 Jose A. Lopes
     ],
819 34af39e8 Jose A. Lopes
     "duration")
820 a3f02317 Iustin Pop
  , ("OpTestAllocator",
821 5cbf7832 Jose A. Lopes
     [t| String |],
822 34af39e8 Jose A. Lopes
     OpDoc.opTestAllocator,
823 a3f02317 Iustin Pop
     [ pIAllocatorDirection
824 a3f02317 Iustin Pop
     , pIAllocatorMode
825 a3f02317 Iustin Pop
     , pIAllocatorReqName
826 a3f02317 Iustin Pop
     , pIAllocatorNics
827 a3f02317 Iustin Pop
     , pIAllocatorDisks
828 a3f02317 Iustin Pop
     , pHypervisor
829 a3f02317 Iustin Pop
     , pIallocator
830 a3f02317 Iustin Pop
     , pInstTags
831 a3f02317 Iustin Pop
     , pIAllocatorMemory
832 a3f02317 Iustin Pop
     , pIAllocatorVCpus
833 a3f02317 Iustin Pop
     , pIAllocatorOs
834 a3f02317 Iustin Pop
     , pDiskTemplate
835 a3f02317 Iustin Pop
     , pIAllocatorInstances
836 a3f02317 Iustin Pop
     , pIAllocatorEvacMode
837 a3f02317 Iustin Pop
     , pTargetGroups
838 a3f02317 Iustin Pop
     , pIAllocatorSpindleUse
839 a3f02317 Iustin Pop
     , pIAllocatorCount
840 34af39e8 Jose A. Lopes
     ],
841 34af39e8 Jose A. Lopes
     "iallocator")
842 a3f02317 Iustin Pop
  , ("OpTestJqueue",
843 5cbf7832 Jose A. Lopes
     [t| Bool |],
844 34af39e8 Jose A. Lopes
     OpDoc.opTestJqueue,
845 a3f02317 Iustin Pop
     [ pJQueueNotifyWaitLock
846 a3f02317 Iustin Pop
     , pJQueueNotifyExec
847 a3f02317 Iustin Pop
     , pJQueueLogMessages
848 a3f02317 Iustin Pop
     , pJQueueFail
849 34af39e8 Jose A. Lopes
     ],
850 34af39e8 Jose A. Lopes
     [])
851 a3f02317 Iustin Pop
  , ("OpTestDummy",
852 34af39e8 Jose A. Lopes
     [t| () |],
853 34af39e8 Jose A. Lopes
     OpDoc.opTestDummy,
854 a3f02317 Iustin Pop
     [ pTestDummyResult
855 a3f02317 Iustin Pop
     , pTestDummyMessages
856 a3f02317 Iustin Pop
     , pTestDummyFail
857 a3f02317 Iustin Pop
     , pTestDummySubmitJobs
858 34af39e8 Jose A. Lopes
     ],
859 34af39e8 Jose A. Lopes
     [])
860 8d239fa4 Iustin Pop
  , ("OpNetworkAdd",
861 34af39e8 Jose A. Lopes
     [t| () |],
862 34af39e8 Jose A. Lopes
     OpDoc.opNetworkAdd,
863 8d239fa4 Iustin Pop
     [ pNetworkName
864 8d239fa4 Iustin Pop
     , pNetworkAddress4
865 8d239fa4 Iustin Pop
     , pNetworkGateway4
866 8d239fa4 Iustin Pop
     , pNetworkAddress6
867 8d239fa4 Iustin Pop
     , pNetworkGateway6
868 8d239fa4 Iustin Pop
     , pNetworkMacPrefix
869 8d239fa4 Iustin Pop
     , pNetworkAddRsvdIps
870 1dbceab9 Iustin Pop
     , pIpConflictsCheck
871 34af39e8 Jose A. Lopes
     , withDoc "Network tags" pInstTags
872 34af39e8 Jose A. Lopes
     ],
873 34af39e8 Jose A. Lopes
     "network_name")
874 8d239fa4 Iustin Pop
  , ("OpNetworkRemove",
875 34af39e8 Jose A. Lopes
     [t| () |],
876 34af39e8 Jose A. Lopes
     OpDoc.opNetworkRemove,
877 8d239fa4 Iustin Pop
     [ pNetworkName
878 8d239fa4 Iustin Pop
     , pForce
879 34af39e8 Jose A. Lopes
     ],
880 34af39e8 Jose A. Lopes
     "network_name")
881 8d239fa4 Iustin Pop
  , ("OpNetworkSetParams",
882 34af39e8 Jose A. Lopes
     [t| () |],
883 34af39e8 Jose A. Lopes
     OpDoc.opNetworkSetParams,
884 8d239fa4 Iustin Pop
     [ pNetworkName
885 8d239fa4 Iustin Pop
     , pNetworkGateway4
886 8d239fa4 Iustin Pop
     , pNetworkAddress6
887 8d239fa4 Iustin Pop
     , pNetworkGateway6
888 8d239fa4 Iustin Pop
     , pNetworkMacPrefix
889 34af39e8 Jose A. Lopes
     , withDoc "Which external IP addresses to reserve" pNetworkAddRsvdIps
890 8d239fa4 Iustin Pop
     , pNetworkRemoveRsvdIps
891 34af39e8 Jose A. Lopes
     ],
892 34af39e8 Jose A. Lopes
     "network_name")
893 8d239fa4 Iustin Pop
  , ("OpNetworkConnect",
894 34af39e8 Jose A. Lopes
     [t| () |],
895 34af39e8 Jose A. Lopes
     OpDoc.opNetworkConnect,
896 8d239fa4 Iustin Pop
     [ pGroupName
897 8d239fa4 Iustin Pop
     , pNetworkName
898 8d239fa4 Iustin Pop
     , pNetworkMode
899 8d239fa4 Iustin Pop
     , pNetworkLink
900 8d239fa4 Iustin Pop
     , pIpConflictsCheck
901 34af39e8 Jose A. Lopes
     ],
902 34af39e8 Jose A. Lopes
     "network_name")
903 8d239fa4 Iustin Pop
  , ("OpNetworkDisconnect",
904 34af39e8 Jose A. Lopes
     [t| () |],
905 34af39e8 Jose A. Lopes
     OpDoc.opNetworkDisconnect,
906 8d239fa4 Iustin Pop
     [ pGroupName
907 8d239fa4 Iustin Pop
     , pNetworkName
908 34af39e8 Jose A. Lopes
     ],
909 34af39e8 Jose A. Lopes
     "network_name")
910 ebf38064 Iustin Pop
  ])
911 12c19659 Iustin Pop
912 a583ec5d Iustin Pop
-- | Returns the OP_ID for a given opcode value.
913 12c19659 Iustin Pop
$(genOpID ''OpCode "opID")
914 702a4ee0 Iustin Pop
915 a583ec5d Iustin Pop
-- | A list of all defined/supported opcode IDs.
916 a583ec5d Iustin Pop
$(genAllOpIDs ''OpCode "allOpIDs")
917 a583ec5d Iustin Pop
918 e713a686 Petr Pudlak
-- | Convert the opcode name to lowercase with underscores and strip
919 e713a686 Petr Pudlak
-- the @Op@ prefix.
920 e713a686 Petr Pudlak
$(genOpLowerStrip (C.opcodeReasonSrcOpcode ++ ":") ''OpCode "opReasonSrcID")
921 e713a686 Petr Pudlak
922 702a4ee0 Iustin Pop
instance JSON OpCode where
923 ebf38064 Iustin Pop
  readJSON = loadOpCode
924 ebf38064 Iustin Pop
  showJSON = saveOpCode
925 4a826364 Iustin Pop
926 ad1c1e41 Iustin Pop
-- | Generates the summary value for an opcode.
927 ad1c1e41 Iustin Pop
opSummaryVal :: OpCode -> Maybe String
928 ad1c1e41 Iustin Pop
opSummaryVal OpClusterVerifyGroup { opGroupName = s } = Just (fromNonEmpty s)
929 ad1c1e41 Iustin Pop
opSummaryVal OpGroupVerifyDisks { opGroupName = s } = Just (fromNonEmpty s)
930 ad1c1e41 Iustin Pop
opSummaryVal OpClusterRename { opName = s } = Just (fromNonEmpty s)
931 ad1c1e41 Iustin Pop
opSummaryVal OpQuery { opWhat = s } = Just (queryTypeOpToRaw s)
932 ad1c1e41 Iustin Pop
opSummaryVal OpQueryFields { opWhat = s } = Just (queryTypeOpToRaw s)
933 ad1c1e41 Iustin Pop
opSummaryVal OpNodeRemove { opNodeName = s } = Just (fromNonEmpty s)
934 ad1c1e41 Iustin Pop
opSummaryVal OpNodeAdd { opNodeName = s } = Just (fromNonEmpty s)
935 ad1c1e41 Iustin Pop
opSummaryVal OpNodeModifyStorage { opNodeName = s } = Just (fromNonEmpty s)
936 ad1c1e41 Iustin Pop
opSummaryVal OpRepairNodeStorage  { opNodeName = s } = Just (fromNonEmpty s)
937 ad1c1e41 Iustin Pop
opSummaryVal OpNodeSetParams { opNodeName = s } = Just (fromNonEmpty s)
938 ad1c1e41 Iustin Pop
opSummaryVal OpNodePowercycle { opNodeName = s } = Just (fromNonEmpty s)
939 ad1c1e41 Iustin Pop
opSummaryVal OpNodeMigrate { opNodeName = s } = Just (fromNonEmpty s)
940 ad1c1e41 Iustin Pop
opSummaryVal OpNodeEvacuate { opNodeName = s } = Just (fromNonEmpty s)
941 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceCreate { opInstanceName = s } = Just s
942 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceReinstall { opInstanceName = s } = Just s
943 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceRemove { opInstanceName = s } = Just s
944 ad1c1e41 Iustin Pop
-- FIXME: instance rename should show both names; currently it shows none
945 ad1c1e41 Iustin Pop
-- opSummaryVal OpInstanceRename { opInstanceName = s } = Just s
946 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceStartup { opInstanceName = s } = Just s
947 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceShutdown { opInstanceName = s } = Just s
948 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceReboot { opInstanceName = s } = Just s
949 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceReplaceDisks { opInstanceName = s } = Just s
950 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceFailover { opInstanceName = s } = Just s
951 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceMigrate { opInstanceName = s } = Just s
952 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceMove { opInstanceName = s } = Just s
953 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceConsole { opInstanceName = s } = Just s
954 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceActivateDisks { opInstanceName = s } = Just s
955 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceDeactivateDisks { opInstanceName = s } = Just s
956 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceRecreateDisks { opInstanceName = s } = Just s
957 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceSetParams { opInstanceName = s } = Just s
958 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceGrowDisk { opInstanceName = s } = Just s
959 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceChangeGroup { opInstanceName = s } = Just s
960 ad1c1e41 Iustin Pop
opSummaryVal OpGroupAdd { opGroupName = s } = Just (fromNonEmpty s)
961 ad1c1e41 Iustin Pop
opSummaryVal OpGroupAssignNodes { opGroupName = s } = Just (fromNonEmpty s)
962 ad1c1e41 Iustin Pop
opSummaryVal OpGroupSetParams { opGroupName = s } = Just (fromNonEmpty s)
963 ad1c1e41 Iustin Pop
opSummaryVal OpGroupRemove { opGroupName = s } = Just (fromNonEmpty s)
964 ad1c1e41 Iustin Pop
opSummaryVal OpGroupEvacuate { opGroupName = s } = Just (fromNonEmpty s)
965 ad1c1e41 Iustin Pop
opSummaryVal OpBackupPrepare { opInstanceName = s } = Just s
966 ad1c1e41 Iustin Pop
opSummaryVal OpBackupExport { opInstanceName = s } = Just s
967 ad1c1e41 Iustin Pop
opSummaryVal OpBackupRemove { opInstanceName = s } = Just s
968 34af39e8 Jose A. Lopes
opSummaryVal OpTagsGet { opKind = s } = Just (show s)
969 ad1c1e41 Iustin Pop
opSummaryVal OpTagsSearch { opTagSearchPattern = s } = Just (fromNonEmpty s)
970 ad1c1e41 Iustin Pop
opSummaryVal OpTestDelay { opDelayDuration = d } = Just (show d)
971 ad1c1e41 Iustin Pop
opSummaryVal OpTestAllocator { opIallocator = s } =
972 ad1c1e41 Iustin Pop
  -- FIXME: Python doesn't handle None fields well, so we have behave the same
973 ad1c1e41 Iustin Pop
  Just $ maybe "None" fromNonEmpty s
974 ad1c1e41 Iustin Pop
opSummaryVal OpNetworkAdd { opNetworkName = s} = Just (fromNonEmpty s)
975 ad1c1e41 Iustin Pop
opSummaryVal OpNetworkRemove { opNetworkName = s} = Just (fromNonEmpty s)
976 ad1c1e41 Iustin Pop
opSummaryVal OpNetworkSetParams { opNetworkName = s} = Just (fromNonEmpty s)
977 ad1c1e41 Iustin Pop
opSummaryVal OpNetworkConnect { opNetworkName = s} = Just (fromNonEmpty s)
978 ad1c1e41 Iustin Pop
opSummaryVal OpNetworkDisconnect { opNetworkName = s} = Just (fromNonEmpty s)
979 ad1c1e41 Iustin Pop
opSummaryVal _ = Nothing
980 ad1c1e41 Iustin Pop
981 ad1c1e41 Iustin Pop
-- | Computes the summary of the opcode.
982 ad1c1e41 Iustin Pop
opSummary :: OpCode -> String
983 ad1c1e41 Iustin Pop
opSummary op =
984 ad1c1e41 Iustin Pop
  case opSummaryVal op of
985 ad1c1e41 Iustin Pop
    Nothing -> op_suffix
986 ad1c1e41 Iustin Pop
    Just s -> op_suffix ++ "(" ++ s ++ ")"
987 ad1c1e41 Iustin Pop
  where op_suffix = drop 3 $ opID op
988 ad1c1e41 Iustin Pop
989 4a826364 Iustin Pop
-- | Generic\/common opcode parameters.
990 4a826364 Iustin Pop
$(buildObject "CommonOpParams" "op"
991 4a826364 Iustin Pop
  [ pDryRun
992 4a826364 Iustin Pop
  , pDebugLevel
993 4a826364 Iustin Pop
  , pOpPriority
994 4a826364 Iustin Pop
  , pDependencies
995 4a826364 Iustin Pop
  , pComment
996 516a0e94 Michele Tartara
  , pReason
997 4a826364 Iustin Pop
  ])
998 4a826364 Iustin Pop
999 4a826364 Iustin Pop
-- | Default common parameter values.
1000 4a826364 Iustin Pop
defOpParams :: CommonOpParams
1001 4a826364 Iustin Pop
defOpParams =
1002 4a826364 Iustin Pop
  CommonOpParams { opDryRun     = Nothing
1003 4a826364 Iustin Pop
                 , opDebugLevel = Nothing
1004 4a826364 Iustin Pop
                 , opPriority   = OpPrioNormal
1005 4a826364 Iustin Pop
                 , opDepends    = Nothing
1006 4a826364 Iustin Pop
                 , opComment    = Nothing
1007 516a0e94 Michele Tartara
                 , opReason     = []
1008 4a826364 Iustin Pop
                 }
1009 4a826364 Iustin Pop
1010 62933497 Klaus Aehlig
-- | Resolve relative dependencies to absolute ones, given the job ID.
1011 62933497 Klaus Aehlig
resolveDependsCommon :: (Monad m) => CommonOpParams -> JobId -> m CommonOpParams
1012 62933497 Klaus Aehlig
resolveDependsCommon p@(CommonOpParams { opDepends = Just deps}) jid = do
1013 62933497 Klaus Aehlig
  deps' <- mapM (`absoluteJobDependency` jid) deps
1014 62933497 Klaus Aehlig
  return p { opDepends = Just deps' }
1015 62933497 Klaus Aehlig
resolveDependsCommon p _ = return p
1016 62933497 Klaus Aehlig
1017 4a826364 Iustin Pop
-- | The top-level opcode type.
1018 ad1c1e41 Iustin Pop
data MetaOpCode = MetaOpCode { metaParams :: CommonOpParams
1019 ad1c1e41 Iustin Pop
                             , metaOpCode :: OpCode
1020 ad1c1e41 Iustin Pop
                             } deriving (Show, Eq)
1021 4a826364 Iustin Pop
1022 62933497 Klaus Aehlig
-- | Resolve relative dependencies to absolute ones, given the job Id.
1023 62933497 Klaus Aehlig
resolveDependencies :: (Monad m) => MetaOpCode -> JobId -> m MetaOpCode
1024 62933497 Klaus Aehlig
resolveDependencies mopc jid = do
1025 62933497 Klaus Aehlig
  mpar <- resolveDependsCommon (metaParams mopc) jid
1026 62933497 Klaus Aehlig
  return (mopc { metaParams = mpar })
1027 62933497 Klaus Aehlig
1028 4a826364 Iustin Pop
-- | JSON serialisation for 'MetaOpCode'.
1029 4a826364 Iustin Pop
showMeta :: MetaOpCode -> JSValue
1030 4a826364 Iustin Pop
showMeta (MetaOpCode params op) =
1031 4a826364 Iustin Pop
  let objparams = toDictCommonOpParams params
1032 4a826364 Iustin Pop
      objop = toDictOpCode op
1033 4a826364 Iustin Pop
  in makeObj (objparams ++ objop)
1034 4a826364 Iustin Pop
1035 4a826364 Iustin Pop
-- | JSON deserialisation for 'MetaOpCode'
1036 4a826364 Iustin Pop
readMeta :: JSValue -> Text.JSON.Result MetaOpCode
1037 4a826364 Iustin Pop
readMeta v = do
1038 4a826364 Iustin Pop
  meta <- readJSON v
1039 4a826364 Iustin Pop
  op <- readJSON v
1040 4a826364 Iustin Pop
  return $ MetaOpCode meta op
1041 4a826364 Iustin Pop
1042 4a826364 Iustin Pop
instance JSON MetaOpCode where
1043 4a826364 Iustin Pop
  showJSON = showMeta
1044 4a826364 Iustin Pop
  readJSON = readMeta
1045 4a826364 Iustin Pop
1046 4a826364 Iustin Pop
-- | Wraps an 'OpCode' with the default parameters to build a
1047 4a826364 Iustin Pop
-- 'MetaOpCode'.
1048 4a826364 Iustin Pop
wrapOpCode :: OpCode -> MetaOpCode
1049 4a826364 Iustin Pop
wrapOpCode = MetaOpCode defOpParams
1050 4a826364 Iustin Pop
1051 4a826364 Iustin Pop
-- | Sets the comment on a meta opcode.
1052 4a826364 Iustin Pop
setOpComment :: String -> MetaOpCode -> MetaOpCode
1053 4a826364 Iustin Pop
setOpComment comment (MetaOpCode common op) =
1054 4a826364 Iustin Pop
  MetaOpCode (common { opComment = Just comment}) op
1055 551b44e2 Iustin Pop
1056 551b44e2 Iustin Pop
-- | Sets the priority on a meta opcode.
1057 551b44e2 Iustin Pop
setOpPriority :: OpSubmitPriority -> MetaOpCode -> MetaOpCode
1058 551b44e2 Iustin Pop
setOpPriority prio (MetaOpCode common op) =
1059 551b44e2 Iustin Pop
  MetaOpCode (common { opPriority = prio }) op