Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ 72e18df1

History | View | Annotate | Download (44.9 kB)

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