Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpCodes.hs @ 3311e336

History | View | Annotate | Download (27 kB)

1 34af39e8 Jose A. Lopes
{-# LANGUAGE ExistentialQuantification, TemplateHaskell #-}
2 34af39e8 Jose A. Lopes
{-# OPTIONS_GHC -fno-warn-orphans #-}
3 e9aaa3c6 Iustin Pop
4 702a4ee0 Iustin Pop
{-| Implementation of the opcodes.
5 702a4ee0 Iustin Pop
6 702a4ee0 Iustin Pop
-}
7 702a4ee0 Iustin Pop
8 702a4ee0 Iustin Pop
{-
9 702a4ee0 Iustin Pop
10 551b44e2 Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012, 2013 Google Inc.
11 702a4ee0 Iustin Pop
12 702a4ee0 Iustin Pop
This program is free software; you can redistribute it and/or modify
13 702a4ee0 Iustin Pop
it under the terms of the GNU General Public License as published by
14 702a4ee0 Iustin Pop
the Free Software Foundation; either version 2 of the License, or
15 702a4ee0 Iustin Pop
(at your option) any later version.
16 702a4ee0 Iustin Pop
17 702a4ee0 Iustin Pop
This program is distributed in the hope that it will be useful, but
18 702a4ee0 Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
19 702a4ee0 Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20 702a4ee0 Iustin Pop
General Public License for more details.
21 702a4ee0 Iustin Pop
22 702a4ee0 Iustin Pop
You should have received a copy of the GNU General Public License
23 702a4ee0 Iustin Pop
along with this program; if not, write to the Free Software
24 702a4ee0 Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25 702a4ee0 Iustin Pop
02110-1301, USA.
26 702a4ee0 Iustin Pop
27 702a4ee0 Iustin Pop
-}
28 702a4ee0 Iustin Pop
29 702a4ee0 Iustin Pop
module Ganeti.OpCodes
30 34af39e8 Jose A. Lopes
  ( pyClasses
31 34af39e8 Jose A. Lopes
  , OpCode(..)
32 ebf38064 Iustin Pop
  , ReplaceDisksMode(..)
33 4a1dc2bf Iustin Pop
  , DiskIndex
34 4a1dc2bf Iustin Pop
  , mkDiskIndex
35 4a1dc2bf Iustin Pop
  , unDiskIndex
36 ebf38064 Iustin Pop
  , opID
37 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 4a826364 Iustin Pop
  , wrapOpCode
44 4a826364 Iustin Pop
  , setOpComment
45 551b44e2 Iustin Pop
  , setOpPriority
46 ebf38064 Iustin Pop
  ) where
47 702a4ee0 Iustin Pop
48 34af39e8 Jose A. Lopes
import Text.JSON (readJSON, JSObject, JSON, JSValue(..), makeObj, fromJSObject)
49 4a826364 Iustin Pop
import qualified Text.JSON
50 702a4ee0 Iustin Pop
51 12c19659 Iustin Pop
import Ganeti.THH
52 e9aaa3c6 Iustin Pop
53 34af39e8 Jose A. Lopes
import qualified Ganeti.Hs2Py.OpDoc as OpDoc
54 92f51573 Iustin Pop
import Ganeti.OpParams
55 c4d68e39 Jose A. Lopes
import Ganeti.PyValueInstances ()
56 34af39e8 Jose A. Lopes
import Ganeti.Types
57 ad1c1e41 Iustin Pop
import Ganeti.Query.Language (queryTypeOpToRaw)
58 4a1dc2bf Iustin Pop
59 34af39e8 Jose A. Lopes
import Data.List (intercalate)
60 34af39e8 Jose A. Lopes
import Data.Map (Map)
61 34af39e8 Jose A. Lopes
62 34af39e8 Jose A. Lopes
import qualified Ganeti.Constants as C
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 34af39e8 Jose A. Lopes
  
82 34af39e8 Jose A. Lopes
instance PyValue a => PyValue (NonEmpty a) where
83 34af39e8 Jose A. Lopes
  showValue = showValue . fromNonEmpty
84 34af39e8 Jose A. Lopes
  
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 34af39e8 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 34af39e8 Jose A. Lopes
type JobIdListOnly = [(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 34af39e8 Jose A. Lopes
     [t| () |],
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 c66f09f5 Iustin Pop
     , pDiskParams
216 c66f09f5 Iustin Pop
     , pCandidatePoolSize
217 c66f09f5 Iustin Pop
     , pUidPool
218 c66f09f5 Iustin Pop
     , pAddUids
219 c66f09f5 Iustin Pop
     , pRemoveUids
220 c66f09f5 Iustin Pop
     , pMaintainNodeHealth
221 c66f09f5 Iustin Pop
     , pPreallocWipeDisks
222 c66f09f5 Iustin Pop
     , pNicParams
223 34af39e8 Jose A. Lopes
     , withDoc "Cluster-wide node parameter defaults" pNdParams
224 34af39e8 Jose A. Lopes
     , withDoc "Cluster-wide ipolicy specs" pIpolicy
225 c66f09f5 Iustin Pop
     , pDrbdHelper
226 c66f09f5 Iustin Pop
     , pDefaultIAllocator
227 c66f09f5 Iustin Pop
     , pMasterNetdev
228 67fc4de7 Iustin Pop
     , pMasterNetmask
229 c66f09f5 Iustin Pop
     , pReservedLvs
230 c66f09f5 Iustin Pop
     , pHiddenOs
231 c66f09f5 Iustin Pop
     , pBlacklistedOs
232 c66f09f5 Iustin Pop
     , pUseExternalMipScript
233 66af5ec5 Helga Velroyen
     , pEnabledDiskTemplates
234 75f2ff7d Michele Tartara
     , pModifyEtcHosts
235 3039e2dc Helga Velroyen
     , pGlobalFileStorageDir
236 4e6cfd11 Helga Velroyen
     , pGlobalSharedFileStorageDir
237 34af39e8 Jose A. Lopes
     ],
238 34af39e8 Jose A. Lopes
     [])
239 34af39e8 Jose A. Lopes
  , ("OpClusterRedistConf",
240 34af39e8 Jose A. Lopes
     [t| () |],
241 34af39e8 Jose A. Lopes
     OpDoc.opClusterRedistConf,
242 34af39e8 Jose A. Lopes
     [],
243 34af39e8 Jose A. Lopes
     [])
244 34af39e8 Jose A. Lopes
  , ("OpClusterActivateMasterIp",
245 34af39e8 Jose A. Lopes
     [t| () |],
246 34af39e8 Jose A. Lopes
     OpDoc.opClusterActivateMasterIp,
247 34af39e8 Jose A. Lopes
     [],
248 34af39e8 Jose A. Lopes
     [])
249 34af39e8 Jose A. Lopes
  , ("OpClusterDeactivateMasterIp",
250 34af39e8 Jose A. Lopes
     [t| () |],
251 34af39e8 Jose A. Lopes
     OpDoc.opClusterDeactivateMasterIp,
252 34af39e8 Jose A. Lopes
     [],
253 34af39e8 Jose A. Lopes
     [])
254 c66f09f5 Iustin Pop
  , ("OpQuery",
255 34af39e8 Jose A. Lopes
     [t| QueryResponse |],
256 34af39e8 Jose A. Lopes
     OpDoc.opQuery,
257 c66f09f5 Iustin Pop
     [ pQueryWhat
258 c66f09f5 Iustin Pop
     , pUseLocking
259 c66f09f5 Iustin Pop
     , pQueryFields
260 c66f09f5 Iustin Pop
     , pQueryFilter
261 34af39e8 Jose A. Lopes
     ],
262 34af39e8 Jose A. Lopes
     "what")
263 c66f09f5 Iustin Pop
  , ("OpQueryFields",
264 34af39e8 Jose A. Lopes
     [t| QueryFieldsResponse |],
265 34af39e8 Jose A. Lopes
     OpDoc.opQueryFields,
266 c66f09f5 Iustin Pop
     [ pQueryWhat
267 34af39e8 Jose A. Lopes
     , pQueryFieldsFields
268 34af39e8 Jose A. Lopes
     ],
269 34af39e8 Jose A. Lopes
     "what")
270 c66f09f5 Iustin Pop
  , ("OpOobCommand",
271 34af39e8 Jose A. Lopes
     [t| [[(QueryResultCode, JSValue)]] |],
272 34af39e8 Jose A. Lopes
     OpDoc.opOobCommand,
273 c66f09f5 Iustin Pop
     [ pNodeNames
274 34af39e8 Jose A. Lopes
     , withDoc "List of node UUIDs to run the OOB command against" pNodeUuids
275 c66f09f5 Iustin Pop
     , pOobCommand
276 c66f09f5 Iustin Pop
     , pOobTimeout
277 c66f09f5 Iustin Pop
     , pIgnoreStatus
278 c66f09f5 Iustin Pop
     , pPowerDelay
279 34af39e8 Jose A. Lopes
     ],
280 34af39e8 Jose A. Lopes
     [])
281 34af39e8 Jose A. Lopes
  , ("OpRestrictedCommand",
282 34af39e8 Jose A. Lopes
     [t| [(Bool, String)] |],
283 34af39e8 Jose A. Lopes
     OpDoc.opRestrictedCommand,
284 34af39e8 Jose A. Lopes
     [ pUseLocking
285 34af39e8 Jose A. Lopes
     , withDoc
286 34af39e8 Jose A. Lopes
       "Nodes on which the command should be run (at least one)"
287 34af39e8 Jose A. Lopes
       pRequiredNodes
288 34af39e8 Jose A. Lopes
     , withDoc
289 34af39e8 Jose A. Lopes
       "Node UUIDs on which the command should be run (at least one)"
290 34af39e8 Jose A. Lopes
       pRequiredNodeUuids
291 34af39e8 Jose A. Lopes
     , pRestrictedCommand
292 34af39e8 Jose A. Lopes
     ],
293 34af39e8 Jose A. Lopes
     [])
294 1c3231aa Thomas Thrainer
  , ("OpNodeRemove",
295 34af39e8 Jose A. Lopes
     [t| () |],
296 34af39e8 Jose A. Lopes
      OpDoc.opNodeRemove,
297 1c3231aa Thomas Thrainer
     [ pNodeName
298 1c3231aa Thomas Thrainer
     , pNodeUuid
299 34af39e8 Jose A. Lopes
     ],
300 34af39e8 Jose A. Lopes
     "node_name")
301 c66f09f5 Iustin Pop
  , ("OpNodeAdd",
302 34af39e8 Jose A. Lopes
     [t| () |],
303 34af39e8 Jose A. Lopes
      OpDoc.opNodeAdd,
304 c66f09f5 Iustin Pop
     [ pNodeName
305 c66f09f5 Iustin Pop
     , pHvState
306 c66f09f5 Iustin Pop
     , pDiskState
307 c66f09f5 Iustin Pop
     , pPrimaryIp
308 c66f09f5 Iustin Pop
     , pSecondaryIp
309 c66f09f5 Iustin Pop
     , pReadd
310 c66f09f5 Iustin Pop
     , pNodeGroup
311 c66f09f5 Iustin Pop
     , pMasterCapable
312 c66f09f5 Iustin Pop
     , pVmCapable
313 c66f09f5 Iustin Pop
     , pNdParams
314 34af39e8 Jose A. Lopes
     ],
315 34af39e8 Jose A. Lopes
     "node_name")
316 34af39e8 Jose A. Lopes
  , ("OpNodeQuery",
317 34af39e8 Jose A. Lopes
     [t| [[JSValue]] |],
318 34af39e8 Jose A. Lopes
     OpDoc.opNodeQuery,
319 34af39e8 Jose A. Lopes
     [ pOutputFields
320 34af39e8 Jose A. Lopes
     , withDoc "Empty list to query all nodes, node names otherwise" pNames
321 34af39e8 Jose A. Lopes
     , pUseLocking
322 34af39e8 Jose A. Lopes
     ],
323 34af39e8 Jose A. Lopes
     [])
324 c66f09f5 Iustin Pop
  , ("OpNodeQueryvols",
325 34af39e8 Jose A. Lopes
     [t| [JSValue] |],
326 34af39e8 Jose A. Lopes
     OpDoc.opNodeQueryvols,
327 c66f09f5 Iustin Pop
     [ pOutputFields
328 34af39e8 Jose A. Lopes
     , withDoc "Empty list to query all nodes, node names otherwise" pNodes
329 34af39e8 Jose A. Lopes
     ],
330 34af39e8 Jose A. Lopes
     [])
331 c66f09f5 Iustin Pop
  , ("OpNodeQueryStorage",
332 34af39e8 Jose A. Lopes
     [t| [[JSValue]] |],
333 34af39e8 Jose A. Lopes
     OpDoc.opNodeQueryStorage,
334 c66f09f5 Iustin Pop
     [ pOutputFields
335 c66f09f5 Iustin Pop
     , pStorageType
336 34af39e8 Jose A. Lopes
     , withDoc
337 34af39e8 Jose A. Lopes
       "Empty list to query all, list of names to query otherwise"
338 34af39e8 Jose A. Lopes
       pNodes
339 c66f09f5 Iustin Pop
     , pStorageName
340 34af39e8 Jose A. Lopes
     ],
341 34af39e8 Jose A. Lopes
     [])
342 c66f09f5 Iustin Pop
  , ("OpNodeModifyStorage",
343 34af39e8 Jose A. Lopes
     [t| () |],
344 34af39e8 Jose A. Lopes
     OpDoc.opNodeModifyStorage,
345 c66f09f5 Iustin Pop
     [ pNodeName
346 1c3231aa Thomas Thrainer
     , pNodeUuid
347 c66f09f5 Iustin Pop
     , pStorageType
348 c66f09f5 Iustin Pop
     , pStorageName
349 c66f09f5 Iustin Pop
     , pStorageChanges
350 34af39e8 Jose A. Lopes
     ],
351 34af39e8 Jose A. Lopes
     "node_name")
352 c66f09f5 Iustin Pop
  , ("OpRepairNodeStorage",
353 34af39e8 Jose A. Lopes
      [t| () |],
354 34af39e8 Jose A. Lopes
      OpDoc.opRepairNodeStorage,
355 c66f09f5 Iustin Pop
     [ pNodeName
356 1c3231aa Thomas Thrainer
     , pNodeUuid
357 c66f09f5 Iustin Pop
     , pStorageType
358 c66f09f5 Iustin Pop
     , pStorageName
359 c66f09f5 Iustin Pop
     , pIgnoreConsistency
360 34af39e8 Jose A. Lopes
     ],
361 34af39e8 Jose A. Lopes
     "node_name")
362 c66f09f5 Iustin Pop
  , ("OpNodeSetParams",
363 34af39e8 Jose A. Lopes
     [t| [(NonEmptyString, JSValue)] |],
364 34af39e8 Jose A. Lopes
     OpDoc.opNodeSetParams,
365 c66f09f5 Iustin Pop
     [ pNodeName
366 1c3231aa Thomas Thrainer
     , pNodeUuid
367 c66f09f5 Iustin Pop
     , pForce
368 c66f09f5 Iustin Pop
     , pHvState
369 c66f09f5 Iustin Pop
     , pDiskState
370 c66f09f5 Iustin Pop
     , pMasterCandidate
371 34af39e8 Jose A. Lopes
     , withDoc "Whether to mark the node offline" pOffline
372 c66f09f5 Iustin Pop
     , pDrained
373 c66f09f5 Iustin Pop
     , pAutoPromote
374 c66f09f5 Iustin Pop
     , pMasterCapable
375 c66f09f5 Iustin Pop
     , pVmCapable
376 c66f09f5 Iustin Pop
     , pSecondaryIp
377 c66f09f5 Iustin Pop
     , pNdParams
378 67fc4de7 Iustin Pop
     , pPowered
379 34af39e8 Jose A. Lopes
     ],
380 34af39e8 Jose A. Lopes
     "node_name")
381 c66f09f5 Iustin Pop
  , ("OpNodePowercycle",
382 34af39e8 Jose A. Lopes
     [t| Maybe NonEmptyString |],
383 34af39e8 Jose A. Lopes
     OpDoc.opNodePowercycle,
384 c66f09f5 Iustin Pop
     [ pNodeName
385 1c3231aa Thomas Thrainer
     , pNodeUuid
386 c66f09f5 Iustin Pop
     , pForce
387 34af39e8 Jose A. Lopes
     ],
388 34af39e8 Jose A. Lopes
     "node_name")
389 c66f09f5 Iustin Pop
  , ("OpNodeMigrate",
390 34af39e8 Jose A. Lopes
     [t| JobIdListOnly |],
391 34af39e8 Jose A. Lopes
     OpDoc.opNodeMigrate,
392 c66f09f5 Iustin Pop
     [ pNodeName
393 1c3231aa Thomas Thrainer
     , pNodeUuid
394 c66f09f5 Iustin Pop
     , pMigrationMode
395 c66f09f5 Iustin Pop
     , pMigrationLive
396 c66f09f5 Iustin Pop
     , pMigrationTargetNode
397 1c3231aa Thomas Thrainer
     , pMigrationTargetNodeUuid
398 c66f09f5 Iustin Pop
     , pAllowRuntimeChgs
399 c66f09f5 Iustin Pop
     , pIgnoreIpolicy
400 c66f09f5 Iustin Pop
     , pIallocator
401 34af39e8 Jose A. Lopes
     ],
402 34af39e8 Jose A. Lopes
     "node_name")
403 c66f09f5 Iustin Pop
  , ("OpNodeEvacuate",
404 34af39e8 Jose A. Lopes
     [t| JobIdListOnly |],
405 34af39e8 Jose A. Lopes
     OpDoc.opNodeEvacuate,
406 c66f09f5 Iustin Pop
     [ pEarlyRelease
407 c66f09f5 Iustin Pop
     , pNodeName
408 1c3231aa Thomas Thrainer
     , pNodeUuid
409 c66f09f5 Iustin Pop
     , pRemoteNode
410 1c3231aa Thomas Thrainer
     , pRemoteNodeUuid
411 c66f09f5 Iustin Pop
     , pIallocator
412 c66f09f5 Iustin Pop
     , pEvacMode
413 34af39e8 Jose A. Lopes
     ],
414 34af39e8 Jose A. Lopes
     "node_name")
415 6d558717 Iustin Pop
  , ("OpInstanceCreate",
416 34af39e8 Jose A. Lopes
     [t| [NonEmptyString] |],
417 34af39e8 Jose A. Lopes
     OpDoc.opInstanceCreate,
418 6d558717 Iustin Pop
     [ pInstanceName
419 6d558717 Iustin Pop
     , pForceVariant
420 6d558717 Iustin Pop
     , pWaitForSync
421 6d558717 Iustin Pop
     , pNameCheck
422 6d558717 Iustin Pop
     , pIgnoreIpolicy
423 34af39e8 Jose A. Lopes
     , pOpportunisticLocking
424 6d558717 Iustin Pop
     , pInstBeParams
425 6d558717 Iustin Pop
     , pInstDisks
426 7b6996a8 Thomas Thrainer
     , pOptDiskTemplate
427 6d558717 Iustin Pop
     , pFileDriver
428 6d558717 Iustin Pop
     , pFileStorageDir
429 6d558717 Iustin Pop
     , pInstHvParams
430 6d558717 Iustin Pop
     , pHypervisor
431 6d558717 Iustin Pop
     , pIallocator
432 6d558717 Iustin Pop
     , pResetDefaults
433 6d558717 Iustin Pop
     , pIpCheck
434 6d558717 Iustin Pop
     , pIpConflictsCheck
435 6d558717 Iustin Pop
     , pInstCreateMode
436 6d558717 Iustin Pop
     , pInstNics
437 6d558717 Iustin Pop
     , pNoInstall
438 6d558717 Iustin Pop
     , pInstOsParams
439 6d558717 Iustin Pop
     , pInstOs
440 6d558717 Iustin Pop
     , pPrimaryNode
441 1c3231aa Thomas Thrainer
     , pPrimaryNodeUuid
442 6d558717 Iustin Pop
     , pSecondaryNode
443 1c3231aa Thomas Thrainer
     , pSecondaryNodeUuid
444 6d558717 Iustin Pop
     , pSourceHandshake
445 6d558717 Iustin Pop
     , pSourceInstance
446 6d558717 Iustin Pop
     , pSourceShutdownTimeout
447 6d558717 Iustin Pop
     , pSourceX509Ca
448 6d558717 Iustin Pop
     , pSrcNode
449 1c3231aa Thomas Thrainer
     , pSrcNodeUuid
450 6d558717 Iustin Pop
     , pSrcPath
451 6d558717 Iustin Pop
     , pStartInstance
452 6d558717 Iustin Pop
     , pInstTags
453 34af39e8 Jose A. Lopes
     ],
454 34af39e8 Jose A. Lopes
     "instance_name")
455 c2d3219b Iustin Pop
  , ("OpInstanceMultiAlloc",
456 34af39e8 Jose A. Lopes
     [t| InstanceMultiAllocResponse |],
457 34af39e8 Jose A. Lopes
     OpDoc.opInstanceMultiAlloc,
458 34af39e8 Jose A. Lopes
     [ pOpportunisticLocking
459 34af39e8 Jose A. Lopes
     , pIallocator
460 c2d3219b Iustin Pop
     , pMultiAllocInstances
461 34af39e8 Jose A. Lopes
     ],
462 34af39e8 Jose A. Lopes
     [])
463 c2d3219b Iustin Pop
  , ("OpInstanceReinstall",
464 34af39e8 Jose A. Lopes
     [t| () |],
465 34af39e8 Jose A. Lopes
     OpDoc.opInstanceReinstall,
466 c2d3219b Iustin Pop
     [ pInstanceName
467 da4a52a3 Thomas Thrainer
     , pInstanceUuid
468 c2d3219b Iustin Pop
     , pForceVariant
469 c2d3219b Iustin Pop
     , pInstOs
470 c2d3219b Iustin Pop
     , pTempOsParams
471 34af39e8 Jose A. Lopes
     ],
472 34af39e8 Jose A. Lopes
     "instance_name")
473 c2d3219b Iustin Pop
  , ("OpInstanceRemove",
474 34af39e8 Jose A. Lopes
     [t| () |],
475 34af39e8 Jose A. Lopes
     OpDoc.opInstanceRemove,
476 c2d3219b Iustin Pop
     [ pInstanceName
477 da4a52a3 Thomas Thrainer
     , pInstanceUuid
478 c2d3219b Iustin Pop
     , pShutdownTimeout
479 c2d3219b Iustin Pop
     , pIgnoreFailures
480 34af39e8 Jose A. Lopes
     ],
481 34af39e8 Jose A. Lopes
     "instance_name")
482 c2d3219b Iustin Pop
  , ("OpInstanceRename",
483 34af39e8 Jose A. Lopes
     [t| NonEmptyString |],
484 34af39e8 Jose A. Lopes
     OpDoc.opInstanceRename,
485 c2d3219b Iustin Pop
     [ pInstanceName
486 da4a52a3 Thomas Thrainer
     , pInstanceUuid
487 34af39e8 Jose A. Lopes
     , withDoc "New instance name" pNewName
488 c2d3219b Iustin Pop
     , pNameCheck
489 c2d3219b Iustin Pop
     , pIpCheck
490 34af39e8 Jose A. Lopes
     ],
491 34af39e8 Jose A. Lopes
     [])
492 c2d3219b Iustin Pop
  , ("OpInstanceStartup",
493 34af39e8 Jose A. Lopes
     [t| () |],
494 34af39e8 Jose A. Lopes
     OpDoc.opInstanceStartup,
495 c2d3219b Iustin Pop
     [ pInstanceName
496 da4a52a3 Thomas Thrainer
     , pInstanceUuid
497 c2d3219b Iustin Pop
     , pForce
498 c2d3219b Iustin Pop
     , pIgnoreOfflineNodes
499 c2d3219b Iustin Pop
     , pTempHvParams
500 c2d3219b Iustin Pop
     , pTempBeParams
501 c2d3219b Iustin Pop
     , pNoRemember
502 c2d3219b Iustin Pop
     , pStartupPaused
503 34af39e8 Jose A. Lopes
     ],
504 34af39e8 Jose A. Lopes
     "instance_name")
505 c2d3219b Iustin Pop
  , ("OpInstanceShutdown",
506 34af39e8 Jose A. Lopes
     [t| () |],
507 34af39e8 Jose A. Lopes
     OpDoc.opInstanceShutdown,
508 c2d3219b Iustin Pop
     [ pInstanceName
509 da4a52a3 Thomas Thrainer
     , pInstanceUuid
510 0d57ce24 Guido Trotter
     , pForce
511 c2d3219b Iustin Pop
     , pIgnoreOfflineNodes
512 5cbf7832 Jose A. Lopes
     , pShutdownTimeout'
513 c2d3219b Iustin Pop
     , pNoRemember
514 34af39e8 Jose A. Lopes
     ],
515 34af39e8 Jose A. Lopes
     "instance_name")
516 c2d3219b Iustin Pop
  , ("OpInstanceReboot",
517 34af39e8 Jose A. Lopes
     [t| () |],
518 34af39e8 Jose A. Lopes
     OpDoc.opInstanceReboot,
519 c2d3219b Iustin Pop
     [ pInstanceName
520 da4a52a3 Thomas Thrainer
     , pInstanceUuid
521 c2d3219b Iustin Pop
     , pShutdownTimeout
522 c2d3219b Iustin Pop
     , pIgnoreSecondaries
523 c2d3219b Iustin Pop
     , pRebootType
524 34af39e8 Jose A. Lopes
     ],
525 34af39e8 Jose A. Lopes
     "instance_name")
526 34af39e8 Jose A. Lopes
  , ("OpInstanceReplaceDisks",
527 34af39e8 Jose A. Lopes
     [t| () |],
528 34af39e8 Jose A. Lopes
     OpDoc.opInstanceReplaceDisks,
529 34af39e8 Jose A. Lopes
     [ pInstanceName
530 34af39e8 Jose A. Lopes
     , pInstanceUuid
531 34af39e8 Jose A. Lopes
     , pEarlyRelease
532 34af39e8 Jose A. Lopes
     , pIgnoreIpolicy
533 34af39e8 Jose A. Lopes
     , pReplaceDisksMode
534 34af39e8 Jose A. Lopes
     , pReplaceDisksList
535 34af39e8 Jose A. Lopes
     , pRemoteNode
536 34af39e8 Jose A. Lopes
     , pRemoteNodeUuid
537 34af39e8 Jose A. Lopes
     , pIallocator
538 34af39e8 Jose A. Lopes
     ],
539 34af39e8 Jose A. Lopes
     "instance_name")
540 34af39e8 Jose A. Lopes
  , ("OpInstanceFailover",
541 34af39e8 Jose A. Lopes
     [t| () |],
542 34af39e8 Jose A. Lopes
     OpDoc.opInstanceFailover,
543 34af39e8 Jose A. Lopes
     [ pInstanceName
544 34af39e8 Jose A. Lopes
     , pInstanceUuid
545 34af39e8 Jose A. Lopes
     , pShutdownTimeout
546 34af39e8 Jose A. Lopes
     , pIgnoreConsistency
547 34af39e8 Jose A. Lopes
     , pMigrationTargetNode
548 34af39e8 Jose A. Lopes
     , pMigrationTargetNodeUuid
549 34af39e8 Jose A. Lopes
     , pIgnoreIpolicy
550 1ca326c8 Thomas Thrainer
     , pMigrationCleanup
551 34af39e8 Jose A. Lopes
     , pIallocator
552 34af39e8 Jose A. Lopes
     ],
553 34af39e8 Jose A. Lopes
     "instance_name")
554 34af39e8 Jose A. Lopes
  , ("OpInstanceMigrate",
555 34af39e8 Jose A. Lopes
     [t| () |],
556 34af39e8 Jose A. Lopes
     OpDoc.opInstanceMigrate,
557 34af39e8 Jose A. Lopes
     [ pInstanceName
558 34af39e8 Jose A. Lopes
     , pInstanceUuid
559 34af39e8 Jose A. Lopes
     , pMigrationMode
560 34af39e8 Jose A. Lopes
     , pMigrationLive
561 34af39e8 Jose A. Lopes
     , pMigrationTargetNode
562 34af39e8 Jose A. Lopes
     , pMigrationTargetNodeUuid
563 34af39e8 Jose A. Lopes
     , pAllowRuntimeChgs
564 34af39e8 Jose A. Lopes
     , pIgnoreIpolicy
565 34af39e8 Jose A. Lopes
     , pMigrationCleanup
566 34af39e8 Jose A. Lopes
     , pIallocator
567 34af39e8 Jose A. Lopes
     , pAllowFailover
568 34af39e8 Jose A. Lopes
     ],
569 34af39e8 Jose A. Lopes
     "instance_name")
570 c2d3219b Iustin Pop
  , ("OpInstanceMove",
571 34af39e8 Jose A. Lopes
     [t| () |],
572 34af39e8 Jose A. Lopes
     OpDoc.opInstanceMove,
573 c2d3219b Iustin Pop
     [ pInstanceName
574 da4a52a3 Thomas Thrainer
     , pInstanceUuid
575 c2d3219b Iustin Pop
     , pShutdownTimeout
576 c2d3219b Iustin Pop
     , pIgnoreIpolicy
577 c2d3219b Iustin Pop
     , pMoveTargetNode
578 1c3231aa Thomas Thrainer
     , pMoveTargetNodeUuid
579 c2d3219b Iustin Pop
     , pIgnoreConsistency
580 34af39e8 Jose A. Lopes
     ],
581 34af39e8 Jose A. Lopes
     "instance_name")
582 c2d3219b Iustin Pop
  , ("OpInstanceConsole",
583 34af39e8 Jose A. Lopes
     [t| JSObject JSValue |],
584 34af39e8 Jose A. Lopes
     OpDoc.opInstanceConsole,
585 da4a52a3 Thomas Thrainer
     [ pInstanceName
586 da4a52a3 Thomas Thrainer
     , pInstanceUuid
587 34af39e8 Jose A. Lopes
     ],
588 34af39e8 Jose A. Lopes
     "instance_name")
589 c2d3219b Iustin Pop
  , ("OpInstanceActivateDisks",
590 34af39e8 Jose A. Lopes
     [t| [(NonEmptyString, NonEmptyString, NonEmptyString)] |],
591 34af39e8 Jose A. Lopes
     OpDoc.opInstanceActivateDisks,
592 c2d3219b Iustin Pop
     [ pInstanceName
593 da4a52a3 Thomas Thrainer
     , pInstanceUuid
594 c2d3219b Iustin Pop
     , pIgnoreDiskSize
595 c2d3219b Iustin Pop
     , pWaitForSyncFalse
596 34af39e8 Jose A. Lopes
     ],
597 34af39e8 Jose A. Lopes
     "instance_name")
598 c2d3219b Iustin Pop
  , ("OpInstanceDeactivateDisks",
599 34af39e8 Jose A. Lopes
     [t| () |],
600 34af39e8 Jose A. Lopes
     OpDoc.opInstanceDeactivateDisks,
601 c2d3219b Iustin Pop
     [ pInstanceName
602 da4a52a3 Thomas Thrainer
     , pInstanceUuid
603 c2d3219b Iustin Pop
     , pForce
604 34af39e8 Jose A. Lopes
     ],
605 34af39e8 Jose A. Lopes
     "instance_name")
606 c2d3219b Iustin Pop
  , ("OpInstanceRecreateDisks",
607 34af39e8 Jose A. Lopes
     [t| () |],
608 34af39e8 Jose A. Lopes
     OpDoc.opInstanceRecreateDisks,
609 c2d3219b Iustin Pop
     [ pInstanceName
610 da4a52a3 Thomas Thrainer
     , pInstanceUuid
611 c2d3219b Iustin Pop
     , pRecreateDisksInfo
612 34af39e8 Jose A. Lopes
     , withDoc "New instance nodes, if relocation is desired" pNodes
613 34af39e8 Jose A. Lopes
     , withDoc "New instance node UUIDs, if relocation is desired" pNodeUuids
614 c2d3219b Iustin Pop
     , pIallocator
615 34af39e8 Jose A. Lopes
     ],
616 34af39e8 Jose A. Lopes
     "instance_name")
617 34af39e8 Jose A. Lopes
  , ("OpInstanceQuery",
618 34af39e8 Jose A. Lopes
     [t| [[JSValue]] |],
619 34af39e8 Jose A. Lopes
     OpDoc.opInstanceQuery,
620 34af39e8 Jose A. Lopes
     [ pOutputFields
621 34af39e8 Jose A. Lopes
     , pUseLocking
622 34af39e8 Jose A. Lopes
     , withDoc
623 34af39e8 Jose A. Lopes
       "Empty list to query all instances, instance names otherwise"
624 34af39e8 Jose A. Lopes
       pNames
625 34af39e8 Jose A. Lopes
     ],
626 34af39e8 Jose A. Lopes
     [])
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 c2d3219b Iustin Pop
     , pWaitForSync
658 34af39e8 Jose A. Lopes
     , withDoc "Whether to mark the instance as offline" pOffline
659 c2d3219b Iustin Pop
     , pIpConflictsCheck
660 34af39e8 Jose A. Lopes
     ],
661 34af39e8 Jose A. Lopes
     "instance_name")
