Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ fc963293

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

    
269
import Control.Monad (liftM, mplus)
270
import Text.JSON (JSON, JSValue(..), JSObject (..), readJSON, showJSON,
271
                  fromJSString, toJSObject)
272
import qualified Text.JSON
273
import Text.JSON.Pretty (pp_value)
274

    
275
import Ganeti.BasicTypes
276
import qualified Ganeti.Constants as C
277
import Ganeti.THH
278
import Ganeti.Utils
279
import Ganeti.JSON
280
import Ganeti.Types
281
import qualified Ganeti.Query.Language as Qlang
282

    
283
-- * Helper functions and types
284

    
285
-- | Build a boolean field.
286
booleanField :: String -> Field
287
booleanField = flip simpleField [t| Bool |]
288

    
289
-- | Default a field to 'False'.
290
defaultFalse :: String -> Field
291
defaultFalse = defaultField [| False |] . booleanField
292

    
293
-- | Default a field to 'True'.
294
defaultTrue :: String -> Field
295
defaultTrue = defaultField [| True |] . booleanField
296

    
297
-- | An alias for a 'String' field.
298
stringField :: String -> Field
299
stringField = flip simpleField [t| String |]
300

    
301
-- | An alias for an optional string field.
302
optionalStringField :: String -> Field
303
optionalStringField = optionalField . stringField
304

    
305
-- | An alias for an optional non-empty string field.
306
optionalNEStringField :: String -> Field
307
optionalNEStringField = optionalField . flip simpleField [t| NonEmptyString |]
308

    
309
-- | Function to force a non-negative value, without returning via a
310
-- monad. This is needed for, and should be used /only/ in the case of
311
-- forcing constants. In case the constant is wrong (< 0), this will
312
-- become a runtime error.
313
forceNonNeg :: (Num a, Ord a, Show a) => a -> NonNegative a
314
forceNonNeg i = case mkNonNegative i of
315
                  Ok n -> n
316
                  Bad msg -> error msg
317

    
318
-- ** Disks
319

    
320
-- | Disk index type (embedding constraints on the index value via a
321
-- smart constructor).
322
newtype DiskIndex = DiskIndex { unDiskIndex :: Int }
323
  deriving (Show, Eq, Ord)
324

    
325
-- | Smart constructor for 'DiskIndex'.
326
mkDiskIndex :: (Monad m) => Int -> m DiskIndex
327
mkDiskIndex i | i >= 0 && i < C.maxDisks = return (DiskIndex i)
328
              | otherwise = fail $ "Invalid value for disk index '" ++
329
                            show i ++ "', required between 0 and " ++
330
                            show C.maxDisks
331

    
332
instance JSON DiskIndex where
333
  readJSON v = readJSON v >>= mkDiskIndex
334
  showJSON = showJSON . unDiskIndex
