Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ 1c88fa29

History | View | Annotate | Download (45.8 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
  , pStartupPaused
87
  , pVerbose
88
  , pDebugSimulateErrors
89
  , pErrorCodes
90
  , pSkipChecks
91
  , pIgnoreErrors
92
  , pOptGroupName
93
  , pGroupDiskParams
94
  , pHvState
95
  , pDiskState
96
  , pIgnoreIpolicy
97
  , pHotplug
98
  , pHotplugIfPossible
99
  , pAllowRuntimeChgs
100
  , pInstDisks
101
  , pDiskTemplate
102
  , pOptDiskTemplate
103
  , pFileDriver
104
  , pFileStorageDir
105
  , pClusterFileStorageDir
106
  , pClusterSharedFileStorageDir
107
  , pVgName
108
  , pEnabledHypervisors
109
  , pHypervisor
110
  , pClusterHvParams
111
  , pInstHvParams
112
  , pClusterBeParams
113
  , pInstBeParams
114
  , pResetDefaults
115
  , pOsHvp
116
  , pClusterOsParams
117
  , pInstOsParams
118
  , pCandidatePoolSize
119
  , pUidPool
120
  , pAddUids
121
  , pRemoveUids
122
  , pMaintainNodeHealth
123
  , pModifyEtcHosts
124
  , pPreallocWipeDisks
125
  , pNicParams
126
  , pInstNics
127
  , pNdParams
128
  , pIpolicy
129
  , pDrbdHelper
130
  , pDefaultIAllocator
131
  , pMasterNetdev
132
  , pMasterNetmask
133
  , pReservedLvs
134
  , pHiddenOs
135
  , pBlacklistedOs
136
  , pUseExternalMipScript
137
  , pQueryFields
138
  , pQueryFilter
139
  , pQueryFieldsFields
140
  , pOobCommand
141
  , pOobTimeout
142
  , pIgnoreStatus
143
  , pPowerDelay
144
  , pPrimaryIp
145
  , pSecondaryIp
146
  , pReadd
147
  , pNodeGroup
148
  , pMasterCapable
149
  , pVmCapable
150
  , pNames
151
  , pNodes
152
  , pRequiredNodes
153
  , pRequiredNodeUuids
154
  , pStorageType
155
  , pStorageTypeOptional
156
  , pStorageChanges
157
  , pMasterCandidate
158
  , pOffline
159
  , pDrained
160
  , pAutoPromote
161
  , pPowered
162
  , pIallocator
163
  , pRemoteNode
164
  , pRemoteNodeUuid
165
  , pEvacMode
166
  , pInstCreateMode
167
  , pNoInstall
168
  , pInstOs
169
  , pPrimaryNode
170
  , pPrimaryNodeUuid
171
  , pSecondaryNode
172
  , pSecondaryNodeUuid
173
  , pSourceHandshake
174
  , pSourceInstance
175
  , pSourceShutdownTimeout
176
  , pSourceX509Ca
177
  , pSrcNode
178
  , pSrcNodeUuid
179
  , pSrcPath
180
  , pStartInstance
181
  , pInstTags
182
  , pMultiAllocInstances
183
  , pTempOsParams
184
  , pTempHvParams
185
  , pTempBeParams
186
  , pIgnoreFailures
187
  , pNewName
188
  , pIgnoreSecondaries
189
  , pRebootType
190
  , pIgnoreDiskSize
191
  , pRecreateDisksInfo
192
  , pStatic
193
  , pInstParamsNicChanges
194
  , pInstParamsDiskChanges
195
  , pRuntimeMem
196
  , pOsNameChange
197
  , pDiskIndex
198
  , pDiskChgAmount
199
  , pDiskChgAbsolute
200
  , pTargetGroups
201
  , pExportMode
202
  , pExportTargetNode
203
  , pExportTargetNodeUuid
204
  , pRemoveInstance
205
  , pIgnoreRemoveFailures
206
  , pX509KeyName
207
  , pX509DestCA
208
  , pTagSearchPattern
209
  , pRestrictedCommand
210
  , pReplaceDisksMode
211
  , pReplaceDisksList
212
  , pAllowFailover
213
  , pForceFailover
214
  , pDelayDuration
215
  , pDelayOnMaster
216
  , pDelayOnNodes
217
  , pDelayOnNodeUuids
218
  , pDelayRepeat
219
  , pDelayNoLocks
220
  , pIAllocatorDirection
221
  , pIAllocatorMode
222
  , pIAllocatorReqName
223
  , pIAllocatorNics
224
  , pIAllocatorDisks
225
  , pIAllocatorMemory
226
  , pIAllocatorVCpus
227
  , pIAllocatorOs
228
  , pIAllocatorInstances
229
  , pIAllocatorEvacMode
230
  , pIAllocatorSpindleUse
231
  , pIAllocatorCount
232
  , pJQueueNotifyWaitLock
233
  , pJQueueNotifyExec
234
  , pJQueueLogMessages
235
  , pJQueueFail
236
  , pTestDummyResult
237
  , pTestDummyMessages
238
  , pTestDummyFail
239
  , pTestDummySubmitJobs
240
  , pNetworkName
241
  , pNetworkAddress4
242
  , pNetworkGateway4
243
  , pNetworkAddress6
244
  , pNetworkGateway6
245
  , pNetworkMacPrefix
246
  , pNetworkAddRsvdIps
247
  , pNetworkRemoveRsvdIps
248
  , pNetworkMode
249
  , pNetworkLink
250
  , pDryRun
251
  , pDebugLevel
252
  , pOpPriority
253
  , pDependencies
254
  , pComment
255
  , pReason
256
  , pSequential
257
  , pEnabledDiskTemplates
258
  ) where
259

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

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

    
273
-- * Helper functions and types
274

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

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

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

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

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

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

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

    
308
-- ** Disks
309

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

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

    
322
instance JSON DiskIndex where
323
  readJSON v = readJSON v >>= mkDiskIndex
324
  showJSON = showJSON . unDiskIndex
325

    
326
-- ** I* param types
327

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

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

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

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

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

    
381
instance JSON RecreateDisksInfo where
382
  readJSON = readRecreateDisks
383
  showJSON  RecreateDisksAll            = showJSON ()
