Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ 96e3dfa7

History | View | Annotate | Download (45.6 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

    
3
{-| Implementation of opcodes parameters.
4

    
5
These are defined in a separate module only due to TemplateHaskell
6
stage restrictions - expressions defined in the current module can't
7
be passed to splices. So we have to either parameters/repeat each
8
parameter definition multiple times, or separate them into this
9
module.
10

    
11
-}
12

    
13
{-
14

    
15
Copyright (C) 2012 Google Inc.
16

    
17
This program is free software; you can redistribute it and/or modify
18
it under the terms of the GNU General Public License as published by
19
the Free Software Foundation; either version 2 of the License, or
20
(at your option) any later version.
21

    
22
This program is distributed in the hope that it will be useful, but
23
WITHOUT ANY WARRANTY; without even the implied warranty of
24
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
25
General Public License for more details.
26

    
27
You should have received a copy of the GNU General Public License
28
along with this program; if not, write to the Free Software
29
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
30
02110-1301, USA.
31

    
32
-}
33

    
34
module Ganeti.OpParams
35
  ( ReplaceDisksMode(..)
36
  , DiskIndex
37
  , mkDiskIndex
38
  , unDiskIndex
39
  , DiskAccess(..)
40
  , INicParams(..)
41
  , IDiskParams(..)
42
  , RecreateDisksInfo(..)
43
  , DdmOldChanges(..)
44
  , SetParamsMods(..)
45
  , ExportTarget(..)
46
  , pInstanceName
47
  , pInstanceUuid
48
  , pInstances
49
  , pName
50
  , pTagsList
51
  , pTagsObject
52
  , pTagsName
53
  , pOutputFields
54
  , pShutdownTimeout
55
  , pShutdownTimeout'
56
  , pShutdownInstance
57
  , pForce
58
  , pIgnoreOfflineNodes
59
  , pNodeName
60
  , pNodeUuid
61
  , pNodeNames
62
  , pNodeUuids
63
  , pGroupName
64
  , pMigrationMode
65
  , pMigrationLive
66
  , pMigrationCleanup
67
  , pForceVariant
68
  , pWaitForSync
69
  , pWaitForSyncFalse
70
  , pIgnoreConsistency
71
  , pStorageName
72
  , pUseLocking
73
  , pOpportunisticLocking
74
  , pNameCheck
75
  , pNodeGroupAllocPolicy
76
  , pGroupNodeParams
77
  , pQueryWhat
78
  , pEarlyRelease
79
  , pIpCheck
80
  , pIpConflictsCheck
81
  , pNoRemember
82
  , pMigrationTargetNode
83
  , pMigrationTargetNodeUuid
84
  , pMoveTargetNode
85
  , pMoveTargetNodeUuid
86
  , pMoveCompress
87
  , pBackupCompress
88
  , pStartupPaused
89
  , pVerbose
90
  , pDebugSimulateErrors
91
  , pErrorCodes
92
  , pSkipChecks
93
  , pIgnoreErrors
94
  , pOptGroupName
95
  , pDiskParams
96
  , pHvState
97
  , pDiskState
98
  , pIgnoreIpolicy
99
  , pHotplug
100
  , pAllowRuntimeChgs
101
  , pInstDisks
102
  , pDiskTemplate
103
  , pOptDiskTemplate
104
  , pFileDriver
105
  , pFileStorageDir
106
  , pClusterFileStorageDir
107
  , pClusterSharedFileStorageDir
108
  , pVgName
109
  , pEnabledHypervisors
110
  , pHypervisor
111
  , pClusterHvParams
112
  , pInstHvParams
113
  , pClusterBeParams
114
  , pInstBeParams
115
  , pResetDefaults
116
  , pOsHvp
117
  , pClusterOsParams
118
  , pInstOsParams
119
  , pCandidatePoolSize
120
  , pUidPool
121
  , pAddUids
122
  , pRemoveUids
123
  , pMaintainNodeHealth
124
  , pModifyEtcHosts
125
  , pPreallocWipeDisks
126
  , pNicParams
127
  , pInstNics
128
  , pNdParams
129
  , pIpolicy
130
  , pDrbdHelper
131
  , pDefaultIAllocator
132
  , pMasterNetdev
133
  , pMasterNetmask
134
  , pReservedLvs
135
  , pHiddenOs
136
  , pBlacklistedOs
137
  , pUseExternalMipScript
138
  , pQueryFields
139
  , pQueryFilter
140
  , pQueryFieldsFields
141
  , pOobCommand
142
  , pOobTimeout
143
  , pIgnoreStatus
144
  , pPowerDelay
145
  , pPrimaryIp
146
  , pSecondaryIp
147
  , pReadd
148
  , pNodeGroup
149
  , pMasterCapable
150
  , pVmCapable
151
  , pNames
152
  , pNodes
153
  , pRequiredNodes
154
  , pRequiredNodeUuids
155
  , pStorageType
156
  , pStorageTypeOptional
157
  , pStorageChanges
158
  , pMasterCandidate
159
  , pOffline
160
  , pDrained
161
  , pAutoPromote
162
  , pPowered
163
  , pIallocator
164
  , pRemoteNode
165
  , pRemoteNodeUuid
166
  , pEvacMode
167
  , pInstCreateMode
168
  , pNoInstall
169
  , pInstOs
170
  , pPrimaryNode
171
  , pPrimaryNodeUuid
172
  , pSecondaryNode
173
  , pSecondaryNodeUuid
174
  , pSourceHandshake
175
  , pSourceInstance
176
  , pSourceShutdownTimeout
177
  , pSourceX509Ca
178
  , pSrcNode
179
  , pSrcNodeUuid
180
  , pSrcPath
181
  , pStartInstance
182
  , pInstTags
183
  , pMultiAllocInstances
184
  , pTempOsParams
185
  , pTempHvParams
186
  , pTempBeParams
187
  , pIgnoreFailures
188
  , pNewName
189
  , pIgnoreSecondaries
190
  , pRebootType
191
  , pIgnoreDiskSize
192
  , pRecreateDisksInfo
193
  , pStatic
194
  , pInstParamsNicChanges
195
  , pInstParamsDiskChanges
196
  , pRuntimeMem
197
  , pOsNameChange
198
  , pDiskIndex
199
  , pDiskChgAmount
200
  , pDiskChgAbsolute
201
  , pTargetGroups
202
  , pExportMode
203
  , pExportTargetNode
204
  , pExportTargetNodeUuid
205
  , pRemoveInstance
206
  , pIgnoreRemoveFailures
207
  , pX509KeyName
208
  , pX509DestCA
209
  , pTagSearchPattern
210
  , pRestrictedCommand
211
  , pReplaceDisksMode
212
  , pReplaceDisksList
213
  , pAllowFailover
214
  , pDelayDuration
215
  , pDelayOnMaster
216
  , pDelayOnNodes
217
  , pDelayOnNodeUuids
218
  , pDelayRepeat
219
  , pIAllocatorDirection
220
  , pIAllocatorMode
221
  , pIAllocatorReqName
222
  , pIAllocatorNics
223
  , pIAllocatorDisks
224
  , pIAllocatorMemory
225
  , pIAllocatorVCpus
226
  , pIAllocatorOs
227
  , pIAllocatorInstances
228
  , pIAllocatorEvacMode
229
  , pIAllocatorSpindleUse
230
  , pIAllocatorCount
231
  , pJQueueNotifyWaitLock
232
  , pJQueueNotifyExec
233
  , pJQueueLogMessages
234
  , pJQueueFail
235
  , pTestDummyResult
236
  , pTestDummyMessages
237
  , pTestDummyFail
238
  , pTestDummySubmitJobs
239
  , pNetworkName
240
  , pNetworkAddress4
241
  , pNetworkGateway4
242
  , pNetworkAddress6
243
  , pNetworkGateway6
244
  , pNetworkMacPrefix
245
  , pNetworkAddRsvdIps
246
  , pNetworkRemoveRsvdIps
247
  , pNetworkMode
248
  , pNetworkLink
249
  , pDryRun
250
  , pDebugLevel
251
  , pOpPriority
252
  , pDependencies
253
  , pComment
254
  , pReason
255
  , pEnabledDiskTemplates
256
  ) where
257

    
258
import Control.Monad (liftM, mplus)
259
import Text.JSON (JSON, JSValue(..), JSObject (..), readJSON, showJSON,
260
                  fromJSString, toJSObject)
261
import qualified Text.JSON
262
import Text.JSON.Pretty (pp_value)
263

    
264
import Ganeti.BasicTypes
265
import qualified Ganeti.Constants as C
266
import Ganeti.THH
267
import Ganeti.JSON
268
import Ganeti.Types
269
import qualified Ganeti.Query.Language as Qlang
270

    
271
-- * Helper functions and types
272

    
273
-- | Build a boolean field.
274
booleanField :: String -> Field
275
booleanField = flip simpleField [t| Bool |]
276

    
277
-- | Default a field to 'False'.
278
defaultFalse :: String -> Field
279
defaultFalse = defaultField [| False |] . booleanField
280

    
281
-- | Default a field to 'True'.
282
defaultTrue :: String -> Field
283
defaultTrue = defaultField [| True |] . booleanField
284

    
285
-- | An alias for a 'String' field.
286
stringField :: String -> Field
287
stringField = flip simpleField [t| String |]
288

    
289
-- | An alias for an optional string field.
290
optionalStringField :: String -> Field
291
optionalStringField = optionalField . stringField
292

    
293
-- | An alias for an optional non-empty string field.
294
optionalNEStringField :: String -> Field
295
optionalNEStringField = optionalField . flip simpleField [t| NonEmptyString |]
296

    
297
-- | Function to force a non-negative value, without returning via a
298
-- monad. This is needed for, and should be used /only/ in the case of
299
-- forcing constants. In case the constant is wrong (< 0), this will
300
-- become a runtime error.
301
forceNonNeg :: (Num a, Ord a, Show a) => a -> NonNegative a
302
forceNonNeg i = case mkNonNegative i of
303
                  Ok n -> n
304
                  Bad msg -> error msg
305

    
306
-- ** Disks
307

    
308
-- | Disk index type (embedding constraints on the index value via a
309
-- smart constructor).
310
newtype DiskIndex = DiskIndex { unDiskIndex :: Int }
311
  deriving (Show, Eq, Ord)
312

    
313
-- | Smart constructor for 'DiskIndex'.
314
mkDiskIndex :: (Monad m) => Int -> m DiskIndex
315
mkDiskIndex i | i >= 0 && i < C.maxDisks = return (DiskIndex i)
316
              | otherwise = fail $ "Invalid value for disk index '" ++
317
                            show i ++ "', required between 0 and " ++
318
                            show C.maxDisks
319

    
320
instance JSON DiskIndex where
321
  readJSON v = readJSON v >>= mkDiskIndex
322
  showJSON = showJSON . unDiskIndex
323

    
324
-- ** I* param types
325

    
326
-- | Type holding disk access modes.
327
$(declareSADT "DiskAccess"
328
  [ ("DiskReadOnly",  'C.diskRdonly)
329
  , ("DiskReadWrite", 'C.diskRdwr)
330
  ])
331
$(makeJSONInstance ''DiskAccess)
332

    
333
-- | NIC modification definition.
334
$(buildObject "INicParams" "inic"
335
  [ optionalField $ simpleField C.inicMac    [t| NonEmptyString |]
336
  , optionalField $ simpleField C.inicIp     [t| String         |]
337
  , optionalField $ simpleField C.inicMode   [t| NonEmptyString |]
338
  , optionalField $ simpleField C.inicLink   [t| NonEmptyString |]
339
  , optionalField $ simpleField C.inicName   [t| NonEmptyString |]
340
  , optionalField $ simpleField C.inicVlan   [t| String         |]
341
  , optionalField $ simpleField C.inicBridge [t| NonEmptyString |]
342
  ])
343

    
344
-- | Disk modification definition. FIXME: disksize should be VTYPE_UNIT.
345
$(buildObject "IDiskParams" "idisk"
346
  [ optionalField $ simpleField C.idiskSize   [t| Int            |]
347
  , optionalField $ simpleField C.idiskMode   [t| DiskAccess     |]
348
  , optionalField $ simpleField C.idiskAdopt  [t| NonEmptyString |]
349
  , optionalField $ simpleField C.idiskVg     [t| NonEmptyString |]
350
  , optionalField $ simpleField C.idiskMetavg [t| NonEmptyString |]
351
  , optionalField $ simpleField C.idiskName   [t| NonEmptyString |]
352
  , optionalField $ simpleField C.idiskSpindles [t| Int          |]
353
  ])
354

    
355
-- | Disk changes type for OpInstanceRecreateDisks. This is a bit
356
-- strange, because the type in Python is something like Either
357
-- [DiskIndex] [DiskChanges], but we can't represent the type of an
358
-- empty list in JSON, so we have to add a custom case for the empty
359
-- list.
360
data RecreateDisksInfo
361
  = RecreateDisksAll
362
  | RecreateDisksIndices (NonEmpty DiskIndex)
363
  | RecreateDisksParams (NonEmpty (DiskIndex, IDiskParams))
364
    deriving (Eq, Show)
365

    
366
readRecreateDisks :: JSValue -> Text.JSON.Result RecreateDisksInfo
367
readRecreateDisks (JSArray []) = return RecreateDisksAll
368
readRecreateDisks v =
369
  case readJSON v::Text.JSON.Result [DiskIndex] of
370
    Text.JSON.Ok indices -> liftM RecreateDisksIndices (mkNonEmpty indices)
371
    _ -> case readJSON v::Text.JSON.Result [(DiskIndex, IDiskParams)] of
372
           Text.JSON.Ok params -> liftM RecreateDisksParams (mkNonEmpty params)
373
           _ -> fail $ "Can't parse disk information as either list of disk"
374
                ++ " indices or list of disk parameters; value received:"
375
                ++ show (pp_value v)
376

    
377
instance JSON RecreateDisksInfo where
378
  readJSON = readRecreateDisks
379
  showJSON  RecreateDisksAll            = showJSON ()
380
  showJSON (RecreateDisksIndices idx)   = showJSON idx
381
  showJSON (RecreateDisksParams params) = showJSON params
382

    
383
-- | Simple type for old-style ddm changes.
384
data DdmOldChanges = DdmOldIndex (NonNegative Int)
385
                   | DdmOldMod DdmSimple
386
                     deriving (Eq, Show)
387

    
388
readDdmOldChanges :: JSValue -> Text.JSON.Result DdmOldChanges
389
readDdmOldChanges v =
390
  case readJSON v::Text.JSON.Result (NonNegative Int) of
391
    Text.JSON.Ok nn -> return $ DdmOldIndex nn
392
    _ -> case readJSON v::Text.JSON.Result DdmSimple of
393
           Text.JSON.Ok ddms -> return $ DdmOldMod ddms
394
           _ -> fail $ "Can't parse value '" ++ show (pp_value v) ++ "' as"
395
                ++ " either index or modification"
396

    
397
instance JSON DdmOldChanges where
398
  showJSON (DdmOldIndex i) = showJSON i
399
  showJSON (DdmOldMod m)   = showJSON m
400
  readJSON = readDdmOldChanges
401

    
402
-- | Instance disk or nic modifications.
403
data SetParamsMods a
404
  = SetParamsEmpty
405
  | SetParamsDeprecated (NonEmpty (DdmOldChanges, a))
406
  | SetParamsNew (NonEmpty (DdmFull, Int, a))
407
  | SetParamsNewName (NonEmpty (DdmFull, String, a))
408
    deriving (Eq, Show)
409

    
410
-- | Custom deserialiser for 'SetParamsMods'.
411
readSetParams :: (JSON a) => JSValue -> Text.JSON.Result (SetParamsMods a)
412
readSetParams (JSArray []) = return SetParamsEmpty
413
readSetParams v =
414
  liftM SetParamsDeprecated (readJSON v)
415
  `mplus` liftM SetParamsNew (readJSON v)
416
  `mplus` liftM SetParamsNewName (readJSON v)
417

    
418
instance (JSON a) => JSON (SetParamsMods a) where
419
  showJSON SetParamsEmpty = showJSON ()
420
  showJSON (SetParamsDeprecated v) = showJSON v
421
  showJSON (SetParamsNew v) = showJSON v
422
  showJSON (SetParamsNewName v) = showJSON v
423
  readJSON = readSetParams
424

    
425
-- | Custom type for target_node parameter of OpBackupExport, which
426
-- varies depending on mode. FIXME: this uses an [JSValue] since
427
-- we don't care about individual rows (just like the Python code
428
-- tests). But the proper type could be parsed if we wanted.
429
data ExportTarget = ExportTargetLocal NonEmptyString
430
                  | ExportTargetRemote [JSValue]
431
                    deriving (Eq, Show)
432

    
433
-- | Custom reader for 'ExportTarget'.
434
readExportTarget :: JSValue -> Text.JSON.Result ExportTarget
435
readExportTarget (JSString s) = liftM ExportTargetLocal $
436
                                mkNonEmpty (fromJSString s)
437
readExportTarget (JSArray arr) = return $ ExportTargetRemote arr
438
readExportTarget v = fail $ "Invalid value received for 'target_node': " ++
439
                     show (pp_value v)
440

    
441
instance JSON ExportTarget where
442
  showJSON (ExportTargetLocal s)  = showJSON s
443
  showJSON (ExportTargetRemote l) = showJSON l
444
  readJSON = readExportTarget
445

    
446
-- * Common opcode parameters
447

    
448
pDryRun :: Field
449
pDryRun =
450
  withDoc "Run checks only, don't execute" .
451
  optionalField $ booleanField "dry_run"
452

    
453
pDebugLevel :: Field
454
pDebugLevel =
455
  withDoc "Debug level" .
456
  optionalField $ simpleField "debug_level" [t| NonNegative Int |]
457

    
458
pOpPriority :: Field
459
pOpPriority =
460
  withDoc "Opcode priority. Note: python uses a separate constant,\
461
          \ we're using the actual value we know it's the default" .
462
  defaultField [| OpPrioNormal |] $
463
  simpleField "priority" [t| OpSubmitPriority |]
464

    
465
pDependencies :: Field
466
pDependencies =
467
  withDoc "Job dependencies" .
468
  optionalNullSerField $ simpleField "depends" [t| [JobDependency] |]
469

    
470
pComment :: Field
471
pComment =
472
  withDoc "Comment field" .
473
  optionalNullSerField $ stringField "comment"
474

    
475
pReason :: Field
476
pReason =
477
  withDoc "Reason trail field" $
478
  simpleField C.opcodeReason [t| ReasonTrail |]
479

    
480
-- * Parameters
481

    
482
pDebugSimulateErrors :: Field
483
pDebugSimulateErrors =
484
  withDoc "Whether to simulate errors (useful for debugging)" $
485
  defaultFalse "debug_simulate_errors"
486

    
487
pErrorCodes :: Field
488
pErrorCodes =
489
  withDoc "Error codes" $
490
  defaultFalse "error_codes"
491

    
492
pSkipChecks :: Field
493
pSkipChecks =
494
  withDoc "Which checks to skip" .
495
  defaultField [| emptyListSet |] $
496
  simpleField "skip_checks" [t| ListSet VerifyOptionalChecks |]
497

    
498
pIgnoreErrors :: Field
499
pIgnoreErrors =
500
  withDoc "List of error codes that should be treated as warnings" .
501
  defaultField [| emptyListSet |] $
502
  simpleField "ignore_errors" [t| ListSet CVErrorCode |]
503

    
504
pVerbose :: Field
505
pVerbose =
506
  withDoc "Verbose mode" $
507
  defaultFalse "verbose"
508

    
509
pOptGroupName :: Field
510
pOptGroupName =
511
  withDoc "Optional group name" .
512
  renameField "OptGroupName" .
513
  optionalField $ simpleField "group_name" [t| NonEmptyString |]
514

    
515
pGroupName :: Field
516
pGroupName =
517
  withDoc "Group name" $
518
  simpleField "group_name" [t| NonEmptyString |]
519

    
520
-- | Whether to hotplug device.
521
pHotplug :: Field
522
pHotplug = defaultFalse "hotplug"
523

    
524
pInstances :: Field
525
pInstances =
526
  withDoc "List of instances" .
527
  defaultField [| [] |] $
528
  simpleField "instances" [t| [NonEmptyString] |]
529

    
530
pOutputFields :: Field
531
pOutputFields =
532
  withDoc "Selected output fields" $
533
  simpleField "output_fields" [t| [NonEmptyString] |]
534

    
535
pName :: Field
536
pName =
537
  withDoc "A generic name" $
538
  simpleField "name" [t| NonEmptyString |]
539

    
540
pForce :: Field
541
pForce =
542
  withDoc "Whether to force the operation" $
543
  defaultFalse "force"
544

    
545
pHvState :: Field
546
pHvState =
547
  withDoc "Set hypervisor states" .
548
  optionalField $ simpleField "hv_state" [t| JSObject JSValue |]
549

    
550
pDiskState :: Field
551
pDiskState =
552
  withDoc "Set disk states" .
553
  optionalField $ simpleField "disk_state" [t| JSObject JSValue |]
554

    
555
-- | Cluster-wide default directory for storing file-backed disks.
556
pClusterFileStorageDir :: Field
557
pClusterFileStorageDir =
558
  renameField "ClusterFileStorageDir" $
559
  optionalStringField "file_storage_dir"
560

    
561
-- | Cluster-wide default directory for storing shared-file-backed disks.
562
pClusterSharedFileStorageDir :: Field
563
pClusterSharedFileStorageDir =
564
  renameField "ClusterSharedFileStorageDir" $
565
  optionalStringField "shared_file_storage_dir"
566

    
567
-- | Volume group name.
568
pVgName :: Field
569
pVgName =
570
  withDoc "Volume group name" $
571
  optionalStringField "vg_name"
572

    
573
pEnabledHypervisors :: Field
574
pEnabledHypervisors =
575
  withDoc "List of enabled hypervisors" .
576
  optionalField $
577
  simpleField "enabled_hypervisors" [t| [Hypervisor] |]
578

    
579
pClusterHvParams :: Field
580
pClusterHvParams =
581
  withDoc "Cluster-wide hypervisor parameters, hypervisor-dependent" .
582
  renameField "ClusterHvParams" .
583
  optionalField $
584
  simpleField "hvparams" [t| GenericContainer String (JSObject JSValue) |]
585

    
586
pClusterBeParams :: Field
587
pClusterBeParams =
588
  withDoc "Cluster-wide backend parameter defaults" .
589
  renameField "ClusterBeParams" .
590
  optionalField $ simpleField "beparams" [t| JSObject JSValue |]
591

    
592
pOsHvp :: Field
593
pOsHvp =
594
  withDoc "Cluster-wide per-OS hypervisor parameter defaults" .
595
  optionalField $
596
  simpleField "os_hvp" [t| GenericContainer String (JSObject JSValue) |]
597

    
598
pClusterOsParams :: Field
599
pClusterOsParams =
600
  withDoc "Cluster-wide OS parameter defaults" .
601
  renameField "ClusterOsParams" .
602
  optionalField $
603
  simpleField "osparams" [t| GenericContainer String (JSObject JSValue) |]
604

    
605
pDiskParams :: Field
606
pDiskParams =
607
  withDoc "Disk templates' parameter defaults" .
608
  optionalField $
609
  simpleField "diskparams"
610
              [t| GenericContainer DiskTemplate (JSObject JSValue) |]
611

    
612
pCandidatePoolSize :: Field
613
pCandidatePoolSize =
614
  withDoc "Master candidate pool size" .
615
  optionalField $ simpleField "candidate_pool_size" [t| Positive Int |]
616

    
617
pUidPool :: Field
618
pUidPool =
619
  withDoc "Set UID pool, must be list of lists describing UID ranges\
620
          \ (two items, start and end inclusive)" .
621
  optionalField $ simpleField "uid_pool" [t| [(Int, Int)] |]
622

    
623
pAddUids :: Field
624
pAddUids =
625
  withDoc "Extend UID pool, must be list of lists describing UID\
626
          \ ranges (two items, start and end inclusive)" .
627
  optionalField $ simpleField "add_uids" [t| [(Int, Int)] |]
628

    
629
pRemoveUids :: Field
630
pRemoveUids =
631
  withDoc "Shrink UID pool, must be list of lists describing UID\
632
          \ ranges (two items, start and end inclusive) to be removed" .
633
  optionalField $ simpleField "remove_uids" [t| [(Int, Int)] |]
634

    
635
pMaintainNodeHealth :: Field
636
pMaintainNodeHealth =
637
  withDoc "Whether to automatically maintain node health" .
638
  optionalField $ booleanField "maintain_node_health"
639

    
640
-- | Whether to modify and keep in sync the @/etc/hosts@ files of nodes.
641
pModifyEtcHosts :: Field
642
pModifyEtcHosts = optionalField $ booleanField "modify_etc_hosts"
643

    
644
-- | Whether to wipe disks before allocating them to instances.
645
pPreallocWipeDisks :: Field
646
pPreallocWipeDisks =
647
  withDoc "Whether to wipe disks before allocating them to instances" .
648
  optionalField $ booleanField "prealloc_wipe_disks"
649

    
650
pNicParams :: Field
651
pNicParams =
652
  withDoc "Cluster-wide NIC parameter defaults" .
653
  optionalField $ simpleField "nicparams" [t| INicParams |]
654

    
655
pIpolicy :: Field
656
pIpolicy =
657
  withDoc "Ipolicy specs" .
658
  optionalField $ simpleField "ipolicy" [t| JSObject JSValue |]
659

    
660
pDrbdHelper :: Field
661
pDrbdHelper =
662
  withDoc "DRBD helper program" $
663
  optionalStringField "drbd_helper"
664

    
665
pDefaultIAllocator :: Field
666
pDefaultIAllocator =
667
  withDoc "Default iallocator for cluster" $
668
  optionalStringField "default_iallocator"
669

    
670
pMasterNetdev :: Field
671
pMasterNetdev =
672
  withDoc "Master network device" $
673
  optionalStringField "master_netdev"
674

    
675
pMasterNetmask :: Field
676
pMasterNetmask =
677
  withDoc "Netmask of the master IP" .
678
  optionalField $ simpleField "master_netmask" [t| NonNegative Int |]
679

    
680
pReservedLvs :: Field
681
pReservedLvs =
682
  withDoc "List of reserved LVs" .
683
  optionalField $ simpleField "reserved_lvs" [t| [NonEmptyString] |]
684

    
685
pHiddenOs :: Field
686
pHiddenOs =
687
  withDoc "Modify list of hidden operating systems: each modification\
688
          \ must have two items, the operation and the OS name; the operation\
689
          \ can be add or remove" .
690
  optionalField $ simpleField "hidden_os" [t| [(DdmSimple, NonEmptyString)] |]
691

    
692
pBlacklistedOs :: Field
693
pBlacklistedOs =
694
  withDoc "Modify list of blacklisted operating systems: each\
695
          \ modification must have two items, the operation and the OS name;\
696
          \ the operation can be add or remove" .
697
  optionalField $
698
  simpleField "blacklisted_os" [t| [(DdmSimple, NonEmptyString)] |]
699

    
700
pUseExternalMipScript :: Field
701
pUseExternalMipScript =
702
  withDoc "Whether to use an external master IP address setup script" .
703
  optionalField $ booleanField "use_external_mip_script"
704

    
705
pEnabledDiskTemplates :: Field
706
pEnabledDiskTemplates =
707
  withDoc "List of enabled disk templates" .
708
  optionalField $
709
  simpleField "enabled_disk_templates" [t| [DiskTemplate] |]
710

    
711
pQueryWhat :: Field
712
pQueryWhat =
713
  withDoc "Resource(s) to query for" $
714
  simpleField "what" [t| Qlang.QueryTypeOp |]
715

    
716
pUseLocking :: Field
717
pUseLocking =
718
  withDoc "Whether to use synchronization" $
719
  defaultFalse "use_locking"
720

    
721
pQueryFields :: Field
722
pQueryFields =
723
  withDoc "Requested fields" $
724
  simpleField "fields" [t| [NonEmptyString] |]
725

    
726
pQueryFilter :: Field
727
pQueryFilter =
728
  withDoc "Query filter" .
729
  optionalField $ simpleField "qfilter" [t| [JSValue] |]
730

    
731
pQueryFieldsFields :: Field
732
pQueryFieldsFields =
733
  withDoc "Requested fields; if not given, all are returned" .
734
  renameField "QueryFieldsFields" $
735
  optionalField pQueryFields
736

    
737
pNodeNames :: Field
738
pNodeNames =
739
  withDoc "List of node names to run the OOB command against" .
740
  defaultField [| [] |] $ simpleField "node_names" [t| [NonEmptyString] |]
741

    
742
pNodeUuids :: Field
743
pNodeUuids =
744
  withDoc "List of node UUIDs" .
745
  optionalField $ simpleField "node_uuids" [t| [NonEmptyString] |]
746

    
747
pOobCommand :: Field
748
pOobCommand =
749
  withDoc "OOB command to run" $
750
  simpleField "command" [t| OobCommand |]
751

    
752
pOobTimeout :: Field
753
pOobTimeout =
754
  withDoc "Timeout before the OOB helper will be terminated" .
755
  defaultField [| C.oobTimeout |] $
756
  simpleField "timeout" [t| Int |]
757

    
758
pIgnoreStatus :: Field
759
pIgnoreStatus =
760
  withDoc "Ignores the node offline status for power off" $
761
  defaultFalse "ignore_status"
762

    
763
pPowerDelay :: Field
764
pPowerDelay =
765
  -- FIXME: we can't use the proper type "NonNegative Double", since
766
  -- the default constant is a plain Double, not a non-negative one.
767
  -- And trying to fix the constant introduces a cyclic import.
768
  withDoc "Time in seconds to wait between powering on nodes" .
769
  defaultField [| C.oobPowerDelay |] $
770
  simpleField "power_delay" [t| Double |]
771

    
772
pRequiredNodes :: Field
773
pRequiredNodes =
774
  withDoc "Required list of node names" .
775
  renameField "ReqNodes " $ simpleField "nodes" [t| [NonEmptyString] |]
776

    
777
pRequiredNodeUuids :: Field
778
pRequiredNodeUuids =
779
  withDoc "Required list of node UUIDs" .
780
  renameField "ReqNodeUuids " . optionalField $
781
  simpleField "node_uuids" [t| [NonEmptyString] |]
782

    
783
pRestrictedCommand :: Field
784
pRestrictedCommand =
785
  withDoc "Restricted command name" .
786
  renameField "RestrictedCommand" $
787
  simpleField "command" [t| NonEmptyString |]
788

    
789
pNodeName :: Field
790
pNodeName =
791
  withDoc "A required node name (for single-node LUs)" $
792
  simpleField "node_name" [t| NonEmptyString |]
793

    
794
pNodeUuid :: Field
795
pNodeUuid =
796
  withDoc "A node UUID (for single-node LUs)" .
797
  optionalField $ simpleField "node_uuid" [t| NonEmptyString |]
798

    
799
pPrimaryIp :: Field
800
pPrimaryIp =
801
  withDoc "Primary IP address" .
802
  optionalField $
803
  simpleField "primary_ip" [t| NonEmptyString |]
804

    
805
pSecondaryIp :: Field
806
pSecondaryIp =
807
  withDoc "Secondary IP address" $
808
  optionalNEStringField "secondary_ip"
809

    
810
pReadd :: Field
811
pReadd =
812
  withDoc "Whether node is re-added to cluster" $
813
  defaultFalse "readd"
814

    
815
pNodeGroup :: Field
816
pNodeGroup =
817
  withDoc "Initial node group" $
818
  optionalNEStringField "group"
819

    
820
pMasterCapable :: Field
821
pMasterCapable =
822
  withDoc "Whether node can become master or master candidate" .
823
  optionalField $ booleanField "master_capable"
824

    
825
pVmCapable :: Field
826
pVmCapable =
827
  withDoc "Whether node can host instances" .
828
  optionalField $ booleanField "vm_capable"
829

    
830
pNdParams :: Field
831
pNdParams =
832
  withDoc "Node parameters" .
833
  renameField "genericNdParams" .
834
  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
835

    
836
pNames :: Field
837
pNames =
838
  withDoc "List of names" .
839
  defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
840

    
841
pNodes :: Field
842
pNodes =
843
  withDoc "List of nodes" .
844
  defaultField [| [] |] $ simpleField "nodes" [t| [NonEmptyString] |]
845

    
846
pStorageType :: Field
847
pStorageType =
848
  withDoc "Storage type" $ simpleField "storage_type" [t| StorageType |]
849

    
850
pStorageTypeOptional :: Field
851
pStorageTypeOptional =
852
  withDoc "Storage type" .
853
  renameField "StorageTypeOptional" .
854
  optionalField $ simpleField "storage_type" [t| StorageType |]
855

    
856
pStorageName :: Field
857
pStorageName =
858
  withDoc "Storage name" .
859
  renameField "StorageName" .
860
  optionalField $ simpleField "name" [t| NonEmptyString |]
861

    
862
pStorageChanges :: Field
863
pStorageChanges =
864
  withDoc "Requested storage changes" $
865
  simpleField "changes" [t| JSObject JSValue |]
866

    
867
pIgnoreConsistency :: Field
868
pIgnoreConsistency =
869
  withDoc "Whether to ignore disk consistency" $
870
  defaultFalse "ignore_consistency"
871

    
872
pMasterCandidate :: Field
873
pMasterCandidate =
874
  withDoc "Whether the node should become a master candidate" .
875
  optionalField $ booleanField "master_candidate"
876

    
877
pOffline :: Field
878
pOffline =
879
  withDoc "Whether to mark the node or instance offline" .
880
  optionalField $ booleanField "offline"
881

    
882
pDrained ::Field
883
pDrained =
884
  withDoc "Whether to mark the node as drained" .
885
  optionalField $ booleanField "drained"
886

    
887
pAutoPromote :: Field
888
pAutoPromote =
889
  withDoc "Whether node(s) should be promoted to master candidate if\
890
          \ necessary" $
891
  defaultFalse "auto_promote"
892

    
893
pPowered :: Field
894
pPowered =
895
  withDoc "Whether the node should be marked as powered" .
896
  optionalField $ booleanField "powered"
897

    
898
pMigrationMode :: Field
899
pMigrationMode =
900
  withDoc "Migration type (live/non-live)" .
901
  renameField "MigrationMode" .
902
  optionalField $
903
  simpleField "mode" [t| MigrationMode |]
904

    
905
pMigrationLive :: Field
906
pMigrationLive =
907
  withDoc "Obsolete \'live\' migration mode (do not use)" .
908
  renameField "OldLiveMode" . optionalField $ booleanField "live"
909

    
910
pMigrationTargetNode :: Field
911
pMigrationTargetNode =
912
  withDoc "Target node for instance migration/failover" $
913
  optionalNEStringField "target_node"
914

    
915
pMigrationTargetNodeUuid :: Field
916
pMigrationTargetNodeUuid =
917
  withDoc "Target node UUID for instance migration/failover" $
918
  optionalNEStringField "target_node_uuid"
919

    
920
pAllowRuntimeChgs :: Field
921
pAllowRuntimeChgs =
922
  withDoc "Whether to allow runtime changes while migrating" $
923
  defaultTrue "allow_runtime_changes"
924

    
925
pIgnoreIpolicy :: Field
926
pIgnoreIpolicy =
927
  withDoc "Whether to ignore ipolicy violations" $
928
  defaultFalse "ignore_ipolicy"
929

    
930
pIallocator :: Field
931
pIallocator =
932
  withDoc "Iallocator for deciding the target node for shared-storage\
933
          \ instances" $
934
  optionalNEStringField "iallocator"
935

    
936
pEarlyRelease :: Field
937
pEarlyRelease =
938
  withDoc "Whether to release locks as soon as possible" $
939
  defaultFalse "early_release"
940

    
941
pRemoteNode :: Field
942
pRemoteNode =
943
  withDoc "New secondary node" $
944
  optionalNEStringField "remote_node"
945

    
946
pRemoteNodeUuid :: Field
947
pRemoteNodeUuid =
948
  withDoc "New secondary node UUID" $
949
  optionalNEStringField "remote_node_uuid"
950

    
951
pEvacMode :: Field
952
pEvacMode =
953
  withDoc "Node evacuation mode" .
954
  renameField "EvacMode" $ simpleField "mode" [t| EvacMode |]
955

    
956
pInstanceName :: Field
957
pInstanceName =
958
  withDoc "A required instance name (for single-instance LUs)" $
959
  simpleField "instance_name" [t| String |]
960

    
961
pForceVariant :: Field
962
pForceVariant =
963
  withDoc "Whether to force an unknown OS variant" $
964
  defaultFalse "force_variant"
965

    
966
pWaitForSync :: Field
967
pWaitForSync =
968
  withDoc "Whether to wait for the disk to synchronize" $
969
  defaultTrue "wait_for_sync"
970

    
971
pNameCheck :: Field
972
pNameCheck =
973
  withDoc "Whether to check name" $
974
  defaultTrue "name_check"
975

    
976
pInstBeParams :: Field
977
pInstBeParams =
978
  withDoc "Backend parameters for instance" .
979
  renameField "InstBeParams" .
980
  defaultField [| toJSObject [] |] $
981
  simpleField "beparams" [t| JSObject JSValue |]
982

    
983
pInstDisks :: Field
984
pInstDisks =
985
  withDoc "List of instance disks" .
986
  renameField "instDisks" $ simpleField "disks" [t| [IDiskParams] |]
987

    
988
pDiskTemplate :: Field
989
pDiskTemplate =
990
  withDoc "Disk template" $
991
  simpleField "disk_template" [t| DiskTemplate |]
992

    
993
pFileDriver :: Field
994
pFileDriver =
995
  withDoc "Driver for file-backed disks" .
996
  optionalField $ simpleField "file_driver" [t| FileDriver |]
997

    
998
pFileStorageDir :: Field
999
pFileStorageDir =
1000
  withDoc "Directory for storing file-backed disks" $
1001
  optionalNEStringField "file_storage_dir"
1002

    
1003
pInstHvParams :: Field
1004
pInstHvParams =
1005
  withDoc "Hypervisor parameters for instance, hypervisor-dependent" .
1006
  renameField "InstHvParams" .
1007
  defaultField [| toJSObject [] |] $
1008
  simpleField "hvparams" [t| JSObject JSValue |]
1009

    
1010
pHypervisor :: Field
1011
pHypervisor =
1012
  withDoc "Selected hypervisor for an instance" .
1013
  optionalField $
1014
  simpleField "hypervisor" [t| Hypervisor |]
1015

    
1016
pResetDefaults :: Field
1017
pResetDefaults =
1018
  withDoc "Reset instance parameters to default if equal" $
1019
  defaultFalse "identify_defaults"
1020

    
1021
pIpCheck :: Field
1022
pIpCheck =
1023
  withDoc "Whether to ensure instance's IP address is inactive" $
1024
  defaultTrue "ip_check"
1025

    
1026
pIpConflictsCheck :: Field
1027
pIpConflictsCheck =
1028
  withDoc "Whether to check for conflicting IP addresses" $
1029
  defaultTrue "conflicts_check"
1030

    
1031
pInstCreateMode :: Field
1032
pInstCreateMode =
1033
  withDoc "Instance creation mode" .
1034
  renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
1035

    
1036
pInstNics :: Field
1037
pInstNics =
1038
  withDoc "List of NIC (network interface) definitions" $
1039
  simpleField "nics" [t| [INicParams] |]
1040

    
1041
pNoInstall :: Field
1042
pNoInstall =
1043
  withDoc "Do not install the OS (will disable automatic start)" .
1044
  optionalField $ booleanField "no_install"
1045

    
1046
pInstOs :: Field
1047
pInstOs =
1048
  withDoc "OS type for instance installation" $
1049
  optionalNEStringField "os_type"
1050

    
1051
pInstOsParams :: Field
1052
pInstOsParams =
1053
  withDoc "OS parameters for instance" .
1054
  renameField "InstOsParams" .
1055
  defaultField [| toJSObject [] |] $
1056
  simpleField "osparams" [t| JSObject JSValue |]
1057

    
1058
pPrimaryNode :: Field
1059
pPrimaryNode =
1060
  withDoc "Primary node for an instance" $
1061
  optionalNEStringField "pnode"
1062

    
1063
pPrimaryNodeUuid :: Field
1064
pPrimaryNodeUuid =
1065
  withDoc "Primary node UUID for an instance" $
1066
  optionalNEStringField "pnode_uuid"
1067

    
1068
pSecondaryNode :: Field
1069
pSecondaryNode =
1070
  withDoc "Secondary node for an instance" $
1071
  optionalNEStringField "snode"
1072

    
1073
pSecondaryNodeUuid :: Field
1074
pSecondaryNodeUuid =
1075
  withDoc "Secondary node UUID for an instance" $
1076
  optionalNEStringField "snode_uuid"
1077

    
1078
pSourceHandshake :: Field
1079
pSourceHandshake =
1080
  withDoc "Signed handshake from source (remote import only)" .
1081
  optionalField $ simpleField "source_handshake" [t| [JSValue] |]
1082

    
1083
pSourceInstance :: Field
1084
pSourceInstance =
1085
  withDoc "Source instance name (remote import only)" $
1086
  optionalNEStringField "source_instance_name"
1087

    
1088
-- FIXME: non-negative int, whereas the constant is a plain int.
1089
pSourceShutdownTimeout :: Field
1090
pSourceShutdownTimeout =
1091
  withDoc "How long source instance was given to shut down (remote import\
1092
          \ only)" .
1093
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1094
  simpleField "source_shutdown_timeout" [t| NonNegative Int |]
1095

    
1096
pSourceX509Ca :: Field
1097
pSourceX509Ca =
1098
  withDoc "Source X509 CA in PEM format (remote import only)" $
1099
  optionalNEStringField "source_x509_ca"
1100

    
1101
pSrcNode :: Field
1102
pSrcNode =
1103
  withDoc "Source node for import" $
1104
  optionalNEStringField "src_node"
1105

    
1106
pSrcNodeUuid :: Field
1107
pSrcNodeUuid =
1108
  withDoc "Source node UUID for import" $
1109
  optionalNEStringField "src_node_uuid"
1110

    
1111
pSrcPath :: Field
1112
pSrcPath =
1113
  withDoc "Source directory for import" $
1114
  optionalNEStringField "src_path"
1115

    
1116
pStartInstance :: Field
1117
pStartInstance =
1118
  withDoc "Whether to start instance after creation" $
1119
  defaultTrue "start"
1120

    
1121
-- FIXME: unify/simplify with pTags, once that migrates to NonEmpty String"
1122
pInstTags :: Field
1123
pInstTags =
1124
  withDoc "Instance tags" .
1125
  renameField "InstTags" .
1126
  defaultField [| [] |] $
1127
  simpleField "tags" [t| [NonEmptyString] |]
1128

    
1129
pMultiAllocInstances :: Field
1130
pMultiAllocInstances =
1131
  withDoc "List of instance create opcodes describing the instances to\
1132
          \ allocate" .
1133
  renameField "InstMultiAlloc" .
1134
  defaultField [| [] |] $
1135
  simpleField "instances"[t| [JSValue] |]
1136

    
1137
pOpportunisticLocking :: Field
1138
pOpportunisticLocking =
1139
  withDoc "Whether to employ opportunistic locking for nodes, meaning\
1140
          \ nodes already locked by another opcode won't be considered for\
1141
          \ instance allocation (only when an iallocator is used)" $
1142
  defaultFalse "opportunistic_locking"
1143

    
1144
pInstanceUuid :: Field
1145
pInstanceUuid =
1146
  withDoc "An instance UUID (for single-instance LUs)" .
1147
  optionalField $ simpleField "instance_uuid" [t| NonEmptyString |]
1148

    
1149
pTempOsParams :: Field
1150
pTempOsParams =
1151
  withDoc "Temporary OS parameters (currently only in reinstall, might be\
1152
          \ added to install as well)" .
