Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ 07e68848

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