Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ de36f091

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