Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpCodes.hs @ ef89d9d5

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