Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ 6dab85ff

History | View | Annotate | Download (44.6 kB)

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