384
  showJSON (RecreateDisksIndices idx)   = showJSON idx
385
  showJSON (RecreateDisksParams params) = showJSON params
386

    
387
-- | Simple type for old-style ddm changes.
388
data DdmOldChanges = DdmOldIndex (NonNegative Int)
389
                   | DdmOldMod DdmSimple
390
                     deriving (Eq, Show)
391

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

    
401
instance JSON DdmOldChanges where
402
  showJSON (DdmOldIndex i) = showJSON i
403
  showJSON (DdmOldMod m)   = showJSON m
404
  readJSON = readDdmOldChanges
405

    
406
-- | Instance disk or nic modifications.
407
data SetParamsMods a
408
  = SetParamsEmpty
409
  | SetParamsDeprecated (NonEmpty (DdmOldChanges, a))
410
  | SetParamsNew (NonEmpty (DdmFull, Int, a))
411
    deriving (Eq, Show)
412

    
413
-- | Custom deserialiser for 'SetParamsMods'.
414
readSetParams :: (JSON a) => JSValue -> Text.JSON.Result (SetParamsMods a)
415
readSetParams (JSArray []) = return SetParamsEmpty
416
readSetParams v =
417
  case readJSON v::Text.JSON.Result [(DdmOldChanges, JSValue)] of
418
    Text.JSON.Ok _ -> liftM SetParamsDeprecated $ readJSON v
419
    _ -> liftM SetParamsNew $ readJSON v
420

    
421
instance (JSON a) => JSON (SetParamsMods a) where
422
  showJSON SetParamsEmpty = showJSON ()
423
  showJSON (SetParamsDeprecated v) = showJSON v
424
  showJSON (SetParamsNew v) = showJSON v
425
  readJSON = readSetParams
426

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

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

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

    
448
-- * Common opcode parameters
449

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

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

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

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

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

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

    
482
pSequential :: Field
483
pSequential =
484
  withDoc "Sequential job execution" $
485
  defaultFalse C.opcodeSequential
486

    
487
-- * Parameters
488

    
489
pDebugSimulateErrors :: Field
490
pDebugSimulateErrors =
491
  withDoc "Whether to simulate errors (useful for debugging)" $
492
  defaultFalse "debug_simulate_errors"
493

    
494
pErrorCodes :: Field
495
pErrorCodes = 
496
  withDoc "Error codes" $
497
  defaultFalse "error_codes"
498

    
499
pSkipChecks :: Field
500
pSkipChecks = 
501
  withDoc "Which checks to skip" .
502
  defaultField [| emptyListSet |] $
503
  simpleField "skip_checks" [t| ListSet VerifyOptionalChecks |]
504

    
505
pIgnoreErrors :: Field
506
pIgnoreErrors =
507
  withDoc "List of error codes that should be treated as warnings" .
508
  defaultField [| emptyListSet |] $
509
  simpleField "ignore_errors" [t| ListSet CVErrorCode |]
510

    
511
pVerbose :: Field
512
pVerbose =
513
  withDoc "Verbose mode" $
514
  defaultFalse "verbose"
515

    
516
pOptGroupName :: Field
517
pOptGroupName =
518
  withDoc "Optional group name" .
519
  renameField "OptGroupName" .
520
  optionalField $ simpleField "group_name" [t| NonEmptyString |]
521

    
522
pGroupName :: Field
523
pGroupName =
524
  withDoc "Group name" $
525
  simpleField "group_name" [t| NonEmptyString |]
526

    
527
-- | Whether to hotplug device.
528
pHotplug :: Field
529
pHotplug = defaultFalse "hotplug"
530

    
531
pHotplugIfPossible :: Field
532
pHotplugIfPossible = defaultFalse "hotplug_if_possible"
533

    
534
pInstances :: Field
535
pInstances =
536
  withDoc "List of instances" .
537
  defaultField [| [] |] $
538
  simpleField "instances" [t| [NonEmptyString] |]
539

    
540
pOutputFields :: Field
541
pOutputFields =
542
  withDoc "Selected output fields" $
543
  simpleField "output_fields" [t| [NonEmptyString] |]
544

    
545
pName :: Field
546
pName =
547
  withDoc "A generic name" $
548
  simpleField "name" [t| NonEmptyString |]
549

    
550
pForce :: Field
551
pForce =
552
  withDoc "Whether to force the operation" $
553
  defaultFalse "force"
554

    
555
pHvState :: Field
556
pHvState =
557
  withDoc "Set hypervisor states" .
558
  optionalField $ simpleField "hv_state" [t| JSObject JSValue |]
559

    
560
pDiskState :: Field
561
pDiskState =
562
  withDoc "Set disk states" .
563
  optionalField $ simpleField "disk_state" [t| JSObject JSValue |]
564

    
565
-- | Cluster-wide default directory for storing file-backed disks.
566
pClusterFileStorageDir :: Field
567
pClusterFileStorageDir =
568
  renameField "ClusterFileStorageDir" $
569
  optionalStringField "file_storage_dir"
570

    
571
-- | Cluster-wide default directory for storing shared-file-backed disks.
572
pClusterSharedFileStorageDir :: Field
573
pClusterSharedFileStorageDir =
574
  renameField "ClusterSharedFileStorageDir" $
575
  optionalStringField "shared_file_storage_dir"
576

    
577
-- | Volume group name.
578
pVgName :: Field
579
pVgName =
580
  withDoc "Volume group name" $
581
  optionalStringField "vg_name"
582

    
583
pEnabledHypervisors :: Field
584
pEnabledHypervisors =
585
  withDoc "List of enabled hypervisors" .
586
  optionalField $
587
  simpleField "enabled_hypervisors" [t| [Hypervisor] |]
588

    
589
pClusterHvParams :: Field
590
pClusterHvParams =
591
  withDoc "Cluster-wide hypervisor parameters, hypervisor-dependent" .
592
  renameField "ClusterHvParams" .
593
  optionalField $
594
  simpleField "hvparams" [t| GenericContainer String (JSObject JSValue) |]
595

    
596
pClusterBeParams :: Field
597
pClusterBeParams =
598
  withDoc "Cluster-wide backend parameter defaults" .
599
  renameField "ClusterBeParams" .
600
  optionalField $ simpleField "beparams" [t| JSObject JSValue |]
