Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ 1c3231aa

History | View | Annotate | Download (44.6 kB)

1 92f51573 Iustin Pop
{-# LANGUAGE TemplateHaskell #-}
2 92f51573 Iustin Pop
3 92f51573 Iustin Pop
{-| Implementation of opcodes parameters.
4 92f51573 Iustin Pop
5 92f51573 Iustin Pop
These are defined in a separate module only due to TemplateHaskell
6 92f51573 Iustin Pop
stage restrictions - expressions defined in the current module can't
7 92f51573 Iustin Pop
be passed to splices. So we have to either parameters/repeat each
8 92f51573 Iustin Pop
parameter definition multiple times, or separate them into this
9 92f51573 Iustin Pop
module.
10 92f51573 Iustin Pop
11 92f51573 Iustin Pop
-}
12 92f51573 Iustin Pop
13 92f51573 Iustin Pop
{-
14 92f51573 Iustin Pop
15 92f51573 Iustin Pop
Copyright (C) 2012 Google Inc.
16 92f51573 Iustin Pop
17 92f51573 Iustin Pop
This program is free software; you can redistribute it and/or modify
18 92f51573 Iustin Pop
it under the terms of the GNU General Public License as published by
19 92f51573 Iustin Pop
the Free Software Foundation; either version 2 of the License, or
20 92f51573 Iustin Pop
(at your option) any later version.
21 92f51573 Iustin Pop
22 92f51573 Iustin Pop
This program is distributed in the hope that it will be useful, but
23 92f51573 Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
24 92f51573 Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
25 92f51573 Iustin Pop
General Public License for more details.
26 92f51573 Iustin Pop
27 92f51573 Iustin Pop
You should have received a copy of the GNU General Public License
28 92f51573 Iustin Pop
along with this program; if not, write to the Free Software
29 92f51573 Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
30 92f51573 Iustin Pop
02110-1301, USA.
31 92f51573 Iustin Pop
32 92f51573 Iustin Pop
-}
33 92f51573 Iustin Pop
34 92f51573 Iustin Pop
module Ganeti.OpParams
35 92f51573 Iustin Pop
  ( TagType(..)
36 92f51573 Iustin Pop
  , TagObject(..)
37 92f51573 Iustin Pop
  , tagObjectFrom
38 ad1c1e41 Iustin Pop
  , tagNameOf
39 92f51573 Iustin Pop
  , decodeTagObject
40 92f51573 Iustin Pop
  , encodeTagObject
41 92f51573 Iustin Pop
  , ReplaceDisksMode(..)
42 92f51573 Iustin Pop
  , DiskIndex
43 92f51573 Iustin Pop
  , mkDiskIndex
44 92f51573 Iustin Pop
  , unDiskIndex
45 6d558717 Iustin Pop
  , DiskAccess(..)
46 d6979f35 Iustin Pop
  , INicParams(..)
47 d6979f35 Iustin Pop
  , IDiskParams(..)
48 c2d3219b Iustin Pop
  , RecreateDisksInfo(..)
49 c2d3219b Iustin Pop
  , DdmOldChanges(..)
50 c2d3219b Iustin Pop
  , SetParamsMods(..)
51 398e9066 Iustin Pop
  , ExportTarget(..)
52 92f51573 Iustin Pop
  , pInstanceName
53 d6979f35 Iustin Pop
  , pInstances
54 d6979f35 Iustin Pop
  , pName
55 92f51573 Iustin Pop
  , pTagsList
56 92f51573 Iustin Pop
  , pTagsObject
57 d6979f35 Iustin Pop
  , pOutputFields
58 d6979f35 Iustin Pop
  , pShutdownTimeout
59 c2d3219b Iustin Pop
  , pShutdownTimeout'
60 67fc4de7 Iustin Pop
  , pShutdownInstance
61 d6979f35 Iustin Pop
  , pForce
62 d6979f35 Iustin Pop
  , pIgnoreOfflineNodes
63 d6979f35 Iustin Pop
  , pNodeName
64 1c3231aa Thomas Thrainer
  , pNodeUuid
65 d6979f35 Iustin Pop
  , pNodeNames
66 1c3231aa Thomas Thrainer
  , pNodeUuids
67 d6979f35 Iustin Pop
  , pGroupName
68 d6979f35 Iustin Pop
  , pMigrationMode
69 d6979f35 Iustin Pop
  , pMigrationLive
70 7d421386 Iustin Pop
  , pMigrationCleanup
71 d6979f35 Iustin Pop
  , pForceVariant
72 d6979f35 Iustin Pop
  , pWaitForSync
73 d6979f35 Iustin Pop
  , pWaitForSyncFalse
74 d6979f35 Iustin Pop
  , pIgnoreConsistency
75 d6979f35 Iustin Pop
  , pStorageName
76 d6979f35 Iustin Pop
  , pUseLocking
77 1f1188c3 Michael Hanselmann
  , pOpportunisticLocking
78 d6979f35 Iustin Pop
  , pNameCheck
79 d6979f35 Iustin Pop
  , pNodeGroupAllocPolicy
80 d6979f35 Iustin Pop
  , pGroupNodeParams
81 d6979f35 Iustin Pop
  , pQueryWhat
82 d6979f35 Iustin Pop
  , pEarlyRelease
83 6d558717 Iustin Pop
  , pIpCheck
84 6d558717 Iustin Pop
  , pIpConflictsCheck
85 d6979f35 Iustin Pop
  , pNoRemember
86 d6979f35 Iustin Pop
  , pMigrationTargetNode
87 1c3231aa Thomas Thrainer
  , pMigrationTargetNodeUuid
88 c2d3219b Iustin Pop
  , pMoveTargetNode
89 1c3231aa Thomas Thrainer
  , pMoveTargetNodeUuid
90 d6979f35 Iustin Pop
  , pStartupPaused
91 d6979f35 Iustin Pop
  , pVerbose
92 d6979f35 Iustin Pop
  , pDebugSimulateErrors
93 d6979f35 Iustin Pop
  , pErrorCodes
94 d6979f35 Iustin Pop
  , pSkipChecks
95 d6979f35 Iustin Pop
  , pIgnoreErrors
96 d6979f35 Iustin Pop
  , pOptGroupName
97 d6979f35 Iustin Pop
  , pDiskParams
98 d6979f35 Iustin Pop
  , pHvState
99 d6979f35 Iustin Pop
  , pDiskState
100 d6979f35 Iustin Pop
  , pIgnoreIpolicy
101 d6979f35 Iustin Pop
  , pAllowRuntimeChgs
102 6d558717 Iustin Pop
  , pInstDisks
103 6d558717 Iustin Pop
  , pDiskTemplate
104 88127c47 Iustin Pop
  , pOptDiskTemplate
105 6d558717 Iustin Pop
  , pFileDriver
106 6d558717 Iustin Pop
  , pFileStorageDir
107 d6979f35 Iustin Pop
  , pVgName
108 d6979f35 Iustin Pop
  , pEnabledHypervisors
109 6d558717 Iustin Pop
  , pHypervisor
110 d6979f35 Iustin Pop
  , pClusterHvParams
111 6d558717 Iustin Pop
  , pInstHvParams
112 d6979f35 Iustin Pop
  , pClusterBeParams
113 6d558717 Iustin Pop
  , pInstBeParams
114 6d558717 Iustin Pop
  , pResetDefaults
115 d6979f35 Iustin Pop
  , pOsHvp
116 6d558717 Iustin Pop
  , pClusterOsParams
117 6d558717 Iustin Pop
  , pInstOsParams
118 d6979f35 Iustin Pop
  , pCandidatePoolSize
119 d6979f35 Iustin Pop
  , pUidPool
120 d6979f35 Iustin Pop
  , pAddUids
121 d6979f35 Iustin Pop
  , pRemoveUids
122 d6979f35 Iustin Pop
  , pMaintainNodeHealth
123 d6979f35 Iustin Pop
  , pPreallocWipeDisks
124 d6979f35 Iustin Pop
  , pNicParams
125 6d558717 Iustin Pop
  , pInstNics
126 d6979f35 Iustin Pop
  , pNdParams
127 d6979f35 Iustin Pop
  , pIpolicy
128 d6979f35 Iustin Pop
  , pDrbdHelper
129 d6979f35 Iustin Pop
  , pDefaultIAllocator
130 d6979f35 Iustin Pop
  , pMasterNetdev
131 d6979f35 Iustin Pop
  , pMasterNetmask
132 d6979f35 Iustin Pop
  , pReservedLvs
133 d6979f35 Iustin Pop
  , pHiddenOs
134 d6979f35 Iustin Pop
  , pBlacklistedOs
135 d6979f35 Iustin Pop
  , pUseExternalMipScript
136 d6979f35 Iustin Pop
  , pQueryFields
137 d6979f35 Iustin Pop
  , pQueryFilter
138 d6979f35 Iustin Pop
  , pOobCommand
139 d6979f35 Iustin Pop
  , pOobTimeout
140 d6979f35 Iustin Pop
  , pIgnoreStatus
141 d6979f35 Iustin Pop
  , pPowerDelay
142 d6979f35 Iustin Pop
  , pPrimaryIp
143 d6979f35 Iustin Pop
  , pSecondaryIp
144 d6979f35 Iustin Pop
  , pReadd
145 d6979f35 Iustin Pop
  , pNodeGroup
146 d6979f35 Iustin Pop
  , pMasterCapable
147 d6979f35 Iustin Pop
  , pVmCapable
148 d6979f35 Iustin Pop
  , pNames
149 d6979f35 Iustin Pop
  , pNodes
150 398e9066 Iustin Pop
  , pRequiredNodes
151 1c3231aa Thomas Thrainer
  , pRequiredNodeUuids
152 d6979f35 Iustin Pop
  , pStorageType
153 d6979f35 Iustin Pop
  , pStorageChanges
154 d6979f35 Iustin Pop
  , pMasterCandidate
155 d6979f35 Iustin Pop
  , pOffline
156 d6979f35 Iustin Pop
  , pDrained
157 d6979f35 Iustin Pop
  , pAutoPromote
158 d6979f35 Iustin Pop
  , pPowered
159 d6979f35 Iustin Pop
  , pIallocator
160 d6979f35 Iustin Pop
  , pRemoteNode
161 1c3231aa Thomas Thrainer
  , pRemoteNodeUuid
162 d6979f35 Iustin Pop
  , pEvacMode
163 6d558717 Iustin Pop
  , pInstCreateMode
164 6d558717 Iustin Pop
  , pNoInstall
165 6d558717 Iustin Pop
  , pInstOs
166 6d558717 Iustin Pop
  , pPrimaryNode
167 1c3231aa Thomas Thrainer
  , pPrimaryNodeUuid
168 6d558717 Iustin Pop
  , pSecondaryNode
169 1c3231aa Thomas Thrainer
  , pSecondaryNodeUuid
170 6d558717 Iustin Pop
  , pSourceHandshake
171 6d558717 Iustin Pop
  , pSourceInstance
172 6d558717 Iustin Pop
  , pSourceShutdownTimeout
173 6d558717 Iustin Pop
  , pSourceX509Ca
174 6d558717 Iustin Pop
  , pSrcNode
175 1c3231aa Thomas Thrainer
  , pSrcNodeUuid
176 6d558717 Iustin Pop
  , pSrcPath
177 6d558717 Iustin Pop
  , pStartInstance
178 6d558717 Iustin Pop
  , pInstTags
179 c2d3219b Iustin Pop
  , pMultiAllocInstances
180 c2d3219b Iustin Pop
  , pTempOsParams
181 c2d3219b Iustin Pop
  , pTempHvParams
182 c2d3219b Iustin Pop
  , pTempBeParams
183 c2d3219b Iustin Pop
  , pIgnoreFailures
184 c2d3219b Iustin Pop
  , pNewName
185 c2d3219b Iustin Pop
  , pIgnoreSecondaries
186 c2d3219b Iustin Pop
  , pRebootType
187 c2d3219b Iustin Pop
  , pIgnoreDiskSize
188 c2d3219b Iustin Pop
  , pRecreateDisksInfo
189 c2d3219b Iustin Pop
  , pStatic
190 c2d3219b Iustin Pop
  , pInstParamsNicChanges
191 c2d3219b Iustin Pop
  , pInstParamsDiskChanges
192 c2d3219b Iustin Pop
  , pRuntimeMem
193 c2d3219b Iustin Pop
  , pOsNameChange
194 c2d3219b Iustin Pop
  , pDiskIndex
195 c2d3219b Iustin Pop
  , pDiskChgAmount
196 c2d3219b Iustin Pop
  , pDiskChgAbsolute
197 c2d3219b Iustin Pop
  , pTargetGroups
198 398e9066 Iustin Pop
  , pExportMode
199 398e9066 Iustin Pop
  , pExportTargetNode
200 1c3231aa Thomas Thrainer
  , pExportTargetNodeUuid
201 398e9066 Iustin Pop
  , pRemoveInstance
202 398e9066 Iustin Pop
  , pIgnoreRemoveFailures
203 398e9066 Iustin Pop
  , pX509KeyName
204 398e9066 Iustin Pop
  , pX509DestCA
205 a451dae2 Iustin Pop
  , pTagSearchPattern
206 1cd563e2 Iustin Pop
  , pRestrictedCommand
207 7d421386 Iustin Pop
  , pReplaceDisksMode
208 7d421386 Iustin Pop
  , pReplaceDisksList
209 7d421386 Iustin Pop
  , pAllowFailover
210 7d421386 Iustin Pop
  , pDelayDuration
211 7d421386 Iustin Pop
  , pDelayOnMaster
212 7d421386 Iustin Pop
  , pDelayOnNodes
213 1c3231aa Thomas Thrainer
  , pDelayOnNodeUuids
214 a451dae2 Iustin Pop
  , pDelayRepeat
215 a3f02317 Iustin Pop
  , pIAllocatorDirection
216 a3f02317 Iustin Pop
  , pIAllocatorMode
217 a3f02317 Iustin Pop
  , pIAllocatorReqName
218 a3f02317 Iustin Pop
  , pIAllocatorNics
219 a3f02317 Iustin Pop
  , pIAllocatorDisks
220 a3f02317 Iustin Pop
  , pIAllocatorMemory
221 a3f02317 Iustin Pop
  , pIAllocatorVCpus
222 a3f02317 Iustin Pop
  , pIAllocatorOs
223 a3f02317 Iustin Pop
  , pIAllocatorInstances
224 a3f02317 Iustin Pop
  , pIAllocatorEvacMode
225 a3f02317 Iustin Pop
  , pIAllocatorSpindleUse
226 a3f02317 Iustin Pop
  , pIAllocatorCount
227 a3f02317 Iustin Pop
  , pJQueueNotifyWaitLock
228 a3f02317 Iustin Pop
  , pJQueueNotifyExec
229 a3f02317 Iustin Pop
  , pJQueueLogMessages
230 a3f02317 Iustin Pop
  , pJQueueFail
231 a3f02317 Iustin Pop
  , pTestDummyResult
232 a3f02317 Iustin Pop
  , pTestDummyMessages
233 a3f02317 Iustin Pop
  , pTestDummyFail
234 a3f02317 Iustin Pop
  , pTestDummySubmitJobs
235 8d239fa4 Iustin Pop
  , pNetworkName
236 8d239fa4 Iustin Pop
  , pNetworkAddress4
237 8d239fa4 Iustin Pop
  , pNetworkGateway4
238 8d239fa4 Iustin Pop
  , pNetworkAddress6
239 8d239fa4 Iustin Pop
  , pNetworkGateway6
240 8d239fa4 Iustin Pop
  , pNetworkMacPrefix
241 8d239fa4 Iustin Pop
  , pNetworkAddRsvdIps
242 8d239fa4 Iustin Pop
  , pNetworkRemoveRsvdIps
243 8d239fa4 Iustin Pop
  , pNetworkMode
244 8d239fa4 Iustin Pop
  , pNetworkLink
245 b46ba79c Iustin Pop
  , pDryRun
246 b46ba79c Iustin Pop
  , pDebugLevel
247 b46ba79c Iustin Pop
  , pOpPriority
248 b46ba79c Iustin Pop
  , pDependencies
249 b46ba79c Iustin Pop
  , pComment
250 516a0e94 Michele Tartara
  , pReason
251 66af5ec5 Helga Velroyen
  , pEnabledDiskTemplates
252 3131adc7 Iustin Pop
  , dOldQuery
253 3131adc7 Iustin Pop
  , dOldQueryNoLocking
254 92f51573 Iustin Pop
  ) where
255 92f51573 Iustin Pop
256 c2d3219b Iustin Pop
import Control.Monad (liftM)
257 d6979f35 Iustin Pop
import qualified Data.Set as Set
258 d6979f35 Iustin Pop
import Text.JSON (readJSON, showJSON, JSON, JSValue(..), fromJSString,
259 6d558717 Iustin Pop
                  JSObject, toJSObject)
260 c2d3219b Iustin Pop
import qualified Text.JSON
261 92f51573 Iustin Pop
import Text.JSON.Pretty (pp_value)
262 92f51573 Iustin Pop
263 6d558717 Iustin Pop
import Ganeti.BasicTypes
264 92f51573 Iustin Pop
import qualified Ganeti.Constants as C
265 92f51573 Iustin Pop
import Ganeti.THH
266 92f51573 Iustin Pop
import Ganeti.JSON
267 d6979f35 Iustin Pop
import Ganeti.Types
268 d6979f35 Iustin Pop
import qualified Ganeti.Query.Language as Qlang
269 92f51573 Iustin Pop
270 92f51573 Iustin Pop
-- * Helper functions and types
271 92f51573 Iustin Pop
272 d6979f35 Iustin Pop
-- * Type aliases
273 d6979f35 Iustin Pop
274 d6979f35 Iustin Pop
-- | Build a boolean field.
275 d6979f35 Iustin Pop
booleanField :: String -> Field
276 d6979f35 Iustin Pop
booleanField = flip simpleField [t| Bool |]
277 d6979f35 Iustin Pop
278 d6979f35 Iustin Pop
-- | Default a field to 'False'.
279 d6979f35 Iustin Pop
defaultFalse :: String -> Field
280 d6979f35 Iustin Pop
defaultFalse = defaultField [| False |] . booleanField
281 d6979f35 Iustin Pop
282 d6979f35 Iustin Pop
-- | Default a field to 'True'.
283 d6979f35 Iustin Pop
defaultTrue :: String -> Field
284 d6979f35 Iustin Pop
defaultTrue = defaultField [| True |] . booleanField
285 d6979f35 Iustin Pop
286 d6979f35 Iustin Pop
-- | An alias for a 'String' field.
287 d6979f35 Iustin Pop
stringField :: String -> Field
288 d6979f35 Iustin Pop
stringField = flip simpleField [t| String |]
289 d6979f35 Iustin Pop
290 d6979f35 Iustin Pop
-- | An alias for an optional string field.
291 d6979f35 Iustin Pop
optionalStringField :: String -> Field
292 d6979f35 Iustin Pop
optionalStringField = optionalField . stringField
293 d6979f35 Iustin Pop
294 d6979f35 Iustin Pop
-- | An alias for an optional non-empty string field.
295 d6979f35 Iustin Pop
optionalNEStringField :: String -> Field
296 d6979f35 Iustin Pop
optionalNEStringField = optionalField . flip simpleField [t| NonEmptyString |]
297 d6979f35 Iustin Pop
298 a3f02317 Iustin Pop
-- | Unchecked value, should be replaced by a better definition.
299 a3f02317 Iustin Pop
type UncheckedValue = JSValue
300 d6979f35 Iustin Pop
301 d6979f35 Iustin Pop
-- | Unchecked dict, should be replaced by a better definition.
302 d6979f35 Iustin Pop
type UncheckedDict = JSObject JSValue
303 d6979f35 Iustin Pop
304 6d558717 Iustin Pop
-- | Unchecked list, shoild be replaced by a better definition.
305 6d558717 Iustin Pop
type UncheckedList = [JSValue]
306 6d558717 Iustin Pop
307 6d558717 Iustin Pop
-- | Function to force a non-negative value, without returning via a
308 6d558717 Iustin Pop
-- monad. This is needed for, and should be used /only/ in the case of
309 6d558717 Iustin Pop
-- forcing constants. In case the constant is wrong (< 0), this will
310 6d558717 Iustin Pop
-- become a runtime error.
311 6d558717 Iustin Pop
forceNonNeg :: (Num a, Ord a, Show a) => a -> NonNegative a
312 6d558717 Iustin Pop
forceNonNeg i = case mkNonNegative i of
313 6d558717 Iustin Pop
                  Ok n -> n
314 6d558717 Iustin Pop
                  Bad msg -> error msg
315 6d558717 Iustin Pop
316 92f51573 Iustin Pop
-- ** Tags
317 92f51573 Iustin Pop
318 92f51573 Iustin Pop
-- | Data type representing what items do the tag operations apply to.
319 92f51573 Iustin Pop
$(declareSADT "TagType"
320 92f51573 Iustin Pop
  [ ("TagTypeInstance", 'C.tagInstance)
321 92f51573 Iustin Pop
  , ("TagTypeNode",     'C.tagNode)
322 92f51573 Iustin Pop
  , ("TagTypeGroup",    'C.tagNodegroup)
323 92f51573 Iustin Pop
  , ("TagTypeCluster",  'C.tagCluster)
324 92f51573 Iustin Pop
  ])
325 92f51573 Iustin Pop
$(makeJSONInstance ''TagType)
326 92f51573 Iustin Pop
327 92f51573 Iustin Pop
-- | Data type holding a tag object (type and object name).
328 92f51573 Iustin Pop
data TagObject = TagInstance String
329 92f51573 Iustin Pop
               | TagNode     String
330 92f51573 Iustin Pop
               | TagGroup    String
331 92f51573 Iustin Pop
               | TagCluster
332 139c0683 Iustin Pop
               deriving (Show, Eq)
333 92f51573 Iustin Pop
334 92f51573 Iustin Pop
-- | Tag type for a given tag object.
335 92f51573 Iustin Pop
tagTypeOf :: TagObject -> TagType
336 92f51573 Iustin Pop
tagTypeOf (TagInstance {}) = TagTypeInstance
337 92f51573 Iustin Pop
tagTypeOf (TagNode     {}) = TagTypeNode
338 92f51573 Iustin Pop
tagTypeOf (TagGroup    {}) = TagTypeGroup
339 92f51573 Iustin Pop
tagTypeOf (TagCluster  {}) = TagTypeCluster
340 92f51573 Iustin Pop
341 92f51573 Iustin Pop
-- | Gets the potential tag object name.
342 92f51573 Iustin Pop
tagNameOf :: TagObject -> Maybe String
343 92f51573 Iustin Pop
tagNameOf (TagInstance s) = Just s
344 92f51573 Iustin Pop
tagNameOf (TagNode     s) = Just s
345 92f51573 Iustin Pop
tagNameOf (TagGroup    s) = Just s
346 92f51573 Iustin Pop
tagNameOf  TagCluster     = Nothing
347 92f51573 Iustin Pop
348 92f51573 Iustin Pop
-- | Builds a 'TagObject' from a tag type and name.
349 92f51573 Iustin Pop
tagObjectFrom :: (Monad m) => TagType -> JSValue -> m TagObject
350 92f51573 Iustin Pop
tagObjectFrom TagTypeInstance (JSString s) =
351 92f51573 Iustin Pop
  return . TagInstance $ fromJSString s
352 92f51573 Iustin Pop
tagObjectFrom TagTypeNode     (JSString s) = return . TagNode $ fromJSString s
353 92f51573 Iustin Pop
tagObjectFrom TagTypeGroup    (JSString s) = return . TagGroup $ fromJSString s
354 92f51573 Iustin Pop
tagObjectFrom TagTypeCluster   JSNull      = return TagCluster
355 92f51573 Iustin Pop
tagObjectFrom t v =
356 92f51573 Iustin Pop
  fail $ "Invalid tag type/name combination: " ++ show t ++ "/" ++
357 92f51573 Iustin Pop
         show (pp_value v)
358 92f51573 Iustin Pop
359 92f51573 Iustin Pop
-- | Name of the tag \"name\" field.
360 92f51573 Iustin Pop
tagNameField :: String
361 92f51573 Iustin Pop
tagNameField = "name"
362 92f51573 Iustin Pop
363 92f51573 Iustin Pop
-- | Custom encoder for 'TagObject' as represented in an opcode.
364 92f51573 Iustin Pop
encodeTagObject :: TagObject -> (JSValue, [(String, JSValue)])
365 92f51573 Iustin Pop
encodeTagObject t = ( showJSON (tagTypeOf t)
366 92f51573 Iustin Pop
                    , [(tagNameField, maybe JSNull showJSON (tagNameOf t))] )
367 92f51573 Iustin Pop
368 92f51573 Iustin Pop
-- | Custom decoder for 'TagObject' as represented in an opcode.
369 92f51573 Iustin Pop
decodeTagObject :: (Monad m) => [(String, JSValue)] -> JSValue -> m TagObject
370 92f51573 Iustin Pop
decodeTagObject obj kind = do
371 92f51573 Iustin Pop
  ttype <- fromJVal kind
372 92f51573 Iustin Pop
  tname <- fromObj obj tagNameField
373 92f51573 Iustin Pop
  tagObjectFrom ttype tname
374 92f51573 Iustin Pop
375 92f51573 Iustin Pop
-- ** Disks
376 92f51573 Iustin Pop
377 92f51573 Iustin Pop
-- | Replace disks type.
378 92f51573 Iustin Pop
$(declareSADT "ReplaceDisksMode"
379 92f51573 Iustin Pop
  [ ("ReplaceOnPrimary",    'C.replaceDiskPri)
380 92f51573 Iustin Pop
  , ("ReplaceOnSecondary",  'C.replaceDiskSec)
381 92f51573 Iustin Pop
  , ("ReplaceNewSecondary", 'C.replaceDiskChg)
382 92f51573 Iustin Pop
  , ("ReplaceAuto",         'C.replaceDiskAuto)
383 92f51573 Iustin Pop
  ])
384 92f51573 Iustin Pop
$(makeJSONInstance ''ReplaceDisksMode)
385 92f51573 Iustin Pop
386 92f51573 Iustin Pop
-- | Disk index type (embedding constraints on the index value via a
387 92f51573 Iustin Pop
-- smart constructor).
388 92f51573 Iustin Pop
newtype DiskIndex = DiskIndex { unDiskIndex :: Int }
389 139c0683 Iustin Pop
  deriving (Show, Eq, Ord)
390 92f51573 Iustin Pop
391 92f51573 Iustin Pop
-- | Smart constructor for 'DiskIndex'.
392 92f51573 Iustin Pop
mkDiskIndex :: (Monad m) => Int -> m DiskIndex
393 92f51573 Iustin Pop
mkDiskIndex i | i >= 0 && i < C.maxDisks = return (DiskIndex i)
394 92f51573 Iustin Pop
              | otherwise = fail $ "Invalid value for disk index '" ++
395 92f51573 Iustin Pop
                            show i ++ "', required between 0 and " ++
396 92f51573 Iustin Pop
                            show C.maxDisks
397 92f51573 Iustin Pop
398 92f51573 Iustin Pop
instance JSON DiskIndex where
399 92f51573 Iustin Pop
  readJSON v = readJSON v >>= mkDiskIndex
400 92f51573 Iustin Pop
  showJSON = showJSON . unDiskIndex
401 92f51573 Iustin Pop
402 d6979f35 Iustin Pop
-- ** I* param types
403 d6979f35 Iustin Pop
404 d6979f35 Iustin Pop
-- | Type holding disk access modes.
405 d6979f35 Iustin Pop
$(declareSADT "DiskAccess"
406 d6979f35 Iustin Pop
  [ ("DiskReadOnly",  'C.diskRdonly)
407 d6979f35 Iustin Pop
  , ("DiskReadWrite", 'C.diskRdwr)
408 d6979f35 Iustin Pop
  ])
409 d6979f35 Iustin Pop
$(makeJSONInstance ''DiskAccess)
410 d6979f35 Iustin Pop
411 d6979f35 Iustin Pop
-- | NIC modification definition.
412 d6979f35 Iustin Pop
$(buildObject "INicParams" "inic"
413 d6979f35 Iustin Pop
  [ optionalField $ simpleField C.inicMac  [t| NonEmptyString |]
414 d6979f35 Iustin Pop
  , optionalField $ simpleField C.inicIp   [t| String         |]
415 d6979f35 Iustin Pop
  , optionalField $ simpleField C.inicMode [t| NonEmptyString |]
416 d6979f35 Iustin Pop
  , optionalField $ simpleField C.inicLink [t| NonEmptyString |]
417 4e4433e8 Christos Stavrakakis
  , optionalField $ simpleField C.inicName [t| NonEmptyString |]
418 d6979f35 Iustin Pop
  ])
419 d6979f35 Iustin Pop
420 6d558717 Iustin Pop
-- | Disk modification definition. FIXME: disksize should be VTYPE_UNIT.
421 d6979f35 Iustin Pop
$(buildObject "IDiskParams" "idisk"
422 6d558717 Iustin Pop
  [ optionalField $ simpleField C.idiskSize   [t| Int            |]
423 6d558717 Iustin Pop
  , optionalField $ simpleField C.idiskMode   [t| DiskAccess     |]
424 6d558717 Iustin Pop
  , optionalField $ simpleField C.idiskAdopt  [t| NonEmptyString |]
425 6d558717 Iustin Pop
  , optionalField $ simpleField C.idiskVg     [t| NonEmptyString |]
426 6d558717 Iustin Pop
  , optionalField $ simpleField C.idiskMetavg [t| NonEmptyString |]
427 4e4433e8 Christos Stavrakakis
  , optionalField $ simpleField C.idiskName   [t| NonEmptyString |]
428 d6979f35 Iustin Pop
  ])
429 d6979f35 Iustin Pop
430 c2d3219b Iustin Pop
-- | Disk changes type for OpInstanceRecreateDisks. This is a bit
431 c2d3219b Iustin Pop
-- strange, because the type in Python is something like Either
432 c2d3219b Iustin Pop
-- [DiskIndex] [DiskChanges], but we can't represent the type of an
433 c2d3219b Iustin Pop
-- empty list in JSON, so we have to add a custom case for the empty
434 c2d3219b Iustin Pop
-- list.
435 c2d3219b Iustin Pop
data RecreateDisksInfo
436 c2d3219b Iustin Pop
  = RecreateDisksAll
437 c2d3219b Iustin Pop
  | RecreateDisksIndices (NonEmpty DiskIndex)
438 c2d3219b Iustin Pop
  | RecreateDisksParams (NonEmpty (DiskIndex, IDiskParams))
439 139c0683 Iustin Pop
    deriving (Eq, Show)
440 c2d3219b Iustin Pop
441 c2d3219b Iustin Pop
readRecreateDisks :: JSValue -> Text.JSON.Result RecreateDisksInfo
442 c2d3219b Iustin Pop
readRecreateDisks (JSArray []) = return RecreateDisksAll
443 c2d3219b Iustin Pop
readRecreateDisks v =
444 c2d3219b Iustin Pop
  case readJSON v::Text.JSON.Result [DiskIndex] of
445 c2d3219b Iustin Pop
    Text.JSON.Ok indices -> liftM RecreateDisksIndices (mkNonEmpty indices)
446 c2d3219b Iustin Pop
    _ -> case readJSON v::Text.JSON.Result [(DiskIndex, IDiskParams)] of
447 c2d3219b Iustin Pop
           Text.JSON.Ok params -> liftM RecreateDisksParams (mkNonEmpty params)
448 c2d3219b Iustin Pop
           _ -> fail $ "Can't parse disk information as either list of disk"
449 f56013fd Iustin Pop
                ++ " indices or list of disk parameters; value received:"
450 c2d3219b Iustin Pop
                ++ show (pp_value v)
451 c2d3219b Iustin Pop
452 c2d3219b Iustin Pop
instance JSON RecreateDisksInfo where
453 c2d3219b Iustin Pop
  readJSON = readRecreateDisks
454 c2d3219b Iustin Pop
  showJSON  RecreateDisksAll            = showJSON ()
455 c2d3219b Iustin Pop
  showJSON (RecreateDisksIndices idx)   = showJSON idx
456 c2d3219b Iustin Pop
  showJSON (RecreateDisksParams params) = showJSON params
457 c2d3219b Iustin Pop
458 c2d3219b Iustin Pop
-- | Simple type for old-style ddm changes.
459 c2d3219b Iustin Pop
data DdmOldChanges = DdmOldIndex (NonNegative Int)
460 c2d3219b Iustin Pop
                   | DdmOldMod DdmSimple
461 139c0683 Iustin Pop
                     deriving (Eq, Show)
462 c2d3219b Iustin Pop
463 c2d3219b Iustin Pop
readDdmOldChanges :: JSValue -> Text.JSON.Result DdmOldChanges
464 c2d3219b Iustin Pop
readDdmOldChanges v =
465 c2d3219b Iustin Pop
  case readJSON v::Text.JSON.Result (NonNegative Int) of
466 c2d3219b Iustin Pop
    Text.JSON.Ok nn -> return $ DdmOldIndex nn
467 c2d3219b Iustin Pop
    _ -> case readJSON v::Text.JSON.Result DdmSimple of
468 c2d3219b Iustin Pop
           Text.JSON.Ok ddms -> return $ DdmOldMod ddms
469 c2d3219b Iustin Pop
           _ -> fail $ "Can't parse value '" ++ show (pp_value v) ++ "' as"
470 c2d3219b Iustin Pop
                ++ " either index or modification"
471 c2d3219b Iustin Pop
472 c2d3219b Iustin Pop
instance JSON DdmOldChanges where
473 c2d3219b Iustin Pop
  showJSON (DdmOldIndex i) = showJSON i
474 c2d3219b Iustin Pop
  showJSON (DdmOldMod m)   = showJSON m
475 c2d3219b Iustin Pop
  readJSON = readDdmOldChanges
476 c2d3219b Iustin Pop
477 c2d3219b Iustin Pop
-- | Instance disk or nic modifications.
478 c2d3219b Iustin Pop
data SetParamsMods a
479 c2d3219b Iustin Pop
  = SetParamsEmpty
480 c2d3219b Iustin Pop
  | SetParamsDeprecated (NonEmpty (DdmOldChanges, a))
481 c2d3219b Iustin Pop
  | SetParamsNew (NonEmpty (DdmFull, Int, a))
482 139c0683 Iustin Pop
    deriving (Eq, Show)
483 c2d3219b Iustin Pop
484 c2d3219b Iustin Pop
-- | Custom deserialiser for 'SetParamsMods'.
485 c2d3219b Iustin Pop
readSetParams :: (JSON a) => JSValue -> Text.JSON.Result (SetParamsMods a)
486 c2d3219b Iustin Pop
readSetParams (JSArray []) = return SetParamsEmpty
487 c2d3219b Iustin Pop
readSetParams v =
488 c2d3219b Iustin Pop
  case readJSON v::Text.JSON.Result [(DdmOldChanges, JSValue)] of
489 c2d3219b Iustin Pop
    Text.JSON.Ok _ -> liftM SetParamsDeprecated $ readJSON v
490 c2d3219b Iustin Pop
    _ -> liftM SetParamsNew $ readJSON v
491 c2d3219b Iustin Pop
492 c2d3219b Iustin Pop
instance (JSON a) => JSON (SetParamsMods a) where
493 c2d3219b Iustin Pop
  showJSON SetParamsEmpty = showJSON ()
494 c2d3219b Iustin Pop
  showJSON (SetParamsDeprecated v) = showJSON v
495 c2d3219b Iustin Pop
  showJSON (SetParamsNew v) = showJSON v
496 c2d3219b Iustin Pop
  readJSON = readSetParams
497 c2d3219b Iustin Pop
498 398e9066 Iustin Pop
-- | Custom type for target_node parameter of OpBackupExport, which
499 398e9066 Iustin Pop
-- varies depending on mode. FIXME: this uses an UncheckedList since
500 398e9066 Iustin Pop
-- we don't care about individual rows (just like the Python code
501 398e9066 Iustin Pop
-- tests). But the proper type could be parsed if we wanted.
502 398e9066 Iustin Pop
data ExportTarget = ExportTargetLocal NonEmptyString
503 398e9066 Iustin Pop
                  | ExportTargetRemote UncheckedList
504 139c0683 Iustin Pop
                    deriving (Eq, Show)
505 398e9066 Iustin Pop
506 398e9066 Iustin Pop
-- | Custom reader for 'ExportTarget'.
507 398e9066 Iustin Pop
readExportTarget :: JSValue -> Text.JSON.Result ExportTarget
508 398e9066 Iustin Pop
readExportTarget (JSString s) = liftM ExportTargetLocal $
509 398e9066 Iustin Pop
                                mkNonEmpty (fromJSString s)
510 398e9066 Iustin Pop
readExportTarget (JSArray arr) = return $ ExportTargetRemote arr
511 398e9066 Iustin Pop
readExportTarget v = fail $ "Invalid value received for 'target_node': " ++
512 398e9066 Iustin Pop
                     show (pp_value v)
513 398e9066 Iustin Pop
514 398e9066 Iustin Pop
instance JSON ExportTarget where
515 398e9066 Iustin Pop
  showJSON (ExportTargetLocal s)  = showJSON s
516 398e9066 Iustin Pop
  showJSON (ExportTargetRemote l) = showJSON l
517 398e9066 Iustin Pop
  readJSON = readExportTarget
518 398e9066 Iustin Pop
519 92f51573 Iustin Pop
-- * Parameters
520 92f51573 Iustin Pop
521 d6979f35 Iustin Pop
-- | A required instance name (for single-instance LUs).
522 92f51573 Iustin Pop
pInstanceName :: Field
523 92f51573 Iustin Pop
pInstanceName = simpleField "instance_name" [t| String |]
524 92f51573 Iustin Pop
525 d6979f35 Iustin Pop
-- | A list of instances.
526 d6979f35 Iustin Pop
pInstances :: Field
527 d6979f35 Iustin Pop
pInstances = defaultField [| [] |] $
528 d6979f35 Iustin Pop
             simpleField "instances" [t| [NonEmptyString] |]
529 d6979f35 Iustin Pop
530 d6979f35 Iustin Pop
-- | A generic name.
531 d6979f35 Iustin Pop
pName :: Field
532 d6979f35 Iustin Pop
pName = simpleField "name" [t| NonEmptyString |]
533 d6979f35 Iustin Pop
534 92f51573 Iustin Pop
-- | Tags list.
535 92f51573 Iustin Pop
pTagsList :: Field
536 92f51573 Iustin Pop
pTagsList = simpleField "tags" [t| [String] |]
537 92f51573 Iustin Pop
538 92f51573 Iustin Pop
-- | Tags object.
539 92f51573 Iustin Pop
pTagsObject :: Field
540 fa10983e Iustin Pop
pTagsObject =
541 fa10983e Iustin Pop
  customField 'decodeTagObject 'encodeTagObject [tagNameField] $
542 fa10983e Iustin Pop
  simpleField "kind" [t| TagObject |]
543 d6979f35 Iustin Pop
544 d6979f35 Iustin Pop
-- | Selected output fields.
545 d6979f35 Iustin Pop
pOutputFields :: Field
546 d6979f35 Iustin Pop
pOutputFields = simpleField "output_fields" [t| [NonEmptyString] |]
547 d6979f35 Iustin Pop
548 d6979f35 Iustin Pop
-- | How long to wait for instance to shut down.
549 d6979f35 Iustin Pop
pShutdownTimeout :: Field
550 c2d3219b Iustin Pop
pShutdownTimeout = defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
551 d6979f35 Iustin Pop
                   simpleField "shutdown_timeout" [t| NonNegative Int |]
552 d6979f35 Iustin Pop
553 c2d3219b Iustin Pop
-- | Another name for the shutdown timeout, because we like to be
554 c2d3219b Iustin Pop
-- inconsistent.
555 c2d3219b Iustin Pop
pShutdownTimeout' :: Field
556 c2d3219b Iustin Pop
pShutdownTimeout' =
557 c2d3219b Iustin Pop
  renameField "InstShutdownTimeout" .
558 c2d3219b Iustin Pop
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
559 c2d3219b Iustin Pop
  simpleField "timeout" [t| NonNegative Int |]
560 c2d3219b Iustin Pop
561 67fc4de7 Iustin Pop
-- | Whether to shutdown the instance in backup-export.
562 67fc4de7 Iustin Pop
pShutdownInstance :: Field
563 67fc4de7 Iustin Pop
pShutdownInstance = defaultTrue "shutdown"
564 67fc4de7 Iustin Pop
565 d6979f35 Iustin Pop
-- | Whether to force the operation.
566 d6979f35 Iustin Pop
pForce :: Field
567 d6979f35 Iustin Pop
pForce = defaultFalse "force"
568 d6979f35 Iustin Pop
569 d6979f35 Iustin Pop
-- | Whether to ignore offline nodes.
570 d6979f35 Iustin Pop
pIgnoreOfflineNodes :: Field
571 d6979f35 Iustin Pop
pIgnoreOfflineNodes = defaultFalse "ignore_offline_nodes"
572 d6979f35 Iustin Pop
573 d6979f35 Iustin Pop
-- | A required node name (for single-node LUs).
574 d6979f35 Iustin Pop
pNodeName :: Field
575 d6979f35 Iustin Pop
pNodeName = simpleField "node_name" [t| NonEmptyString |]
576 d6979f35 Iustin Pop
577 1c3231aa Thomas Thrainer
-- | A node UUID (for single-node LUs).
578 1c3231aa Thomas Thrainer
pNodeUuid :: Field
579 1c3231aa Thomas Thrainer
pNodeUuid = optionalField $ simpleField "node_uuid" [t| NonEmptyString |]
580 1c3231aa Thomas Thrainer
581 d6979f35 Iustin Pop
-- | List of nodes.
582 d6979f35 Iustin Pop
pNodeNames :: Field
583 d6979f35 Iustin Pop
pNodeNames =
584 d6979f35 Iustin Pop
  defaultField [| [] |] $ simpleField "node_names" [t| [NonEmptyString] |]
585 d6979f35 Iustin Pop
586 1c3231aa Thomas Thrainer
-- | List of node UUIDs.
587 1c3231aa Thomas Thrainer
pNodeUuids :: Field
588 1c3231aa Thomas Thrainer
pNodeUuids =
589 1c3231aa Thomas Thrainer
  optionalField $ simpleField "node_uuids" [t| [NonEmptyString] |]
590 1c3231aa Thomas Thrainer
591 d6979f35 Iustin Pop
-- | A required node group name (for single-group LUs).
592 d6979f35 Iustin Pop
pGroupName :: Field
593 d6979f35 Iustin Pop
pGroupName = simpleField "group_name" [t| NonEmptyString |]
594 d6979f35 Iustin Pop
595 d6979f35 Iustin Pop
-- | Migration type (live\/non-live).
596 d6979f35 Iustin Pop
pMigrationMode :: Field
597 d6979f35 Iustin Pop
pMigrationMode =
598 417ab39c Iustin Pop
  renameField "MigrationMode" .
599 d6979f35 Iustin Pop
  optionalField $
600 d6979f35 Iustin Pop
  simpleField "mode" [t| MigrationMode |]
601 d6979f35 Iustin Pop
602 d6979f35 Iustin Pop
-- | Obsolete \'live\' migration mode (boolean).
603 d6979f35 Iustin Pop
pMigrationLive :: Field
604 d6979f35 Iustin Pop
pMigrationLive =
605 417ab39c Iustin Pop
  renameField "OldLiveMode" . optionalField $ booleanField "live"
606 d6979f35 Iustin Pop
607 7d421386 Iustin Pop
-- | Migration cleanup parameter.
608 7d421386 Iustin Pop
pMigrationCleanup :: Field
609 7d421386 Iustin Pop
pMigrationCleanup = renameField "MigrationCleanup" $ defaultFalse "cleanup"
610 7d421386 Iustin Pop
611 d6979f35 Iustin Pop
-- | Whether to force an unknown OS variant.
612 d6979f35 Iustin Pop
pForceVariant :: Field
613 d6979f35 Iustin Pop
pForceVariant = defaultFalse "force_variant"
614 d6979f35 Iustin Pop
615 d6979f35 Iustin Pop
-- | Whether to wait for the disk to synchronize.
616 d6979f35 Iustin Pop
pWaitForSync :: Field
617 d6979f35 Iustin Pop
pWaitForSync = defaultTrue "wait_for_sync"
618 d6979f35 Iustin Pop
619 d6979f35 Iustin Pop
-- | Whether to wait for the disk to synchronize (defaults to false).
620 d6979f35 Iustin Pop
pWaitForSyncFalse :: Field
621 d6979f35 Iustin Pop
pWaitForSyncFalse = defaultField [| False |] pWaitForSync
622 d6979f35 Iustin Pop
623 d6979f35 Iustin Pop
-- | Whether to ignore disk consistency
624 d6979f35 Iustin Pop
pIgnoreConsistency :: Field
625 d6979f35 Iustin Pop
pIgnoreConsistency = defaultFalse "ignore_consistency"
626 d6979f35 Iustin Pop
627 d6979f35 Iustin Pop
-- | Storage name.
628 d6979f35 Iustin Pop
pStorageName :: Field
629 d6979f35 Iustin Pop
pStorageName =
630 d6979f35 Iustin Pop
  renameField "StorageName" $ simpleField "name" [t| NonEmptyString |]
631 d6979f35 Iustin Pop
632 d6979f35 Iustin Pop
-- | Whether to use synchronization.
633 d6979f35 Iustin Pop
pUseLocking :: Field
634 d6979f35 Iustin Pop
pUseLocking = defaultFalse "use_locking"
635 d6979f35 Iustin Pop
636 1f1188c3 Michael Hanselmann
-- | Whether to employ opportunistic locking for nodes, meaning nodes already
637 1f1188c3 Michael Hanselmann
-- locked by another opcode won't be considered for instance allocation (only
638 1f1188c3 Michael Hanselmann
-- when an iallocator is used).
639 1f1188c3 Michael Hanselmann
pOpportunisticLocking :: Field
640 1f1188c3 Michael Hanselmann
pOpportunisticLocking = defaultFalse "opportunistic_locking"
641 1f1188c3 Michael Hanselmann
642 d6979f35 Iustin Pop
-- | Whether to check name.
643 d6979f35 Iustin Pop
pNameCheck :: Field
644 d6979f35 Iustin Pop
pNameCheck = defaultTrue "name_check"
645 d6979f35 Iustin Pop
646 d6979f35 Iustin Pop
-- | Instance allocation policy.
647 d6979f35 Iustin Pop
pNodeGroupAllocPolicy :: Field
648 d6979f35 Iustin Pop
pNodeGroupAllocPolicy = optionalField $
649 d6979f35 Iustin Pop
                        simpleField "alloc_policy" [t| AllocPolicy |]
650 d6979f35 Iustin Pop
651 d6979f35 Iustin Pop
-- | Default node parameters for group.
652 d6979f35 Iustin Pop
pGroupNodeParams :: Field
653 d6979f35 Iustin Pop
pGroupNodeParams = optionalField $ simpleField "ndparams" [t| UncheckedDict |]
654 d6979f35 Iustin Pop
655 d6979f35 Iustin Pop
-- | Resource(s) to query for.
656 d6979f35 Iustin Pop
pQueryWhat :: Field
657 d6979f35 Iustin Pop
pQueryWhat = simpleField "what" [t| Qlang.QueryTypeOp |]
658 d6979f35 Iustin Pop
659 d6979f35 Iustin Pop
-- | Whether to release locks as soon as possible.
660 d6979f35 Iustin Pop
pEarlyRelease :: Field
661 d6979f35 Iustin Pop
pEarlyRelease = defaultFalse "early_release"
662 d6979f35 Iustin Pop
663 6d558717 Iustin Pop
-- | Whether to ensure instance's IP address is inactive.
664 6d558717 Iustin Pop
pIpCheck :: Field
665 6d558717 Iustin Pop
pIpCheck = defaultTrue "ip_check"
666 6d558717 Iustin Pop
667 6d558717 Iustin Pop
-- | Check for conflicting IPs.
668 6d558717 Iustin Pop
pIpConflictsCheck :: Field
669 6d558717 Iustin Pop
pIpConflictsCheck = defaultTrue "conflicts_check"
670 d6979f35 Iustin Pop
671 d6979f35 Iustin Pop
-- | Do not remember instance state changes.
672 d6979f35 Iustin Pop
pNoRemember :: Field
673 d6979f35 Iustin Pop
pNoRemember = defaultFalse "no_remember"
674 d6979f35 Iustin Pop
675 d6979f35 Iustin Pop
-- | Target node for instance migration/failover.
676 d6979f35 Iustin Pop
pMigrationTargetNode :: Field
677 d6979f35 Iustin Pop
pMigrationTargetNode = optionalNEStringField "target_node"
678 d6979f35 Iustin Pop
679 1c3231aa Thomas Thrainer
-- | Target node UUID for instance migration/failover.
680 1c3231aa Thomas Thrainer
pMigrationTargetNodeUuid :: Field
681 1c3231aa Thomas Thrainer
pMigrationTargetNodeUuid = optionalNEStringField "target_node_uuid"
682 1c3231aa Thomas Thrainer
683 c2d3219b Iustin Pop
-- | Target node for instance move (required).
684 c2d3219b Iustin Pop
pMoveTargetNode :: Field
685 c2d3219b Iustin Pop
pMoveTargetNode =
686 c2d3219b Iustin Pop
  renameField "MoveTargetNode" $
687 c2d3219b Iustin Pop
  simpleField "target_node" [t| NonEmptyString |]
688 c2d3219b Iustin Pop
689 1c3231aa Thomas Thrainer
-- | Target node UUID for instance move.
690 1c3231aa Thomas Thrainer
pMoveTargetNodeUuid :: Field
691 1c3231aa Thomas Thrainer
pMoveTargetNodeUuid =
692 1c3231aa Thomas Thrainer
  renameField "MoveTargetNodeUuid" . optionalField $
693 1c3231aa Thomas Thrainer
  simpleField "target_node_uuid" [t| NonEmptyString |]
694 1c3231aa Thomas Thrainer
695 d6979f35 Iustin Pop
-- | Pause instance at startup.
696 d6979f35 Iustin Pop
pStartupPaused :: Field
697 d6979f35 Iustin Pop
pStartupPaused = defaultFalse "startup_paused"
698 d6979f35 Iustin Pop
699 d6979f35 Iustin Pop
-- | Verbose mode.
700 d6979f35 Iustin Pop
pVerbose :: Field
701 d6979f35 Iustin Pop
pVerbose = defaultFalse "verbose"
702 d6979f35 Iustin Pop
703 d6979f35 Iustin Pop
-- ** Parameters for cluster verification
704 d6979f35 Iustin Pop
705 d6979f35 Iustin Pop
-- | Whether to simulate errors (useful for debugging).
706 d6979f35 Iustin Pop
pDebugSimulateErrors :: Field
707 d6979f35 Iustin Pop
pDebugSimulateErrors = defaultFalse "debug_simulate_errors"
708 d6979f35 Iustin Pop
709 d6979f35 Iustin Pop
-- | Error codes.
710 d6979f35 Iustin Pop
pErrorCodes :: Field
711 d6979f35 Iustin Pop
pErrorCodes = defaultFalse "error_codes"
712 d6979f35 Iustin Pop
713 d6979f35 Iustin Pop
-- | Which checks to skip.
714 d6979f35 Iustin Pop
pSkipChecks :: Field
715 d6979f35 Iustin Pop
pSkipChecks = defaultField [| Set.empty |] $
716 d6979f35 Iustin Pop
              simpleField "skip_checks" [t| Set.Set VerifyOptionalChecks |]
717 d6979f35 Iustin Pop
718 d6979f35 Iustin Pop
-- | List of error codes that should be treated as warnings.
719 d6979f35 Iustin Pop
pIgnoreErrors :: Field
720 d6979f35 Iustin Pop
pIgnoreErrors = defaultField [| Set.empty |] $
721 d6979f35 Iustin Pop
                simpleField "ignore_errors" [t| Set.Set CVErrorCode |]
722 d6979f35 Iustin Pop
723 d6979f35 Iustin Pop
-- | Optional group name.
724 d6979f35 Iustin Pop
pOptGroupName :: Field
725 417ab39c Iustin Pop
pOptGroupName = renameField "OptGroupName" .
726 d6979f35 Iustin Pop
                optionalField $ simpleField "group_name" [t| NonEmptyString |]
727 d6979f35 Iustin Pop
728 d6979f35 Iustin Pop
-- | Disk templates' parameter defaults.
729 d6979f35 Iustin Pop
pDiskParams :: Field
730 d6979f35 Iustin Pop
pDiskParams = optionalField $
731 d6979f35 Iustin Pop
              simpleField "diskparams" [t| GenericContainer DiskTemplate
732 d6979f35 Iustin Pop
                                           UncheckedDict |]
733 d6979f35 Iustin Pop
734 d6979f35 Iustin Pop
-- * Parameters for node resource model
735 d6979f35 Iustin Pop
736 d6979f35 Iustin Pop
-- | Set hypervisor states.
737 d6979f35 Iustin Pop
pHvState :: Field
738 d6979f35 Iustin Pop
pHvState = optionalField $ simpleField "hv_state" [t| UncheckedDict |]
739 d6979f35 Iustin Pop
740 d6979f35 Iustin Pop
-- | Set disk states.
741 d6979f35 Iustin Pop
pDiskState :: Field
742 d6979f35 Iustin Pop
pDiskState = optionalField $ simpleField "disk_state" [t| UncheckedDict |]
743 d6979f35 Iustin Pop
744 d6979f35 Iustin Pop
-- | Whether to ignore ipolicy violations.
745 d6979f35 Iustin Pop
pIgnoreIpolicy :: Field
746 d6979f35 Iustin Pop
pIgnoreIpolicy = defaultFalse "ignore_ipolicy"
747 d6979f35 Iustin Pop
748 d6979f35 Iustin Pop
-- | Allow runtime changes while migrating.
749 d6979f35 Iustin Pop
pAllowRuntimeChgs :: Field
750 d6979f35 Iustin Pop
pAllowRuntimeChgs = defaultTrue "allow_runtime_changes"
751 d6979f35 Iustin Pop
752 d6979f35 Iustin Pop
-- | Utility type for OpClusterSetParams.
753 d6979f35 Iustin Pop
type TestClusterOsListItem = (DdmSimple, NonEmptyString)
754 d6979f35 Iustin Pop
755 d6979f35 Iustin Pop
-- | Utility type of OsList.
756 d6979f35 Iustin Pop
type TestClusterOsList = [TestClusterOsListItem]
757 d6979f35 Iustin Pop
758 d6979f35 Iustin Pop
-- Utility type for NIC definitions.
759 d6979f35 Iustin Pop
--type TestNicDef = INicParams
760 6d558717 Iustin Pop
761 6d558717 Iustin Pop
-- | List of instance disks.
762 6d558717 Iustin Pop
pInstDisks :: Field
763 6d558717 Iustin Pop
pInstDisks = renameField "instDisks" $ simpleField "disks" [t| [IDiskParams] |]
764 6d558717 Iustin Pop
765 6d558717 Iustin Pop
-- | Instance disk template.
766 6d558717 Iustin Pop
pDiskTemplate :: Field
767 6d558717 Iustin Pop
pDiskTemplate = simpleField "disk_template" [t| DiskTemplate |]
768 6d558717 Iustin Pop
769 88127c47 Iustin Pop
-- | Instance disk template.
770 88127c47 Iustin Pop
pOptDiskTemplate :: Field
771 88127c47 Iustin Pop
pOptDiskTemplate =
772 88127c47 Iustin Pop
  optionalField .
773 88127c47 Iustin Pop
  renameField "OptDiskTemplate" $
774 88127c47 Iustin Pop
  simpleField "disk_template" [t| DiskTemplate |]
775 88127c47 Iustin Pop
776 6d558717 Iustin Pop
-- | File driver.
777 6d558717 Iustin Pop
pFileDriver :: Field
778 6d558717 Iustin Pop
pFileDriver = optionalField $ simpleField "file_driver" [t| FileDriver |]
779 6d558717 Iustin Pop
780 6d558717 Iustin Pop
-- | Directory for storing file-backed disks.
781 6d558717 Iustin Pop
pFileStorageDir :: Field
782 6d558717 Iustin Pop
pFileStorageDir = optionalNEStringField "file_storage_dir"
783 d6979f35 Iustin Pop
784 d6979f35 Iustin Pop
-- | Volume group name.
785 d6979f35 Iustin Pop
pVgName :: Field
786 d6979f35 Iustin Pop
pVgName = optionalStringField "vg_name"
787 d6979f35 Iustin Pop
788 d6979f35 Iustin Pop
-- | List of enabled hypervisors.
789 d6979f35 Iustin Pop
pEnabledHypervisors :: Field
790 d6979f35 Iustin Pop
pEnabledHypervisors =
791 d6979f35 Iustin Pop
  optionalField $
792 d6979f35 Iustin Pop
  simpleField "enabled_hypervisors" [t| NonEmpty Hypervisor |]
793 d6979f35 Iustin Pop
794 66af5ec5 Helga Velroyen
-- | List of enabled disk templates.
795 66af5ec5 Helga Velroyen
pEnabledDiskTemplates :: Field
796 66af5ec5 Helga Velroyen
pEnabledDiskTemplates =
797 66af5ec5 Helga Velroyen
  optionalField $
798 66af5ec5 Helga Velroyen
  simpleField "enabled_disk_templates" [t| NonEmpty DiskTemplate |]
799 66af5ec5 Helga Velroyen
800 6d558717 Iustin Pop
-- | Selected hypervisor for an instance.
801 6d558717 Iustin Pop
pHypervisor :: Field
802 6d558717 Iustin Pop
pHypervisor =
803 6d558717 Iustin Pop
  optionalField $
804 6d558717 Iustin Pop
  simpleField "hypervisor" [t| Hypervisor |]
805 6d558717 Iustin Pop
806 d6979f35 Iustin Pop
-- | Cluster-wide hypervisor parameters, hypervisor-dependent.
807 d6979f35 Iustin Pop
pClusterHvParams :: Field
808 d6979f35 Iustin Pop
pClusterHvParams =
809 6d558717 Iustin Pop
  renameField "ClusterHvParams" .
810 d6979f35 Iustin Pop
  optionalField $
811 d6979f35 Iustin Pop
  simpleField "hvparams" [t| Container UncheckedDict |]
812 d6979f35 Iustin Pop
813 6d558717 Iustin Pop
-- | Instance hypervisor parameters.
814 6d558717 Iustin Pop
pInstHvParams :: Field
815 6d558717 Iustin Pop
pInstHvParams =
816 6d558717 Iustin Pop
  renameField "InstHvParams" .
817 6d558717 Iustin Pop
  defaultField [| toJSObject [] |] $
818 6d558717 Iustin Pop
  simpleField "hvparams" [t| UncheckedDict |]
819 6d558717 Iustin Pop
820 d6979f35 Iustin Pop
-- | Cluster-wide beparams.
821 d6979f35 Iustin Pop
pClusterBeParams :: Field
822 6d558717 Iustin Pop
pClusterBeParams =
823 6d558717 Iustin Pop
  renameField "ClusterBeParams" .
824 6d558717 Iustin Pop
  optionalField $ simpleField "beparams" [t| UncheckedDict |]
825 6d558717 Iustin Pop
826 6d558717 Iustin Pop
-- | Instance beparams.
827 6d558717 Iustin Pop
pInstBeParams :: Field
828 6d558717 Iustin Pop
pInstBeParams =
829 6d558717 Iustin Pop
  renameField "InstBeParams" .
830 6d558717 Iustin Pop
  defaultField [| toJSObject [] |] $
831 6d558717 Iustin Pop
  simpleField "beparams" [t| UncheckedDict |]
832 6d558717 Iustin Pop
833 6d558717 Iustin Pop
-- | Reset instance parameters to default if equal.
834 6d558717 Iustin Pop
pResetDefaults :: Field
835 6d558717 Iustin Pop
pResetDefaults = defaultFalse "identify_defaults"
836 d6979f35 Iustin Pop
837 d6979f35 Iustin Pop
-- | Cluster-wide per-OS hypervisor parameter defaults.
838 d6979f35 Iustin Pop
pOsHvp :: Field
839 d6979f35 Iustin Pop
pOsHvp = optionalField $ simpleField "os_hvp" [t| Container UncheckedDict |]
840 d6979f35 Iustin Pop
841 d6979f35 Iustin Pop
-- | Cluster-wide OS parameter defaults.
842 6d558717 Iustin Pop
pClusterOsParams :: Field
843 6d558717 Iustin Pop
pClusterOsParams =
844 c2d3219b Iustin Pop
  renameField "ClusterOsParams" .
845 d6979f35 Iustin Pop
  optionalField $ simpleField "osparams" [t| Container UncheckedDict |]
846 d6979f35 Iustin Pop
847 6d558717 Iustin Pop
-- | Instance OS parameters.
848 6d558717 Iustin Pop
pInstOsParams :: Field
849 6d558717 Iustin Pop
pInstOsParams =
850 c2d3219b Iustin Pop
  renameField "InstOsParams" . defaultField [| toJSObject [] |] $
851 6d558717 Iustin Pop
  simpleField "osparams" [t| UncheckedDict |]
852 6d558717 Iustin Pop
853 c2d3219b Iustin Pop
-- | Temporary OS parameters (currently only in reinstall, might be
854 c2d3219b Iustin Pop
-- added to install as well).
855 c2d3219b Iustin Pop
pTempOsParams :: Field
856 c2d3219b Iustin Pop
pTempOsParams =
857 c2d3219b Iustin Pop
  renameField "TempOsParams" .
858 c2d3219b Iustin Pop
  optionalField $ simpleField "osparams" [t| UncheckedDict |]
859 c2d3219b Iustin Pop
860 c2d3219b Iustin Pop
-- | Temporary hypervisor parameters, hypervisor-dependent.
861 c2d3219b Iustin Pop
pTempHvParams :: Field
862 c2d3219b Iustin Pop
pTempHvParams =
863 c2d3219b Iustin Pop
  renameField "TempHvParams" .
864 c2d3219b Iustin Pop
  defaultField [| toJSObject [] |] $
865 c2d3219b Iustin Pop
  simpleField "hvparams" [t| UncheckedDict |]
866 c2d3219b Iustin Pop
867 c2d3219b Iustin Pop
-- | Temporary backend parameters.
868 c2d3219b Iustin Pop
pTempBeParams :: Field
869 c2d3219b Iustin Pop
pTempBeParams =
870 c2d3219b Iustin Pop
  renameField "TempBeParams" .
871 c2d3219b Iustin Pop
  defaultField [| toJSObject [] |] $
872 c2d3219b Iustin Pop
  simpleField "beparams" [t| UncheckedDict |]
873 c2d3219b Iustin Pop
874 d6979f35 Iustin Pop
-- | Candidate pool size.
875 d6979f35 Iustin Pop
pCandidatePoolSize :: Field
876 d6979f35 Iustin Pop
pCandidatePoolSize =
877 d6979f35 Iustin Pop
  optionalField $ simpleField "candidate_pool_size" [t| Positive Int |]
878 d6979f35 Iustin Pop
879 d6979f35 Iustin Pop
-- | Set UID pool, must be list of lists describing UID ranges (two
880 d6979f35 Iustin Pop
-- items, start and end inclusive.
881 d6979f35 Iustin Pop
pUidPool :: Field
882 d6979f35 Iustin Pop
pUidPool = optionalField $ simpleField "uid_pool" [t| [[(Int, Int)]] |]
883 d6979f35 Iustin Pop
884 d6979f35 Iustin Pop
-- | Extend UID pool, must be list of lists describing UID ranges (two
885 d6979f35 Iustin Pop
-- items, start and end inclusive.
886 d6979f35 Iustin Pop
pAddUids :: Field
887 d6979f35 Iustin Pop
pAddUids = optionalField $ simpleField "add_uids" [t| [[(Int, Int)]] |]
888 d6979f35 Iustin Pop
889 d6979f35 Iustin Pop
-- | Shrink UID pool, must be list of lists describing UID ranges (two
890 d6979f35 Iustin Pop
-- items, start and end inclusive) to be removed.
891 d6979f35 Iustin Pop
pRemoveUids :: Field
892 d6979f35 Iustin Pop
pRemoveUids = optionalField $ simpleField "remove_uids" [t| [[(Int, Int)]] |]
893 d6979f35 Iustin Pop
894 d6979f35 Iustin Pop
-- | Whether to automatically maintain node health.
895 d6979f35 Iustin Pop
pMaintainNodeHealth :: Field
896 d6979f35 Iustin Pop
pMaintainNodeHealth = optionalField $ booleanField "maintain_node_health"
897 d6979f35 Iustin Pop
898 d6979f35 Iustin Pop
-- | Whether to wipe disks before allocating them to instances.
899 d6979f35 Iustin Pop
pPreallocWipeDisks :: Field
900 d6979f35 Iustin Pop
pPreallocWipeDisks = optionalField $ booleanField "prealloc_wipe_disks"
901 d6979f35 Iustin Pop
902 d6979f35 Iustin Pop
-- | Cluster-wide NIC parameter defaults.
903 d6979f35 Iustin Pop
pNicParams :: Field
904 d6979f35 Iustin Pop
pNicParams = optionalField $ simpleField "nicparams" [t| INicParams |]
905 d6979f35 Iustin Pop
906 6d558717 Iustin Pop
-- | Instance NIC definitions.
907 6d558717 Iustin Pop
pInstNics :: Field
908 6d558717 Iustin Pop
pInstNics = simpleField "nics" [t| [INicParams] |]
909 6d558717 Iustin Pop
910 d6979f35 Iustin Pop
-- | Cluster-wide node parameter defaults.
911 d6979f35 Iustin Pop
pNdParams :: Field
912 d6979f35 Iustin Pop
pNdParams = optionalField $ simpleField "ndparams" [t| UncheckedDict |]
913 d6979f35 Iustin Pop
914 398e9066 Iustin Pop
-- | Cluster-wide ipolicy specs.
915 d6979f35 Iustin Pop
pIpolicy :: Field
916 d6979f35 Iustin Pop
pIpolicy = optionalField $ simpleField "ipolicy" [t| UncheckedDict |]
917 d6979f35 Iustin Pop
918 d6979f35 Iustin Pop
-- | DRBD helper program.
919 d6979f35 Iustin Pop
pDrbdHelper :: Field
920 d6979f35 Iustin Pop
pDrbdHelper = optionalStringField "drbd_helper"
921 d6979f35 Iustin Pop
922 d6979f35 Iustin Pop
-- | Default iallocator for cluster.
923 d6979f35 Iustin Pop
pDefaultIAllocator :: Field
924 d6979f35 Iustin Pop
pDefaultIAllocator = optionalStringField "default_iallocator"
925 d6979f35 Iustin Pop
926 d6979f35 Iustin Pop
-- | Master network device.
927 d6979f35 Iustin Pop
pMasterNetdev :: Field
928 d6979f35 Iustin Pop
pMasterNetdev = optionalStringField "master_netdev"
929 d6979f35 Iustin Pop
930 d6979f35 Iustin Pop
-- | Netmask of the master IP.
931 d6979f35 Iustin Pop
pMasterNetmask :: Field
932 67fc4de7 Iustin Pop
pMasterNetmask =
933 67fc4de7 Iustin Pop
  optionalField $ simpleField "master_netmask" [t| NonNegative Int |]
934 d6979f35 Iustin Pop
935 d6979f35 Iustin Pop
-- | List of reserved LVs.
936 d6979f35 Iustin Pop
pReservedLvs :: Field
937 d6979f35 Iustin Pop
pReservedLvs =
938 d6979f35 Iustin Pop
  optionalField $ simpleField "reserved_lvs" [t| [NonEmptyString] |]
939 d6979f35 Iustin Pop
940 d6979f35 Iustin Pop
-- | Modify list of hidden operating systems: each modification must
941 d6979f35 Iustin Pop
-- have two items, the operation and the OS name; the operation can be
942 d6979f35 Iustin Pop
-- add or remove.
943 d6979f35 Iustin Pop
pHiddenOs :: Field
944 d6979f35 Iustin Pop
pHiddenOs = optionalField $ simpleField "hidden_os" [t| TestClusterOsList |]
945 d6979f35 Iustin Pop
946 d6979f35 Iustin Pop
-- | Modify list of blacklisted operating systems: each modification
947 d6979f35 Iustin Pop
-- must have two items, the operation and the OS name; the operation
948 d6979f35 Iustin Pop
-- can be add or remove.
949 d6979f35 Iustin Pop
pBlacklistedOs :: Field
950 d6979f35 Iustin Pop
pBlacklistedOs =
951 d6979f35 Iustin Pop
  optionalField $ simpleField "blacklisted_os" [t| TestClusterOsList |]
952 d6979f35 Iustin Pop
953 d6979f35 Iustin Pop
-- | Whether to use an external master IP address setup script.
954 d6979f35 Iustin Pop
pUseExternalMipScript :: Field
955 d6979f35 Iustin Pop
pUseExternalMipScript = optionalField $ booleanField "use_external_mip_script"
956 d6979f35 Iustin Pop
957 d6979f35 Iustin Pop
-- | Requested fields.
958 d6979f35 Iustin Pop
pQueryFields :: Field
959 d6979f35 Iustin Pop
pQueryFields = simpleField "fields" [t| [NonEmptyString] |]
960 d6979f35 Iustin Pop
961 d6979f35 Iustin Pop
-- | Query filter.
962 d6979f35 Iustin Pop
pQueryFilter :: Field
963 d6979f35 Iustin Pop
pQueryFilter = simpleField "qfilter" [t| Qlang.Filter String |]
964 d6979f35 Iustin Pop
965 d6979f35 Iustin Pop
-- | OOB command to run.
966 d6979f35 Iustin Pop
pOobCommand :: Field
967 d6979f35 Iustin Pop
pOobCommand = simpleField "command" [t| OobCommand |]
968 d6979f35 Iustin Pop
969 d6979f35 Iustin Pop
-- | Timeout before the OOB helper will be terminated.
970 d6979f35 Iustin Pop
pOobTimeout :: Field
971 d6979f35 Iustin Pop
pOobTimeout =
972 d6979f35 Iustin Pop
  defaultField [| C.oobTimeout |] $ simpleField "timeout" [t| Int |]
973 d6979f35 Iustin Pop
974 d6979f35 Iustin Pop
-- | Ignores the node offline status for power off.
975 d6979f35 Iustin Pop
pIgnoreStatus :: Field
976 d6979f35 Iustin Pop
pIgnoreStatus = defaultFalse "ignore_status"
977 d6979f35 Iustin Pop
978 d6979f35 Iustin Pop
-- | Time in seconds to wait between powering on nodes.
979 d6979f35 Iustin Pop
pPowerDelay :: Field
980 d6979f35 Iustin Pop
pPowerDelay =
981 d6979f35 Iustin Pop
  -- FIXME: we can't use the proper type "NonNegative Double", since
982 d6979f35 Iustin Pop
  -- the default constant is a plain Double, not a non-negative one.
983 d6979f35 Iustin Pop
  defaultField [| C.oobPowerDelay |] $
984 d6979f35 Iustin Pop
  simpleField "power_delay" [t| Double |]
985 d6979f35 Iustin Pop
986 d6979f35 Iustin Pop
-- | Primary IP address.
987 d6979f35 Iustin Pop
pPrimaryIp :: Field
988 d6979f35 Iustin Pop
pPrimaryIp = optionalStringField "primary_ip"
989 d6979f35 Iustin Pop
990 d6979f35 Iustin Pop
-- | Secondary IP address.
991 d6979f35 Iustin Pop
pSecondaryIp :: Field
992 d6979f35 Iustin Pop
pSecondaryIp = optionalNEStringField "secondary_ip"
993 d6979f35 Iustin Pop
994 d6979f35 Iustin Pop
-- | Whether node is re-added to cluster.
995 d6979f35 Iustin Pop
pReadd :: Field
996 d6979f35 Iustin Pop
pReadd = defaultFalse "readd"
997 d6979f35 Iustin Pop
998 d6979f35 Iustin Pop
-- | Initial node group.
999 d6979f35 Iustin Pop
pNodeGroup :: Field
1000 d6979f35 Iustin Pop
pNodeGroup = optionalNEStringField "group"
1001 d6979f35 Iustin Pop
1002 d6979f35 Iustin Pop
-- | Whether node can become master or master candidate.
1003 d6979f35 Iustin Pop
pMasterCapable :: Field
1004 d6979f35 Iustin Pop
pMasterCapable = optionalField $ booleanField "master_capable"
1005 d6979f35 Iustin Pop
1006 d6979f35 Iustin Pop
-- | Whether node can host instances.
1007 d6979f35 Iustin Pop
pVmCapable :: Field
1008 d6979f35 Iustin Pop
pVmCapable = optionalField $ booleanField "vm_capable"
1009 d6979f35 Iustin Pop
1010 d6979f35 Iustin Pop
-- | List of names.
1011 d6979f35 Iustin Pop
pNames :: Field
1012 d6979f35 Iustin Pop
pNames = defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
1013 d6979f35 Iustin Pop
1014 d6979f35 Iustin Pop
-- | List of node names.
1015 d6979f35 Iustin Pop
pNodes :: Field
1016 d6979f35 Iustin Pop
pNodes = defaultField [| [] |] $ simpleField "nodes" [t| [NonEmptyString] |]
1017 d6979f35 Iustin Pop
1018 398e9066 Iustin Pop
-- | Required list of node names.
1019 398e9066 Iustin Pop
pRequiredNodes :: Field
1020 398e9066 Iustin Pop
pRequiredNodes =
1021 398e9066 Iustin Pop
  renameField "ReqNodes " $ simpleField "nodes" [t| [NonEmptyString] |]
1022 398e9066 Iustin Pop
1023 1c3231aa Thomas Thrainer
-- | Required list of node names.
1024 1c3231aa Thomas Thrainer
pRequiredNodeUuids :: Field
1025 1c3231aa Thomas Thrainer
pRequiredNodeUuids =
1026 1c3231aa Thomas Thrainer
  renameField "ReqNodeUuids " . optionalField $
1027 1c3231aa Thomas Thrainer
    simpleField "node_uuids" [t| [NonEmptyString] |]
1028 1c3231aa Thomas Thrainer
1029 d6979f35 Iustin Pop
-- | Storage type.
1030 d6979f35 Iustin Pop
pStorageType :: Field
1031 d6979f35 Iustin Pop
pStorageType = simpleField "storage_type" [t| StorageType |]
1032 d6979f35 Iustin Pop
1033 d6979f35 Iustin Pop
-- | Storage changes (unchecked).
1034 d6979f35 Iustin Pop
pStorageChanges :: Field
1035 d6979f35 Iustin Pop
pStorageChanges = simpleField "changes" [t| UncheckedDict |]
1036 d6979f35 Iustin Pop
1037 d6979f35 Iustin Pop
-- | Whether the node should become a master candidate.
1038 d6979f35 Iustin Pop
pMasterCandidate :: Field
1039 d6979f35 Iustin Pop
pMasterCandidate = optionalField $ booleanField "master_candidate"
1040 d6979f35 Iustin Pop
1041 d6979f35 Iustin Pop
-- | Whether the node should be marked as offline.
1042 d6979f35 Iustin Pop
pOffline :: Field
1043 d6979f35 Iustin Pop
pOffline = optionalField $ booleanField "offline"
1044 d6979f35 Iustin Pop
1045 d6979f35 Iustin Pop
-- | Whether the node should be marked as drained.
1046 d6979f35 Iustin Pop
pDrained ::Field
1047 d6979f35 Iustin Pop
pDrained = optionalField $ booleanField "drained"
1048 d6979f35 Iustin Pop
1049 d6979f35 Iustin Pop
-- | Whether node(s) should be promoted to master candidate if necessary.
1050 d6979f35 Iustin Pop
pAutoPromote :: Field
1051 d6979f35 Iustin Pop
pAutoPromote = defaultFalse "auto_promote"
1052 d6979f35 Iustin Pop
1053 d6979f35 Iustin Pop
-- | Whether the node should be marked as powered
1054 d6979f35 Iustin Pop
pPowered :: Field
1055 d6979f35 Iustin Pop
pPowered = optionalField $ booleanField "powered"
1056 d6979f35 Iustin Pop
1057 d6979f35 Iustin Pop
-- | Iallocator for deciding the target node for shared-storage
1058 d6979f35 Iustin Pop
-- instances during migrate and failover.
1059 d6979f35 Iustin Pop
pIallocator :: Field
1060 d6979f35 Iustin Pop
pIallocator = optionalNEStringField "iallocator"
1061 d6979f35 Iustin Pop
1062 d6979f35 Iustin Pop
-- | New secondary node.
1063 d6979f35 Iustin Pop
pRemoteNode :: Field
1064 d6979f35 Iustin Pop
pRemoteNode = optionalNEStringField "remote_node"
1065 d6979f35 Iustin Pop
1066 1c3231aa Thomas Thrainer
-- | New secondary node UUID.
1067 1c3231aa Thomas Thrainer
pRemoteNodeUuid :: Field
1068 1c3231aa Thomas Thrainer
pRemoteNodeUuid = optionalNEStringField "remote_node_uuid"
1069 1c3231aa Thomas Thrainer
1070 d6979f35 Iustin Pop
-- | Node evacuation mode.
1071 d6979f35 Iustin Pop
pEvacMode :: Field
1072 d6979f35 Iustin Pop
pEvacMode = renameField "EvacMode" $ simpleField "mode" [t| NodeEvacMode |]
1073 6d558717 Iustin Pop
1074 6d558717 Iustin Pop
-- | Instance creation mode.
1075 6d558717 Iustin Pop
pInstCreateMode :: Field
1076 6d558717 Iustin Pop
pInstCreateMode =
1077 6d558717 Iustin Pop
  renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
1078 6d558717 Iustin Pop
1079 6d558717 Iustin Pop
-- | Do not install the OS (will disable automatic start).
1080 6d558717 Iustin Pop
pNoInstall :: Field
1081 6d558717 Iustin Pop
pNoInstall = optionalField $ booleanField "no_install"
1082 6d558717 Iustin Pop
1083 6d558717 Iustin Pop
-- | OS type for instance installation.
1084 6d558717 Iustin Pop
pInstOs :: Field
1085 6d558717 Iustin Pop
pInstOs = optionalNEStringField "os_type"
1086 6d558717 Iustin Pop
1087 6d558717 Iustin Pop
-- | Primary node for an instance.
1088 6d558717 Iustin Pop
pPrimaryNode :: Field
1089 6d558717 Iustin Pop
pPrimaryNode = optionalNEStringField "pnode"
1090 6d558717 Iustin Pop
1091 1c3231aa Thomas Thrainer
-- | Primary node UUID for an instance.
1092 1c3231aa Thomas Thrainer
pPrimaryNodeUuid :: Field
1093 1c3231aa Thomas Thrainer
pPrimaryNodeUuid = optionalNEStringField "pnode_uuid"
1094 1c3231aa Thomas Thrainer
1095 6d558717 Iustin Pop
-- | Secondary node for an instance.
1096 6d558717 Iustin Pop
pSecondaryNode :: Field
1097 6d558717 Iustin Pop
pSecondaryNode = optionalNEStringField "snode"
1098 6d558717 Iustin Pop
1099 1c3231aa Thomas Thrainer
-- | Secondary node UUID for an instance.
1100 1c3231aa Thomas Thrainer
pSecondaryNodeUuid :: Field
1101 1c3231aa Thomas Thrainer
pSecondaryNodeUuid = optionalNEStringField "snode_uuid"
1102 1c3231aa Thomas Thrainer
1103 6d558717 Iustin Pop
-- | Signed handshake from source (remote import only).
1104 6d558717 Iustin Pop
pSourceHandshake :: Field
1105 6d558717 Iustin Pop
pSourceHandshake =
1106 6d558717 Iustin Pop
  optionalField $ simpleField "source_handshake" [t| UncheckedList |]
1107 6d558717 Iustin Pop
1108 6d558717 Iustin Pop
-- | Source instance name (remote import only).
1109 6d558717 Iustin Pop
pSourceInstance :: Field
1110 6d558717 Iustin Pop
pSourceInstance = optionalNEStringField "source_instance_name"
1111 6d558717 Iustin Pop
1112 6d558717 Iustin Pop
-- | How long source instance was given to shut down (remote import only).
1113 6d558717 Iustin Pop
-- FIXME: non-negative int, whereas the constant is a plain int.
1114 6d558717 Iustin Pop
pSourceShutdownTimeout :: Field
1115 6d558717 Iustin Pop
pSourceShutdownTimeout =
1116 6d558717 Iustin Pop
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1117 6d558717 Iustin Pop
  simpleField "source_shutdown_timeout" [t| NonNegative Int |]
1118 6d558717 Iustin Pop
1119 6d558717 Iustin Pop
-- | Source X509 CA in PEM format (remote import only).
1120 6d558717 Iustin Pop
pSourceX509Ca :: Field
1121 6d558717 Iustin Pop
pSourceX509Ca = optionalNEStringField "source_x509_ca"
1122 6d558717 Iustin Pop
1123 6d558717 Iustin Pop
-- | Source node for import.
1124 6d558717 Iustin Pop
pSrcNode :: Field
1125 6d558717 Iustin Pop
pSrcNode = optionalNEStringField "src_node"
1126 6d558717 Iustin Pop
1127 1c3231aa Thomas Thrainer
-- | Source node for import.
1128 1c3231aa Thomas Thrainer
pSrcNodeUuid :: Field
1129 1c3231aa Thomas Thrainer
pSrcNodeUuid = optionalNEStringField "src_node_uuid"
1130 1c3231aa Thomas Thrainer
1131 6d558717 Iustin Pop
-- | Source directory for import.
1132 6d558717 Iustin Pop
pSrcPath :: Field
1133 6d558717 Iustin Pop
pSrcPath = optionalNEStringField "src_path"
1134 6d558717 Iustin Pop
1135 6d558717 Iustin Pop
-- | Whether to start instance after creation.
1136 6d558717 Iustin Pop
pStartInstance :: Field
1137 6d558717 Iustin Pop
pStartInstance = defaultTrue "start"
1138 6d558717 Iustin Pop
1139 6d558717 Iustin Pop
-- | Instance tags. FIXME: unify/simplify with pTags, once that
1140 6d558717 Iustin Pop
-- migrates to NonEmpty String.
1141 6d558717 Iustin Pop
pInstTags :: Field
1142 6d558717 Iustin Pop
pInstTags =
1143 6d558717 Iustin Pop
  renameField "InstTags" .
1144 6d558717 Iustin Pop
  defaultField [| [] |] $
1145 6d558717 Iustin Pop
  simpleField "tags" [t| [NonEmptyString] |]
1146 c2d3219b Iustin Pop
1147 c2d3219b Iustin Pop
-- | Unchecked list of OpInstanceCreate, used in OpInstanceMultiAlloc.
1148 c2d3219b Iustin Pop
pMultiAllocInstances :: Field
1149 c2d3219b Iustin Pop
pMultiAllocInstances =
1150 c2d3219b Iustin Pop
  renameField "InstMultiAlloc" .
1151 c2d3219b Iustin Pop
  defaultField [| [] |] $
1152 c2d3219b Iustin Pop
  simpleField "instances"[t| UncheckedList |]
1153 c2d3219b Iustin Pop
1154 c2d3219b Iustin Pop
-- | Ignore failures parameter.
1155 c2d3219b Iustin Pop
pIgnoreFailures :: Field
1156 c2d3219b Iustin Pop
pIgnoreFailures = defaultFalse "ignore_failures"
1157 c2d3219b Iustin Pop
1158 c2d3219b Iustin Pop
-- | New instance or cluster name.
1159 c2d3219b Iustin Pop
pNewName :: Field
1160 c2d3219b Iustin Pop
pNewName = simpleField "new_name" [t| NonEmptyString |]
1161 c2d3219b Iustin Pop
1162 c2d3219b Iustin Pop
-- | Whether to start the instance even if secondary disks are failing.
1163 c2d3219b Iustin Pop
pIgnoreSecondaries :: Field
1164 c2d3219b Iustin Pop
pIgnoreSecondaries = defaultFalse "ignore_secondaries"
1165 c2d3219b Iustin Pop
1166 c2d3219b Iustin Pop
-- | How to reboot the instance.
1167 c2d3219b Iustin Pop
pRebootType :: Field
1168 c2d3219b Iustin Pop
pRebootType = simpleField "reboot_type" [t| RebootType |]
1169 c2d3219b Iustin Pop
1170 c2d3219b Iustin Pop
-- | Whether to ignore recorded disk size.
1171 c2d3219b Iustin Pop
pIgnoreDiskSize :: Field
1172 c2d3219b Iustin Pop
pIgnoreDiskSize = defaultFalse "ignore_size"
1173 c2d3219b Iustin Pop
1174 c2d3219b Iustin Pop
-- | Disk list for recreate disks.
1175 c2d3219b Iustin Pop
pRecreateDisksInfo :: Field
1176 c2d3219b Iustin Pop
pRecreateDisksInfo =
1177 c2d3219b Iustin Pop
  renameField "RecreateDisksInfo" .
1178 c2d3219b Iustin Pop
  defaultField [| RecreateDisksAll |] $
1179 c2d3219b Iustin Pop
  simpleField "disks" [t| RecreateDisksInfo |]
1180 c2d3219b Iustin Pop
1181 c2d3219b Iustin Pop
-- | Whether to only return configuration data without querying nodes.
1182 c2d3219b Iustin Pop
pStatic :: Field
1183 c2d3219b Iustin Pop
pStatic = defaultFalse "static"
1184 c2d3219b Iustin Pop
1185 c2d3219b Iustin Pop
-- | InstanceSetParams NIC changes.
1186 c2d3219b Iustin Pop
pInstParamsNicChanges :: Field
1187 c2d3219b Iustin Pop
pInstParamsNicChanges =
1188 c2d3219b Iustin Pop
  renameField "InstNicChanges" .
1189 c2d3219b Iustin Pop
  defaultField [| SetParamsEmpty |] $
1190 c2d3219b Iustin Pop
  simpleField "nics" [t| SetParamsMods INicParams |]
1191 c2d3219b Iustin Pop
1192 c2d3219b Iustin Pop
-- | InstanceSetParams Disk changes.
1193 c2d3219b Iustin Pop
pInstParamsDiskChanges :: Field
1194 c2d3219b Iustin Pop
pInstParamsDiskChanges =
1195 c2d3219b Iustin Pop
  renameField "InstDiskChanges" .
1196 c2d3219b Iustin Pop
  defaultField [| SetParamsEmpty |] $
1197 c2d3219b Iustin Pop
  simpleField "disks" [t| SetParamsMods IDiskParams |]
1198 c2d3219b Iustin Pop
1199 c2d3219b Iustin Pop
-- | New runtime memory.
1200 c2d3219b Iustin Pop
pRuntimeMem :: Field
1201 c2d3219b Iustin Pop
pRuntimeMem = optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1202 c2d3219b Iustin Pop
1203 c2d3219b Iustin Pop
-- | Change the instance's OS without reinstalling the instance
1204 c2d3219b Iustin Pop
pOsNameChange :: Field
1205 c2d3219b Iustin Pop
pOsNameChange = optionalNEStringField "os_name"
1206 c2d3219b Iustin Pop
1207 c2d3219b Iustin Pop
-- | Disk index for e.g. grow disk.
1208 c2d3219b Iustin Pop
pDiskIndex :: Field
1209 c2d3219b Iustin Pop
pDiskIndex = renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
1210 c2d3219b Iustin Pop
1211 c2d3219b Iustin Pop
-- | Disk amount to add or grow to.
1212 c2d3219b Iustin Pop
pDiskChgAmount :: Field
1213 c2d3219b Iustin Pop
pDiskChgAmount =
1214 c2d3219b Iustin Pop
  renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
1215 c2d3219b Iustin Pop
1216 c2d3219b Iustin Pop
-- | Whether the amount parameter is an absolute target or a relative one.
1217 c2d3219b Iustin Pop
pDiskChgAbsolute :: Field
1218 c2d3219b Iustin Pop
pDiskChgAbsolute = renameField "DiskChkAbsolute" $ defaultFalse "absolute"
1219 c2d3219b Iustin Pop
1220 c2d3219b Iustin Pop
-- | Destination group names or UUIDs (defaults to \"all but current group\".
1221 c2d3219b Iustin Pop
pTargetGroups :: Field
1222 c2d3219b Iustin Pop
pTargetGroups =
1223 c2d3219b Iustin Pop
  optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
1224 398e9066 Iustin Pop
1225 398e9066 Iustin Pop
-- | Export mode field.
1226 398e9066 Iustin Pop
pExportMode :: Field
1227 398e9066 Iustin Pop
pExportMode =
1228 398e9066 Iustin Pop
  renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1229 398e9066 Iustin Pop
1230 398e9066 Iustin Pop
-- | Export target_node field, depends on mode.
1231 398e9066 Iustin Pop
pExportTargetNode :: Field
1232 398e9066 Iustin Pop
pExportTargetNode =
1233 398e9066 Iustin Pop
  renameField "ExportTarget" $
1234 398e9066 Iustin Pop
  simpleField "target_node" [t| ExportTarget |]
1235 398e9066 Iustin Pop
1236 1c3231aa Thomas Thrainer
-- | Export target node UUID field.
1237 1c3231aa Thomas Thrainer
pExportTargetNodeUuid :: Field
1238 1c3231aa Thomas Thrainer
pExportTargetNodeUuid =
1239 1c3231aa Thomas Thrainer
  renameField "ExportTargetNodeUuid" . optionalField $
1240 1c3231aa Thomas Thrainer
  simpleField "target_node_uuid" [t| NonEmptyString |]
1241 1c3231aa Thomas Thrainer
1242 398e9066 Iustin Pop
-- | Whether to remove instance after export.
1243 398e9066 Iustin Pop
pRemoveInstance :: Field
1244 398e9066 Iustin Pop
pRemoveInstance = defaultFalse "remove_instance"
1245 398e9066 Iustin Pop
1246 398e9066 Iustin Pop
-- | Whether to ignore failures while removing instances.
1247 398e9066 Iustin Pop
pIgnoreRemoveFailures :: Field
1248 398e9066 Iustin Pop
pIgnoreRemoveFailures = defaultFalse "ignore_remove_failures"
1249 398e9066 Iustin Pop
1250 398e9066 Iustin Pop
-- | Name of X509 key (remote export only).
1251 398e9066 Iustin Pop
pX509KeyName :: Field
1252 398e9066 Iustin Pop
pX509KeyName = optionalField $ simpleField "x509_key_name" [t| UncheckedList |]
1253 398e9066 Iustin Pop
1254 398e9066 Iustin Pop
-- | Destination X509 CA (remote export only).
1255 398e9066 Iustin Pop
pX509DestCA :: Field
1256 398e9066 Iustin Pop
pX509DestCA = optionalNEStringField "destination_x509_ca"
1257 a451dae2 Iustin Pop
1258 a451dae2 Iustin Pop
-- | Search pattern (regular expression). FIXME: this should be
1259 a451dae2 Iustin Pop
-- compiled at load time?
1260 a451dae2 Iustin Pop
pTagSearchPattern :: Field
1261 a451dae2 Iustin Pop
pTagSearchPattern =
1262 a451dae2 Iustin Pop
  renameField "TagSearchPattern" $ simpleField "pattern" [t| NonEmptyString |]
1263 a451dae2 Iustin Pop
1264 1cd563e2 Iustin Pop
-- | Restricted command name.
1265 1cd563e2 Iustin Pop
pRestrictedCommand :: Field
1266 1cd563e2 Iustin Pop
pRestrictedCommand =
1267 1cd563e2 Iustin Pop
  renameField "RestrictedCommand" $
1268 1cd563e2 Iustin Pop
  simpleField "command" [t| NonEmptyString |]
1269 1cd563e2 Iustin Pop
1270 7d421386 Iustin Pop
-- | Replace disks mode.
1271 7d421386 Iustin Pop
pReplaceDisksMode :: Field
1272 7d421386 Iustin Pop
pReplaceDisksMode =
1273 7d421386 Iustin Pop
  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1274 7d421386 Iustin Pop
1275 7d421386 Iustin Pop
-- | List of disk indices.
1276 7d421386 Iustin Pop
pReplaceDisksList :: Field
1277 7d421386 Iustin Pop
pReplaceDisksList =
1278 7d421386 Iustin Pop
  renameField "ReplaceDisksList" $ simpleField "disks" [t| [DiskIndex] |]
1279 7d421386 Iustin Pop
1280 7d421386 Iustin Pop
-- | Whether do allow failover in migrations.
1281 7d421386 Iustin Pop
pAllowFailover :: Field
1282 7d421386 Iustin Pop
pAllowFailover = defaultFalse "allow_failover"
1283 7d421386 Iustin Pop
1284 a3f02317 Iustin Pop
-- * Test opcode parameters
1285 a3f02317 Iustin Pop
1286 7d421386 Iustin Pop
-- | Duration parameter for 'OpTestDelay'.
1287 7d421386 Iustin Pop
pDelayDuration :: Field
1288 7d421386 Iustin Pop
pDelayDuration =
1289 60f20a41 Iustin Pop
  renameField "DelayDuration" $ simpleField "duration" [t| Double |]
1290 7d421386 Iustin Pop
1291 7d421386 Iustin Pop
-- | on_master field for 'OpTestDelay'.
1292 7d421386 Iustin Pop
pDelayOnMaster :: Field
1293 7d421386 Iustin Pop
pDelayOnMaster = renameField "DelayOnMaster" $ defaultTrue "on_master"
1294 7d421386 Iustin Pop
1295 7d421386 Iustin Pop
-- | on_nodes field for 'OpTestDelay'.
1296 7d421386 Iustin Pop
pDelayOnNodes :: Field
1297 7d421386 Iustin Pop
pDelayOnNodes =
1298 7d421386 Iustin Pop
  renameField "DelayOnNodes" .
1299 7d421386 Iustin Pop
  defaultField [| [] |] $
1300 7d421386 Iustin Pop
  simpleField "on_nodes" [t| [NonEmptyString] |]
1301 7d421386 Iustin Pop
1302 1c3231aa Thomas Thrainer
-- | on_node_uuids field for 'OpTestDelay'.
1303 1c3231aa Thomas Thrainer
pDelayOnNodeUuids :: Field
1304 1c3231aa Thomas Thrainer
pDelayOnNodeUuids =
1305 1c3231aa Thomas Thrainer
  renameField "DelayOnNodeUuids" . optionalField $
1306 1c3231aa Thomas Thrainer
  simpleField "on_node_uuids" [t| [NonEmptyString] |]
1307 1c3231aa Thomas Thrainer
1308 a451dae2 Iustin Pop
-- | Repeat parameter for OpTestDelay.
1309 a451dae2 Iustin Pop
pDelayRepeat :: Field
1310 a451dae2 Iustin Pop
pDelayRepeat =
1311 a451dae2 Iustin Pop
  renameField "DelayRepeat" .
1312 a451dae2 Iustin Pop
  defaultField [| forceNonNeg (0::Int) |] $
1313 a451dae2 Iustin Pop
  simpleField "repeat" [t| NonNegative Int |]
1314 a3f02317 Iustin Pop
1315 a3f02317 Iustin Pop
-- | IAllocator test direction.
1316 a3f02317 Iustin Pop
pIAllocatorDirection :: Field
1317 a3f02317 Iustin Pop
pIAllocatorDirection =
1318 a3f02317 Iustin Pop
  renameField "IAllocatorDirection" $
1319 a3f02317 Iustin Pop
  simpleField "direction" [t| IAllocatorTestDir |]
1320 a3f02317 Iustin Pop
1321 a3f02317 Iustin Pop
-- | IAllocator test mode.
1322 a3f02317 Iustin Pop
pIAllocatorMode :: Field
1323 a3f02317 Iustin Pop
pIAllocatorMode =
1324 a3f02317 Iustin Pop
  renameField "IAllocatorMode" $
1325 a3f02317 Iustin Pop
  simpleField "mode" [t| IAllocatorMode |]
1326 a3f02317 Iustin Pop
1327 a3f02317 Iustin Pop
-- | IAllocator target name (new instance, node to evac, etc.).
1328 a3f02317 Iustin Pop
pIAllocatorReqName :: Field
1329 a3f02317 Iustin Pop
pIAllocatorReqName =
1330 a3f02317 Iustin Pop
  renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
1331 a3f02317 Iustin Pop
1332 a3f02317 Iustin Pop
-- | Custom OpTestIAllocator nics.
1333 a3f02317 Iustin Pop
pIAllocatorNics :: Field
1334 a3f02317 Iustin Pop
pIAllocatorNics =
1335 a3f02317 Iustin Pop
  renameField "IAllocatorNics" $ simpleField "nics" [t| [UncheckedDict] |]
1336 a3f02317 Iustin Pop
1337 a3f02317 Iustin Pop
-- | Custom OpTestAllocator disks.
1338 a3f02317 Iustin Pop
pIAllocatorDisks :: Field
1339 a3f02317 Iustin Pop
pIAllocatorDisks =
1340 a3f02317 Iustin Pop
  renameField "IAllocatorDisks" $ simpleField "disks" [t| UncheckedList |]
1341 a3f02317 Iustin Pop
1342 a3f02317 Iustin Pop
-- | IAllocator memory field.
1343 a3f02317 Iustin Pop
pIAllocatorMemory :: Field
1344 a3f02317 Iustin Pop
pIAllocatorMemory =
1345 a3f02317 Iustin Pop
  renameField "IAllocatorMem" .
1346 a3f02317 Iustin Pop
  optionalField $
1347 a3f02317 Iustin Pop
  simpleField "memory" [t| NonNegative Int |]
1348 a3f02317 Iustin Pop
1349 a3f02317 Iustin Pop
-- | IAllocator vcpus field.
1350 a3f02317 Iustin Pop
pIAllocatorVCpus :: Field
1351 a3f02317 Iustin Pop
pIAllocatorVCpus =
1352 a3f02317 Iustin Pop
  renameField "IAllocatorVCpus" .
1353 a3f02317 Iustin Pop
  optionalField $
1354 a3f02317 Iustin Pop
  simpleField "vcpus" [t| NonNegative Int |]
1355 a3f02317 Iustin Pop
1356 a3f02317 Iustin Pop
-- | IAllocator os field.
1357 a3f02317 Iustin Pop
pIAllocatorOs :: Field
1358 a3f02317 Iustin Pop
pIAllocatorOs = renameField "IAllocatorOs" $ optionalNEStringField "os"
1359 a3f02317 Iustin Pop
1360 a3f02317 Iustin Pop
-- | IAllocator instances field.
1361 a3f02317 Iustin Pop
pIAllocatorInstances :: Field
1362 a3f02317 Iustin Pop
pIAllocatorInstances =
1363 a3f02317 Iustin Pop
  renameField "IAllocatorInstances " .
1364 a3f02317 Iustin Pop
  optionalField $
1365 a3f02317 Iustin Pop
  simpleField "instances" [t| [NonEmptyString] |]
1366 a3f02317 Iustin Pop
1367 a3f02317 Iustin Pop
-- | IAllocator evac mode.
1368 a3f02317 Iustin Pop
pIAllocatorEvacMode :: Field
1369 a3f02317 Iustin Pop
pIAllocatorEvacMode =
1370 a3f02317 Iustin Pop
  renameField "IAllocatorEvacMode" .
1371 a3f02317 Iustin Pop
  optionalField $
1372 a3f02317 Iustin Pop
  simpleField "evac_mode" [t| NodeEvacMode |]
1373 a3f02317 Iustin Pop
1374 a3f02317 Iustin Pop
-- | IAllocator spindle use.
1375 a3f02317 Iustin Pop
pIAllocatorSpindleUse :: Field
1376 a3f02317 Iustin Pop
pIAllocatorSpindleUse =
1377 a3f02317 Iustin Pop
  renameField "IAllocatorSpindleUse" .
1378 a3f02317 Iustin Pop
  defaultField [| forceNonNeg (1::Int) |] $
1379 a3f02317 Iustin Pop
  simpleField "spindle_use" [t| NonNegative Int |]
1380 a3f02317 Iustin Pop
1381 a3f02317 Iustin Pop
-- | IAllocator count field.
1382 a3f02317 Iustin Pop
pIAllocatorCount :: Field
1383 a3f02317 Iustin Pop
pIAllocatorCount =
1384 a3f02317 Iustin Pop
  renameField "IAllocatorCount" .
1385 a3f02317 Iustin Pop
  defaultField [| forceNonNeg (1::Int) |] $
1386 a3f02317 Iustin Pop
  simpleField "count" [t| NonNegative Int |]
1387 a3f02317 Iustin Pop
1388 a3f02317 Iustin Pop
-- | 'OpTestJqueue' notify_waitlock.
1389 a3f02317 Iustin Pop
pJQueueNotifyWaitLock :: Field
1390 a3f02317 Iustin Pop
pJQueueNotifyWaitLock = defaultFalse "notify_waitlock"
1391 a3f02317 Iustin Pop
1392 a3f02317 Iustin Pop
-- | 'OpTestJQueue' notify_exec.
1393 a3f02317 Iustin Pop
pJQueueNotifyExec :: Field
1394 a3f02317 Iustin Pop
pJQueueNotifyExec = defaultFalse "notify_exec"
1395 a3f02317 Iustin Pop
1396 a3f02317 Iustin Pop
-- | 'OpTestJQueue' log_messages.
1397 a3f02317 Iustin Pop
pJQueueLogMessages :: Field
1398 a3f02317 Iustin Pop
pJQueueLogMessages =
1399 a3f02317 Iustin Pop
  defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
1400 a3f02317 Iustin Pop
1401 a3f02317 Iustin Pop
-- | 'OpTestJQueue' fail attribute.
1402 a3f02317 Iustin Pop
pJQueueFail :: Field
1403 a3f02317 Iustin Pop
pJQueueFail =
1404 a3f02317 Iustin Pop
  renameField "JQueueFail" $ defaultFalse "fail"
1405 a3f02317 Iustin Pop
1406 a3f02317 Iustin Pop
-- | 'OpTestDummy' result field.
1407 a3f02317 Iustin Pop
pTestDummyResult :: Field
1408 a3f02317 Iustin Pop
pTestDummyResult =
1409 a3f02317 Iustin Pop
  renameField "TestDummyResult" $ simpleField "result" [t| UncheckedValue |]
1410 a3f02317 Iustin Pop
1411 a3f02317 Iustin Pop
-- | 'OpTestDummy' messages field.
1412 a3f02317 Iustin Pop
pTestDummyMessages :: Field
1413 a3f02317 Iustin Pop
pTestDummyMessages =
1414 a3f02317 Iustin Pop
  renameField "TestDummyMessages" $
1415 a3f02317 Iustin Pop
  simpleField "messages" [t| UncheckedValue |]
1416 a3f02317 Iustin Pop
1417 a3f02317 Iustin Pop
-- | 'OpTestDummy' fail field.
1418 a3f02317 Iustin Pop
pTestDummyFail :: Field
1419 a3f02317 Iustin Pop
pTestDummyFail =
1420 a3f02317 Iustin Pop
  renameField "TestDummyFail" $ simpleField "fail" [t| UncheckedValue |]
1421 a3f02317 Iustin Pop
1422 a3f02317 Iustin Pop
-- | 'OpTestDummy' submit_jobs field.
1423 a3f02317 Iustin Pop
pTestDummySubmitJobs :: Field
1424 a3f02317 Iustin Pop
pTestDummySubmitJobs =
1425 a3f02317 Iustin Pop
  renameField "TestDummySubmitJobs" $
1426 a3f02317 Iustin Pop
  simpleField "submit_jobs" [t| UncheckedValue |]
1427 8d239fa4 Iustin Pop
1428 8d239fa4 Iustin Pop
-- * Network parameters
1429 8d239fa4 Iustin Pop
1430 8d239fa4 Iustin Pop
-- | Network name.
1431 8d239fa4 Iustin Pop
pNetworkName :: Field
1432 8d239fa4 Iustin Pop
pNetworkName = simpleField "network_name" [t| NonEmptyString |]
1433 8d239fa4 Iustin Pop
1434 8d239fa4 Iustin Pop
-- | Network address (IPv4 subnet). FIXME: no real type for this.
1435 8d239fa4 Iustin Pop
pNetworkAddress4 :: Field
1436 8d239fa4 Iustin Pop
pNetworkAddress4 =
1437 8d239fa4 Iustin Pop
  renameField "NetworkAddress4" $
1438 8d239fa4 Iustin Pop
  simpleField "network" [t| NonEmptyString |]
1439 8d239fa4 Iustin Pop
1440 8d239fa4 Iustin Pop
-- | Network gateway (IPv4 address). FIXME: no real type for this.
1441 8d239fa4 Iustin Pop
pNetworkGateway4 :: Field
1442 8d239fa4 Iustin Pop
pNetworkGateway4 =
1443 8d239fa4 Iustin Pop
  renameField "NetworkGateway4" $
1444 8d239fa4 Iustin Pop
  optionalNEStringField "gateway"
1445 8d239fa4 Iustin Pop
1446 8d239fa4 Iustin Pop
-- | Network address (IPv6 subnet). FIXME: no real type for this.
1447 8d239fa4 Iustin Pop
pNetworkAddress6 :: Field
1448 8d239fa4 Iustin Pop
pNetworkAddress6 =
1449 8d239fa4 Iustin Pop
  renameField "NetworkAddress6" $
1450 8d239fa4 Iustin Pop
  optionalNEStringField "network6"
1451 8d239fa4 Iustin Pop
1452 8d239fa4 Iustin Pop
-- | Network gateway (IPv6 address). FIXME: no real type for this.
1453 8d239fa4 Iustin Pop
pNetworkGateway6 :: Field
1454 8d239fa4 Iustin Pop
pNetworkGateway6 =
1455 8d239fa4 Iustin Pop
  renameField "NetworkGateway6" $
1456 8d239fa4 Iustin Pop
  optionalNEStringField "gateway6"
1457 8d239fa4 Iustin Pop
1458 8d239fa4 Iustin Pop
-- | Network specific mac prefix (that overrides the cluster one).
1459 8d239fa4 Iustin Pop
pNetworkMacPrefix :: Field
1460 8d239fa4 Iustin Pop
pNetworkMacPrefix =
1461 8d239fa4 Iustin Pop
  renameField "NetMacPrefix" $
1462 8d239fa4 Iustin Pop
  optionalNEStringField "mac_prefix"
1463 8d239fa4 Iustin Pop
1464 8d239fa4 Iustin Pop
-- | Network add reserved IPs.
1465 8d239fa4 Iustin Pop
pNetworkAddRsvdIps :: Field
1466 8d239fa4 Iustin Pop
pNetworkAddRsvdIps =
1467 8d239fa4 Iustin Pop
  renameField "NetworkAddRsvdIps" .
1468 8d239fa4 Iustin Pop
  optionalField $
1469 8d239fa4 Iustin Pop
  simpleField "add_reserved_ips" [t| [NonEmptyString] |]
1470 8d239fa4 Iustin Pop
1471 8d239fa4 Iustin Pop
-- | Network remove reserved IPs.
1472 8d239fa4 Iustin Pop
pNetworkRemoveRsvdIps :: Field
1473 8d239fa4 Iustin Pop
pNetworkRemoveRsvdIps =
1474 8d239fa4 Iustin Pop
  renameField "NetworkRemoveRsvdIps" .
1475 8d239fa4 Iustin Pop
  optionalField $
1476 8d239fa4 Iustin Pop
  simpleField "remove_reserved_ips" [t| [NonEmptyString] |]
1477 8d239fa4 Iustin Pop
1478 8d239fa4 Iustin Pop
-- | Network mode when connecting to a group.
1479 8d239fa4 Iustin Pop
pNetworkMode :: Field
1480 8d239fa4 Iustin Pop
pNetworkMode = simpleField "network_mode" [t| NICMode |]
1481 8d239fa4 Iustin Pop
1482 8d239fa4 Iustin Pop
-- | Network link when connecting to a group.
1483 8d239fa4 Iustin Pop
pNetworkLink :: Field
1484 8d239fa4 Iustin Pop
pNetworkLink = simpleField "network_link" [t| NonEmptyString |]
1485 3131adc7 Iustin Pop
1486 b46ba79c Iustin Pop
-- * Common opcode parameters
1487 b46ba79c Iustin Pop
1488 b46ba79c Iustin Pop
-- | Run checks only, don't execute.
1489 b46ba79c Iustin Pop
pDryRun :: Field
1490 b46ba79c Iustin Pop
pDryRun = optionalField $ booleanField "dry_run"
1491 b46ba79c Iustin Pop
1492 b46ba79c Iustin Pop
-- | Debug level.
1493 b46ba79c Iustin Pop
pDebugLevel :: Field
1494 b46ba79c Iustin Pop
pDebugLevel = optionalField $ simpleField "debug_level" [t| NonNegative Int |]
1495 b46ba79c Iustin Pop
1496 b46ba79c Iustin Pop
-- | Opcode priority. Note: python uses a separate constant, we're
1497 b46ba79c Iustin Pop
-- using the actual value we know it's the default.
1498 b46ba79c Iustin Pop
pOpPriority :: Field
1499 b46ba79c Iustin Pop
pOpPriority =
1500 b46ba79c Iustin Pop
  defaultField [| OpPrioNormal |] $
1501 b46ba79c Iustin Pop
  simpleField "priority" [t| OpSubmitPriority |]
1502 b46ba79c Iustin Pop
1503 b46ba79c Iustin Pop
-- | Job dependencies.
1504 b46ba79c Iustin Pop
pDependencies :: Field
1505 1496f5f3 Iustin Pop
pDependencies =
1506 1496f5f3 Iustin Pop
  optionalNullSerField $ simpleField "depends" [t| [JobDependency] |]
1507 b46ba79c Iustin Pop
1508 b46ba79c Iustin Pop
-- | Comment field.
1509 b46ba79c Iustin Pop
pComment :: Field
1510 1496f5f3 Iustin Pop
pComment = optionalNullSerField $ stringField "comment"
1511 b46ba79c Iustin Pop
1512 516a0e94 Michele Tartara
-- | Reason trail field.
1513 516a0e94 Michele Tartara
pReason :: Field
1514 516a0e94 Michele Tartara
pReason = simpleField C.opcodeReason [t| ReasonTrail |]
1515 516a0e94 Michele Tartara
1516 3131adc7 Iustin Pop
-- * Entire opcode parameter list
1517 3131adc7 Iustin Pop
1518 3131adc7 Iustin Pop
-- | Old-style query opcode, with locking.
1519 3131adc7 Iustin Pop
dOldQuery :: [Field]
1520 3131adc7 Iustin Pop
dOldQuery =
1521 3131adc7 Iustin Pop
  [ pOutputFields
1522 3131adc7 Iustin Pop
  , pNames
1523 3131adc7 Iustin Pop
  , pUseLocking
1524 3131adc7 Iustin Pop
  ]
1525 3131adc7 Iustin Pop
1526 3131adc7 Iustin Pop
-- | Old-style query opcode, without locking.
1527 3131adc7 Iustin Pop
dOldQueryNoLocking :: [Field]
1528 3131adc7 Iustin Pop
dOldQueryNoLocking =
1529 3131adc7 Iustin Pop
  [ pOutputFields
1530 3131adc7 Iustin Pop
  , pNames
1531 3131adc7 Iustin Pop
  ]