Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ 731152ce

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.THH.Field
281
import Ganeti.Utils
282
import Ganeti.JSON
283
import Ganeti.Types
284
import qualified Ganeti.Query.Language as Qlang
285

    
286
-- * Helper functions and types
287

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

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

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

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

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

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

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

    
321
-- ** Disks
322

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

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

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

    
339
-- ** I* param types
340

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
464
-- * Common opcode parameters
465

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

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

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

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

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

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

    
498
-- * Parameters
499

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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