1153
  renameField "TempOsParams" .
1154
  optionalField $ simpleField "osparams" [t| JSObject JSValue |]
1155

    
1156
pShutdownTimeout :: Field
1157
pShutdownTimeout =
1158
  withDoc "How long to wait for instance to shut down" .
1159
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1160
  simpleField "shutdown_timeout" [t| NonNegative Int |]
1161

    
1162
-- | Another name for the shutdown timeout, because we like to be
1163
-- inconsistent.
1164
pShutdownTimeout' :: Field
1165
pShutdownTimeout' =
1166
  withDoc "How long to wait for instance to shut down" .
1167
  renameField "InstShutdownTimeout" .
1168
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1169
  simpleField "timeout" [t| NonNegative Int |]
1170

    
1171
pIgnoreFailures :: Field
1172
pIgnoreFailures =
1173
  withDoc "Whether to ignore failures during removal" $
1174
  defaultFalse "ignore_failures"
1175

    
1176
pNewName :: Field
1177
pNewName =
1178
  withDoc "New group or instance name" $
1179
  simpleField "new_name" [t| NonEmptyString |]
1180

    
1181
pIgnoreOfflineNodes :: Field
1182
pIgnoreOfflineNodes =
1183
  withDoc "Whether to ignore offline nodes" $