601

    
602
pOsHvp :: Field
603
pOsHvp =
604
  withDoc "Cluster-wide per-OS hypervisor parameter defaults" .
605
  optionalField $
606
  simpleField "os_hvp" [t| GenericContainer String (JSObject JSValue) |]
607

    
608
pClusterOsParams :: Field
609
pClusterOsParams =
610
  withDoc "Cluster-wide OS parameter defaults" .
611
  renameField "ClusterOsParams" .
612
  optionalField $
613
  simpleField "osparams" [t| GenericContainer String (JSObject JSValue) |]
614

    
615
pGroupDiskParams :: Field
616
pGroupDiskParams =
617
  withDoc "Disk templates' parameter defaults" .
618
  optionalField $
619
  simpleField "diskparams"
620
              [t| GenericContainer DiskTemplate (JSObject JSValue) |]
621

    
622
pCandidatePoolSize :: Field
623
pCandidatePoolSize =
624
  withDoc "Master candidate pool size" .
625
  optionalField $ simpleField "candidate_pool_size" [t| Positive Int |]
626

    
627
pUidPool :: Field
628
pUidPool =
629
  withDoc "Set UID pool, must be list of lists describing UID ranges\
630
          \ (two items, start and end inclusive)" .
631
  optionalField $ simpleField "uid_pool" [t| [(Int, Int)] |]
632

    
633
pAddUids :: Field
634
pAddUids =
635
  withDoc "Extend UID pool, must be list of lists describing UID\
636
          \ ranges (two items, start and end inclusive)" .
637
  optionalField $ simpleField "add_uids" [t| [(Int, Int)] |]
638

    
639
pRemoveUids :: Field
640
pRemoveUids =
641
  withDoc "Shrink UID pool, must be list of lists describing UID\
642
          \ ranges (two items, start and end inclusive) to be removed" .
643
  optionalField $ simpleField "remove_uids" [t| [(Int, Int)] |]
644

    
645
pMaintainNodeHealth :: Field
646
pMaintainNodeHealth =
647
  withDoc "Whether to automatically maintain node health" .
648
  optionalField $ booleanField "maintain_node_health"
649

    
650
-- | Whether to modify and keep in sync the @/etc/hosts@ files of nodes.
651
pModifyEtcHosts :: Field
652
pModifyEtcHosts = optionalField $ booleanField "modify_etc_hosts"
653

    
654
-- | Whether to wipe disks before allocating them to instances.
655
pPreallocWipeDisks :: Field
656
pPreallocWipeDisks =
657
  withDoc "Whether to wipe disks before allocating them to instances" .
658
  optionalField $ booleanField "prealloc_wipe_disks"
659

    
660
pNicParams :: Field
661
pNicParams =
662
  withDoc "Cluster-wide NIC parameter defaults" .
663
  optionalField $ simpleField "nicparams" [t| INicParams |]
664

    
665
pIpolicy :: Field
666
pIpolicy =
667
  withDoc "Ipolicy specs" .
668
  optionalField $ simpleField "ipolicy" [t| JSObject JSValue |]
669

    
670
pDrbdHelper :: Field
671
pDrbdHelper =
672
  withDoc "DRBD helper program" $
673
  optionalStringField "drbd_helper"
674

    
675
pDefaultIAllocator :: Field
676
pDefaultIAllocator =
677
  withDoc "Default iallocator for cluster" $
678
  optionalStringField "default_iallocator"
679

    
680
pMasterNetdev :: Field
681
pMasterNetdev =
682
  withDoc "Master network device" $
683
  optionalStringField "master_netdev"
684

    
685
pMasterNetmask :: Field
686
pMasterNetmask =
687
  withDoc "Netmask of the master IP" .
688
  optionalField $ simpleField "master_netmask" [t| NonNegative Int |]
689

    
690
pReservedLvs :: Field
691
pReservedLvs =
692
  withDoc "List of reserved LVs" .
693
  optionalField $ simpleField "reserved_lvs" [t| [NonEmptyString] |]
694

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

    
702
pBlacklistedOs :: Field
703
pBlacklistedOs =
704
  withDoc "Modify list of blacklisted operating systems: each\
705
          \ modification must have two items, the operation and the OS name;\
706
          \ the operation can be add or remove" .
707
  optionalField $
708
  simpleField "blacklisted_os" [t| [(DdmSimple, NonEmptyString)] |]
709

    
710
pUseExternalMipScript :: Field
711
pUseExternalMipScript =
712
  withDoc "Whether to use an external master IP address setup script" .
713
  optionalField $ booleanField "use_external_mip_script"
714

    
715
pEnabledDiskTemplates :: Field
716
pEnabledDiskTemplates =
717
  withDoc "List of enabled disk templates" .
718
  optionalField $
719
  simpleField "enabled_disk_templates" [t| [DiskTemplate] |]
720

    
721
pQueryWhat :: Field
722
pQueryWhat =
723
  withDoc "Resource(s) to query for" $
724
  simpleField "what" [t| Qlang.QueryTypeOp |]
725

    
726
pUseLocking :: Field
727
pUseLocking =
728
  withDoc "Whether to use synchronization" $
729
  defaultFalse "use_locking"
730

    
731
pQueryFields :: Field
732
pQueryFields =
733
  withDoc "Requested fields" $
734
  simpleField "fields" [t| [NonEmptyString] |]
735

    
736
pQueryFilter :: Field
737
pQueryFilter =
738
  withDoc "Query filter" .
739
  optionalField $ simpleField "qfilter" [t| [JSValue] |]
740

    
741
pQueryFieldsFields :: Field
742
pQueryFieldsFields =
743
  withDoc "Requested fields; if not given, all are returned" .
744
  renameField "QueryFieldsFields" $
745
  optionalField pQueryFields
746

    
747
pNodeNames :: Field
748
pNodeNames =
749
  withDoc "List of node names to run the OOB command against" .
750
  defaultField [| [] |] $ simpleField "node_names" [t| [NonEmptyString] |]
751

    
752
pNodeUuids :: Field
753
pNodeUuids =
754
  withDoc "List of node UUIDs" .
755
  optionalField $ simpleField "node_uuids" [t| [NonEmptyString] |]
