Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ 2868f3f7

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

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

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

    
285
-- * Helper functions and types
286

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

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

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

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

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

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

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

    
320
-- ** Disks
321

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

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

    
334
instance JSON DiskIndex where
335
  readJSON v = readJSON v >>= mkDiskIndex
336
  showJSON = showJSON . unDiskIndex
337

    
338
-- ** I* param types
339

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
463
-- * Common opcode parameters
464

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

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

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

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

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

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

    
497
-- * Parameters
498

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

    
504
pErrorCodes :: Field
505
pErrorCodes =
506
  withDoc "Error codes" $
507
  defaultFalse "error_codes"
508

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

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

    
521
pVerbose :: Field
522
pVerbose =
523
  withDoc "Verbose mode" $
524
  defaultFalse "verbose"
525

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

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

    
537
-- | Whether to hotplug device.
538
pHotplug :: Field
539
pHotplug = defaultFalse "hotplug"
540

    
541
pHotplugIfPossible :: Field
542
pHotplugIfPossible = defaultFalse "hotplug_if_possible"
543

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

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

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

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

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

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

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

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

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

    
593
pInstanceCommunicationNetwork :: Field
594
pInstanceCommunicationNetwork =
595
  optionalStringField "instance_communication_network"
596

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
704
pDrbdHelper :: Field
705
pDrbdHelper =
706
  withDoc "DRBD helper program" $
707
  optionalStringField "drbd_helper"
708

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

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

    
719
pMasterNetdev :: Field
720
pMasterNetdev =
721
  withDoc "Master network device" $
722
  optionalStringField "master_netdev"
723

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
854
pSecondaryIp :: Field
855
pSecondaryIp =
856
  withDoc "Secondary IP address" $
857
  optionalNEStringField "secondary_ip"
858

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

    
864
pNodeGroup :: Field
865
pNodeGroup =
866
  withDoc "Initial node group" $
867
  optionalNEStringField "group"
868

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
990
pRemoteNode :: Field
991
pRemoteNode =
992
  withDoc "New secondary node" $
993
  optionalNEStringField "remote_node"
994

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

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

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

    
1010
pInstanceCommunication :: Field
1011
pInstanceCommunication =
1012
  withDoc C.instanceCommunicationDoc $
1013
  defaultFalse "instance_communication"
1014

    
1015
pOptInstanceCommunication :: Field
1016
pOptInstanceCommunication =
1017
  withDoc C.instanceCommunicationDoc .
1018
  renameField "OptInstanceCommunication" .
1019
  optionalField $
1020
  booleanField "instance_communication"
1021

    
1022
pForceVariant :: Field
1023
pForceVariant =
1024
  withDoc "Whether to force an unknown OS variant" $
1025
  defaultFalse "force_variant"
1026

    
1027
pWaitForSync :: Field
1028
pWaitForSync =
1029
  withDoc "Whether to wait for the disk to synchronize" $
1030
  defaultTrue "wait_for_sync"
1031

    
1032
pNameCheck :: Field
1033
pNameCheck =
1034
  withDoc "Whether to check name" $
1035
  defaultTrue "name_check"
1036

    
1037
pInstBeParams :: Field
1038
pInstBeParams =
1039
  withDoc "Backend parameters for instance" .
1040
  renameField "InstBeParams" .
1041
  defaultField [| toJSObject [] |] $
1042
  simpleField "beparams" [t| JSObject JSValue |]
1043

    
1044
pInstDisks :: Field
1045
pInstDisks =
1046
  withDoc "List of instance disks" .
1047
  renameField "instDisks" $ simpleField "disks" [t| [IDiskParams] |]
1048

    
1049
pDiskTemplate :: Field
1050
pDiskTemplate =
1051
  withDoc "Disk template" $
1052
  simpleField "disk_template" [t| DiskTemplate |]
1053

    
1054
pFileDriver :: Field
1055
pFileDriver =
1056
  withDoc "Driver for file-backed disks" .
1057
  optionalField $ simpleField "file_driver" [t| FileDriver |]