1184
  defaultFalse "ignore_offline_nodes"
1185

    
1186
pTempHvParams :: Field
1187
pTempHvParams =
1188
  withDoc "Temporary hypervisor parameters, hypervisor-dependent" .
1189
  renameField "TempHvParams" .
1190
  defaultField [| toJSObject [] |] $
1191
  simpleField "hvparams" [t| JSObject JSValue |]
1192

    
1193
pTempBeParams :: Field
1194
pTempBeParams =
1195
  withDoc "Temporary backend parameters" .
1196
  renameField "TempBeParams" .
1197
  defaultField [| toJSObject [] |] $
1198
  simpleField "beparams" [t| JSObject JSValue |]
1199

    
1200
pNoRemember :: Field
1201
pNoRemember =
1202
  withDoc "Do not remember instance state changes" $
1203
  defaultFalse "no_remember"
1204

    
1205
pStartupPaused :: Field
1206
pStartupPaused =
1207
  withDoc "Pause instance at startup" $
1208
  defaultFalse "startup_paused"
1209

    
1210
pIgnoreSecondaries :: Field
1211
pIgnoreSecondaries =
1212
  withDoc "Whether to start the instance even if secondary disks are failing" $
1213
  defaultFalse "ignore_secondaries"
1214

    
1215
pRebootType :: Field
1216
pRebootType =
1217
  withDoc "How to reboot the instance" $