756

    
757
pOobCommand :: Field
758
pOobCommand =
759
  withDoc "OOB command to run" $
760
  simpleField "command" [t| OobCommand |]
761

    
762
pOobTimeout :: Field
763
pOobTimeout =
764
  withDoc "Timeout before the OOB helper will be terminated" .
765
  defaultField [| C.oobTimeout |] $
766
  simpleField "timeout" [t| Int |]
767

    
768
pIgnoreStatus :: Field
769
pIgnoreStatus =
770
  withDoc "Ignores the node offline status for power off" $
771
  defaultFalse "ignore_status"
772

    
773
pPowerDelay :: Field
774
pPowerDelay =
775
  -- FIXME: we can't use the proper type "NonNegative Double", since
776
  -- the default constant is a plain Double, not a non-negative one.
777
  -- And trying to fix the constant introduces a cyclic import.
778
  withDoc "Time in seconds to wait between powering on nodes" .
779
  defaultField [| C.oobPowerDelay |] $
780
  simpleField "power_delay" [t| Double |]
781

    
782
pRequiredNodes :: Field
783
pRequiredNodes =
784
  withDoc "Required list of node names" .
785
  renameField "ReqNodes " $ simpleField "nodes" [t| [NonEmptyString] |]
786

    
787
pRequiredNodeUuids :: Field
788
pRequiredNodeUuids =
789
  withDoc "Required list of node UUIDs" .
790
  renameField "ReqNodeUuids " . optionalField $
791
  simpleField "node_uuids" [t| [NonEmptyString] |]
792

    
793
pRestrictedCommand :: Field
794
pRestrictedCommand =
795
  withDoc "Restricted command name" .
796
  renameField "RestrictedCommand" $
797
  simpleField "command" [t| NonEmptyString |]
798

    
799
pNodeName :: Field
800
pNodeName =
801
  withDoc "A required node name (for single-node LUs)" $
802
  simpleField "node_name" [t| NonEmptyString |]
803

    
804
pNodeUuid :: Field
805
pNodeUuid =
806
  withDoc "A node UUID (for single-node LUs)" .
807
  optionalField $ simpleField "node_uuid" [t| NonEmptyString |]
808

    
809
pPrimaryIp :: Field
810
pPrimaryIp =
811
  withDoc "Primary IP address" .
812
  optionalField $
813
  simpleField "primary_ip" [t| NonEmptyString |]
814

    
815
pSecondaryIp :: Field
816
pSecondaryIp =
817
  withDoc "Secondary IP address" $
818
  optionalNEStringField "secondary_ip"
819

    
820
pReadd :: Field
821
pReadd =
822
  withDoc "Whether node is re-added to cluster" $
823
  defaultFalse "readd"
824

    
825
pNodeGroup :: Field
826
pNodeGroup =
827
  withDoc "Initial node group" $
828
  optionalNEStringField "group"
829

    
830
pMasterCapable :: Field
831
pMasterCapable =
832
  withDoc "Whether node can become master or master candidate" .
833
  optionalField $ booleanField "master_capable"
834

    
835
pVmCapable :: Field
836
pVmCapable =
837
  withDoc "Whether node can host instances" .
838
  optionalField $ booleanField "vm_capable"
839

    
840
pNdParams :: Field
841
pNdParams =
842
  withDoc "Node parameters" .
843
  renameField "genericNdParams" .
844
  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
845
  
846
pNames :: Field
847
pNames =
848
  withDoc "List of names" .
849
  defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
850

    
851
pNodes :: Field
852
pNodes =
853
  withDoc "List of nodes" .
854
  defaultField [| [] |] $ simpleField "nodes" [t| [NonEmptyString] |]
855

    
856
pStorageType :: Field
857
pStorageType =
858
  withDoc "Storage type" $ simpleField "storage_type" [t| StorageType |]
859

    
860
pStorageTypeOptional :: Field
861
pStorageTypeOptional =
862
  withDoc "Storage type" .
863
  renameField "StorageTypeOptional" .
864
  optionalField $ simpleField "storage_type" [t| StorageType |]
865

    
866
pStorageName :: Field
867
pStorageName =
868
  withDoc "Storage name" .
869
  renameField "StorageName" .
870
  optionalField $ simpleField "name" [t| NonEmptyString |]
871

    
872
pStorageChanges :: Field
873
pStorageChanges =
874
  withDoc "Requested storage changes" $
875
  simpleField "changes" [t| JSObject JSValue |]
876

    
877
pIgnoreConsistency :: Field
878
pIgnoreConsistency =
879
  withDoc "Whether to ignore disk consistency" $
880
  defaultFalse "ignore_consistency"
881

    
882
pMasterCandidate :: Field
883
pMasterCandidate =
884
  withDoc "Whether the node should become a master candidate" .
885
  optionalField $ booleanField "master_candidate"
886

    
887
pOffline :: Field
888
pOffline =
889
  withDoc "Whether to mark the node or instance offline" .
890
  optionalField $ booleanField "offline"
891

    
892
pDrained ::Field
893
pDrained =
894
  withDoc "Whether to mark the node as drained" .
895
  optionalField $ booleanField "drained"
896

    
897
pAutoPromote :: Field
898
pAutoPromote =
899
  withDoc "Whether node(s) should be promoted to master candidate if\
900
          \ necessary" $
901
  defaultFalse "auto_promote"
902

    
903
pPowered :: Field
904
pPowered =
905
  withDoc "Whether the node should be marked as powered" .
906
  optionalField $ booleanField "powered"
907

    
908
pMigrationMode :: Field
909
pMigrationMode =
910
  withDoc "Migration type (live/non-live)" .
911
  renameField "MigrationMode" .
912
  optionalField $
913
  simpleField "mode" [t| MigrationMode |]
914

    
915
pMigrationLive :: Field
916
pMigrationLive =
917
  withDoc "Obsolete \'live\' migration mode (do not use)" .
918
  renameField "OldLiveMode" . optionalField $ booleanField "live"
919

    
920
pMigrationTargetNode :: Field
921
pMigrationTargetNode =
922
  withDoc "Target node for instance migration/failover" $
923
  optionalNEStringField "target_node"
924

    
925
pMigrationTargetNodeUuid :: Field
926
pMigrationTargetNodeUuid =
927
  withDoc "Target node UUID for instance migration/failover" $