1058

    
1059
pFileStorageDir :: Field
1060
pFileStorageDir =
1061
  withDoc "Directory for storing file-backed disks" $
1062
  optionalNEStringField "file_storage_dir"
1063

    
1064
pInstHvParams :: Field
1065
pInstHvParams =
1066
  withDoc "Hypervisor parameters for instance, hypervisor-dependent" .
1067
  renameField "InstHvParams" .
1068
  defaultField [| toJSObject [] |] $
1069
  simpleField "hvparams" [t| JSObject JSValue |]
1070

    
1071
pHypervisor :: Field
1072
pHypervisor =
1073
  withDoc "Selected hypervisor for an instance" .
1074
  optionalField $
1075
  simpleField "hypervisor" [t| Hypervisor |]
1076

    
1077
pResetDefaults :: Field
1078
pResetDefaults =
1079
  withDoc "Reset instance parameters to default if equal" $
1080
  defaultFalse "identify_defaults"
1081

    
1082
pIpCheck :: Field
1083
pIpCheck =
1084
  withDoc "Whether to ensure instance's IP address is inactive" $
1085
  defaultTrue "ip_check"
1086

    
1087
pIpConflictsCheck :: Field
1088
pIpConflictsCheck =
1089
  withDoc "Whether to check for conflicting IP addresses" $
1090
  defaultTrue "conflicts_check"
1091

    
1092
pInstCreateMode :: Field
1093
pInstCreateMode =
1094
  withDoc "Instance creation mode" .
1095
  renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
1096

    
1097
pInstNics :: Field
1098
pInstNics =
1099
  withDoc "List of NIC (network interface) definitions" $
1100
  simpleField "nics" [t| [INicParams] |]
1101

    
1102
pNoInstall :: Field
1103
pNoInstall =
1104
  withDoc "Do not install the OS (will disable automatic start)" .
1105
  optionalField $ booleanField "no_install"
1106

    
1107
pInstOs :: Field
1108
pInstOs =
1109
  withDoc "OS type for instance installation" $
1110
  optionalNEStringField "os_type"
1111

    
1112
pInstOsParams :: Field
1113
pInstOsParams =
1114
  withDoc "OS parameters for instance" .
1115
  renameField "InstOsParams" .
1116
  defaultField [| toJSObject [] |] $
1117
  simpleField "osparams" [t| JSObject JSValue |]
1118

    
1119
pInstOsParamsPrivate :: Field
1120
pInstOsParamsPrivate =
1121
  withDoc "Private OS parameters for instance" .
1122
  optionalField $
1123
  simpleField "osparams_private" [t| JSObject (Private JSValue) |]
1124

    
1125
pInstOsParamsSecret :: Field
1126
pInstOsParamsSecret =
1127
  withDoc "Secret OS parameters for instance" .
1128
  optionalField $
1129
  simpleField "osparams_secret" [t| JSObject (Private JSValue) |]
1130

    
1131
pPrimaryNode :: Field
1132
pPrimaryNode =
1133
  withDoc "Primary node for an instance" $
1134
  optionalNEStringField "pnode"
1135

    
1136
pPrimaryNodeUuid :: Field
1137
pPrimaryNodeUuid =
1138
  withDoc "Primary node UUID for an instance" $
1139
  optionalNEStringField "pnode_uuid"
1140

    
1141
pSecondaryNode :: Field
1142
pSecondaryNode =
1143
  withDoc "Secondary node for an instance" $
1144
  optionalNEStringField "snode"
1145

    
1146
pSecondaryNodeUuid :: Field
1147
pSecondaryNodeUuid =
1148
  withDoc "Secondary node UUID for an instance" $
1149
  optionalNEStringField "snode_uuid"
1150

    
1151
pSourceHandshake :: Field
1152
pSourceHandshake =
1153
  withDoc "Signed handshake from source (remote import only)" .
1154
  optionalField $ simpleField "source_handshake" [t| [JSValue] |]