1218
  simpleField "reboot_type" [t| RebootType |]
1219

    
1220
pReplaceDisksMode :: Field
1221
pReplaceDisksMode =
1222
  withDoc "Replacement mode" .
1223
  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1224

    
1225
pReplaceDisksList :: Field
1226
pReplaceDisksList =
1227
  withDoc "List of disk indices" .
1228
  renameField "ReplaceDisksList" .
1229
  defaultField [| [] |] $
1230
  simpleField "disks" [t| [DiskIndex] |]
1231

    
1232
pMigrationCleanup :: Field
1233
pMigrationCleanup =
1234
  withDoc "Whether a previously failed migration should be cleaned up" .
1235
  renameField "MigrationCleanup" $ defaultFalse "cleanup"
1236

    
1237
pAllowFailover :: Field
1238
pAllowFailover =
1239
  withDoc "Whether we can fallback to failover if migration is not possible" $
1240
  defaultFalse "allow_failover"
1241

    
1242
pMoveTargetNode :: Field
1243
pMoveTargetNode =
1244
  withDoc "Target node for instance move" .
1245
  renameField "MoveTargetNode" $
1246
  simpleField "target_node" [t| NonEmptyString |]
1247

    
1248
pMoveTargetNodeUuid :: Field
1249
pMoveTargetNodeUuid =
1250
  withDoc "Target node UUID for instance move" .