928
  optionalNEStringField "target_node_uuid"
929

    
930
pAllowRuntimeChgs :: Field
931
pAllowRuntimeChgs =
932
  withDoc "Whether to allow runtime changes while migrating" $
933
  defaultTrue "allow_runtime_changes"
934

    
935
pIgnoreIpolicy :: Field
936
pIgnoreIpolicy =
937
  withDoc "Whether to ignore ipolicy violations" $
938
  defaultFalse "ignore_ipolicy"
939
  
940
pIallocator :: Field
941
pIallocator =
942
  withDoc "Iallocator for deciding the target node for shared-storage\
943
          \ instances" $
944
  optionalNEStringField "iallocator"
945

    
946
pEarlyRelease :: Field
947
pEarlyRelease =
948
  withDoc "Whether to release locks as soon as possible" $
949
  defaultFalse "early_release"
950

    
951
pRemoteNode :: Field
952
pRemoteNode =
953
  withDoc "New secondary node" $
954
  optionalNEStringField "remote_node"
955

    
956
pRemoteNodeUuid :: Field
957
pRemoteNodeUuid =
958
  withDoc "New secondary node UUID" $
959
  optionalNEStringField "remote_node_uuid"
960

    
961
pEvacMode :: Field
962
pEvacMode =
963
  withDoc "Node evacuation mode" .
964
  renameField "EvacMode" $ simpleField "mode" [t| EvacMode |]
965

    
966
pInstanceName :: Field
967
pInstanceName =
968
  withDoc "A required instance name (for single-instance LUs)" $
969
  simpleField "instance_name" [t| String |]
970

    
971
pForceVariant :: Field
972
pForceVariant =
973
  withDoc "Whether to force an unknown OS variant" $
974
  defaultFalse "force_variant"
975

    
976
pWaitForSync :: Field
977
pWaitForSync =
978
  withDoc "Whether to wait for the disk to synchronize" $
979
  defaultTrue "wait_for_sync"
980

    
981
pNameCheck :: Field
982
pNameCheck =
983
  withDoc "Whether to check name" $
984
  defaultTrue "name_check"
985

    
986
pInstBeParams :: Field
987
pInstBeParams =
988
  withDoc "Backend parameters for instance" .
989
  renameField "InstBeParams" .
990
  defaultField [| toJSObject [] |] $
991
  simpleField "beparams" [t| JSObject JSValue |]
992

    
993
pInstDisks :: Field
994
pInstDisks =
995
  withDoc "List of instance disks" .
996
  renameField "instDisks" $ simpleField "disks" [t| [IDiskParams] |]
997

    
998
pDiskTemplate :: Field
999
pDiskTemplate =
1000
  withDoc "Disk template" $
1001
  simpleField "disk_template" [t| DiskTemplate |]
1002

    
1003
pFileDriver :: Field
1004
pFileDriver =
1005
  withDoc "Driver for file-backed disks" .
1006
  optionalField $ simpleField "file_driver" [t| FileDriver |]
1007

    
1008
pFileStorageDir :: Field
1009
pFileStorageDir =
1010
  withDoc "Directory for storing file-backed disks" $
1011
  optionalNEStringField "file_storage_dir"
1012

    
1013
pInstHvParams :: Field
1014
pInstHvParams =
1015
  withDoc "Hypervisor parameters for instance, hypervisor-dependent" .
1016
  renameField "InstHvParams" .
1017
  defaultField [| toJSObject [] |] $
1018
  simpleField "hvparams" [t| JSObject JSValue |]
1019

    
1020
pHypervisor :: Field
1021
pHypervisor =
1022
  withDoc "Selected hypervisor for an instance" .
1023
  optionalField $
1024
  simpleField "hypervisor" [t| Hypervisor |]
1025

    
1026
pResetDefaults :: Field
1027
pResetDefaults =
1028
  withDoc "Reset instance parameters to default if equal" $
1029
  defaultFalse "identify_defaults"
1030

    
1031
pIpCheck :: Field
1032
pIpCheck =
1033
  withDoc "Whether to ensure instance's IP address is inactive" $
1034
  defaultTrue "ip_check"
1035

    
1036
pIpConflictsCheck :: Field
1037
pIpConflictsCheck =
1038
  withDoc "Whether to check for conflicting IP addresses" $
1039
  defaultTrue "conflicts_check"
1040

    
1041
pInstCreateMode :: Field
1042
pInstCreateMode =
1043
  withDoc "Instance creation mode" .
1044
  renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
1045

    
1046
pInstNics :: Field
1047
pInstNics =
1048
  withDoc "List of NIC (network interface) definitions" $
1049
  simpleField "nics" [t| [INicParams] |]
1050

    
1051
pNoInstall :: Field
1052
pNoInstall =
1053
  withDoc "Do not install the OS (will disable automatic start)" .
1054
  optionalField $ booleanField "no_install"
1055

    
1056
pInstOs :: Field
1057
pInstOs =
1058
  withDoc "OS type for instance installation" $
1059
  optionalNEStringField "os_type"
1060

    
1061
pInstOsParams :: Field
1062
pInstOsParams =
1063
  withDoc "OS parameters for instance" .
1064
  renameField "InstOsParams" .
1065
  defaultField [| toJSObject [] |] $
1066
  simpleField "osparams" [t| JSObject JSValue |]
1067

    
1068
pPrimaryNode :: Field
1069
pPrimaryNode =
1070
  withDoc "Primary node for an instance" $
1071
  optionalNEStringField "pnode"
1072

    
1073
pPrimaryNodeUuid :: Field
1074
pPrimaryNodeUuid =
1075
  withDoc "Primary node UUID for an instance" $
1076
  optionalNEStringField "pnode_uuid"
1077

    
1078
pSecondaryNode :: Field
1079
pSecondaryNode =
1080
  withDoc "Secondary node for an instance" $
1081
  optionalNEStringField "snode"
1082

    
1083
pSecondaryNodeUuid :: Field
1084
pSecondaryNodeUuid =
1085
  withDoc "Secondary node UUID for an instance" $
1086
  optionalNEStringField "snode_uuid"