1155

    
1156
pSourceInstance :: Field
1157
pSourceInstance =
1158
  withDoc "Source instance name (remote import only)" $
1159
  optionalNEStringField "source_instance_name"
1160

    
1161
-- FIXME: non-negative int, whereas the constant is a plain int.
1162
pSourceShutdownTimeout :: Field
1163
pSourceShutdownTimeout =
1164
  withDoc "How long source instance was given to shut down (remote import\
1165
          \ only)" .
1166
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1167
  simpleField "source_shutdown_timeout" [t| NonNegative Int |]
1168

    
1169
pSourceX509Ca :: Field
1170
pSourceX509Ca =
1171
  withDoc "Source X509 CA in PEM format (remote import only)" $
1172
  optionalNEStringField "source_x509_ca"
1173

    
1174
pSrcNode :: Field
1175
pSrcNode =
1176
  withDoc "Source node for import" $
1177
  optionalNEStringField "src_node"
1178

    
1179
pSrcNodeUuid :: Field
1180
pSrcNodeUuid =
1181
  withDoc "Source node UUID for import" $
1182
  optionalNEStringField "src_node_uuid"
1183

    
1184
pSrcPath :: Field
1185
pSrcPath =
1186
  withDoc "Source directory for import" $
1187
  optionalNEStringField "src_path"
1188

    
1189
pStartInstance :: Field
1190
pStartInstance =
1191
  withDoc "Whether to start instance after creation" $
1192
  defaultTrue "start"
1193

    
1194
-- FIXME: unify/simplify with pTags, once that migrates to NonEmpty String"
1195
pInstTags :: Field
1196
pInstTags =
1197
  withDoc "Instance tags" .
1198
  renameField "InstTags" .
1199
  defaultField [| [] |] $
1200
  simpleField "tags" [t| [NonEmptyString] |]
1201

    
1202
pMultiAllocInstances :: Field
1203
pMultiAllocInstances =
1204
  withDoc "List of instance create opcodes describing the instances to\
1205
          \ allocate" .
1206
  renameField "InstMultiAlloc" .
1207
  defaultField [| [] |] $
1208
  simpleField "instances"[t| [JSValue] |]
1209

    
1210
pOpportunisticLocking :: Field
1211
pOpportunisticLocking =
1212
  withDoc "Whether to employ opportunistic locking for nodes, meaning\
1213
          \ nodes already locked by another opcode won't be considered for\
1214
          \ instance allocation (only when an iallocator is used)" $
1215
  defaultFalse "opportunistic_locking"
1216

    
1217
pInstanceUuid :: Field
1218
pInstanceUuid =
1219
  withDoc "An instance UUID (for single-instance LUs)" .
1220
  optionalField $ simpleField "instance_uuid" [t| NonEmptyString |]
1221

    
1222
pTempOsParams :: Field
1223
pTempOsParams =
1224
  withDoc "Temporary OS parameters (currently only in reinstall, might be\
1225
          \ added to install as well)" .
1226
  renameField "TempOsParams" .
1227
  optionalField $ simpleField "osparams" [t| JSObject JSValue |]
1228

    
1229
pTempOsParamsPrivate :: Field
1230
pTempOsParamsPrivate =
1231
  withDoc "Private OS parameters for instance reinstalls" .
1232
  optionalField $
1233
  simpleField "osparams_private" [t| JSObject (Private JSValue) |]
1234

    
1235
pTempOsParamsSecret :: Field
1236
pTempOsParamsSecret =
1237
  withDoc "Secret OS parameters for instance reinstalls" .
1238
  optionalField $
1239
  simpleField "osparams_secret" [t| JSObject (Private JSValue) |]
1240

    
1241
pShutdownTimeout :: Field
1242
pShutdownTimeout =
1243
  withDoc "How long to wait for instance to shut down" .
1244
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1245
  simpleField "shutdown_timeout" [t| NonNegative Int |]
1246

    
1247
-- | Another name for the shutdown timeout, because we like to be
1248
-- inconsistent.
1249
pShutdownTimeout' :: Field
1250
pShutdownTimeout' =
1251
  withDoc "How long to wait for instance to shut down" .