1251
  renameField "MoveTargetNodeUuid" . optionalField $
1252
  simpleField "target_node_uuid" [t| NonEmptyString |]
1253

    
1254
pMoveCompress :: Field
1255
pMoveCompress =
1256
  withDoc "Compression mode to use during instance moves" .
1257
  defaultField [| None |] $
1258
  simpleField "compress" [t| ImportExportCompression |]
1259

    
1260
pBackupCompress :: Field
1261
pBackupCompress =
1262
  withDoc "Compression mode to use for moves during backups/imports" .
1263
  defaultField [| None |] $
1264
  simpleField "compress" [t| ImportExportCompression |]
1265

    
1266
pIgnoreDiskSize :: Field
1267
pIgnoreDiskSize =
1268
  withDoc "Whether to ignore recorded disk size" $
1269
  defaultFalse "ignore_size"
1270

    
1271
pWaitForSyncFalse :: Field
1272
pWaitForSyncFalse =
1273
  withDoc "Whether to wait for the disk to synchronize (defaults to false)" $
1274
  defaultField [| False |] pWaitForSync
1275

    
1276
pRecreateDisksInfo :: Field
1277
pRecreateDisksInfo =
1278
  withDoc "Disk list for recreate disks" .
1279
  renameField "RecreateDisksInfo" .