662 c2d3219b Iustin Pop
  , ("OpInstanceGrowDisk",
663 34af39e8 Jose A. Lopes
     [t| () |],
664 34af39e8 Jose A. Lopes
     OpDoc.opInstanceGrowDisk,
665 c2d3219b Iustin Pop
     [ pInstanceName
666 da4a52a3 Thomas Thrainer
     , pInstanceUuid
667 c2d3219b Iustin Pop
     , pWaitForSync
668 c2d3219b Iustin Pop
     , pDiskIndex
669 c2d3219b Iustin Pop
     , pDiskChgAmount
670 c2d3219b Iustin Pop
     , pDiskChgAbsolute
671 34af39e8 Jose A. Lopes
     ],
672 34af39e8 Jose A. Lopes
     "instance_name")
673 c2d3219b Iustin Pop
  , ("OpInstanceChangeGroup",
674 34af39e8 Jose A. Lopes
     [t| JobIdListOnly |],
675 34af39e8 Jose A. Lopes
     OpDoc.opInstanceChangeGroup,
676 c2d3219b Iustin Pop
     [ pInstanceName
677 da4a52a3 Thomas Thrainer
     , pInstanceUuid
678 c2d3219b Iustin Pop
     , pEarlyRelease
679 c2d3219b Iustin Pop
     , pIallocator
680 c2d3219b Iustin Pop
     , pTargetGroups
681 34af39e8 Jose A. Lopes
     ],
682 34af39e8 Jose A. Lopes
     "instance_name")
