Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ 7ad422ec

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