Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ d9f1d93c

History | View | Annotate | Download (44.4 kB)

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