683 398e9066 Iustin Pop
  , ("OpGroupAdd",
684 34af39e8 Jose A. Lopes
     [t| () |],
685 34af39e8 Jose A. Lopes
     OpDoc.opGroupAdd,
686 398e9066 Iustin Pop
     [ pGroupName
687 398e9066 Iustin Pop
     , pNodeGroupAllocPolicy
688 398e9066 Iustin Pop
     , pGroupNodeParams
689 398e9066 Iustin Pop
     , pDiskParams
690 398e9066 Iustin Pop
     , pHvState
691 398e9066 Iustin Pop
     , pDiskState
692 34af39e8 Jose A. Lopes
     , withDoc "Group-wide ipolicy specs" pIpolicy
693 34af39e8 Jose A. Lopes
     ],
694 34af39e8 Jose A. Lopes
     "group_name")
695 398e9066 Iustin Pop
  , ("OpGroupAssignNodes",
696 34af39e8 Jose A. Lopes
     [t| () |],
697 34af39e8 Jose A. Lopes
     OpDoc.opGroupAssignNodes,
698 398e9066 Iustin Pop
     [ pGroupName
699 398e9066 Iustin Pop
     , pForce
700 34af39e8 Jose A. Lopes
     , withDoc "List of nodes to assign" pRequiredNodes
701 34af39e8 Jose A. Lopes
     , withDoc "List of node UUIDs to assign" pRequiredNodeUuids
702 34af39e8 Jose A. Lopes
     ],
703 34af39e8 Jose A. Lopes
     "group_name")
