Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpCodes.hs @ 0cffcdb1

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