1252
  renameField "InstShutdownTimeout" .
1253
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1254
  simpleField "timeout" [t| NonNegative Int |]
1255

    
1256
pIgnoreFailures :: Field
1257
pIgnoreFailures =
1258
  withDoc "Whether to ignore failures during removal" $
1259
  defaultFalse "ignore_failures"
1260

    
1261
pNewName :: Field
1262
pNewName =
1263
  withDoc "New group or instance name" $
1264
  simpleField "new_name" [t| NonEmptyString |]
1265

    
1266
pIgnoreOfflineNodes :: Field
1267
pIgnoreOfflineNodes =
1268
  withDoc "Whether to ignore offline nodes" $
1269
  defaultFalse "ignore_offline_nodes"
1270

    
1271
pTempHvParams :: Field
1272
pTempHvParams =
1273
  withDoc "Temporary hypervisor parameters, hypervisor-dependent" .
1274
  renameField "TempHvParams" .
1275
  defaultField [| toJSObject [] |] $
1276
  simpleField "hvparams" [t| JSObject JSValue |]
1277

    
1278
pTempBeParams :: Field
1279
pTempBeParams =
1280
  withDoc "Temporary backend parameters" .
1281
  renameField "TempBeParams" .
1282
  defaultField [| toJSObject [] |] $
1283
  simpleField "beparams" [t| JSObject JSValue |]
1284

    
1285
pNoRemember :: Field
1286
pNoRemember =
1287
  withDoc "Do not remember instance state changes" $
1288
  defaultFalse "no_remember"
1289

    
1290
pStartupPaused :: Field
1291
pStartupPaused =
1292
  withDoc "Pause instance at startup" $
1293
  defaultFalse "startup_paused"
1294

    
1295
pIgnoreSecondaries :: Field
1296
pIgnoreSecondaries =
1297
  withDoc "Whether to start the instance even if secondary disks are failing" $
1298
  defaultFalse "ignore_secondaries"
1299

    
1300
pRebootType :: Field
1301
pRebootType =
1302
  withDoc "How to reboot the instance" $
1303
  simpleField "reboot_type" [t| RebootType |]
1304

    
1305
pReplaceDisksMode :: Field
1306
pReplaceDisksMode =
1307
  withDoc "Replacement mode" .
1308
  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1309

    
1310
pReplaceDisksList :: Field
1311
pReplaceDisksList =
1312
  withDoc "List of disk indices" .
1313
  renameField "ReplaceDisksList" .
1314
  defaultField [| [] |] $
1315
  simpleField "disks" [t| [DiskIndex] |]
1316

    
1317
pMigrationCleanup :: Field
1318
pMigrationCleanup =
1319
  withDoc "Whether a previously failed migration should be cleaned up" .
1320
  renameField "MigrationCleanup" $ defaultFalse "cleanup"
1321

    
1322
pAllowFailover :: Field
1323
pAllowFailover =
1324
  withDoc "Whether we can fallback to failover if migration is not possible" $
1325
  defaultFalse "allow_failover"
1326

    
1327
pMoveTargetNode :: Field
1328
pMoveTargetNode =
1329
  withDoc "Target node for instance move" .
1330
  renameField "MoveTargetNode" $
1331
  simpleField "target_node" [t| NonEmptyString |]
1332

    
1333
pMoveTargetNodeUuid :: Field
1334
pMoveTargetNodeUuid =
1335
  withDoc "Target node UUID for instance move" .
1336
  renameField "MoveTargetNodeUuid" . optionalField $
1337
  simpleField "target_node_uuid" [t| NonEmptyString |]
1338

    
1339
pMoveCompress :: Field
1340
pMoveCompress =
1341
  withDoc "Compression mode to use during instance moves" .
1342
  defaultField [| None |] $
1343
  simpleField "compress" [t| ImportExportCompression |]
1344

    
1345
pBackupCompress :: Field
1346
pBackupCompress =
1347
  withDoc "Compression mode to use for moves during backups/imports" .