335

    
336
-- ** I* param types
337

    
338
-- | Type holding disk access modes.
339
$(declareSADT "DiskAccess"
340
  [ ("DiskReadOnly",  'C.diskRdonly)
341
  , ("DiskReadWrite", 'C.diskRdwr)
342
  ])
343
$(makeJSONInstance ''DiskAccess)
344

    
345
-- | NIC modification definition.
346
$(buildObject "INicParams" "inic"
347
  [ optionalField $ simpleField C.inicMac    [t| NonEmptyString |]
348
  , optionalField $ simpleField C.inicIp     [t| String         |]
349
  , optionalField $ simpleField C.inicMode   [t| NonEmptyString |]
350
  , optionalField $ simpleField C.inicLink   [t| NonEmptyString |]
351
  , optionalField $ simpleField C.inicName   [t| NonEmptyString |]
352
  , optionalField $ simpleField C.inicVlan   [t| String         |]
353
  , optionalField $ simpleField C.inicBridge [t| NonEmptyString |]
354
  ])
355

    
356
-- | Disk modification definition.
357
$(buildObject "IDiskParams" "idisk"
358
  [ specialNumericalField 'parseUnitAssumeBinary . optionalField
359
      $ simpleField C.idiskSize               [t| Int            |]
360
  , optionalField $ simpleField C.idiskMode   [t| DiskAccess     |]
361
  , optionalField $ simpleField C.idiskAdopt  [t| NonEmptyString |]
362
  , optionalField $ simpleField C.idiskVg     [t| NonEmptyString |]
363
  , optionalField $ simpleField C.idiskMetavg [t| NonEmptyString |]
364
  , optionalField $ simpleField C.idiskName   [t| NonEmptyString |]
365
  , optionalField $ simpleField C.idiskProvider [t| NonEmptyString |]
366
  , optionalField $ simpleField C.idiskSpindles [t| Int          |]
367
  , andRestArguments "opaque"
368
  ])
369

    
370
-- | Disk changes type for OpInstanceRecreateDisks. This is a bit
371
-- strange, because the type in Python is something like Either
372
-- [DiskIndex] [DiskChanges], but we can't represent the type of an
373
-- empty list in JSON, so we have to add a custom case for the empty
374
-- list.
375
data RecreateDisksInfo
376
  = RecreateDisksAll
377
  | RecreateDisksIndices (NonEmpty DiskIndex)
378
  | RecreateDisksParams (NonEmpty (DiskIndex, IDiskParams))
379
    deriving (Eq, Show)
380

    
381
readRecreateDisks :: JSValue -> Text.JSON.Result RecreateDisksInfo
382
readRecreateDisks (JSArray []) = return RecreateDisksAll
383
readRecreateDisks v =
384
  case readJSON v::Text.JSON.Result [DiskIndex] of
385
    Text.JSON.Ok indices -> liftM RecreateDisksIndices (mkNonEmpty indices)
386
    _ -> case readJSON v::Text.JSON.Result [(DiskIndex, IDiskParams)] of
387
           Text.JSON.Ok params -> liftM RecreateDisksParams (mkNonEmpty params)
388
           _ -> fail $ "Can't parse disk information as either list of disk"
389
                ++ " indices or list of disk parameters; value received:"
390
                ++ show (pp_value v)
391

    
392
instance JSON RecreateDisksInfo where
393
  readJSON = readRecreateDisks
394
  showJSON  RecreateDisksAll            = showJSON ()
395
  showJSON (RecreateDisksIndices idx)   = showJSON idx
396
  showJSON (RecreateDisksParams params) = showJSON params
397

    
398
-- | Simple type for old-style ddm changes.
399
data DdmOldChanges = DdmOldIndex (NonNegative Int)
400
                   | DdmOldMod DdmSimple
401
                     deriving (Eq, Show)
402

    
403
readDdmOldChanges :: JSValue -> Text.JSON.Result DdmOldChanges
404
readDdmOldChanges v =
405
  case readJSON v::Text.JSON.Result (NonNegative Int) of
406
    Text.JSON.Ok nn -> return $ DdmOldIndex nn
407
    _ -> case readJSON v::Text.JSON.Result DdmSimple of
408
           Text.JSON.Ok ddms -> return $ DdmOldMod ddms
409
           _ -> fail $ "Can't parse value '" ++ show (pp_value v) ++ "' as"
410
                ++ " either index or modification"
411

    
412
instance JSON DdmOldChanges where
413
  showJSON (DdmOldIndex i) = showJSON i
414
  showJSON (DdmOldMod m)   = showJSON m
415
  readJSON = readDdmOldChanges
416

    
417
-- | Instance disk or nic modifications.
418
data SetParamsMods a
419
  = SetParamsEmpty
420
  | SetParamsDeprecated (NonEmpty (DdmOldChanges, a))
421
  | SetParamsNew (NonEmpty (DdmFull, Int, a))
422
  | SetParamsNewName (NonEmpty (DdmFull, String, a))
423
    deriving (Eq, Show)
424

    
425
-- | Custom deserialiser for 'SetParamsMods'.
426
readSetParams :: (JSON a) => JSValue -> Text.JSON.Result (SetParamsMods a)
427
readSetParams (JSArray []) = return SetParamsEmpty
428
readSetParams v =
429
  liftM SetParamsDeprecated (readJSON v)
430
  `mplus` liftM SetParamsNew (readJSON v)
431
  `mplus` liftM SetParamsNewName (readJSON v)
432

    
433
instance (JSON a) => JSON (SetParamsMods a) where
434
  showJSON SetParamsEmpty = showJSON ()
435
  showJSON (SetParamsDeprecated v) = showJSON v
436
  showJSON (SetParamsNew v) = showJSON v
437
  showJSON (SetParamsNewName v) = showJSON v
438
  readJSON = readSetParams
439

    
440
-- | Custom type for target_node parameter of OpBackupExport, which
441
-- varies depending on mode. FIXME: this uses an [JSValue] since
442
-- we don't care about individual rows (just like the Python code
443
-- tests). But the proper type could be parsed if we wanted.
444
data ExportTarget = ExportTargetLocal NonEmptyString
445
                  | ExportTargetRemote [JSValue]
446
                    deriving (Eq, Show)
447

    
448
-- | Custom reader for 'ExportTarget'.
449
readExportTarget :: JSValue -> Text.JSON.Result ExportTarget
450
readExportTarget (JSString s) = liftM ExportTargetLocal $
451
                                mkNonEmpty (fromJSString s)
452
readExportTarget (JSArray arr) = return $ ExportTargetRemote arr
453
readExportTarget v = fail $ "Invalid value received for 'target_node': " ++
454
                     show (pp_value v)
455

    
456
instance JSON ExportTarget where
457
  showJSON (ExportTargetLocal s)  = showJSON s
458
  showJSON (ExportTargetRemote l) = showJSON l
459
  readJSON = readExportTarget
460

    
461
-- * Common opcode parameters
462

    
463
pDryRun :: Field
464
pDryRun =
465
  withDoc "Run checks only, don't execute" .
466
  optionalField $ booleanField "dry_run"
467

    
468
pDebugLevel :: Field
469
pDebugLevel =
470
  withDoc "Debug level" .
471
  optionalField $ simpleField "debug_level" [t| NonNegative Int |]
472

    
473
pOpPriority :: Field
474
pOpPriority =
475
  withDoc "Opcode priority. Note: python uses a separate constant,\
476
          \ we're using the actual value we know it's the default" .
477
  defaultField [| OpPrioNormal |] $
478
  simpleField "priority" [t| OpSubmitPriority |]
479

    
480
pDependencies :: Field
481
pDependencies =
482
  withDoc "Job dependencies" .
483
  optionalNullSerField $ simpleField "depends" [t| [JobDependency] |]
484

    
485
pComment :: Field
486
pComment =
487
  withDoc "Comment field" .
488
  optionalNullSerField $ stringField "comment"
489

    
490
pReason :: Field
491
pReason =
492
  withDoc "Reason trail field" $
493
  simpleField C.opcodeReason [t| ReasonTrail |]
494

    
495
-- * Parameters
496

    
497
pDebugSimulateErrors :: Field
498
pDebugSimulateErrors =
499
  withDoc "Whether to simulate errors (useful for debugging)" $
500
  defaultFalse "debug_simulate_errors"
501

    
502
pErrorCodes :: Field
503
pErrorCodes =
504
  withDoc "Error codes" $
505
  defaultFalse "error_codes"
506

    
507
pSkipChecks :: Field
508
pSkipChecks =
509
  withDoc "Which checks to skip" .
510
  defaultField [| emptyListSet |] $
511
  simpleField "skip_checks" [t| ListSet VerifyOptionalChecks |]
512

    
513
pIgnoreErrors :: Field
514
pIgnoreErrors =
515
  withDoc "List of error codes that should be treated as warnings" .
516
  defaultField [| emptyListSet |] $
517
  simpleField "ignore_errors" [t| ListSet CVErrorCode |]
518

    
519
pVerbose :: Field
520
pVerbose =
521
  withDoc "Verbose mode" $
522
  defaultFalse "verbose"
523

    
524
pOptGroupName :: Field
525
pOptGroupName =
526
  withDoc "Optional group name" .
527
  renameField "OptGroupName" .
528
  optionalField $ simpleField "group_name" [t| NonEmptyString |]
529

    
530
pGroupName :: Field
531
pGroupName =
532
  withDoc "Group name" $
533
  simpleField "group_name" [t| NonEmptyString |]
534

    
535
-- | Whether to hotplug device.
536
pHotplug :: Field
537
pHotplug = defaultFalse "hotplug"
538

    
539
pHotplugIfPossible :: Field
540
pHotplugIfPossible = defaultFalse "hotplug_if_possible"
541

    
542
pInstances :: Field
543
pInstances =
544
  withDoc "List of instances" .
545
  defaultField [| [] |] $
546
  simpleField "instances" [t| [NonEmptyString] |]
547

    
548
pOutputFields :: Field
549
pOutputFields =
550
  withDoc "Selected output fields" $
551
  simpleField "output_fields" [t| [NonEmptyString] |]
552

    
553
pName :: Field
554
pName =
555
  withDoc "A generic name" $
556
  simpleField "name" [t| NonEmptyString |]
557

    
558
pForce :: Field
559
pForce =
560
  withDoc "Whether to force the operation" $
561
  defaultFalse "force"
562

    
563
pHvState :: Field
564
pHvState =
565
  withDoc "Set hypervisor states" .
566
  optionalField $ simpleField "hv_state" [t| JSObject JSValue |]
567

    
568
pDiskState :: Field
569
pDiskState =
570
  withDoc "Set disk states" .
571
  optionalField $ simpleField "disk_state" [t| JSObject JSValue |]
572

    
573
-- | Cluster-wide default directory for storing file-backed disks.
574
pClusterFileStorageDir :: Field
575
pClusterFileStorageDir =
576
  renameField "ClusterFileStorageDir" $
577
  optionalStringField "file_storage_dir"
578

    
579
-- | Cluster-wide default directory for storing shared-file-backed disks.
580
pClusterSharedFileStorageDir :: Field
581
pClusterSharedFileStorageDir =
582
  renameField "ClusterSharedFileStorageDir" $
583
  optionalStringField "shared_file_storage_dir"
584

    
585
-- | Cluster-wide default directory for storing Gluster-backed disks.
586
pClusterGlusterStorageDir :: Field
587
pClusterGlusterStorageDir =
588
  renameField "ClusterGlusterStorageDir" $
589
  optionalStringField "gluster_storage_dir"
590

    
591
pInstanceCommunicationNetwork :: Field
592
pInstanceCommunicationNetwork =
593
  optionalStringField "instance_communication_network"
594

    
595
-- | Volume group name.
596
pVgName :: Field
597
pVgName =
598
  withDoc "Volume group name" $
599
  optionalStringField "vg_name"
600

    
601
pEnabledHypervisors :: Field
602
pEnabledHypervisors =
603
  withDoc "List of enabled hypervisors" .
604
  optionalField $
605
  simpleField "enabled_hypervisors" [t| [Hypervisor] |]
606

    
607
pClusterHvParams :: Field
608
pClusterHvParams =
609
  withDoc "Cluster-wide hypervisor parameters, hypervisor-dependent" .
610
  renameField "ClusterHvParams" .
611
  optionalField $
612
  simpleField "hvparams" [t| GenericContainer String (JSObject JSValue) |]
613

    
614
pClusterBeParams :: Field
615
pClusterBeParams =
616
  withDoc "Cluster-wide backend parameter defaults" .
617
  renameField "ClusterBeParams" .
618
  optionalField $ simpleField "beparams" [t| JSObject JSValue |]
619

    
620
pOsHvp :: Field
621
pOsHvp =
622
  withDoc "Cluster-wide per-OS hypervisor parameter defaults" .
623
  optionalField $
624
  simpleField "os_hvp" [t| GenericContainer String (JSObject JSValue) |]
625

    
626
pClusterOsParams :: Field
627
pClusterOsParams =
628
  withDoc "Cluster-wide OS parameter defaults" .
629
  renameField "ClusterOsParams" .
630
  optionalField $
631
  simpleField "osparams" [t| GenericContainer String (JSObject JSValue) |]
632

    
633
pClusterOsParamsPrivate :: Field
634
pClusterOsParamsPrivate =
635
  withDoc "Cluster-wide private OS parameter defaults" .
636
  renameField "ClusterOsParamsPrivate" .
637
  optionalField $
638
  -- This field needs an unique name to aid Python deserialization
639
  simpleField "osparams_private_cluster"
640
    [t| GenericContainer String (JSObject (Private JSValue)) |]
641

    
642
pDiskParams :: Field
643
pDiskParams =
644
  withDoc "Disk templates' parameter defaults" .
645
  optionalField $
646
  simpleField "diskparams"
647
              [t| GenericContainer DiskTemplate (JSObject JSValue) |]
648

    
649
pCandidatePoolSize :: Field
650
pCandidatePoolSize =
651
  withDoc "Master candidate pool size" .
652
  optionalField $ simpleField "candidate_pool_size" [t| Positive Int |]
653

    
654
pMaxRunningJobs :: Field
655
pMaxRunningJobs =
656
  withDoc "Maximal number of jobs to run simultaneously" .
657
  optionalField $ simpleField "max_running_jobs" [t| Positive Int |]
658

    
659
pUidPool :: Field
660
pUidPool =
661
  withDoc "Set UID pool, must be list of lists describing UID ranges\
662
          \ (two items, start and end inclusive)" .
663
  optionalField $ simpleField "uid_pool" [t| [(Int, Int)] |]
664

    
665
pAddUids :: Field
666
pAddUids =
667
  withDoc "Extend UID pool, must be list of lists describing UID\
668
          \ ranges (two items, start and end inclusive)" .
669
  optionalField $ simpleField "add_uids" [t| [(Int, Int)] |]
670

    
671
pRemoveUids :: Field
672
pRemoveUids =
673
  withDoc "Shrink UID pool, must be list of lists describing UID\
674
          \ ranges (two items, start and end inclusive) to be removed" .
675
  optionalField $ simpleField "remove_uids" [t| [(Int, Int)] |]
676

    
677
pMaintainNodeHealth :: Field
678
pMaintainNodeHealth =
679
  withDoc "Whether to automatically maintain node health" .
680
  optionalField $ booleanField "maintain_node_health"
681

    
682
-- | Whether to modify and keep in sync the @/etc/hosts@ files of nodes.
683
pModifyEtcHosts :: Field
684
pModifyEtcHosts = optionalField $ booleanField "modify_etc_hosts"
685

    
686
-- | Whether to wipe disks before allocating them to instances.
687
pPreallocWipeDisks :: Field
688
pPreallocWipeDisks =
689
  withDoc "Whether to wipe disks before allocating them to instances" .
690
  optionalField $ booleanField "prealloc_wipe_disks"
691

    
692
pNicParams :: Field
693
pNicParams =
694
  withDoc "Cluster-wide NIC parameter defaults" .
695
  optionalField $ simpleField "nicparams" [t| INicParams |]
696

    
697
pIpolicy :: Field
698
pIpolicy =
699
  withDoc "Ipolicy specs" .
700
  optionalField $ simpleField "ipolicy" [t| JSObject JSValue |]
701

    
702
pDrbdHelper :: Field
703
pDrbdHelper =
704
  withDoc "DRBD helper program" $
705
  optionalStringField "drbd_helper"
706

    
707
pDefaultIAllocator :: Field
708
pDefaultIAllocator =
709
  withDoc "Default iallocator for cluster" $
710
  optionalStringField "default_iallocator"
711

    
712
pDefaultIAllocatorParams :: Field
713
pDefaultIAllocatorParams =
714
  withDoc "Default iallocator parameters for cluster" . optionalField
715
    $ simpleField "default_iallocator_params" [t| JSObject JSValue |]
716

    
717
pMasterNetdev :: Field
718
pMasterNetdev =
719
  withDoc "Master network device" $
720
  optionalStringField "master_netdev"
721

    
722
pMasterNetmask :: Field
723
pMasterNetmask =
724
  withDoc "Netmask of the master IP" .
725
  optionalField $ simpleField "master_netmask" [t| NonNegative Int |]
726

    
727
pReservedLvs :: Field
728
pReservedLvs =
729
  withDoc "List of reserved LVs" .
730
  optionalField $ simpleField "reserved_lvs" [t| [NonEmptyString] |]
731

    
732
pHiddenOs :: Field
733
pHiddenOs =
734
  withDoc "Modify list of hidden operating systems: each modification\
735
          \ must have two items, the operation and the OS name; the operation\
736
          \ can be add or remove" .
737
  optionalField $ simpleField "hidden_os" [t| [(DdmSimple, NonEmptyString)] |]
738

    
739
pBlacklistedOs :: Field
740
pBlacklistedOs =
741
  withDoc "Modify list of blacklisted operating systems: each\
742
          \ modification must have two items, the operation and the OS name;\
743
          \ the operation can be add or remove" .
744
  optionalField $
745
  simpleField "blacklisted_os" [t| [(DdmSimple, NonEmptyString)] |]
746

    
747
pUseExternalMipScript :: Field
748
pUseExternalMipScript =
749
  withDoc "Whether to use an external master IP address setup script" .
750
  optionalField $ booleanField "use_external_mip_script"
751

    
752
pEnabledDiskTemplates :: Field
753
pEnabledDiskTemplates =
754
  withDoc "List of enabled disk templates" .
755
  optionalField $
756
  simpleField "enabled_disk_templates" [t| [DiskTemplate] |]
757

    
758
pQueryWhat :: Field
759
pQueryWhat =
760
  withDoc "Resource(s) to query for" $
761
  simpleField "what" [t| Qlang.QueryTypeOp |]
762

    
763
pUseLocking :: Field
764
pUseLocking =
765
  withDoc "Whether to use synchronization" $
766
  defaultFalse "use_locking"
767

    
768
pQueryFields :: Field
769
pQueryFields =
770
  withDoc "Requested fields" $
771
  simpleField "fields" [t| [NonEmptyString] |]
772

    
773
pQueryFilter :: Field
774
pQueryFilter =
775
  withDoc "Query filter" .
776
  optionalField $ simpleField "qfilter" [t| [JSValue] |]
777

    
778
pQueryFieldsFields :: Field
779
pQueryFieldsFields =
780
  withDoc "Requested fields; if not given, all are returned" .
781
  renameField "QueryFieldsFields" $
782
  optionalField pQueryFields
783

    
784
pNodeNames :: Field
785
pNodeNames =
786
  withDoc "List of node names to run the OOB command against" .
787
  defaultField [| [] |] $ simpleField "node_names" [t| [NonEmptyString] |]
788

    
789
pNodeUuids :: Field
790
pNodeUuids =
791
  withDoc "List of node UUIDs" .
792
  optionalField $ simpleField "node_uuids" [t| [NonEmptyString] |]
793

    
794
pOobCommand :: Field
795
pOobCommand =
796
  withDoc "OOB command to run" $
797
  simpleField "command" [t| OobCommand |]
798

    
799
pOobTimeout :: Field
800
pOobTimeout =
801
  withDoc "Timeout before the OOB helper will be terminated" .
802
  defaultField [| C.oobTimeout |] $
803
  simpleField "timeout" [t| Int |]
804

    
805
pIgnoreStatus :: Field
806
pIgnoreStatus =
807
  withDoc "Ignores the node offline status for power off" $
808
  defaultFalse "ignore_status"
809

    
810
pPowerDelay :: Field
811
pPowerDelay =
812
  -- FIXME: we can't use the proper type "NonNegative Double", since
813
  -- the default constant is a plain Double, not a non-negative one.
814
  -- And trying to fix the constant introduces a cyclic import.
815
  withDoc "Time in seconds to wait between powering on nodes" .
816
  defaultField [| C.oobPowerDelay |] $
817
  simpleField "power_delay" [t| Double |]
818

    
819
pRequiredNodes :: Field
820
pRequiredNodes =
821
  withDoc "Required list of node names" .
822
  renameField "ReqNodes " $ simpleField "nodes" [t| [NonEmptyString] |]
823

    
824
pRequiredNodeUuids :: Field
825
pRequiredNodeUuids =
826
  withDoc "Required list of node UUIDs" .
827
  renameField "ReqNodeUuids " . optionalField $
828
  simpleField "node_uuids" [t| [NonEmptyString] |]
829

    
830
pRestrictedCommand :: Field
831
pRestrictedCommand =
832
  withDoc "Restricted command name" .
833
  renameField "RestrictedCommand" $
834
  simpleField "command" [t| NonEmptyString |]
835

    
836
pNodeName :: Field
837
pNodeName =
838
  withDoc "A required node name (for single-node LUs)" $
839
  simpleField "node_name" [t| NonEmptyString |]
840

    
841
pNodeUuid :: Field
842
pNodeUuid =
843
  withDoc "A node UUID (for single-node LUs)" .
844
  optionalField $ simpleField "node_uuid" [t| NonEmptyString |]
845

    
846
pPrimaryIp :: Field
847
pPrimaryIp =
848
  withDoc "Primary IP address" .
849
  optionalField $
850
  simpleField "primary_ip" [t| NonEmptyString |]
851

    
852
pSecondaryIp :: Field
853
pSecondaryIp =
854
  withDoc "Secondary IP address" $
855
  optionalNEStringField "secondary_ip"
856

    
857
pReadd :: Field
858
pReadd =
859
  withDoc "Whether node is re-added to cluster" $
860
  defaultFalse "readd"
861

    
862
pNodeGroup :: Field
863
pNodeGroup =
864
  withDoc "Initial node group" $
865
  optionalNEStringField "group"
866

    
867
pMasterCapable :: Field
868
pMasterCapable =
869
  withDoc "Whether node can become master or master candidate" .
870
  optionalField $ booleanField "master_capable"
871

    
872
pVmCapable :: Field
873
pVmCapable =
874
  withDoc "Whether node can host instances" .
875
  optionalField $ booleanField "vm_capable"
876

    
877
pNdParams :: Field
878
pNdParams =
879
  withDoc "Node parameters" .
880
  renameField "genericNdParams" .
881
  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
882

    
883
pNames :: Field
884
pNames =
885
  withDoc "List of names" .
886
  defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
887

    
888
pNodes :: Field
889
pNodes =
890
  withDoc "List of nodes" .
891
  defaultField [| [] |] $ simpleField "nodes" [t| [NonEmptyString] |]
892

    
893
pStorageType :: Field
894
pStorageType =
895
  withDoc "Storage type" $ simpleField "storage_type" [t| StorageType |]
896

    
897
pOptStorageType :: Field
898
pOptStorageType =
899
  withDoc "Storage type" .
900
  renameField "OptStorageType" .
901
  optionalField $ simpleField "storage_type" [t| StorageType |]
902

    
903
pStorageName :: Field
904
pStorageName =
905
  withDoc "Storage name" .
906
  renameField "StorageName" .
907
  optionalField $ simpleField "name" [t| NonEmptyString |]
908

    
909
pStorageChanges :: Field
910
pStorageChanges =
911
  withDoc "Requested storage changes" $
912
  simpleField "changes" [t| JSObject JSValue |]
913

    
914
pIgnoreConsistency :: Field
915
pIgnoreConsistency =
916
  withDoc "Whether to ignore disk consistency" $
917
  defaultFalse "ignore_consistency"
918

    
919
pMasterCandidate :: Field
920
pMasterCandidate =
921
  withDoc "Whether the node should become a master candidate" .
922
  optionalField $ booleanField "master_candidate"
923

    
924
pOffline :: Field
925
pOffline =
926
  withDoc "Whether to mark the node or instance offline" .
927
  optionalField $ booleanField "offline"
928

    
929
pDrained ::Field
930
pDrained =
931
  withDoc "Whether to mark the node as drained" .
932
  optionalField $ booleanField "drained"
933

    
934
pAutoPromote :: Field
935
pAutoPromote =
936
  withDoc "Whether node(s) should be promoted to master candidate if\
937
          \ necessary" $
938
  defaultFalse "auto_promote"
939

    
940
pPowered :: Field
941
pPowered =
942
  withDoc "Whether the node should be marked as powered" .
943
  optionalField $ booleanField "powered"
944

    
945
pMigrationMode :: Field
946
pMigrationMode =
947
  withDoc "Migration type (live/non-live)" .
948
  renameField "MigrationMode" .
949
  optionalField $
950
  simpleField "mode" [t| MigrationMode |]
951

    
952
pMigrationLive :: Field
953
pMigrationLive =
954
  withDoc "Obsolete \'live\' migration mode (do not use)" .
955
  renameField "OldLiveMode" . optionalField $ booleanField "live"
956

    
957
pMigrationTargetNode :: Field
958
pMigrationTargetNode =
959
  withDoc "Target node for instance migration/failover" $
960
  optionalNEStringField "target_node"
961

    
962
pMigrationTargetNodeUuid :: Field
963
pMigrationTargetNodeUuid =
964
  withDoc "Target node UUID for instance migration/failover" $
965
  optionalNEStringField "target_node_uuid"
966

    
967
pAllowRuntimeChgs :: Field
968
pAllowRuntimeChgs =
969
  withDoc "Whether to allow runtime changes while migrating" $
970
  defaultTrue "allow_runtime_changes"
971

    
972
pIgnoreIpolicy :: Field
973
pIgnoreIpolicy =
974
  withDoc "Whether to ignore ipolicy violations" $
975
  defaultFalse "ignore_ipolicy"
976

    
977
pIallocator :: Field
978
pIallocator =
979
  withDoc "Iallocator for deciding the target node for shared-storage\
980
          \ instances" $
981
  optionalNEStringField "iallocator"
982

    
983
pEarlyRelease :: Field
984
pEarlyRelease =
985
  withDoc "Whether to release locks as soon as possible" $
986
  defaultFalse "early_release"
987

    
988
pRemoteNode :: Field
989
pRemoteNode =
990
  withDoc "New secondary node" $
991
  optionalNEStringField "remote_node"
992

    
993
pRemoteNodeUuid :: Field
994
pRemoteNodeUuid =
995
  withDoc "New secondary node UUID" $
996
  optionalNEStringField "remote_node_uuid"
997

    
998
pEvacMode :: Field
999
pEvacMode =
1000
  withDoc "Node evacuation mode" .
1001
  renameField "EvacMode" $ simpleField "mode" [t| EvacMode |]
1002

    
1003
pInstanceName :: Field
1004
pInstanceName =
1005
  withDoc "A required instance name (for single-instance LUs)" $
1006
  simpleField "instance_name" [t| String |]
1007

    
1008
pInstanceCommunication :: Field
1009
pInstanceCommunication =
1010
  withDoc C.instanceCommunicationDoc $
1011
  defaultFalse "instance_communication"
1012

    
1013
pForceVariant :: Field
1014
pForceVariant =
1015
  withDoc "Whether to force an unknown OS variant" $
1016
  defaultFalse "force_variant"
1017

    
1018
pWaitForSync :: Field
1019
pWaitForSync =
1020
  withDoc "Whether to wait for the disk to synchronize" $
1021
  defaultTrue "wait_for_sync"
1022

    
1023
pNameCheck :: Field
1024
pNameCheck =
1025
  withDoc "Whether to check name" $
1026
  defaultTrue "name_check"
1027

    
1028
pInstBeParams :: Field
1029
pInstBeParams =
1030
  withDoc "Backend parameters for instance" .
1031
  renameField "InstBeParams" .
1032
  defaultField [| toJSObject [] |] $
1033
  simpleField "beparams" [t| JSObject JSValue |]
1034

    
1035
pInstDisks :: Field
1036
pInstDisks =
1037
  withDoc "List of instance disks" .
1038
  renameField "instDisks" $ simpleField "disks" [t| [IDiskParams] |]
1039

    
1040
pDiskTemplate :: Field
1041
pDiskTemplate =
1042
  withDoc "Disk template" $
1043
  simpleField "disk_template" [t| DiskTemplate |]
1044

    
1045
pFileDriver :: Field
1046
pFileDriver =
1047
  withDoc "Driver for file-backed disks" .
1048
  optionalField $ simpleField "file_driver" [t| FileDriver |]
1049

    
1050
pFileStorageDir :: Field
1051
pFileStorageDir =
1052
  withDoc "Directory for storing file-backed disks" $
1053
  optionalNEStringField "file_storage_dir"
1054

    
1055
pInstHvParams :: Field
1056
pInstHvParams =
1057
  withDoc "Hypervisor parameters for instance, hypervisor-dependent" .
1058
  renameField "InstHvParams" .
1059
  defaultField [| toJSObject [] |] $
1060
  simpleField "hvparams" [t| JSObject JSValue |]
1061

    
1062
pHypervisor :: Field
1063
pHypervisor =
1064
  withDoc "Selected hypervisor for an instance" .
1065
  optionalField $
1066
  simpleField "hypervisor" [t| Hypervisor |]
1067

    
1068
pResetDefaults :: Field
1069
pResetDefaults =
1070
  withDoc "Reset instance parameters to default if equal" $
1071
  defaultFalse "identify_defaults"
1072

    
1073
pIpCheck :: Field
1074
pIpCheck =
1075
  withDoc "Whether to ensure instance's IP address is inactive" $
1076
  defaultTrue "ip_check"
1077

    
1078
pIpConflictsCheck :: Field
1079
pIpConflictsCheck =
1080
  withDoc "Whether to check for conflicting IP addresses" $
1081
  defaultTrue "conflicts_check"
1082

    
1083
pInstCreateMode :: Field
1084
pInstCreateMode =
1085
  withDoc "Instance creation mode" .
1086
  renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
1087

    
1088
pInstNics :: Field
1089
pInstNics =
1090
  withDoc "List of NIC (network interface) definitions" $
1091
  simpleField "nics" [t| [INicParams] |]
1092

    
1093
pNoInstall :: Field
1094
pNoInstall =
1095
  withDoc "Do not install the OS (will disable automatic start)" .
1096
  optionalField $ booleanField "no_install"
1097

    
1098
pInstOs :: Field
1099
pInstOs =
1100
  withDoc "OS type for instance installation" $
1101
  optionalNEStringField "os_type"
1102

    
1103
pInstOsParams :: Field
1104
pInstOsParams =
1105
  withDoc "OS parameters for instance" .
1106
  renameField "InstOsParams" .
1107
  defaultField [| toJSObject [] |] $
1108
  simpleField "osparams" [t| JSObject JSValue |]
1109

    
1110
pInstOsParamsPrivate :: Field
1111
pInstOsParamsPrivate =
1112
  withDoc "Private OS parameters for instance" .
1113
  optionalField $
1114
  simpleField "osparams_private" [t| JSObject (Private JSValue) |]
1115

    
1116
pInstOsParamsSecret :: Field
1117
pInstOsParamsSecret =
1118
  withDoc "Secret OS parameters for instance" .
1119
  optionalField $
1120
  simpleField "osparams_secret" [t| JSObject (Private JSValue) |]
1121

    
1122
pPrimaryNode :: Field
1123
pPrimaryNode =
1124
  withDoc "Primary node for an instance" $
1125
  optionalNEStringField "pnode"
1126

    
1127
pPrimaryNodeUuid :: Field
1128
pPrimaryNodeUuid =
1129
  withDoc "Primary node UUID for an instance" $
1130
  optionalNEStringField "pnode_uuid"
1131

    
1132
pSecondaryNode :: Field
1133
pSecondaryNode =
1134
  withDoc "Secondary node for an instance" $
1135
  optionalNEStringField "snode"
1136

    
1137
pSecondaryNodeUuid :: Field
1138
pSecondaryNodeUuid =
1139
  withDoc "Secondary node UUID for an instance" $
1140
  optionalNEStringField "snode_uuid"
1141

    
1142
pSourceHandshake :: Field
1143
pSourceHandshake =
1144
  withDoc "Signed handshake from source (remote import only)" .
1145
  optionalField $ simpleField "source_handshake" [t| [JSValue] |]
1146

    
1147
pSourceInstance :: Field
1148
pSourceInstance =
1149
  withDoc "Source instance name (remote import only)" $
1150
  optionalNEStringField "source_instance_name"
1151

    
1152
-- FIXME: non-negative int, whereas the constant is a plain int.
1153
pSourceShutdownTimeout :: Field
1154
pSourceShutdownTimeout =
1155
  withDoc "How long source instance was given to shut down (remote import\
1156
          \ only)" .