1280
  defaultField [| RecreateDisksAll |] $
1281
  simpleField "disks" [t| RecreateDisksInfo |]
1282

    
1283
pStatic :: Field
1284
pStatic =
1285
  withDoc "Whether to only return configuration data without querying nodes" $
1286
  defaultFalse "static"
1287

    
1288
pInstParamsNicChanges :: Field
1289
pInstParamsNicChanges =
1290
  withDoc "List of NIC changes" .
1291
  renameField "InstNicChanges" .
1292
  defaultField [| SetParamsEmpty |] $
1293
  simpleField "nics" [t| SetParamsMods INicParams |]
1294

    
1295
pInstParamsDiskChanges :: Field
1296
pInstParamsDiskChanges =
1297
  withDoc "List of disk changes" .
1298
  renameField "InstDiskChanges" .
1299
  defaultField [| SetParamsEmpty |] $
1300
  simpleField "disks" [t| SetParamsMods IDiskParams |]
1301

    
1302
pRuntimeMem :: Field
1303
pRuntimeMem =
1304
  withDoc "New runtime memory" .
1305
  optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1306

    
1307
pOptDiskTemplate :: Field
1308
pOptDiskTemplate =
1309
  withDoc "Instance disk template" .
1310
  optionalField .
1311
  renameField "OptDiskTemplate" $