1348
  defaultField [| None |] $
1349
  simpleField "compress" [t| ImportExportCompression |]
1350

    
1351
pIgnoreDiskSize :: Field
1352
pIgnoreDiskSize =
1353
  withDoc "Whether to ignore recorded disk size" $
1354
  defaultFalse "ignore_size"
1355

    
1356
pWaitForSyncFalse :: Field
1357
pWaitForSyncFalse =
1358
  withDoc "Whether to wait for the disk to synchronize (defaults to false)" $
1359
  defaultField [| False |] pWaitForSync
1360

    
1361
pRecreateDisksInfo :: Field
1362
pRecreateDisksInfo =
1363
  withDoc "Disk list for recreate disks" .
1364
  renameField "RecreateDisksInfo" .
1365
  defaultField [| RecreateDisksAll |] $
1366
  simpleField "disks" [t| RecreateDisksInfo |]
1367

    
1368
pStatic :: Field
1369
pStatic =
1370
  withDoc "Whether to only return configuration data without querying nodes" $
1371
  defaultFalse "static"
1372

    
1373
pInstParamsNicChanges :: Field
1374
pInstParamsNicChanges =
1375
  withDoc "List of NIC changes" .
1376
  renameField "InstNicChanges" .
1377
  defaultField [| SetParamsEmpty |] $
1378
  simpleField "nics" [t| SetParamsMods INicParams |]
1379

    
1380
pInstParamsDiskChanges :: Field
1381
pInstParamsDiskChanges =
1382
  withDoc "List of disk changes" .
1383
  renameField "InstDiskChanges" .
1384
  defaultField [| SetParamsEmpty |] $
1385
  simpleField "disks" [t| SetParamsMods IDiskParams |]
1386

    
1387
pRuntimeMem :: Field
1388
pRuntimeMem =
1389
  withDoc "New runtime memory" .
1390
  optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1391

    
1392
pOptDiskTemplate :: Field
1393
pOptDiskTemplate =
1394
  withDoc "Instance disk template" .
1395
  optionalField .
1396
  renameField "OptDiskTemplate" $
1397
  simpleField "disk_template" [t| DiskTemplate |]
1398

    
1399
pOsNameChange :: Field
1400
pOsNameChange =
1401
  withDoc "Change the instance's OS without reinstalling the instance" $
1402
  optionalNEStringField "os_name"
1403

    
1404
pDiskIndex :: Field
1405
pDiskIndex =
1406
  withDoc "Disk index for e.g. grow disk" .
1407
  renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
1408

    
1409
pDiskChgAmount :: Field
1410
pDiskChgAmount =
1411
  withDoc "Disk amount to add or grow to" .
1412
  renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
1413

    
1414
pDiskChgAbsolute :: Field
1415
pDiskChgAbsolute =
1416
  withDoc
1417
    "Whether the amount parameter is an absolute target or a relative one" .
1418
  renameField "DiskChkAbsolute" $ defaultFalse "absolute"
1419

    
1420
pTargetGroups :: Field
1421
pTargetGroups =
1422
  withDoc
1423
    "Destination group names or UUIDs (defaults to \"all but current group\")" .
1424
  optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
1425

    
1426
pNodeGroupAllocPolicy :: Field
1427
pNodeGroupAllocPolicy =
1428
  withDoc "Instance allocation policy" .
1429
  optionalField $
1430
  simpleField "alloc_policy" [t| AllocPolicy |]
1431

    
1432
pGroupNodeParams :: Field
1433
pGroupNodeParams =
1434
  withDoc "Default node parameters for group" .
1435
  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
1436

    
1437
pExportMode :: Field
1438
pExportMode =
1439
  withDoc "Export mode" .
1440
  renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1441

    
1442
-- FIXME: Rename target_node as it changes meaning for different
1443
-- export modes (e.g. "destination")
1444
pExportTargetNode :: Field
1445
pExportTargetNode =
1446
  withDoc "Target node (depends on export mode)" .