1087

    
1088
pSourceHandshake :: Field
1089
pSourceHandshake =
1090
  withDoc "Signed handshake from source (remote import only)" .
1091
  optionalField $ simpleField "source_handshake" [t| [JSValue] |]
1092

    
1093
pSourceInstance :: Field
1094
pSourceInstance =
1095
  withDoc "Source instance name (remote import only)" $
1096
  optionalNEStringField "source_instance_name"
1097

    
1098
-- FIXME: non-negative int, whereas the constant is a plain int.
1099
pSourceShutdownTimeout :: Field
1100
pSourceShutdownTimeout =
1101
  withDoc "How long source instance was given to shut down (remote import\
1102
          \ only)" .
1103
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1104
  simpleField "source_shutdown_timeout" [t| NonNegative Int |]
1105

    
1106
pSourceX509Ca :: Field
1107
pSourceX509Ca =
1108
  withDoc "Source X509 CA in PEM format (remote import only)" $
1109
  optionalNEStringField "source_x509_ca"
1110

    
1111
pSrcNode :: Field
1112
pSrcNode =
1113
  withDoc "Source node for import" $
1114
  optionalNEStringField "src_node"
1115

    
1116
pSrcNodeUuid :: Field
1117
pSrcNodeUuid =
1118
  withDoc "Source node UUID for import" $
1119
  optionalNEStringField "src_node_uuid"
1120

    
1121
pSrcPath :: Field
1122
pSrcPath =
1123
  withDoc "Source directory for import" $
1124
  optionalNEStringField "src_path"
1125

    
1126
pStartInstance :: Field
1127
pStartInstance =
1128
  withDoc "Whether to start instance after creation" $
1129
  defaultTrue "start"
1130

    
1131
-- FIXME: unify/simplify with pTags, once that migrates to NonEmpty String"
1132
pInstTags :: Field
1133
pInstTags =
1134
  withDoc "Instance tags" .
1135
  renameField "InstTags" .
1136
  defaultField [| [] |] $
1137
  simpleField "tags" [t| [NonEmptyString] |]
1138

    
1139
pMultiAllocInstances :: Field
1140
pMultiAllocInstances =
1141
  withDoc "List of instance create opcodes describing the instances to\
1142
          \ allocate" .
1143
  renameField "InstMultiAlloc" .
1144
  defaultField [| [] |] $
1145
  simpleField "instances"[t| [JSValue] |]
1146

    
1147
pOpportunisticLocking :: Field
1148
pOpportunisticLocking =
1149
  withDoc "Whether to employ opportunistic locking for nodes, meaning\
1150
          \ nodes already locked by another opcode won't be considered for\
1151
          \ instance allocation (only when an iallocator is used)" $
1152
  defaultFalse "opportunistic_locking"
1153

    
1154
pInstanceUuid :: Field
1155
pInstanceUuid =
1156
  withDoc "An instance UUID (for single-instance LUs)" .
1157
  optionalField $ simpleField "instance_uuid" [t| NonEmptyString |]
1158

    
1159
pTempOsParams :: Field
1160
pTempOsParams =
1161
  withDoc "Temporary OS parameters (currently only in reinstall, might be\
1162
          \ added to install as well)" .
1163
  renameField "TempOsParams" .
1164
  optionalField $ simpleField "osparams" [t| JSObject JSValue |]
1165

    
1166
pShutdownTimeout :: Field
1167
pShutdownTimeout =
1168
  withDoc "How long to wait for instance to shut down" .
1169
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1170
  simpleField "shutdown_timeout" [t| NonNegative Int |]
1171

    
1172
-- | Another name for the shutdown timeout, because we like to be
1173
-- inconsistent.
1174
pShutdownTimeout' :: Field
1175
pShutdownTimeout' =
1176
  withDoc "How long to wait for instance to shut down" .
1177
  renameField "InstShutdownTimeout" .
1178
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1179
  simpleField "timeout" [t| NonNegative Int |]
1180

    
1181
pIgnoreFailures :: Field
1182
pIgnoreFailures =
1183
  withDoc "Whether to ignore failures during removal" $
1184
  defaultFalse "ignore_failures"
1185

    
1186
pNewName :: Field
1187
pNewName =
1188
  withDoc "New group or instance name" $
1189
  simpleField "new_name" [t| NonEmptyString |]
1190
  
1191
pIgnoreOfflineNodes :: Field
1192
pIgnoreOfflineNodes =
1193
  withDoc "Whether to ignore offline nodes" $
1194
  defaultFalse "ignore_offline_nodes"
1195

    
1196
pTempHvParams :: Field
1197
pTempHvParams =
1198
  withDoc "Temporary hypervisor parameters, hypervisor-dependent" .
1199
  renameField "TempHvParams" .
1200
  defaultField [| toJSObject [] |] $
1201
  simpleField "hvparams" [t| JSObject JSValue |]
1202

    
1203
pTempBeParams :: Field
1204
pTempBeParams =
1205
  withDoc "Temporary backend parameters" .
1206
  renameField "TempBeParams" .
1207
  defaultField [| toJSObject [] |] $
1208
  simpleField "beparams" [t| JSObject JSValue |]
1209

    
1210
pNoRemember :: Field
1211
pNoRemember =
1212
  withDoc "Do not remember instance state changes" $
1213
  defaultFalse "no_remember"
1214

    
1215
pStartupPaused :: Field
1216
pStartupPaused =
1217
  withDoc "Pause instance at startup" $
1218
  defaultFalse "startup_paused"
1219

    
1220
pIgnoreSecondaries :: Field
1221
pIgnoreSecondaries =
1222
  withDoc "Whether to start the instance even if secondary disks are failing" $
1223
  defaultFalse "ignore_secondaries"
1224

    
1225
pRebootType :: Field
1226
pRebootType =
1227
  withDoc "How to reboot the instance" $
1228
  simpleField "reboot_type" [t| RebootType |]
1229

    
1230
pReplaceDisksMode :: Field
1231
pReplaceDisksMode =
1232
  withDoc "Replacement mode" .
1233
  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1234

    
1235
pReplaceDisksList :: Field
1236
pReplaceDisksList =
1237
  withDoc "List of disk indices" .
1238
  renameField "ReplaceDisksList" .
1239
  defaultField [| [] |] $
