Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ dcd54d32

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