1312
  simpleField "disk_template" [t| DiskTemplate |]
1313

    
1314
pOsNameChange :: Field
1315
pOsNameChange =
1316
  withDoc "Change the instance's OS without reinstalling the instance" $
1317
  optionalNEStringField "os_name"
1318

    
1319
pDiskIndex :: Field
1320
pDiskIndex =
1321
  withDoc "Disk index for e.g. grow disk" .
1322
  renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
1323

    
1324
pDiskChgAmount :: Field
1325
pDiskChgAmount =
1326
  withDoc "Disk amount to add or grow to" .
1327
  renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
1328

    
1329
pDiskChgAbsolute :: Field
1330
pDiskChgAbsolute =
1331
  withDoc
1332
    "Whether the amount parameter is an absolute target or a relative one" .
1333
  renameField "DiskChkAbsolute" $ defaultFalse "absolute"
1334

    
1335
pTargetGroups :: Field
1336
pTargetGroups =
1337
  withDoc
1338
    "Destination group names or UUIDs (defaults to \"all but current group\")" .
1339
  optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
1340

    
1341
pNodeGroupAllocPolicy :: Field
1342
pNodeGroupAllocPolicy =
1343
  withDoc "Instance allocation policy" .
1344
  optionalField $
1345
  simpleField "alloc_policy" [t| AllocPolicy |]
1346

    
1347
pGroupNodeParams :: Field
1348
pGroupNodeParams =
1349
  withDoc "Default node parameters for group" .
1350
  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
1351

    
1352
pExportMode :: Field
1353
pExportMode =
1354
  withDoc "Export mode" .
1355
  renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1356

    
1357
-- FIXME: Rename target_node as it changes meaning for different
1358
-- export modes (e.g. "destination")
1359
pExportTargetNode :: Field
1360
pExportTargetNode =
1361
  withDoc "Target node (depends on export mode)" .
1362
  renameField "ExportTarget" $
1363
  simpleField "target_node" [t| ExportTarget |]
1364

    
1365
pExportTargetNodeUuid :: Field
1366
pExportTargetNodeUuid =
1367
  withDoc "Target node UUID (if local export)" .
1368
  renameField "ExportTargetNodeUuid" . optionalField $
1369
  simpleField "target_node_uuid" [t| NonEmptyString |]
1370

    
1371
pShutdownInstance :: Field
1372
pShutdownInstance =
1373
  withDoc "Whether to shutdown the instance before export" $
1374
  defaultTrue "shutdown"
1375

    
1376
pRemoveInstance :: Field
1377
pRemoveInstance =
1378
  withDoc "Whether to remove instance after export" $
1379
  defaultFalse "remove_instance"
1380

    
1381
pIgnoreRemoveFailures :: Field
1382
pIgnoreRemoveFailures =
1383
  withDoc "Whether to ignore failures while removing instances" $
1384
  defaultFalse "ignore_remove_failures"
1385

    
1386
pX509KeyName :: Field
1387
pX509KeyName =
1388
  withDoc "Name of X509 key (remote export only)" .
1389
  optionalField $ simpleField "x509_key_name" [t| [JSValue] |]
1390

    
1391
pX509DestCA :: Field
1392
pX509DestCA =
1393
  withDoc "Destination X509 CA (remote export only)" $
1394
  optionalNEStringField "destination_x509_ca"
1395

    
1396
pTagsObject :: Field
1397
pTagsObject =
1398
  withDoc "Tag kind" $
1399
  simpleField "kind" [t| TagKind |]
1400

    
1401
pTagsName :: Field
1402
pTagsName =
1403
  withDoc "Name of object" .
1404
  renameField "TagsGetName" .
1405
  optionalField $ simpleField "name" [t| String |]
1406

    
1407
pTagsList :: Field
1408
pTagsList =
1409
  withDoc "List of tag names" $
1410
  simpleField "tags" [t| [String] |]
1411

    
1412
-- FIXME: this should be compiled at load time?
1413
pTagSearchPattern :: Field
1414
pTagSearchPattern =
1415
  withDoc "Search pattern (regular expression)" .
1416
  renameField "TagSearchPattern" $
1417
  simpleField "pattern" [t| NonEmptyString |]
1418

    
1419
pDelayDuration :: Field
1420
pDelayDuration =
1421
  withDoc "Duration parameter for 'OpTestDelay'" .
1422
  renameField "DelayDuration" $
1423
  simpleField "duration" [t| Double |]
1424

    
1425
pDelayOnMaster :: Field
1426
pDelayOnMaster =
1427
  withDoc "on_master field for 'OpTestDelay'" .
1428
  renameField "DelayOnMaster" $
1429
  defaultTrue "on_master"
1430

    
1431
pDelayOnNodes :: Field
1432
pDelayOnNodes =
1433
  withDoc "on_nodes field for 'OpTestDelay'" .
1434
  renameField "DelayOnNodes" .
1435
  defaultField [| [] |] $
1436
  simpleField "on_nodes" [t| [NonEmptyString] |]
1437

    
1438
pDelayOnNodeUuids :: Field
1439
pDelayOnNodeUuids =
1440
  withDoc "on_node_uuids field for 'OpTestDelay'" .
1441
  renameField "DelayOnNodeUuids" . optionalField $
1442
  simpleField "on_node_uuids" [t| [NonEmptyString] |]