704 34af39e8 Jose A. Lopes
  , ("OpGroupQuery",
705 34af39e8 Jose A. Lopes
     [t| [[JSValue]] |],
706 34af39e8 Jose A. Lopes
     OpDoc.opGroupQuery,
707 34af39e8 Jose A. Lopes
     [ pOutputFields
708 34af39e8 Jose A. Lopes
     , withDoc "Empty list to query all groups, group names otherwise" pNames
709 34af39e8 Jose A. Lopes
     ],
710 34af39e8 Jose A. Lopes
     [])
711 398e9066 Iustin Pop
  , ("OpGroupSetParams",
712 34af39e8 Jose A. Lopes
     [t| [(NonEmptyString, JSValue)] |],
713 34af39e8 Jose A. Lopes
     OpDoc.opGroupSetParams,
714 398e9066 Iustin Pop
     [ pGroupName
715 398e9066 Iustin Pop
     , pNodeGroupAllocPolicy
716 398e9066 Iustin Pop
     , pGroupNodeParams
717 398e9066 Iustin Pop
     , pDiskParams
718 398e9066 Iustin Pop
     , pHvState
719 398e9066 Iustin Pop
     , pDiskState
720 34af39e8 Jose A. Lopes
     , withDoc "Group-wide ipolicy specs" pIpolicy
721 34af39e8 Jose A. Lopes
     ],
722 34af39e8 Jose A. Lopes
     "group_name")