1157
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1158
  simpleField "source_shutdown_timeout" [t| NonNegative Int |]
1159

    
1160
pSourceX509Ca :: Field
1161
pSourceX509Ca =
1162
  withDoc "Source X509 CA in PEM format (remote import only)" $
1163
  optionalNEStringField "source_x509_ca"
1164

    
1165
pSrcNode :: Field
1166
pSrcNode =
1167
  withDoc "Source node for import" $
1168
  optionalNEStringField "src_node"
1169

    
1170
pSrcNodeUuid :: Field
1171
pSrcNodeUuid =
1172
  withDoc "Source node UUID for import" $
1173
  optionalNEStringField "src_node_uuid"
1174

    
1175
pSrcPath :: Field
1176
pSrcPath =
1177
  withDoc "Source directory for import" $
1178
  optionalNEStringField "src_path"
1179

    
1180
pStartInstance :: Field
1181
pStartInstance =
1182
  withDoc "Whether to start instance after creation" $
1183
  defaultTrue "start"
1184

    
1185
-- FIXME: unify/simplify with pTags, once that migrates to NonEmpty String"
1186
pInstTags :: Field
1187
pInstTags =
1188
  withDoc "Instance tags" .
1189
  renameField "InstTags" .
1190
  defaultField [| [] |] $