1443

    
1444
pDelayRepeat :: Field
1445
pDelayRepeat =
1446
  withDoc "Repeat parameter for OpTestDelay" .
1447
  renameField "DelayRepeat" .
1448
  defaultField [| forceNonNeg (0::Int) |] $
1449
  simpleField "repeat" [t| NonNegative Int |]
1450

    
1451
pIAllocatorDirection :: Field
1452
pIAllocatorDirection =
1453
  withDoc "IAllocator test direction" .
1454
  renameField "IAllocatorDirection" $
1455
  simpleField "direction" [t| IAllocatorTestDir |]
1456

    
1457
pIAllocatorMode :: Field
1458
pIAllocatorMode =
1459
  withDoc "IAllocator test mode" .
1460
  renameField "IAllocatorMode" $
1461
  simpleField "mode" [t| IAllocatorMode |]
1462

    
1463
pIAllocatorReqName :: Field
1464
pIAllocatorReqName =
1465
  withDoc "IAllocator target name (new instance, node to evac, etc.)" .
1466
  renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
1467

    
1468
pIAllocatorNics :: Field
1469
pIAllocatorNics =
1470
  withDoc "Custom OpTestIAllocator nics" .
1471
  renameField "IAllocatorNics" .
1472
  optionalField $ simpleField "nics" [t| [INicParams] |]
1473

    
1474
pIAllocatorDisks :: Field
1475
pIAllocatorDisks =
1476
  withDoc "Custom OpTestAllocator disks" .
1477
  renameField "IAllocatorDisks" .
1478
  optionalField $ simpleField "disks" [t| [JSValue] |]
1479

    
1480
pIAllocatorMemory :: Field
1481
pIAllocatorMemory =
1482
  withDoc "IAllocator memory field" .
1483
  renameField "IAllocatorMem" .
1484
  optionalField $
1485
  simpleField "memory" [t| NonNegative Int |]
1486

    
1487
pIAllocatorVCpus :: Field
1488
pIAllocatorVCpus =
1489
  withDoc "IAllocator vcpus field" .
1490
  renameField "IAllocatorVCpus" .
1491
  optionalField $
1492
  simpleField "vcpus" [t| NonNegative Int |]
1493

    
1494
pIAllocatorOs :: Field
1495
pIAllocatorOs =
1496
  withDoc "IAllocator os field" .
1497
  renameField "IAllocatorOs" $ optionalNEStringField "os"
1498

    
1499
pIAllocatorInstances :: Field
1500
pIAllocatorInstances =
1501
  withDoc "IAllocator instances field" .
1502
  renameField "IAllocatorInstances " .
1503
  optionalField $
1504
  simpleField "instances" [t| [NonEmptyString] |]
1505

    
1506
pIAllocatorEvacMode :: Field
1507
pIAllocatorEvacMode =
1508
  withDoc "IAllocator evac mode" .
1509
  renameField "IAllocatorEvacMode" .
1510
  optionalField $
1511
  simpleField "evac_mode" [t| EvacMode |]
1512

    
1513
pIAllocatorSpindleUse :: Field
1514
pIAllocatorSpindleUse =
1515
  withDoc "IAllocator spindle use" .
1516
  renameField "IAllocatorSpindleUse" .
1517
  defaultField [| forceNonNeg (1::Int) |] $
1518
  simpleField "spindle_use" [t| NonNegative Int |]
1519

    
1520
pIAllocatorCount :: Field
1521
pIAllocatorCount =
1522
  withDoc "IAllocator count field" .
1523
  renameField "IAllocatorCount" .
1524
  defaultField [| forceNonNeg (1::Int) |] $
1525
  simpleField "count" [t| NonNegative Int |]
1526

    
1527
pJQueueNotifyWaitLock :: Field
1528
pJQueueNotifyWaitLock =
1529
  withDoc "'OpTestJqueue' notify_waitlock" $
1530
  defaultFalse "notify_waitlock"
1531

    
1532
pJQueueNotifyExec :: Field
1533
pJQueueNotifyExec =
1534
  withDoc "'OpTestJQueue' notify_exec" $
1535
  defaultFalse "notify_exec"
1536

    
1537
pJQueueLogMessages :: Field
1538
pJQueueLogMessages =
1539
  withDoc "'OpTestJQueue' log_messages" .
1540
  defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
1541

    
1542
pJQueueFail :: Field
1543
pJQueueFail =
1544
  withDoc "'OpTestJQueue' fail attribute" .
1545
  renameField "JQueueFail" $ defaultFalse "fail"
1546

    
1547
pTestDummyResult :: Field
1548
pTestDummyResult =
1549
  withDoc "'OpTestDummy' result field" .
1550
  renameField "TestDummyResult" $ simpleField "result" [t| JSValue |]
1551

    
1552
pTestDummyMessages :: Field
1553
pTestDummyMessages =
1554
  withDoc "'OpTestDummy' messages field" .
1555
  renameField "TestDummyMessages" $
1556
  simpleField "messages" [t| JSValue |]
1557

    
1558
pTestDummyFail :: Field
1559
pTestDummyFail =
1560
  withDoc "'OpTestDummy' fail field" .
1561
  renameField "TestDummyFail" $ simpleField "fail" [t| JSValue |]
1562

    
1563
pTestDummySubmitJobs :: Field
1564
pTestDummySubmitJobs =
1565
  withDoc "'OpTestDummy' submit_jobs field" .
1566
  renameField "TestDummySubmitJobs" $
1567
  simpleField "submit_jobs" [t| JSValue |]
1568

    
1569
pNetworkName :: Field
1570
pNetworkName =
1571
  withDoc "Network name" $
1572
  simpleField "network_name" [t| NonEmptyString |]
1573

    
1574
pNetworkAddress4 :: Field
1575
pNetworkAddress4 =
1576
  withDoc "Network address (IPv4 subnet)" .
1577
  renameField "NetworkAddress4" $
1578
  simpleField "network" [t| IPv4Network |]
1579

    
1580
pNetworkGateway4 :: Field
1581
pNetworkGateway4 =
1582
  withDoc "Network gateway (IPv4 address)" .
1583
  renameField "NetworkGateway4" .
1584
  optionalField $ simpleField "gateway" [t| IPv4Address |]
1585

    
1586
pNetworkAddress6 :: Field
1587
pNetworkAddress6 =
1588
  withDoc "Network address (IPv6 subnet)" .
1589
  renameField "NetworkAddress6" .
1590
  optionalField $ simpleField "network6" [t| IPv6Network |]
1591

    
1592
pNetworkGateway6 :: Field
1593
pNetworkGateway6 =
1594
  withDoc "Network gateway (IPv6 address)" .
1595
  renameField "NetworkGateway6" .
1596
  optionalField $ simpleField "gateway6" [t| IPv6Address |]
1597

    
1598
pNetworkMacPrefix :: Field
1599
pNetworkMacPrefix =
1600
  withDoc "Network specific mac prefix (that overrides the cluster one)" .
1601
  renameField "NetMacPrefix" $
1602
  optionalNEStringField "mac_prefix"
1603

    
1604
pNetworkAddRsvdIps :: Field
1605
pNetworkAddRsvdIps =
1606
  withDoc "Which IP addresses to reserve" .
1607
  renameField "NetworkAddRsvdIps" .
1608
  optionalField $
1609
  simpleField "add_reserved_ips" [t| [IPv4Address] |]
1610

    
1611
pNetworkRemoveRsvdIps :: Field
1612
pNetworkRemoveRsvdIps =
1613
  withDoc "Which external IP addresses to release" .
1614
  renameField "NetworkRemoveRsvdIps" .
1615
  optionalField $
1616
  simpleField "remove_reserved_ips" [t| [IPv4Address] |]
1617

    
1618
pNetworkMode :: Field
1619
pNetworkMode =
1620
  withDoc "Network mode when connecting to a group" $
1621
  simpleField "network_mode" [t| NICMode |]
1622

    
1623
pNetworkLink :: Field
1624
pNetworkLink =
1625
  withDoc "Network link when connecting to a group" $
1626
  simpleField "network_link" [t| NonEmptyString |]