Statistics
| Branch: | Tag: | Revision:

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

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