1191
  simpleField "tags" [t| [NonEmptyString] |]
1192

    
1193
pMultiAllocInstances :: Field
1194
pMultiAllocInstances =
1195
  withDoc "List of instance create opcodes describing the instances to\
1196
          \ allocate" .
1197
  renameField "InstMultiAlloc" .
1198
  defaultField [| [] |] $
1199
  simpleField "instances"[t| [JSValue] |]
1200

    
1201
pOpportunisticLocking :: Field
1202
pOpportunisticLocking =
1203
  withDoc "Whether to employ opportunistic locking for nodes, meaning\
1204
          \ nodes already locked by another opcode won't be considered for\
1205
          \ instance allocation (only when an iallocator is used)" $
1206
  defaultFalse "opportunistic_locking"
1207

    
1208
pInstanceUuid :: Field
1209
pInstanceUuid =
1210
  withDoc "An instance UUID (for single-instance LUs)" .
1211
  optionalField $ simpleField "instance_uuid" [t| NonEmptyString |]
1212

    
1213
pTempOsParams :: Field
1214
pTempOsParams =
1215
  withDoc "Temporary OS parameters (currently only in reinstall, might be\
1216
          \ added to install as well)" .
1217
  renameField "TempOsParams" .
1218
  optionalField $ simpleField "osparams" [t| JSObject JSValue |]
