Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpCodes.hs @ 26e32dee

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