723 398e9066 Iustin Pop
  , ("OpGroupRemove",
724 34af39e8 Jose A. Lopes
     [t| () |],
725 34af39e8 Jose A. Lopes
     OpDoc.opGroupRemove,
726 34af39e8 Jose A. Lopes
     [ pGroupName
727 34af39e8 Jose A. Lopes
     ],
728 34af39e8 Jose A. Lopes
     "group_name")
729 398e9066 Iustin Pop
  , ("OpGroupRename",
730 34af39e8 Jose A. Lopes
     [t| NonEmptyString |],
731 34af39e8 Jose A. Lopes
     OpDoc.opGroupRename,
732 398e9066 Iustin Pop
     [ pGroupName
733 34af39e8 Jose A. Lopes
     , withDoc "New group name" pNewName
734 34af39e8 Jose A. Lopes
     ],
735 34af39e8 Jose A. Lopes
     [])
736 398e9066 Iustin Pop
  , ("OpGroupEvacuate",
737 34af39e8 Jose A. Lopes
     [t| JobIdListOnly |],
738 34af39e8 Jose A. Lopes
     OpDoc.opGroupEvacuate,
739 398e9066 Iustin Pop
     [ pGroupName
740 398e9066 Iustin Pop
     , pEarlyRelease
741 398e9066 Iustin Pop
     , pIallocator
742 398e9066 Iustin Pop
     , pTargetGroups
743 34af39e8 Jose A. Lopes
     ],
744 34af39e8 Jose A. Lopes
     "group_name")