1219

    
1220
pTempOsParamsPrivate :: Field
1221
pTempOsParamsPrivate =
1222
  withDoc "Private OS parameters for instance reinstalls" .
1223
  optionalField $
1224
  simpleField "osparams_private" [t| JSObject (Private JSValue) |]
1225

    
1226
pTempOsParamsSecret :: Field
1227
pTempOsParamsSecret =
1228
  withDoc "Secret OS parameters for instance reinstalls" .
1229
  optionalField $
1230
  simpleField "osparams_secret" [t| JSObject (Private JSValue) |]
1231

    
1232
pShutdownTimeout :: Field
1233
pShutdownTimeout =
1234
  withDoc "How long to wait for instance to shut down" .
1235
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1236
  simpleField "shutdown_timeout" [t| NonNegative Int |]
1237

    
1238
-- | Another name for the shutdown timeout, because we like to be
1239
-- inconsistent.
1240
pShutdownTimeout' :: Field
1241
pShutdownTimeout' =
1242
  withDoc "How long to wait for instance to shut down" .
1243
  renameField "InstShutdownTimeout" .
1244
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1245
  simpleField "timeout" [t| NonNegative Int |]
1246

    
1247
pIgnoreFailures :: Field
1248
pIgnoreFailures =
1249
  withDoc "Whether to ignore failures during removal" $