1240
  simpleField "disks" [t| [DiskIndex] |]
1241

    
1242
pMigrationCleanup :: Field
1243
pMigrationCleanup =
1244
  withDoc "Whether a previously failed migration should be cleaned up" .
1245
  renameField "MigrationCleanup" $ defaultFalse "cleanup"
1246

    
1247
pAllowFailover :: Field
1248
pAllowFailover =
1249
  withDoc "Whether we can fallback to failover if migration is not possible" $
1250
  defaultFalse "allow_failover"
1251

    
1252
pForceFailover :: Field
1253
pForceFailover =
1254
  withDoc "Disallow migration moves and always use failovers" $
1255
  defaultFalse "force_failover"
1256

    
1257
pMoveTargetNode :: Field
1258
pMoveTargetNode =
1259
  withDoc "Target node for instance move" .
1260
  renameField "MoveTargetNode" $
1261
  simpleField "target_node" [t| NonEmptyString |]
1262

    
1263
pMoveTargetNodeUuid :: Field
1264
pMoveTargetNodeUuid =
1265
  withDoc "Target node UUID for instance move" .
1266
  renameField "MoveTargetNodeUuid" . optionalField $
1267
  simpleField "target_node_uuid" [t| NonEmptyString |]
1268

    
1269
pIgnoreDiskSize :: Field
1270
pIgnoreDiskSize =
1271
  withDoc "Whether to ignore recorded disk size" $
1272
  defaultFalse "ignore_size"
1273
  
1274
pWaitForSyncFalse :: Field
1275
pWaitForSyncFalse =
1276
  withDoc "Whether to wait for the disk to synchronize (defaults to false)" $
1277
  defaultField [| False |] pWaitForSync
1278
  
1279
pRecreateDisksInfo :: Field
1280
pRecreateDisksInfo =
1281
  withDoc "Disk list for recreate disks" .
1282
  renameField "RecreateDisksInfo" .
1283
  defaultField [| RecreateDisksAll |] $
1284
  simpleField "disks" [t| RecreateDisksInfo |]
1285

    
1286
pStatic :: Field
1287
pStatic =
1288
  withDoc "Whether to only return configuration data without querying nodes" $
1289
  defaultFalse "static"
1290

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

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

    
1305
pRuntimeMem :: Field
1306
pRuntimeMem =
1307
  withDoc "New runtime memory" .
1308
  optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1309

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

    
1317
pOsNameChange :: Field
1318
pOsNameChange =
1319
  withDoc "Change the instance's OS without reinstalling the instance" $
1320
  optionalNEStringField "os_name"
1321

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

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

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

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

    
1344
pNodeGroupAllocPolicy :: Field
1345
pNodeGroupAllocPolicy =
1346
  withDoc "Instance allocation policy" .
1347
  optionalField $
1348
  simpleField "alloc_policy" [t| AllocPolicy |]
1349

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

    
1355
pExportMode :: Field
1356
pExportMode =
1357
  withDoc "Export mode" .
1358
  renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1359

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

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

    
1374
pShutdownInstance :: Field
1375
pShutdownInstance =
1376
  withDoc "Whether to shutdown the instance before export" $
1377
  defaultTrue "shutdown"
1378

    
1379
pRemoveInstance :: Field
1380
pRemoveInstance =
1381
  withDoc "Whether to remove instance after export" $
1382
  defaultFalse "remove_instance"
1383

    
1384
pIgnoreRemoveFailures :: Field
1385
pIgnoreRemoveFailures =
1386
  withDoc "Whether to ignore failures while removing instances" $
1387
  defaultFalse "ignore_remove_failures"
1388

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

    
1394
pX509DestCA :: Field
1395
pX509DestCA =
1396
  withDoc "Destination X509 CA (remote export only)" $
1397
  optionalNEStringField "destination_x509_ca"
1398

    
1399
pTagsObject :: Field
1400
pTagsObject =
1401
  withDoc "Tag kind" $
1402
  simpleField "kind" [t| TagKind |]
1403

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

    
1410
pTagsList :: Field
1411
pTagsList =
1412
  withDoc "List of tag names" $
1413
  simpleField "tags" [t| [String] |]
1414

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

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

    
1428
pDelayOnMaster :: Field
1429
pDelayOnMaster =
1430
  withDoc "on_master field for 'OpTestDelay'" .
1431
  renameField "DelayOnMaster" $
1432
  defaultTrue "on_master"
1433

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

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

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

    
1454
pDelayNoLocks :: Field
1455
pDelayNoLocks =
1456
  withDoc "Don't take locks during the delay" .
1457
  renameField "DelayNoLocks" $
1458
  defaultTrue "no_locks"
1459

    
1460
pIAllocatorDirection :: Field
1461
pIAllocatorDirection =
1462
  withDoc "IAllocator test direction" .
1463
  renameField "IAllocatorDirection" $
1464
  simpleField "direction" [t| IAllocatorTestDir |]
1465

    
1466
pIAllocatorMode :: Field
1467
pIAllocatorMode =
1468
  withDoc "IAllocator test mode" .
1469
  renameField "IAllocatorMode" $
1470
  simpleField "mode" [t| IAllocatorMode |]
1471

    
1472
pIAllocatorReqName :: Field
1473
pIAllocatorReqName =
1474
  withDoc "IAllocator target name (new instance, node to evac, etc.)" .
1475
  renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
1476

    
1477
pIAllocatorNics :: Field
1478
pIAllocatorNics =
1479
  withDoc "Custom OpTestIAllocator nics" .
1480
  renameField "IAllocatorNics" .
1481
  optionalField $ simpleField "nics" [t| [INicParams] |]
1482

    
1483
pIAllocatorDisks :: Field
1484
pIAllocatorDisks =
1485
  withDoc "Custom OpTestAllocator disks" .
1486
  renameField "IAllocatorDisks" .
1487
  optionalField $ simpleField "disks" [t| [JSValue] |]
1488

    
1489
pIAllocatorMemory :: Field
1490
pIAllocatorMemory =
1491
  withDoc "IAllocator memory field" .
1492
  renameField "IAllocatorMem" .
1493
  optionalField $
1494
  simpleField "memory" [t| NonNegative Int |]