745 398e9066 Iustin Pop
  , ("OpOsDiagnose",
746 34af39e8 Jose A. Lopes
     [t| [[JSValue]] |],
747 34af39e8 Jose A. Lopes
     OpDoc.opOsDiagnose,
748 398e9066 Iustin Pop
     [ pOutputFields
749 34af39e8 Jose A. Lopes
     , withDoc "Which operating systems to diagnose" pNames
750 34af39e8 Jose A. Lopes
     ],
751 34af39e8 Jose A. Lopes
     [])
752 b954f097 Constantinos Venetsanopoulos
  , ("OpExtStorageDiagnose",
753 34af39e8 Jose A. Lopes
     [t| [[JSValue]] |],
754 34af39e8 Jose A. Lopes
     OpDoc.opExtStorageDiagnose,
755 b954f097 Constantinos Venetsanopoulos
     [ pOutputFields
756 34af39e8 Jose A. Lopes
     , withDoc "Which ExtStorage Provider to diagnose" pNames
757 34af39e8 Jose A. Lopes
     ],
758 34af39e8 Jose A. Lopes
     [])
759 398e9066 Iustin Pop
  , ("OpBackupQuery",
760 34af39e8 Jose A. Lopes
     [t| JSObject (Either Bool [NonEmptyString]) |],
761 34af39e8 Jose A. Lopes
     OpDoc.opBackupQuery,
762 398e9066 Iustin Pop
     [ pUseLocking
763 34af39e8 Jose A. Lopes
     , withDoc "Empty list to query all nodes, node names otherwise" pNodes
764 34af39e8 Jose A. Lopes
     ],
765 34af39e8 Jose A. Lopes
     [])
766 398e9066 Iustin Pop
  , ("OpBackupPrepare",
767 34af39e8 Jose A. Lopes
     [t| Maybe (JSObject JSValue) |],
768 34af39e8 Jose A. Lopes
     OpDoc.opBackupPrepare,
769 398e9066 Iustin Pop
     [ pInstanceName
770 da4a52a3 Thomas Thrainer
     , pInstanceUuid
771 398e9066 Iustin Pop
     , pExportMode
772 34af39e8 Jose A. Lopes
     ],
773 34af39e8 Jose A. Lopes
     "instance_name")
774 398e9066 Iustin Pop
  , ("OpBackupExport",
775 34af39e8 Jose A. Lopes
     [t| (Bool, [Bool]) |],
776 34af39e8 Jose A. Lopes
     OpDoc.opBackupExport,
777 398e9066 Iustin Pop
     [ pInstanceName
778 da4a52a3 Thomas Thrainer
     , pInstanceUuid
779 398e9066 Iustin Pop
     , pShutdownTimeout
780 398e9066 Iustin Pop
     , pExportTargetNode
781 1c3231aa Thomas Thrainer
     , pExportTargetNodeUuid
782 67fc4de7 Iustin Pop
     , pShutdownInstance
783 398e9066 Iustin Pop
     , pRemoveInstance
784 398e9066 Iustin Pop
     , pIgnoreRemoveFailures
785 34af39e8 Jose A. Lopes
     , defaultField [| ExportModeLocal |] pExportMode
786 398e9066 Iustin Pop
     , pX509KeyName
787 398e9066 Iustin Pop
     , pX509DestCA
788 34af39e8 Jose A. Lopes
     ],
789 34af39e8 Jose A. Lopes
     "instance_name")
790 398e9066 Iustin Pop
  , ("OpBackupRemove",
791 34af39e8 Jose A. Lopes
     [t| () |],
792 34af39e8 Jose A. Lopes
     OpDoc.opBackupRemove,
793 da4a52a3 Thomas Thrainer
     [ pInstanceName
794 da4a52a3 Thomas Thrainer
     , pInstanceUuid
795 34af39e8 Jose A. Lopes
     ],
796 34af39e8 Jose A. Lopes
     "instance_name")
797 34af39e8 Jose A. Lopes
  , ("OpTagsGet",
798 34af39e8 Jose A. Lopes
     [t| [NonEmptyString] |],
799 34af39e8 Jose A. Lopes
     OpDoc.opTagsGet,
800 34af39e8 Jose A. Lopes
     [ pTagsObject
801 34af39e8 Jose A. Lopes
     , pUseLocking
802 34af39e8 Jose A. Lopes
     , withDoc "Name of object to retrieve tags from" pTagsName
803 34af39e8 Jose A. Lopes
     ],
804 34af39e8 Jose A. Lopes
     "name")
805 34af39e8 Jose A. Lopes
  , ("OpTagsSearch",
806 34af39e8 Jose A. Lopes
     [t| [(NonEmptyString, NonEmptyString)] |],
807 34af39e8 Jose A. Lopes
     OpDoc.opTagsSearch,
808 34af39e8 Jose A. Lopes
     [ pTagSearchPattern
809 34af39e8 Jose A. Lopes
     ],
810 34af39e8 Jose A. Lopes
     "pattern")
811 34af39e8 Jose A. Lopes
  , ("OpTagsSet",
812 34af39e8 Jose A. Lopes
     [t| () |],
813 34af39e8 Jose A. Lopes
     OpDoc.opTagsSet,
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 added" pTagsName
817 34af39e8 Jose A. Lopes
     ],
818 34af39e8 Jose A. Lopes
     [])
819 34af39e8 Jose A. Lopes
  , ("OpTagsDel",
820 34af39e8 Jose A. Lopes
     [t| () |],
821 34af39e8 Jose A. Lopes
     OpDoc.opTagsDel,
822 34af39e8 Jose A. Lopes
     [ pTagsObject
823 34af39e8 Jose A. Lopes
     , pTagsList
824 34af39e8 Jose A. Lopes
     , withDoc "Name of object where tag(s) should be deleted" pTagsName
825 34af39e8 Jose A. Lopes
     ],
826 34af39e8 Jose A. Lopes
     [])
827 34af39e8 Jose A. Lopes
  , ("OpTestDelay",
828 34af39e8 Jose A. Lopes
     [t| () |],
829 34af39e8 Jose A. Lopes
     OpDoc.opTestDelay,
830 34af39e8 Jose A. Lopes
     [ pDelayDuration
831 34af39e8 Jose A. Lopes
     , pDelayOnMaster
832 34af39e8 Jose A. Lopes
     , pDelayOnNodes
833 34af39e8 Jose A. Lopes
     , pDelayOnNodeUuids
834 34af39e8 Jose A. Lopes
     , pDelayRepeat
835 34af39e8 Jose A. Lopes
     ],
836 34af39e8 Jose A. Lopes
     "duration")
837 a3f02317 Iustin Pop
  , ("OpTestAllocator",
838 5cbf7832 Jose A. Lopes
     [t| String |],
839 34af39e8 Jose A. Lopes
     OpDoc.opTestAllocator,
840 a3f02317 Iustin Pop
     [ pIAllocatorDirection
841 a3f02317 Iustin Pop
     , pIAllocatorMode
842 a3f02317 Iustin Pop
     , pIAllocatorReqName
843 a3f02317 Iustin Pop
     , pIAllocatorNics
844 a3f02317 Iustin Pop
     , pIAllocatorDisks
845 a3f02317 Iustin Pop
     , pHypervisor
846 a3f02317 Iustin Pop
     , pIallocator
847 a3f02317 Iustin Pop
     , pInstTags
848 a3f02317 Iustin Pop
     , pIAllocatorMemory
849 a3f02317 Iustin Pop
     , pIAllocatorVCpus
850 a3f02317 Iustin Pop
     , pIAllocatorOs
851 a3f02317 Iustin Pop
     , pDiskTemplate
852 a3f02317 Iustin Pop
     , pIAllocatorInstances
853 a3f02317 Iustin Pop
     , pIAllocatorEvacMode
854 a3f02317 Iustin Pop
     , pTargetGroups
855 a3f02317 Iustin Pop
     , pIAllocatorSpindleUse
856 a3f02317 Iustin Pop
     , pIAllocatorCount
857 34af39e8 Jose A. Lopes
     ],
858 34af39e8 Jose A. Lopes
     "iallocator")