1250
  defaultFalse "ignore_failures"
1251

    
1252
pNewName :: Field
1253
pNewName =
1254
  withDoc "New group or instance name" $
1255
  simpleField "new_name" [t| NonEmptyString |]
1256

    
1257
pIgnoreOfflineNodes :: Field
1258
pIgnoreOfflineNodes =
1259
  withDoc "Whether to ignore offline nodes" $
1260
  defaultFalse "ignore_offline_nodes"
1261

    
1262
pTempHvParams :: Field
1263
pTempHvParams =
1264
  withDoc "Temporary hypervisor parameters, hypervisor-dependent" .
1265
  renameField "TempHvParams" .
1266
  defaultField [| toJSObject [] |] $
1267
  simpleField "hvparams" [t| JSObject JSValue |]
1268

    
1269
pTempBeParams :: Field
1270
pTempBeParams =
1271
  withDoc "Temporary backend parameters" .
1272
  renameField "TempBeParams" .
1273
  defaultField [| toJSObject [] |] $
1274
  simpleField "beparams" [t| JSObject JSValue |]
1275

    
1276
pNoRemember :: Field
1277
pNoRemember =
1278
  withDoc "Do not remember instance state changes" $
1279
  defaultFalse "no_remember"
1280

    
1281
pStartupPaused :: Field
1282
pStartupPaused =
1283
  withDoc "Pause instance at startup" $
1284
  defaultFalse "startup_paused"
1285

    
1286
pIgnoreSecondaries :: Field
1287
pIgnoreSecondaries =
1288
  withDoc "Whether to start the instance even if secondary disks are failing" $
1289
  defaultFalse "ignore_secondaries"
1290

    
1291
pRebootType :: Field
1292
pRebootType =
1293
  withDoc "How to reboot the instance" $
1294
  simpleField "reboot_type" [t| RebootType |]
1295

    
1296
pReplaceDisksMode :: Field
1297
pReplaceDisksMode =
1298
  withDoc "Replacement mode" .
1299
  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1300

    
1301
pReplaceDisksList :: Field
1302
pReplaceDisksList =
1303
  withDoc "List of disk indices" .
1304
  renameField "ReplaceDisksList" .
1305
  defaultField [| [] |] $
1306
  simpleField "disks" [t| [DiskIndex] |]
1307

    
1308
pMigrationCleanup :: Field
1309
pMigrationCleanup =
1310
  withDoc "Whether a previously failed migration should be cleaned up" .
1311
  renameField "MigrationCleanup" $ defaultFalse "cleanup"
1312

    
1313
pAllowFailover :: Field
1314
pAllowFailover =
1315
  withDoc "Whether we can fallback to failover if migration is not possible" $
1316
  defaultFalse "allow_failover"
1317

    
1318
pMoveTargetNode :: Field
1319
pMoveTargetNode =
1320
  withDoc "Target node for instance move" .
1321
  renameField "MoveTargetNode" $
1322
  simpleField "target_node" [t| NonEmptyString |]
1323

    
1324
pMoveTargetNodeUuid :: Field
1325
pMoveTargetNodeUuid =
1326
  withDoc "Target node UUID for instance move" .
1327
  renameField "MoveTargetNodeUuid" . optionalField $
1328
  simpleField "target_node_uuid" [t| NonEmptyString |]
1329

    
1330
pMoveCompress :: Field
1331
pMoveCompress =
1332
  withDoc "Compression mode to use during instance moves" .
1333
  defaultField [| None |] $
1334
  simpleField "compress" [t| ImportExportCompression |]
1335

    
1336
pBackupCompress :: Field
1337
pBackupCompress =
1338
  withDoc "Compression mode to use for moves during backups/imports" .
1339
  defaultField [| None |] $
1340
  simpleField "compress" [t| ImportExportCompression |]
1341

    
1342
pIgnoreDiskSize :: Field
1343
pIgnoreDiskSize =
1344
  withDoc "Whether to ignore recorded disk size" $
1345
  defaultFalse "ignore_size"
1346

    
1347
pWaitForSyncFalse :: Field
1348
pWaitForSyncFalse =
1349
  withDoc "Whether to wait for the disk to synchronize (defaults to false)" $