1447
  renameField "ExportTarget" $
1448
  simpleField "target_node" [t| ExportTarget |]
1449

    
1450
pExportTargetNodeUuid :: Field
1451
pExportTargetNodeUuid =
1452
  withDoc "Target node UUID (if local export)" .
1453
  renameField "ExportTargetNodeUuid" . optionalField $
1454
  simpleField "target_node_uuid" [t| NonEmptyString |]
1455

    
1456
pShutdownInstance :: Field
1457
pShutdownInstance =
1458
  withDoc "Whether to shutdown the instance before export" $
1459
  defaultTrue "shutdown"
1460

    
1461
pRemoveInstance :: Field
1462
pRemoveInstance =
1463
  withDoc "Whether to remove instance after export" $
1464
  defaultFalse "remove_instance"
1465

    
1466
pIgnoreRemoveFailures :: Field
1467
pIgnoreRemoveFailures =
1468
  withDoc "Whether to ignore failures while removing instances" $
1469
  defaultFalse "ignore_remove_failures"
1470

    
1471
pX509KeyName :: Field
1472
pX509KeyName =
1473
  withDoc "Name of X509 key (remote export only)" .
1474
  optionalField $ simpleField "x509_key_name" [t| [JSValue] |]
1475

    
1476
pX509DestCA :: Field
1477
pX509DestCA =
1478
  withDoc "Destination X509 CA (remote export only)" $
1479
  optionalNEStringField "destination_x509_ca"
1480

    
1481
pTagsObject :: Field
1482
pTagsObject =
1483
  withDoc "Tag kind" $
1484
  simpleField "kind" [t| TagKind |]
1485

    
1486
pTagsName :: Field
1487
pTagsName =
1488
  withDoc "Name of object" .
1489
  renameField "TagsGetName" .
1490
  optionalField $ simpleField "name" [t| String |]
1491

    
1492
pTagsList :: Field
1493
pTagsList =
1494
  withDoc "List of tag names" $
1495
  simpleField "tags" [t| [String] |]
1496

    
1497
-- FIXME: this should be compiled at load time?
1498
pTagSearchPattern :: Field
1499
pTagSearchPattern =
1500
  withDoc "Search pattern (regular expression)" .
1501
  renameField "TagSearchPattern" $
1502
  simpleField "pattern" [t| NonEmptyString |]
1503

    
1504
pDelayDuration :: Field
1505
pDelayDuration =
1506
  withDoc "Duration parameter for 'OpTestDelay'" .
1507
  renameField "DelayDuration" $
1508
  simpleField "duration" [t| Double |]
1509

    
1510
pDelayOnMaster :: Field
1511
pDelayOnMaster =
1512
  withDoc "on_master field for 'OpTestDelay'" .
1513
  renameField "DelayOnMaster" $
1514
  defaultTrue "on_master"
1515

    
1516
pDelayOnNodes :: Field
1517
pDelayOnNodes =
1518
  withDoc "on_nodes field for 'OpTestDelay'" .
1519
  renameField "DelayOnNodes" .
1520
  defaultField [| [] |] $
1521
  simpleField "on_nodes" [t| [NonEmptyString] |]
1522

    
1523
pDelayOnNodeUuids :: Field
1524
pDelayOnNodeUuids =
1525
  withDoc "on_node_uuids field for 'OpTestDelay'" .
1526
  renameField "DelayOnNodeUuids" . optionalField $
1527
  simpleField "on_node_uuids" [t| [NonEmptyString] |]
1528

    
1529
pDelayRepeat :: Field
1530
pDelayRepeat =
1531
  withDoc "Repeat parameter for OpTestDelay" .
1532
  renameField "DelayRepeat" .
1533
  defaultField [| forceNonNeg (0::Int) |] $
1534
  simpleField "repeat" [t| NonNegative Int |]
1535

    
1536
pDelayInterruptible :: Field
1537
pDelayInterruptible =
1538
  withDoc "Allows socket-based interruption of a running OpTestDelay" .