859 a3f02317 Iustin Pop
  , ("OpTestJqueue",
860 5cbf7832 Jose A. Lopes
     [t| Bool |],
861 34af39e8 Jose A. Lopes
     OpDoc.opTestJqueue,
862 a3f02317 Iustin Pop
     [ pJQueueNotifyWaitLock
863 a3f02317 Iustin Pop
     , pJQueueNotifyExec
864 a3f02317 Iustin Pop
     , pJQueueLogMessages
865 a3f02317 Iustin Pop
     , pJQueueFail
866 34af39e8 Jose A. Lopes
     ],
867 34af39e8 Jose A. Lopes
     [])
868 a3f02317 Iustin Pop
  , ("OpTestDummy",
869 34af39e8 Jose A. Lopes
     [t| () |],
870 34af39e8 Jose A. Lopes
     OpDoc.opTestDummy,
871 a3f02317 Iustin Pop
     [ pTestDummyResult
872 a3f02317 Iustin Pop
     , pTestDummyMessages
873 a3f02317 Iustin Pop
     , pTestDummyFail
874 a3f02317 Iustin Pop
     , pTestDummySubmitJobs
875 34af39e8 Jose A. Lopes
     ],
876 34af39e8 Jose A. Lopes
     [])
877 8d239fa4 Iustin Pop
  , ("OpNetworkAdd",
878 34af39e8 Jose A. Lopes
     [t| () |],
879 34af39e8 Jose A. Lopes
     OpDoc.opNetworkAdd,
880 8d239fa4 Iustin Pop
     [ pNetworkName
881 8d239fa4 Iustin Pop
     , pNetworkAddress4
882 8d239fa4 Iustin Pop
     , pNetworkGateway4
883 8d239fa4 Iustin Pop
     , pNetworkAddress6
884 8d239fa4 Iustin Pop
     , pNetworkGateway6
885 8d239fa4 Iustin Pop
     , pNetworkMacPrefix
886 8d239fa4 Iustin Pop
     , pNetworkAddRsvdIps
887 1dbceab9 Iustin Pop
     , pIpConflictsCheck
888 34af39e8 Jose A. Lopes
     , withDoc "Network tags" pInstTags
889 34af39e8 Jose A. Lopes
     ],
890 34af39e8 Jose A. Lopes
     "network_name")
891 8d239fa4 Iustin Pop
  , ("OpNetworkRemove",
892 34af39e8 Jose A. Lopes
     [t| () |],
893 34af39e8 Jose A. Lopes
     OpDoc.opNetworkRemove,
894 8d239fa4 Iustin Pop
     [ pNetworkName
895 8d239fa4 Iustin Pop
     , pForce
896 34af39e8 Jose A. Lopes
     ],
897 34af39e8 Jose A. Lopes
     "network_name")
898 8d239fa4 Iustin Pop
  , ("OpNetworkSetParams",
899 34af39e8 Jose A. Lopes
     [t| () |],
900 34af39e8 Jose A. Lopes
     OpDoc.opNetworkSetParams,
901 8d239fa4 Iustin Pop
     [ pNetworkName
902 8d239fa4 Iustin Pop
     , pNetworkGateway4
903 8d239fa4 Iustin Pop
     , pNetworkAddress6
904 8d239fa4 Iustin Pop
     , pNetworkGateway6
905 8d239fa4 Iustin Pop
     , pNetworkMacPrefix
906 34af39e8 Jose A. Lopes
     , withDoc "Which external IP addresses to reserve" pNetworkAddRsvdIps
907 8d239fa4 Iustin Pop
     , pNetworkRemoveRsvdIps
908 34af39e8 Jose A. Lopes
     ],
909 34af39e8 Jose A. Lopes
     "network_name")
910 8d239fa4 Iustin Pop
  , ("OpNetworkConnect",
911 34af39e8 Jose A. Lopes
     [t| () |],
912 34af39e8 Jose A. Lopes
     OpDoc.opNetworkConnect,
913 8d239fa4 Iustin Pop
     [ pGroupName
914 8d239fa4 Iustin Pop
     , pNetworkName
915 8d239fa4 Iustin Pop
     , pNetworkMode
916 8d239fa4 Iustin Pop
     , pNetworkLink
917 8d239fa4 Iustin Pop
     , pIpConflictsCheck
918 34af39e8 Jose A. Lopes
     ],
919 34af39e8 Jose A. Lopes
     "network_name")
920 8d239fa4 Iustin Pop
  , ("OpNetworkDisconnect",
921 34af39e8 Jose A. Lopes
     [t| () |],
922 34af39e8 Jose A. Lopes
     OpDoc.opNetworkDisconnect,
923 8d239fa4 Iustin Pop
     [ pGroupName
924 8d239fa4 Iustin Pop
     , pNetworkName
925 34af39e8 Jose A. Lopes
     ],
926 34af39e8 Jose A. Lopes
     "network_name")
927 34af39e8 Jose A. Lopes
  , ("OpNetworkQuery",
928 34af39e8 Jose A. Lopes
     [t| [[JSValue]] |],
929 34af39e8 Jose A. Lopes
     OpDoc.opNetworkQuery,
930 34af39e8 Jose A. Lopes
     [ pOutputFields
931 34af39e8 Jose A. Lopes
     , pUseLocking
932 34af39e8 Jose A. Lopes
     , withDoc "Empty list to query all groups, group names otherwise" pNames
933 34af39e8 Jose A. Lopes
     ],
934 34af39e8 Jose A. Lopes
     [])
935 ebf38064 Iustin Pop
  ])
936 12c19659 Iustin Pop
937 a583ec5d Iustin Pop
-- | Returns the OP_ID for a given opcode value.
938 12c19659 Iustin Pop
$(genOpID ''OpCode "opID")
939 702a4ee0 Iustin Pop
940 a583ec5d Iustin Pop
-- | A list of all defined/supported opcode IDs.
941 a583ec5d Iustin Pop
$(genAllOpIDs ''OpCode "allOpIDs")
942 a583ec5d Iustin Pop
943 702a4ee0 Iustin Pop
instance JSON OpCode where
944 ebf38064 Iustin Pop
  readJSON = loadOpCode
945 ebf38064 Iustin Pop
  showJSON = saveOpCode