1350
  defaultField [| False |] pWaitForSync
1351

    
1352
pRecreateDisksInfo :: Field
1353
pRecreateDisksInfo =
1354
  withDoc "Disk list for recreate disks" .
1355
  renameField "RecreateDisksInfo" .
1356
  defaultField [| RecreateDisksAll |] $
1357
  simpleField "disks" [t| RecreateDisksInfo |]
1358

    
1359
pStatic :: Field
1360
pStatic =
1361
  withDoc "Whether to only return configuration data without querying nodes" $
1362
  defaultFalse "static"
1363

    
1364
pInstParamsNicChanges :: Field
1365
pInstParamsNicChanges =
1366
  withDoc "List of NIC changes" .
1367
  renameField "InstNicChanges" .
1368
  defaultField [| SetParamsEmpty |] $
1369
  simpleField "nics" [t| SetParamsMods INicParams |]
1370

    
1371
pInstParamsDiskChanges :: Field
1372
pInstParamsDiskChanges =
1373
  withDoc "List of disk changes" .
1374
  renameField "InstDiskChanges" .
1375
  defaultField [| SetParamsEmpty |] $
1376
  simpleField "disks" [t| SetParamsMods IDiskParams |]
1377

    
1378
pRuntimeMem :: Field
1379
pRuntimeMem =
1380
  withDoc "New runtime memory" .
1381
  optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1382

    
1383
pOptDiskTemplate :: Field
1384
pOptDiskTemplate =
1385
  withDoc "Instance disk template" .
1386
  optionalField .
1387
  renameField "OptDiskTemplate" $
1388
  simpleField "disk_template" [t| DiskTemplate |]
1389

    
1390
pOsNameChange :: Field
1391
pOsNameChange =
1392
  withDoc "Change the instance's OS without reinstalling the instance" $
1393
  optionalNEStringField "os_name"
1394

    
1395
pDiskIndex :: Field
1396
pDiskIndex =
1397
  withDoc "Disk index for e.g. grow disk" .
1398
  renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
1399

    
1400
pDiskChgAmount :: Field
1401
pDiskChgAmount =
1402
  withDoc "Disk amount to add or grow to" .
1403
  renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
1404

    
1405
pDiskChgAbsolute :: Field
1406
pDiskChgAbsolute =
1407
  withDoc
1408
    "Whether the amount parameter is an absolute target or a relative one" .
1409
  renameField "DiskChkAbsolute" $ defaultFalse "absolute"
1410

    
1411
pTargetGroups :: Field
1412
pTargetGroups =
1413
  withDoc
1414
    "Destination group names or UUIDs (defaults to \"all but current group\")" .
1415
  optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
1416

    
1417
pNodeGroupAllocPolicy :: Field
1418
pNodeGroupAllocPolicy =
1419
  withDoc "Instance allocation policy" .
1420
  optionalField $
1421
  simpleField "alloc_policy" [t| AllocPolicy |]
1422

    
1423
pGroupNodeParams :: Field
1424
pGroupNodeParams =
1425
  withDoc "Default node parameters for group" .
1426
  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
1427

    
1428
pExportMode :: Field
1429
pExportMode =
1430
  withDoc "Export mode" .
1431
  renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1432

    
1433
-- FIXME: Rename target_node as it changes meaning for different
1434
-- export modes (e.g. "destination")
1435
pExportTargetNode :: Field
1436
pExportTargetNode =
1437
  withDoc "Target node (depends on export mode)" .
1438
  renameField "ExportTarget" $
1439
  simpleField "target_node" [t| ExportTarget |]
1440

    
1441
pExportTargetNodeUuid :: Field
1442
pExportTargetNodeUuid =
1443
  withDoc "Target node UUID (if local export)" .
1444
  renameField "ExportTargetNodeUuid" . optionalField $
1445
  simpleField "target_node_uuid" [t| NonEmptyString |]
1446

    
1447
pShutdownInstance :: Field
1448
pShutdownInstance =
1449
  withDoc "Whether to shutdown the instance before export" $
1450
  defaultTrue "shutdown"
1451

    
1452
pRemoveInstance :: Field
1453
pRemoveInstance =
1454
  withDoc "Whether to remove instance after export" $
1455
  defaultFalse "remove_instance"
1456

    
1457
pIgnoreRemoveFailures :: Field
1458
pIgnoreRemoveFailures =
1459
  withDoc "Whether to ignore failures while removing instances" $
1460
  defaultFalse "ignore_remove_failures"
1461

    
1462
pX509KeyName :: Field
1463
pX509KeyName =
1464
  withDoc "Name of X509 key (remote export only)" .
1465
  optionalField $ simpleField "x509_key_name" [t| [JSValue] |]
1466

    
1467
pX509DestCA :: Field
1468
pX509DestCA =
1469
  withDoc "Destination X509 CA (remote export only)" $
1470
  optionalNEStringField "destination_x509_ca"
1471

    
1472
pTagsObject :: Field
1473
pTagsObject =
1474
  withDoc "Tag kind" $
1475
  simpleField "kind" [t| TagKind |]
1476

    
1477
pTagsName :: Field
1478
pTagsName =
1479
  withDoc "Name of object" .
1480
  renameField "TagsGetName" .
1481
  optionalField $ simpleField "name" [t| String |]
1482

    
1483
pTagsList :: Field
1484
pTagsList =
1485
  withDoc "List of tag names" $
1486
  simpleField "tags" [t| [String] |]
1487

    
1488
-- FIXME: this should be compiled at load time?
1489
pTagSearchPattern :: Field
1490
pTagSearchPattern =
1491
  withDoc "Search pattern (regular expression)" .
1492
  renameField "TagSearchPattern" $
1493
  simpleField "pattern" [t| NonEmptyString |]
1494

    
1495
pDelayDuration :: Field
1496
pDelayDuration =
1497
  withDoc "Duration parameter for 'OpTestDelay'" .
1498
  renameField "DelayDuration" $
1499
  simpleField "duration" [t| Double |]
1500

    
1501
pDelayOnMaster :: Field
1502
pDelayOnMaster =
1503
  withDoc "on_master field for 'OpTestDelay'" .
1504
  renameField "DelayOnMaster" $
1505
  defaultTrue "on_master"
1506

    
1507
pDelayOnNodes :: Field
1508
pDelayOnNodes =
1509
  withDoc "on_nodes field for 'OpTestDelay'" .
1510
  renameField "DelayOnNodes" .
1511
  defaultField [| [] |] $
1512
  simpleField "on_nodes" [t| [NonEmptyString] |]
1513

    
1514
pDelayOnNodeUuids :: Field
1515
pDelayOnNodeUuids =
1516
  withDoc "on_node_uuids field for 'OpTestDelay'" .
1517
  renameField "DelayOnNodeUuids" . optionalField $
1518
  simpleField "on_node_uuids" [t| [NonEmptyString] |]
1519

    
1520
pDelayRepeat :: Field
1521
pDelayRepeat =
1522
  withDoc "Repeat parameter for OpTestDelay" .
1523
  renameField "DelayRepeat" .
1524
  defaultField [| forceNonNeg (0::Int) |] $
1525
  simpleField "repeat" [t| NonNegative Int |]
1526

    
1527
pIAllocatorDirection :: Field
1528
pIAllocatorDirection =
1529
  withDoc "IAllocator test direction" .
1530
  renameField "IAllocatorDirection" $
1531
  simpleField "direction" [t| IAllocatorTestDir |]