1539
  renameField "DelayInterruptible" .
1540
  defaultField [| False |] $
1541
  simpleField "interruptible" [t| Bool |]
1542

    
1543
pIAllocatorDirection :: Field
1544
pIAllocatorDirection =
1545
  withDoc "IAllocator test direction" .
1546
  renameField "IAllocatorDirection" $
1547
  simpleField "direction" [t| IAllocatorTestDir |]
1548

    
1549
pIAllocatorMode :: Field
1550
pIAllocatorMode =
1551
  withDoc "IAllocator test mode" .
1552
  renameField "IAllocatorMode" $
1553
  simpleField "mode" [t| IAllocatorMode |]
1554

    
1555
pIAllocatorReqName :: Field
1556
pIAllocatorReqName =
1557
  withDoc "IAllocator target name (new instance, node to evac, etc.)" .
1558
  renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
1559

    
1560
pIAllocatorNics :: Field
1561
pIAllocatorNics =
1562
  withDoc "Custom OpTestIAllocator nics" .
1563
  renameField "IAllocatorNics" .
1564
  optionalField $ simpleField "nics" [t| [INicParams] |]
1565

    
1566
pIAllocatorDisks :: Field
1567
pIAllocatorDisks =
1568
  withDoc "Custom OpTestAllocator disks" .
1569
  renameField "IAllocatorDisks" .
1570
  optionalField $ simpleField "disks" [t| [JSValue] |]
1571

    
1572
pIAllocatorMemory :: Field
1573
pIAllocatorMemory =
1574
  withDoc "IAllocator memory field" .
1575
  renameField "IAllocatorMem" .
1576
  optionalField $
1577
  simpleField "memory" [t| NonNegative Int |]
1578

    
1579
pIAllocatorVCpus :: Field
1580
pIAllocatorVCpus =
1581
  withDoc "IAllocator vcpus field" .
1582
  renameField "IAllocatorVCpus" .
1583
  optionalField $
1584
  simpleField "vcpus" [t| NonNegative Int |]
1585

    
1586
pIAllocatorOs :: Field
1587
pIAllocatorOs =
1588
  withDoc "IAllocator os field" .
1589
  renameField "IAllocatorOs" $ optionalNEStringField "os"
1590

    
1591
pIAllocatorInstances :: Field
1592
pIAllocatorInstances =
1593
  withDoc "IAllocator instances field" .
1594
  renameField "IAllocatorInstances " .
1595
  optionalField $
1596
  simpleField "instances" [t| [NonEmptyString] |]
1597

    
1598
pIAllocatorEvacMode :: Field
1599
pIAllocatorEvacMode =
1600
  withDoc "IAllocator evac mode" .
1601
  renameField "IAllocatorEvacMode" .
1602
  optionalField $
1603
  simpleField "evac_mode" [t| EvacMode |]
1604

    
1605
pIAllocatorSpindleUse :: Field
1606
pIAllocatorSpindleUse =
1607
  withDoc "IAllocator spindle use" .
1608
  renameField "IAllocatorSpindleUse" .
1609
  defaultField [| forceNonNeg (1::Int) |] $
1610
  simpleField "spindle_use" [t| NonNegative Int |]
1611

    
1612
pIAllocatorCount :: Field
1613
pIAllocatorCount =
1614
  withDoc "IAllocator count field" .
1615
  renameField "IAllocatorCount" .
1616
  defaultField [| forceNonNeg (1::Int) |] $
1617
  simpleField "count" [t| NonNegative Int |]
1618

    
1619
pJQueueNotifyWaitLock :: Field
1620
pJQueueNotifyWaitLock =
1621
  withDoc "'OpTestJqueue' notify_waitlock" $
1622
  defaultFalse "notify_waitlock"
1623

    
1624
pJQueueNotifyExec :: Field
1625
pJQueueNotifyExec =
1626
  withDoc "'OpTestJQueue' notify_exec" $
1627
  defaultFalse "notify_exec"