946 4a826364 Iustin Pop
947 ad1c1e41 Iustin Pop
-- | Generates the summary value for an opcode.
948 ad1c1e41 Iustin Pop
opSummaryVal :: OpCode -> Maybe String
949 ad1c1e41 Iustin Pop
opSummaryVal OpClusterVerifyGroup { opGroupName = s } = Just (fromNonEmpty s)
950 ad1c1e41 Iustin Pop
opSummaryVal OpGroupVerifyDisks { opGroupName = s } = Just (fromNonEmpty s)
951 ad1c1e41 Iustin Pop
opSummaryVal OpClusterRename { opName = s } = Just (fromNonEmpty s)
952 ad1c1e41 Iustin Pop
opSummaryVal OpQuery { opWhat = s } = Just (queryTypeOpToRaw s)
953 ad1c1e41 Iustin Pop
opSummaryVal OpQueryFields { opWhat = s } = Just (queryTypeOpToRaw s)
954 ad1c1e41 Iustin Pop
opSummaryVal OpNodeRemove { opNodeName = s } = Just (fromNonEmpty s)
955 ad1c1e41 Iustin Pop
opSummaryVal OpNodeAdd { opNodeName = s } = Just (fromNonEmpty s)
956 ad1c1e41 Iustin Pop
opSummaryVal OpNodeModifyStorage { opNodeName = s } = Just (fromNonEmpty s)
957 ad1c1e41 Iustin Pop
opSummaryVal OpRepairNodeStorage  { opNodeName = s } = Just (fromNonEmpty s)
958 ad1c1e41 Iustin Pop
opSummaryVal OpNodeSetParams { opNodeName = s } = Just (fromNonEmpty s)
959 ad1c1e41 Iustin Pop
opSummaryVal OpNodePowercycle { opNodeName = s } = Just (fromNonEmpty s)
960 ad1c1e41 Iustin Pop
opSummaryVal OpNodeMigrate { opNodeName = s } = Just (fromNonEmpty s)
961 ad1c1e41 Iustin Pop
opSummaryVal OpNodeEvacuate { opNodeName = s } = Just (fromNonEmpty s)
962 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceCreate { opInstanceName = s } = Just s
963 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceReinstall { opInstanceName = s } = Just s
964 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceRemove { opInstanceName = s } = Just s
965 ad1c1e41 Iustin Pop
-- FIXME: instance rename should show both names; currently it shows none
966 ad1c1e41 Iustin Pop
-- opSummaryVal OpInstanceRename { opInstanceName = s } = Just s
967 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceStartup { opInstanceName = s } = Just s
968 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceShutdown { opInstanceName = s } = Just s
969 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceReboot { opInstanceName = s } = Just s
970 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceReplaceDisks { opInstanceName = s } = Just s
971 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceFailover { opInstanceName = s } = Just s
972 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceMigrate { opInstanceName = s } = Just s
973 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceMove { opInstanceName = s } = Just s
974 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceConsole { opInstanceName = s } = Just s
975 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceActivateDisks { opInstanceName = s } = Just s
976 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceDeactivateDisks { opInstanceName = s } = Just s
977 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceRecreateDisks { opInstanceName = s } = Just s
978 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceSetParams { opInstanceName = s } = Just s
979 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceGrowDisk { opInstanceName = s } = Just s
980 ad1c1e41 Iustin Pop
opSummaryVal OpInstanceChangeGroup { opInstanceName = s } = Just s
981 ad1c1e41 Iustin Pop
opSummaryVal OpGroupAdd { opGroupName = s } = Just (fromNonEmpty s)
982 ad1c1e41 Iustin Pop
opSummaryVal OpGroupAssignNodes { opGroupName = s } = Just (fromNonEmpty s)
983 ad1c1e41 Iustin Pop
opSummaryVal OpGroupSetParams { opGroupName = s } = Just (fromNonEmpty s)
984 ad1c1e41 Iustin Pop
opSummaryVal OpGroupRemove { opGroupName = s } = Just (fromNonEmpty s)
985 ad1c1e41 Iustin Pop
opSummaryVal OpGroupEvacuate { opGroupName = s } = Just (fromNonEmpty s)
986 ad1c1e41 Iustin Pop
opSummaryVal OpBackupPrepare { opInstanceName = s } = Just s
987 ad1c1e41 Iustin Pop
opSummaryVal OpBackupExport { opInstanceName = s } = Just s
988 ad1c1e41 Iustin Pop
opSummaryVal OpBackupRemove { opInstanceName = s } = Just s
989 34af39e8 Jose A. Lopes
opSummaryVal OpTagsGet { opKind = s } = Just (show s)
990 ad1c1e41 Iustin Pop
opSummaryVal OpTagsSearch { opTagSearchPattern = s } = Just (fromNonEmpty s)
991 ad1c1e41 Iustin Pop
opSummaryVal OpTestDelay { opDelayDuration = d } = Just (show d)
992 ad1c1e41 Iustin Pop
opSummaryVal OpTestAllocator { opIallocator = s } =
993 ad1c1e41 Iustin Pop
  -- FIXME: Python doesn't handle None fields well, so we have behave the same
994 ad1c1e41 Iustin Pop
  Just $ maybe "None" fromNonEmpty s
995 ad1c1e41 Iustin Pop
opSummaryVal OpNetworkAdd { opNetworkName = s} = Just (fromNonEmpty s)
996 ad1c1e41 Iustin Pop
opSummaryVal OpNetworkRemove { opNetworkName = s} = Just (fromNonEmpty s)
997 ad1c1e41 Iustin Pop
opSummaryVal OpNetworkSetParams { opNetworkName = s} = Just (fromNonEmpty s)
998 ad1c1e41 Iustin Pop
opSummaryVal OpNetworkConnect { opNetworkName = s} = Just (fromNonEmpty s)
999 ad1c1e41 Iustin Pop
opSummaryVal OpNetworkDisconnect { opNetworkName = s} = Just (fromNonEmpty s)
1000 ad1c1e41 Iustin Pop
opSummaryVal _ = Nothing
1001 ad1c1e41 Iustin Pop
1002 ad1c1e41 Iustin Pop
-- | Computes the summary of the opcode.
1003 ad1c1e41 Iustin Pop
opSummary :: OpCode -> String
1004 ad1c1e41 Iustin Pop
opSummary op =
1005 ad1c1e41 Iustin Pop
  case opSummaryVal op of
1006 ad1c1e41 Iustin Pop
    Nothing -> op_suffix
1007 ad1c1e41 Iustin Pop
    Just s -> op_suffix ++ "(" ++ s ++ ")"
1008 ad1c1e41 Iustin Pop
  where op_suffix = drop 3 $ opID op
1009 ad1c1e41 Iustin Pop
1010 4a826364 Iustin Pop
-- | Generic\/common opcode parameters.
1011 4a826364 Iustin Pop
$(buildObject "CommonOpParams" "op"
1012 4a826364 Iustin Pop
  [ pDryRun
1013 4a826364 Iustin Pop
  , pDebugLevel
1014 4a826364 Iustin Pop
  , pOpPriority
1015 4a826364 Iustin Pop
  , pDependencies
1016 4a826364 Iustin Pop
  , pComment
1017 516a0e94 Michele Tartara
  , pReason
1018 4a826364 Iustin Pop
  ])
1019 4a826364 Iustin Pop
1020 4a826364 Iustin Pop
-- | Default common parameter values.
1021 4a826364 Iustin Pop
defOpParams :: CommonOpParams
1022 4a826364 Iustin Pop
defOpParams =
1023 4a826364 Iustin Pop
  CommonOpParams { opDryRun     = Nothing
1024 4a826364 Iustin Pop
                 , opDebugLevel = Nothing
1025 4a826364 Iustin Pop
                 , opPriority   = OpPrioNormal
1026 4a826364 Iustin Pop
                 , opDepends    = Nothing
1027 4a826364 Iustin Pop
                 , opComment    = Nothing
1028 516a0e94 Michele Tartara
                 , opReason     = []
1029 4a826364 Iustin Pop
                 }
1030 4a826364 Iustin Pop
1031 4a826364 Iustin Pop
-- | The top-level opcode type.
1032 ad1c1e41 Iustin Pop
data MetaOpCode = MetaOpCode { metaParams :: CommonOpParams
1033 ad1c1e41 Iustin Pop
                             , metaOpCode :: OpCode
1034 ad1c1e41 Iustin Pop
                             } deriving (Show, Eq)
1035 4a826364 Iustin Pop
1036 4a826364 Iustin Pop
-- | JSON serialisation for 'MetaOpCode'.
1037 4a826364 Iustin Pop
showMeta :: MetaOpCode -> JSValue
1038 4a826364 Iustin Pop
showMeta (MetaOpCode params op) =
1039 4a826364 Iustin Pop
  let objparams = toDictCommonOpParams 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