1495

    
1496
pIAllocatorVCpus :: Field
1497
pIAllocatorVCpus =
1498
  withDoc "IAllocator vcpus field" .
1499
  renameField "IAllocatorVCpus" .
1500
  optionalField $
1501
  simpleField "vcpus" [t| NonNegative Int |]
1502

    
1503
pIAllocatorOs :: Field
1504
pIAllocatorOs =
1505
  withDoc "IAllocator os field" .
1506
  renameField "IAllocatorOs" $ optionalNEStringField "os"
1507

    
1508
pIAllocatorInstances :: Field
1509
pIAllocatorInstances =
1510
  withDoc "IAllocator instances field" .
1511
  renameField "IAllocatorInstances " .
1512
  optionalField $
1513
  simpleField "instances" [t| [NonEmptyString] |]
1514

    
1515
pIAllocatorEvacMode :: Field
1516
pIAllocatorEvacMode =
1517
  withDoc "IAllocator evac mode" .
1518
  renameField "IAllocatorEvacMode" .
1519
  optionalField $
1520
  simpleField "evac_mode" [t| EvacMode |]
1521

    
1522
pIAllocatorSpindleUse :: Field
1523
pIAllocatorSpindleUse =
1524
  withDoc "IAllocator spindle use" .
1525
  renameField "IAllocatorSpindleUse" .
1526
  defaultField [| forceNonNeg (1::Int) |] $
1527
  simpleField "spindle_use" [t| NonNegative Int |]
1528

    
1529
pIAllocatorCount :: Field
1530
pIAllocatorCount =
1531
  withDoc "IAllocator count field" .
1532
  renameField "IAllocatorCount" .
1533
  defaultField [| forceNonNeg (1::Int) |] $
1534
  simpleField "count" [t| NonNegative Int |]
1535

    
1536
pJQueueNotifyWaitLock :: Field
1537
pJQueueNotifyWaitLock =
1538
  withDoc "'OpTestJqueue' notify_waitlock" $
1539
  defaultFalse "notify_waitlock"
1540

    
1541
pJQueueNotifyExec :: Field
1542
pJQueueNotifyExec =
1543
  withDoc "'OpTestJQueue' notify_exec" $
1544
  defaultFalse "notify_exec"
1545

    
1546
pJQueueLogMessages :: Field
1547
pJQueueLogMessages =
1548
  withDoc "'OpTestJQueue' log_messages" .
1549
  defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
1550

    
1551
pJQueueFail :: Field
1552
pJQueueFail =
1553
  withDoc "'OpTestJQueue' fail attribute" .
1554
  renameField "JQueueFail" $ defaultFalse "fail"
1555

    
1556
pTestDummyResult :: Field
1557
pTestDummyResult =
1558
  withDoc "'OpTestDummy' result field" .
1559
  renameField "TestDummyResult" $ simpleField "result" [t| JSValue |]
1560

    
1561
pTestDummyMessages :: Field
1562
pTestDummyMessages =
1563
  withDoc "'OpTestDummy' messages field" .
1564
  renameField "TestDummyMessages" $
1565
  simpleField "messages" [t| JSValue |]
1566

    
1567
pTestDummyFail :: Field
1568
pTestDummyFail =
1569
  withDoc "'OpTestDummy' fail field" .
1570
  renameField "TestDummyFail" $ simpleField "fail" [t| JSValue |]
1571

    
1572
pTestDummySubmitJobs :: Field
1573
pTestDummySubmitJobs =
1574
  withDoc "'OpTestDummy' submit_jobs field" .
1575
  renameField "TestDummySubmitJobs" $
1576
  simpleField "submit_jobs" [t| JSValue |]
1577

    
1578
pNetworkName :: Field
1579
pNetworkName =
1580
  withDoc "Network name" $
1581
  simpleField "network_name" [t| NonEmptyString |]
1582

    
1583
pNetworkAddress4 :: Field
1584
pNetworkAddress4 =
1585
  withDoc "Network address (IPv4 subnet)" .
1586
  renameField "NetworkAddress4" $
1587
  simpleField "network" [t| IPv4Network |]
1588

    
1589
pNetworkGateway4 :: Field
1590
pNetworkGateway4 =
1591
  withDoc "Network gateway (IPv4 address)" .
1592
  renameField "NetworkGateway4" .
1593
  optionalField $ simpleField "gateway" [t| IPv4Address |]
1594

    
1595
pNetworkAddress6 :: Field
1596
pNetworkAddress6 =
1597
  withDoc "Network address (IPv6 subnet)" .
1598
  renameField "NetworkAddress6" .
1599
  optionalField $ simpleField "network6" [t| IPv6Network |]
1600

    
1601
pNetworkGateway6 :: Field
1602
pNetworkGateway6 =
1603
  withDoc "Network gateway (IPv6 address)" .
1604
  renameField "NetworkGateway6" .
1605
  optionalField $ simpleField "gateway6" [t| IPv6Address |]
1606

    
1607
pNetworkMacPrefix :: Field
1608
pNetworkMacPrefix =
1609
  withDoc "Network specific mac prefix (that overrides the cluster one)" .
1610
  renameField "NetMacPrefix" $
1611
  optionalNEStringField "mac_prefix"
1612

    
1613
pNetworkAddRsvdIps :: Field
1614
pNetworkAddRsvdIps =
1615
  withDoc "Which IP addresses to reserve" .
1616
  renameField "NetworkAddRsvdIps" .
1617
  optionalField $
1618
  simpleField "add_reserved_ips" [t| [IPv4Address] |]
1619

    
1620
pNetworkRemoveRsvdIps :: Field
1621
pNetworkRemoveRsvdIps =
1622
  withDoc "Which external IP addresses to release" .
1623
  renameField "NetworkRemoveRsvdIps" .
1624
  optionalField $
1625
  simpleField "remove_reserved_ips" [t| [IPv4Address] |]
1626

    
1627
pNetworkMode :: Field
1628
pNetworkMode =
1629
  withDoc "Network mode when connecting to a group" $
1630
  simpleField "network_mode" [t| NICMode |]
1631

    
1632
pNetworkLink :: Field
1633
pNetworkLink =
1634
  withDoc "Network link when connecting to a group" $
1635
  simpleField "network_link" [t| NonEmptyString |]