1532

    
1533
pIAllocatorMode :: Field
1534
pIAllocatorMode =
1535
  withDoc "IAllocator test mode" .
1536
  renameField "IAllocatorMode" $
1537
  simpleField "mode" [t| IAllocatorMode |]
1538

    
1539
pIAllocatorReqName :: Field
1540
pIAllocatorReqName =
1541
  withDoc "IAllocator target name (new instance, node to evac, etc.)" .
1542
  renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
1543

    
1544
pIAllocatorNics :: Field
1545
pIAllocatorNics =
1546
  withDoc "Custom OpTestIAllocator nics" .
1547
  renameField "IAllocatorNics" .
1548
  optionalField $ simpleField "nics" [t| [INicParams] |]
1549

    
1550
pIAllocatorDisks :: Field
1551
pIAllocatorDisks =
1552
  withDoc "Custom OpTestAllocator disks" .
1553
  renameField "IAllocatorDisks" .
1554
  optionalField $ simpleField "disks" [t| [JSValue] |]
1555

    
1556
pIAllocatorMemory :: Field
1557
pIAllocatorMemory =
1558
  withDoc "IAllocator memory field" .
1559
  renameField "IAllocatorMem" .
1560
  optionalField $
1561
  simpleField "memory" [t| NonNegative Int |]
1562

    
1563
pIAllocatorVCpus :: Field
1564
pIAllocatorVCpus =
1565
  withDoc "IAllocator vcpus field" .
1566
  renameField "IAllocatorVCpus" .
1567
  optionalField $
1568
  simpleField "vcpus" [t| NonNegative Int |]
1569

    
1570
pIAllocatorOs :: Field
1571
pIAllocatorOs =
1572
  withDoc "IAllocator os field" .
1573
  renameField "IAllocatorOs" $ optionalNEStringField "os"
1574

    
1575
pIAllocatorInstances :: Field
1576
pIAllocatorInstances =
1577
  withDoc "IAllocator instances field" .
1578
  renameField "IAllocatorInstances " .
1579
  optionalField $
1580
  simpleField "instances" [t| [NonEmptyString] |]
1581

    
1582
pIAllocatorEvacMode :: Field
1583
pIAllocatorEvacMode =
1584
  withDoc "IAllocator evac mode" .
1585
  renameField "IAllocatorEvacMode" .
1586
  optionalField $
1587
  simpleField "evac_mode" [t| EvacMode |]
1588

    
1589
pIAllocatorSpindleUse :: Field
1590
pIAllocatorSpindleUse =
1591
  withDoc "IAllocator spindle use" .
1592
  renameField "IAllocatorSpindleUse" .
1593
  defaultField [| forceNonNeg (1::Int) |] $
1594
  simpleField "spindle_use" [t| NonNegative Int |]
1595

    
1596
pIAllocatorCount :: Field
1597
pIAllocatorCount =
1598
  withDoc "IAllocator count field" .
1599
  renameField "IAllocatorCount" .
1600
  defaultField [| forceNonNeg (1::Int) |] $
1601
  simpleField "count" [t| NonNegative Int |]
1602

    
1603
pJQueueNotifyWaitLock :: Field
1604
pJQueueNotifyWaitLock =
1605
  withDoc "'OpTestJqueue' notify_waitlock" $
1606
  defaultFalse "notify_waitlock"
1607

    
1608
pJQueueNotifyExec :: Field
1609
pJQueueNotifyExec =
1610
  withDoc "'OpTestJQueue' notify_exec" $
1611
  defaultFalse "notify_exec"
1612

    
1613
pJQueueLogMessages :: Field
1614
pJQueueLogMessages =
1615
  withDoc "'OpTestJQueue' log_messages" .
1616
  defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
1617

    
1618
pJQueueFail :: Field
1619
pJQueueFail =
1620
  withDoc "'OpTestJQueue' fail attribute" .
1621
  renameField "JQueueFail" $ defaultFalse "fail"
1622

    
1623
pTestDummyResult :: Field
1624
pTestDummyResult =
1625
  withDoc "'OpTestDummy' result field" .
1626
  renameField "TestDummyResult" $ simpleField "result" [t| JSValue |]
1627

    
1628
pTestDummyMessages :: Field
1629
pTestDummyMessages =
1630
  withDoc "'OpTestDummy' messages field" .
1631
  renameField "TestDummyMessages" $
1632
  simpleField "messages" [t| JSValue |]
1633

    
1634
pTestDummyFail :: Field
1635
pTestDummyFail =
1636
  withDoc "'OpTestDummy' fail field" .
1637
  renameField "TestDummyFail" $ simpleField "fail" [t| JSValue |]
1638

    
1639
pTestDummySubmitJobs :: Field
1640
pTestDummySubmitJobs =
1641
  withDoc "'OpTestDummy' submit_jobs field" .
1642
  renameField "TestDummySubmitJobs" $
1643
  simpleField "submit_jobs" [t| JSValue |]
1644

    
1645
pNetworkName :: Field
1646
pNetworkName =
1647
  withDoc "Network name" $
1648
  simpleField "network_name" [t| NonEmptyString |]
1649

    
1650
pNetworkAddress4 :: Field
1651
pNetworkAddress4 =
1652
  withDoc "Network address (IPv4 subnet)" .
1653
  renameField "NetworkAddress4" $
1654
  simpleField "network" [t| IPv4Network |]
1655

    
1656
pNetworkGateway4 :: Field
1657
pNetworkGateway4 =
1658
  withDoc "Network gateway (IPv4 address)" .
1659
  renameField "NetworkGateway4" .
1660
  optionalField $ simpleField "gateway" [t| IPv4Address |]
1661

    
1662
pNetworkAddress6 :: Field
1663
pNetworkAddress6 =
1664
  withDoc "Network address (IPv6 subnet)" .
1665
  renameField "NetworkAddress6" .
1666
  optionalField $ simpleField "network6" [t| IPv6Network |]
1667

    
1668
pNetworkGateway6 :: Field
1669
pNetworkGateway6 =
1670
  withDoc "Network gateway (IPv6 address)" .
1671
  renameField "NetworkGateway6" .
1672
  optionalField $ simpleField "gateway6" [t| IPv6Address |]
1673

    
1674
pNetworkMacPrefix :: Field
1675
pNetworkMacPrefix =
1676
  withDoc "Network specific mac prefix (that overrides the cluster one)" .
1677
  renameField "NetMacPrefix" $
1678
  optionalNEStringField "mac_prefix"
1679

    
1680
pNetworkAddRsvdIps :: Field
1681
pNetworkAddRsvdIps =
1682
  withDoc "Which IP addresses to reserve" .
1683
  renameField "NetworkAddRsvdIps" .
1684
  optionalField $
1685
  simpleField "add_reserved_ips" [t| [IPv4Address] |]
1686

    
1687
pNetworkRemoveRsvdIps :: Field
1688
pNetworkRemoveRsvdIps =
1689
  withDoc "Which external IP addresses to release" .
1690
  renameField "NetworkRemoveRsvdIps" .
1691
  optionalField $
1692
  simpleField "remove_reserved_ips" [t| [IPv4Address] |]
1693

    
1694
pNetworkMode :: Field
1695
pNetworkMode =
1696
  withDoc "Network mode when connecting to a group" $
1697
  simpleField "network_mode" [t| NICMode |]
1698

    
1699
pNetworkLink :: Field
1700
pNetworkLink =
1701
  withDoc "Network link when connecting to a group" $
1702
  simpleField "network_link" [t| NonEmptyString |]