Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ b75430d9

History | View | Annotate | Download (46.5 kB)

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