1628

    
1629
pJQueueLogMessages :: Field
1630
pJQueueLogMessages =
1631
  withDoc "'OpTestJQueue' log_messages" .
1632
  defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
1633

    
1634
pJQueueFail :: Field
1635
pJQueueFail =
1636
  withDoc "'OpTestJQueue' fail attribute" .
1637
  renameField "JQueueFail" $ defaultFalse "fail"
1638

    
1639
pTestDummyResult :: Field
1640
pTestDummyResult =
1641
  withDoc "'OpTestDummy' result field" .
1642
  renameField "TestDummyResult" $ simpleField "result" [t| JSValue |]
1643

    
1644
pTestDummyMessages :: Field
1645
pTestDummyMessages =
1646
  withDoc "'OpTestDummy' messages field" .
1647
  renameField "TestDummyMessages" $
1648
  simpleField "messages" [t| JSValue |]
1649

    
1650
pTestDummyFail :: Field
1651
pTestDummyFail =
1652
  withDoc "'OpTestDummy' fail field" .
1653
  renameField "TestDummyFail" $ simpleField "fail" [t| JSValue |]
1654

    
1655
pTestDummySubmitJobs :: Field
1656
pTestDummySubmitJobs =
1657
  withDoc "'OpTestDummy' submit_jobs field" .
1658
  renameField "TestDummySubmitJobs" $
1659
  simpleField "submit_jobs" [t| JSValue |]
1660

    
1661
pNetworkName :: Field
1662
pNetworkName =
1663
  withDoc "Network name" $
1664
  simpleField "network_name" [t| NonEmptyString |]
1665

    
1666
pNetworkAddress4 :: Field
1667
pNetworkAddress4 =
1668
  withDoc "Network address (IPv4 subnet)" .
1669
  renameField "NetworkAddress4" $
1670
  simpleField "network" [t| IPv4Network |]
1671

    
1672
pNetworkGateway4 :: Field
1673
pNetworkGateway4 =
1674
  withDoc "Network gateway (IPv4 address)" .
1675
  renameField "NetworkGateway4" .
1676
  optionalField $ simpleField "gateway" [t| IPv4Address |]
1677

    
1678
pNetworkAddress6 :: Field
1679
pNetworkAddress6 =
1680
  withDoc "Network address (IPv6 subnet)" .
1681
  renameField "NetworkAddress6" .
1682
  optionalField $ simpleField "network6" [t| IPv6Network |]
1683

    
1684
pNetworkGateway6 :: Field
1685
pNetworkGateway6 =
1686
  withDoc "Network gateway (IPv6 address)" .
1687
  renameField "NetworkGateway6" .
1688
  optionalField $ simpleField "gateway6" [t| IPv6Address |]
1689

    
1690
pNetworkMacPrefix :: Field
1691
pNetworkMacPrefix =
1692
  withDoc "Network specific mac prefix (that overrides the cluster one)" .
1693
  renameField "NetMacPrefix" $
1694
  optionalNEStringField "mac_prefix"
1695

    
1696
pNetworkAddRsvdIps :: Field
1697
pNetworkAddRsvdIps =
1698
  withDoc "Which IP addresses to reserve" .
1699
  renameField "NetworkAddRsvdIps" .
1700
  optionalField $
1701
  simpleField "add_reserved_ips" [t| [IPv4Address] |]
1702

    
1703
pNetworkRemoveRsvdIps :: Field
1704
pNetworkRemoveRsvdIps =
1705
  withDoc "Which external IP addresses to release" .
1706
  renameField "NetworkRemoveRsvdIps" .
1707
  optionalField $
1708
  simpleField "remove_reserved_ips" [t| [IPv4Address] |]
1709

    
1710
pNetworkMode :: Field
1711
pNetworkMode =
1712
  withDoc "Network mode when connecting to a group" $
1713
  simpleField "network_mode" [t| NICMode |]
1714

    
1715
pNetworkLink :: Field
1716
pNetworkLink =
1717
  withDoc "Network link when connecting to a group" $
1718
  simpleField "network_link" [t| NonEmptyString |]