Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ 93f1e606

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