Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpCodes.hs @ 5cbf7832

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