Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ 6bce7ba2

History | View | Annotate | Download (47.4 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

    
3
{-| Implementation of opcodes parameters.
4

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

    
11
-}
12

    
13
{-
14

    
15
Copyright (C) 2012, 2014 Google Inc.
16

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

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

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

    
32
-}
33

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

    
266
import Control.Monad (liftM, mplus)
267
import Text.JSON (JSON, JSValue(..), JSObject (..), readJSON, showJSON,
268
                  fromJSString, toJSObject)
269
import qualified Text.JSON
270
import Text.JSON.Pretty (pp_value)
271

    
272
import Ganeti.BasicTypes
273
import qualified Ganeti.Constants as C
274
import Ganeti.THH
275
import Ganeti.Utils
276
import Ganeti.JSON
277
import Ganeti.Types
278
import qualified Ganeti.Query.Language as Qlang
279

    
280
-- * Helper functions and types
281

    
282
-- | Build a boolean field.
283
booleanField :: String -> Field
284
booleanField = flip simpleField [t| Bool |]
285

    
286
-- | Default a field to 'False'.
287
defaultFalse :: String -> Field
288
defaultFalse = defaultField [| False |] . booleanField
289

    
290
-- | Default a field to 'True'.
291
defaultTrue :: String -> Field
292
defaultTrue = defaultField [| True |] . booleanField
293

    
294
-- | An alias for a 'String' field.
295
stringField :: String -> Field
296
stringField = flip simpleField [t| String |]
297

    
298
-- | An alias for an optional string field.
299
optionalStringField :: String -> Field
300
optionalStringField = optionalField . stringField
301

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

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

    
315
-- ** Disks
316

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

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

    
329
instance JSON DiskIndex where
330
  readJSON v = readJSON v >>= mkDiskIndex
331
  showJSON = showJSON . unDiskIndex
332

    
333
-- ** I* param types
334

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

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

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

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

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

    
389
instance JSON RecreateDisksInfo where
390
  readJSON = readRecreateDisks
391
  showJSON  RecreateDisksAll            = showJSON ()
392
  showJSON (RecreateDisksIndices idx)   = showJSON idx
393
  showJSON (RecreateDisksParams params) = showJSON params
394

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

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

    
409
instance JSON DdmOldChanges where
410
  showJSON (DdmOldIndex i) = showJSON i
411
  showJSON (DdmOldMod m)   = showJSON m
412
  readJSON = readDdmOldChanges
413

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

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

    
430
instance (JSON a) => JSON (SetParamsMods a) where
431
  showJSON SetParamsEmpty = showJSON ()
432
  showJSON (SetParamsDeprecated v) = showJSON v
433
  showJSON (SetParamsNew v) = showJSON v
434
  showJSON (SetParamsNewName v) = showJSON v
435
  readJSON = readSetParams
436

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

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

    
453
instance JSON ExportTarget where
454
  showJSON (ExportTargetLocal s)  = showJSON s
455
  showJSON (ExportTargetRemote l) = showJSON l
456
  readJSON = readExportTarget
457

    
458
-- * Common opcode parameters
459

    
460
pDryRun :: Field
461
pDryRun =
462
  withDoc "Run checks only, don't execute" .
463
  optionalField $ booleanField "dry_run"
464

    
465
pDebugLevel :: Field
466
pDebugLevel =
467
  withDoc "Debug level" .
468
  optionalField $ simpleField "debug_level" [t| NonNegative Int |]
469

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

    
477
pDependencies :: Field
478
pDependencies =
479
  withDoc "Job dependencies" .
480
  optionalNullSerField $ simpleField "depends" [t| [JobDependency] |]
481

    
482
pComment :: Field
483
pComment =
484
  withDoc "Comment field" .
485
  optionalNullSerField $ stringField "comment"
486

    
487
pReason :: Field
488
pReason =
489
  withDoc "Reason trail field" $
490
  simpleField C.opcodeReason [t| ReasonTrail |]
491

    
492
-- * Parameters
493

    
494
pDebugSimulateErrors :: Field
495
pDebugSimulateErrors =
496
  withDoc "Whether to simulate errors (useful for debugging)" $
497
  defaultFalse "debug_simulate_errors"
498

    
499
pErrorCodes :: Field
500
pErrorCodes =
501
  withDoc "Error codes" $
502
  defaultFalse "error_codes"
503

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

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

    
516
pVerbose :: Field
517
pVerbose =
518
  withDoc "Verbose mode" $
519
  defaultFalse "verbose"
520

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

    
527
pGroupName :: Field
528
pGroupName =
529
  withDoc "Group name" $
530
  simpleField "group_name" [t| NonEmptyString |]
531

    
532
-- | Whether to hotplug device.
533
pHotplug :: Field
534
pHotplug = defaultFalse "hotplug"
535

    
536
pHotplugIfPossible :: Field
537
pHotplugIfPossible = defaultFalse "hotplug_if_possible"
538

    
539
pInstances :: Field
540
pInstances =
541
  withDoc "List of instances" .
542
  defaultField [| [] |] $
543
  simpleField "instances" [t| [NonEmptyString] |]
544

    
545
pOutputFields :: Field
546
pOutputFields =
547
  withDoc "Selected output fields" $
548
  simpleField "output_fields" [t| [NonEmptyString] |]
549

    
550
pName :: Field
551
pName =
552
  withDoc "A generic name" $
553
  simpleField "name" [t| NonEmptyString |]
554

    
555
pForce :: Field
556
pForce =
557
  withDoc "Whether to force the operation" $
558
  defaultFalse "force"
559

    
560
pHvState :: Field
561
pHvState =
562
  withDoc "Set hypervisor states" .
563
  optionalField $ simpleField "hv_state" [t| JSObject JSValue |]
564

    
565
pDiskState :: Field
566
pDiskState =
567
  withDoc "Set disk states" .
568
  optionalField $ simpleField "disk_state" [t| JSObject JSValue |]
569

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

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

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

    
588
-- | Volume group name.
589
pVgName :: Field
590
pVgName =
591
  withDoc "Volume group name" $
592
  optionalStringField "vg_name"
593

    
594
pEnabledHypervisors :: Field
595
pEnabledHypervisors =
596
  withDoc "List of enabled hypervisors" .
597
  optionalField $
598
  simpleField "enabled_hypervisors" [t| [Hypervisor] |]
599

    
600
pClusterHvParams :: Field
601
pClusterHvParams =
602
  withDoc "Cluster-wide hypervisor parameters, hypervisor-dependent" .
603
  renameField "ClusterHvParams" .
604
  optionalField $
605
  simpleField "hvparams" [t| GenericContainer String (JSObject JSValue) |]
606

    
607
pClusterBeParams :: Field
608
pClusterBeParams =
609
  withDoc "Cluster-wide backend parameter defaults" .
610
  renameField "ClusterBeParams" .
611
  optionalField $ simpleField "beparams" [t| JSObject JSValue |]
612

    
613
pOsHvp :: Field
614
pOsHvp =
615
  withDoc "Cluster-wide per-OS hypervisor parameter defaults" .
616
  optionalField $
617
  simpleField "os_hvp" [t| GenericContainer String (JSObject JSValue) |]
618

    
619
pClusterOsParams :: Field
620
pClusterOsParams =
621
  withDoc "Cluster-wide OS parameter defaults" .
622
  renameField "ClusterOsParams" .
623
  optionalField $
624
  simpleField "osparams" [t| GenericContainer String (JSObject JSValue) |]
625

    
626
pClusterOsParamsPrivate :: Field
627
pClusterOsParamsPrivate =
628
  withDoc "Cluster-wide private OS parameter defaults" .
629
  renameField "ClusterOsParamsPrivate" .
630
  optionalField $
631
  -- This field needs an unique name to aid Python deserialization
632
  simpleField "osparams_private_cluster"
633
    [t| GenericContainer String (JSObject (Private JSValue)) |]
634

    
635
pDiskParams :: Field
636
pDiskParams =
637
  withDoc "Disk templates' parameter defaults" .
638
  optionalField $
639
  simpleField "diskparams"
640
              [t| GenericContainer DiskTemplate (JSObject JSValue) |]
641

    
642
pCandidatePoolSize :: Field
643
pCandidatePoolSize =
644
  withDoc "Master candidate pool size" .
645
  optionalField $ simpleField "candidate_pool_size" [t| Positive Int |]
646

    
647
pMaxRunningJobs :: Field
648
pMaxRunningJobs =
649
  withDoc "Maximal number of jobs to run simultaneously" .
650
  optionalField $ simpleField "max_running_jobs" [t| Positive Int |]
651

    
652
pUidPool :: Field
653
pUidPool =
654
  withDoc "Set UID pool, must be list of lists describing UID ranges\
655
          \ (two items, start and end inclusive)" .
656
  optionalField $ simpleField "uid_pool" [t| [(Int, Int)] |]
657

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

    
664
pRemoveUids :: Field
665
pRemoveUids =
666
  withDoc "Shrink UID pool, must be list of lists describing UID\
667
          \ ranges (two items, start and end inclusive) to be removed" .
668
  optionalField $ simpleField "remove_uids" [t| [(Int, Int)] |]
669

    
670
pMaintainNodeHealth :: Field
671
pMaintainNodeHealth =
672
  withDoc "Whether to automatically maintain node health" .
673
  optionalField $ booleanField "maintain_node_health"
674

    
675
-- | Whether to modify and keep in sync the @/etc/hosts@ files of nodes.
676
pModifyEtcHosts :: Field
677
pModifyEtcHosts = optionalField $ booleanField "modify_etc_hosts"
678

    
679
-- | Whether to wipe disks before allocating them to instances.
680
pPreallocWipeDisks :: Field
681
pPreallocWipeDisks =
682
  withDoc "Whether to wipe disks before allocating them to instances" .
683
  optionalField $ booleanField "prealloc_wipe_disks"
684

    
685
pNicParams :: Field
686
pNicParams =
687
  withDoc "Cluster-wide NIC parameter defaults" .
688
  optionalField $ simpleField "nicparams" [t| INicParams |]
689

    
690
pIpolicy :: Field
691
pIpolicy =
692
  withDoc "Ipolicy specs" .
693
  optionalField $ simpleField "ipolicy" [t| JSObject JSValue |]
694

    
695
pDrbdHelper :: Field
696
pDrbdHelper =
697
  withDoc "DRBD helper program" $
698
  optionalStringField "drbd_helper"
699

    
700
pDefaultIAllocator :: Field
701
pDefaultIAllocator =
702
  withDoc "Default iallocator for cluster" $
703
  optionalStringField "default_iallocator"
704

    
705
pDefaultIAllocatorParams :: Field
706
pDefaultIAllocatorParams =
707
  withDoc "Default iallocator parameters for cluster" . optionalField
708
    $ simpleField "default_iallocator_params" [t| JSObject JSValue |]
709

    
710
pMasterNetdev :: Field
711
pMasterNetdev =
712
  withDoc "Master network device" $
713
  optionalStringField "master_netdev"
714

    
715
pMasterNetmask :: Field
716
pMasterNetmask =
717
  withDoc "Netmask of the master IP" .
718
  optionalField $ simpleField "master_netmask" [t| NonNegative Int |]
719

    
720
pReservedLvs :: Field
721
pReservedLvs =
722
  withDoc "List of reserved LVs" .
723
  optionalField $ simpleField "reserved_lvs" [t| [NonEmptyString] |]
724

    
725
pHiddenOs :: Field
726
pHiddenOs =
727
  withDoc "Modify list of hidden operating systems: each modification\
728
          \ must have two items, the operation and the OS name; the operation\
729
          \ can be add or remove" .
730
  optionalField $ simpleField "hidden_os" [t| [(DdmSimple, NonEmptyString)] |]
731

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

    
740
pUseExternalMipScript :: Field
741
pUseExternalMipScript =
742
  withDoc "Whether to use an external master IP address setup script" .
743
  optionalField $ booleanField "use_external_mip_script"
744

    
745
pEnabledDiskTemplates :: Field
746
pEnabledDiskTemplates =
747
  withDoc "List of enabled disk templates" .
748
  optionalField $
749
  simpleField "enabled_disk_templates" [t| [DiskTemplate] |]
750

    
751
pQueryWhat :: Field
752
pQueryWhat =
753
  withDoc "Resource(s) to query for" $
754
  simpleField "what" [t| Qlang.QueryTypeOp |]
755

    
756
pUseLocking :: Field
757
pUseLocking =
758
  withDoc "Whether to use synchronization" $
759
  defaultFalse "use_locking"
760

    
761
pQueryFields :: Field
762
pQueryFields =
763
  withDoc "Requested fields" $
764
  simpleField "fields" [t| [NonEmptyString] |]
765

    
766
pQueryFilter :: Field
767
pQueryFilter =
768
  withDoc "Query filter" .
769
  optionalField $ simpleField "qfilter" [t| [JSValue] |]
770

    
771
pQueryFieldsFields :: Field
772
pQueryFieldsFields =
773
  withDoc "Requested fields; if not given, all are returned" .
774
  renameField "QueryFieldsFields" $
775
  optionalField pQueryFields
776

    
777
pNodeNames :: Field
778
pNodeNames =
779
  withDoc "List of node names to run the OOB command against" .
780
  defaultField [| [] |] $ simpleField "node_names" [t| [NonEmptyString] |]
781

    
782
pNodeUuids :: Field
783
pNodeUuids =
784
  withDoc "List of node UUIDs" .
785
  optionalField $ simpleField "node_uuids" [t| [NonEmptyString] |]
786

    
787
pOobCommand :: Field
788
pOobCommand =
789
  withDoc "OOB command to run" $
790
  simpleField "command" [t| OobCommand |]
791

    
792
pOobTimeout :: Field
793
pOobTimeout =
794
  withDoc "Timeout before the OOB helper will be terminated" .
795
  defaultField [| C.oobTimeout |] $
796
  simpleField "timeout" [t| Int |]
797

    
798
pIgnoreStatus :: Field
799
pIgnoreStatus =
800
  withDoc "Ignores the node offline status for power off" $
801
  defaultFalse "ignore_status"
802

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

    
812
pRequiredNodes :: Field
813
pRequiredNodes =
814
  withDoc "Required list of node names" .
815
  renameField "ReqNodes " $ simpleField "nodes" [t| [NonEmptyString] |]
816

    
817
pRequiredNodeUuids :: Field
818
pRequiredNodeUuids =
819
  withDoc "Required list of node UUIDs" .
820
  renameField "ReqNodeUuids " . optionalField $
821
  simpleField "node_uuids" [t| [NonEmptyString] |]
822

    
823
pRestrictedCommand :: Field
824
pRestrictedCommand =
825
  withDoc "Restricted command name" .
826
  renameField "RestrictedCommand" $
827
  simpleField "command" [t| NonEmptyString |]
828

    
829
pNodeName :: Field
830
pNodeName =
831
  withDoc "A required node name (for single-node LUs)" $
832
  simpleField "node_name" [t| NonEmptyString |]
833

    
834
pNodeUuid :: Field
835
pNodeUuid =
836
  withDoc "A node UUID (for single-node LUs)" .
837
  optionalField $ simpleField "node_uuid" [t| NonEmptyString |]
838

    
839
pPrimaryIp :: Field
840
pPrimaryIp =
841
  withDoc "Primary IP address" .
842
  optionalField $
843
  simpleField "primary_ip" [t| NonEmptyString |]
844

    
845
pSecondaryIp :: Field
846
pSecondaryIp =
847
  withDoc "Secondary IP address" $
848
  optionalNEStringField "secondary_ip"
849

    
850
pReadd :: Field
851
pReadd =
852
  withDoc "Whether node is re-added to cluster" $
853
  defaultFalse "readd"
854

    
855
pNodeGroup :: Field
856
pNodeGroup =
857
  withDoc "Initial node group" $
858
  optionalNEStringField "group"
859

    
860
pMasterCapable :: Field
861
pMasterCapable =
862
  withDoc "Whether node can become master or master candidate" .
863
  optionalField $ booleanField "master_capable"
864

    
865
pVmCapable :: Field
866
pVmCapable =
867
  withDoc "Whether node can host instances" .
868
  optionalField $ booleanField "vm_capable"
869

    
870
pNdParams :: Field
871
pNdParams =
872
  withDoc "Node parameters" .
873
  renameField "genericNdParams" .
874
  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
875

    
876
pNames :: Field
877
pNames =
878
  withDoc "List of names" .
879
  defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
880

    
881
pNodes :: Field
882
pNodes =
883
  withDoc "List of nodes" .
884
  defaultField [| [] |] $ simpleField "nodes" [t| [NonEmptyString] |]
885

    
886
pStorageType :: Field
887
pStorageType =
888
  withDoc "Storage type" $ simpleField "storage_type" [t| StorageType |]
889

    
890
pStorageTypeOptional :: Field
891
pStorageTypeOptional =
892
  withDoc "Storage type" .
893
  renameField "StorageTypeOptional" .
894
  optionalField $ simpleField "storage_type" [t| StorageType |]
895

    
896
pStorageName :: Field
897
pStorageName =
898
  withDoc "Storage name" .
899
  renameField "StorageName" .
900
  optionalField $ simpleField "name" [t| NonEmptyString |]
901

    
902
pStorageChanges :: Field
903
pStorageChanges =
904
  withDoc "Requested storage changes" $
905
  simpleField "changes" [t| JSObject JSValue |]
906

    
907
pIgnoreConsistency :: Field
908
pIgnoreConsistency =
909
  withDoc "Whether to ignore disk consistency" $
910
  defaultFalse "ignore_consistency"
911

    
912
pMasterCandidate :: Field
913
pMasterCandidate =
914
  withDoc "Whether the node should become a master candidate" .
915
  optionalField $ booleanField "master_candidate"
916

    
917
pOffline :: Field
918
pOffline =
919
  withDoc "Whether to mark the node or instance offline" .
920
  optionalField $ booleanField "offline"
921

    
922
pDrained ::Field
923
pDrained =
924
  withDoc "Whether to mark the node as drained" .
925
  optionalField $ booleanField "drained"
926

    
927
pAutoPromote :: Field
928
pAutoPromote =
929
  withDoc "Whether node(s) should be promoted to master candidate if\
930
          \ necessary" $
931
  defaultFalse "auto_promote"
932

    
933
pPowered :: Field
934
pPowered =
935
  withDoc "Whether the node should be marked as powered" .
936
  optionalField $ booleanField "powered"
937

    
938
pMigrationMode :: Field
939
pMigrationMode =
940
  withDoc "Migration type (live/non-live)" .
941
  renameField "MigrationMode" .
942
  optionalField $
943
  simpleField "mode" [t| MigrationMode |]
944

    
945
pMigrationLive :: Field
946
pMigrationLive =
947
  withDoc "Obsolete \'live\' migration mode (do not use)" .
948
  renameField "OldLiveMode" . optionalField $ booleanField "live"
949

    
950
pMigrationTargetNode :: Field
951
pMigrationTargetNode =
952
  withDoc "Target node for instance migration/failover" $
953
  optionalNEStringField "target_node"
954

    
955
pMigrationTargetNodeUuid :: Field
956
pMigrationTargetNodeUuid =
957
  withDoc "Target node UUID for instance migration/failover" $
958
  optionalNEStringField "target_node_uuid"
959

    
960
pAllowRuntimeChgs :: Field
961
pAllowRuntimeChgs =
962
  withDoc "Whether to allow runtime changes while migrating" $
963
  defaultTrue "allow_runtime_changes"
964

    
965
pIgnoreIpolicy :: Field
966
pIgnoreIpolicy =
967
  withDoc "Whether to ignore ipolicy violations" $
968
  defaultFalse "ignore_ipolicy"
969

    
970
pIallocator :: Field
971
pIallocator =
972
  withDoc "Iallocator for deciding the target node for shared-storage\
973
          \ instances" $
974
  optionalNEStringField "iallocator"
975

    
976
pEarlyRelease :: Field
977
pEarlyRelease =
978
  withDoc "Whether to release locks as soon as possible" $
979
  defaultFalse "early_release"
980

    
981
pRemoteNode :: Field
982
pRemoteNode =
983
  withDoc "New secondary node" $
984
  optionalNEStringField "remote_node"
985

    
986
pRemoteNodeUuid :: Field
987
pRemoteNodeUuid =
988
  withDoc "New secondary node UUID" $
989
  optionalNEStringField "remote_node_uuid"
990

    
991
pEvacMode :: Field
992
pEvacMode =
993
  withDoc "Node evacuation mode" .
994
  renameField "EvacMode" $ simpleField "mode" [t| EvacMode |]
995

    
996
pInstanceName :: Field
997
pInstanceName =
998
  withDoc "A required instance name (for single-instance LUs)" $
999
  simpleField "instance_name" [t| String |]
1000

    
1001
pInstanceCommunication :: Field
1002
pInstanceCommunication =
1003
  withDoc C.instanceCommunicationDoc $
1004
  defaultFalse "instance_communication"
1005

    
1006
pForceVariant :: Field
1007
pForceVariant =
1008
  withDoc "Whether to force an unknown OS variant" $
1009
  defaultFalse "force_variant"
1010

    
1011
pWaitForSync :: Field
1012
pWaitForSync =
1013
  withDoc "Whether to wait for the disk to synchronize" $
1014
  defaultTrue "wait_for_sync"
1015

    
1016
pNameCheck :: Field
1017
pNameCheck =
1018
  withDoc "Whether to check name" $
1019
  defaultTrue "name_check"
1020

    
1021
pInstBeParams :: Field
1022
pInstBeParams =
1023
  withDoc "Backend parameters for instance" .
1024
  renameField "InstBeParams" .
1025
  defaultField [| toJSObject [] |] $
1026
  simpleField "beparams" [t| JSObject JSValue |]
1027

    
1028
pInstDisks :: Field
1029
pInstDisks =
1030
  withDoc "List of instance disks" .
1031
  renameField "instDisks" $ simpleField "disks" [t| [IDiskParams] |]
1032

    
1033
pDiskTemplate :: Field
1034
pDiskTemplate =
1035
  withDoc "Disk template" $
1036
  simpleField "disk_template" [t| DiskTemplate |]
1037

    
1038
pFileDriver :: Field
1039
pFileDriver =
1040
  withDoc "Driver for file-backed disks" .
1041
  optionalField $ simpleField "file_driver" [t| FileDriver |]
1042

    
1043
pFileStorageDir :: Field
1044
pFileStorageDir =
1045
  withDoc "Directory for storing file-backed disks" $
1046
  optionalNEStringField "file_storage_dir"
1047

    
1048
pInstHvParams :: Field
1049
pInstHvParams =
1050
  withDoc "Hypervisor parameters for instance, hypervisor-dependent" .
1051
  renameField "InstHvParams" .
1052
  defaultField [| toJSObject [] |] $
1053
  simpleField "hvparams" [t| JSObject JSValue |]
1054

    
1055
pHypervisor :: Field
1056
pHypervisor =
1057
  withDoc "Selected hypervisor for an instance" .
1058
  optionalField $
1059
  simpleField "hypervisor" [t| Hypervisor |]
1060

    
1061
pResetDefaults :: Field
1062
pResetDefaults =
1063
  withDoc "Reset instance parameters to default if equal" $
1064
  defaultFalse "identify_defaults"
1065

    
1066
pIpCheck :: Field
1067
pIpCheck =
1068
  withDoc "Whether to ensure instance's IP address is inactive" $
1069
  defaultTrue "ip_check"
1070

    
1071
pIpConflictsCheck :: Field
1072
pIpConflictsCheck =
1073
  withDoc "Whether to check for conflicting IP addresses" $
1074
  defaultTrue "conflicts_check"
1075

    
1076
pInstCreateMode :: Field
1077
pInstCreateMode =
1078
  withDoc "Instance creation mode" .
1079
  renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
1080

    
1081
pInstNics :: Field
1082
pInstNics =
1083
  withDoc "List of NIC (network interface) definitions" $
1084
  simpleField "nics" [t| [INicParams] |]
1085

    
1086
pNoInstall :: Field
1087
pNoInstall =
1088
  withDoc "Do not install the OS (will disable automatic start)" .
1089
  optionalField $ booleanField "no_install"
1090

    
1091
pInstOs :: Field
1092
pInstOs =
1093
  withDoc "OS type for instance installation" $
1094
  optionalNEStringField "os_type"
1095

    
1096
pInstOsParams :: Field
1097
pInstOsParams =
1098
  withDoc "OS parameters for instance" .
1099
  renameField "InstOsParams" .
1100
  defaultField [| toJSObject [] |] $
1101
  simpleField "osparams" [t| JSObject JSValue |]
1102

    
1103
pInstOsParamsPrivate :: Field
1104
pInstOsParamsPrivate =
1105
  withDoc "Private OS parameters for instance" .
1106
  optionalField $
1107
  simpleField "osparams_private" [t| JSObject (Private JSValue) |]
1108

    
1109
pInstOsParamsSecret :: Field
1110
pInstOsParamsSecret =
1111
  withDoc "Secret OS parameters for instance" .
1112
  optionalField $
1113
  simpleField "osparams_secret" [t| JSObject (Private JSValue) |]
1114

    
1115
pPrimaryNode :: Field
1116
pPrimaryNode =
1117
  withDoc "Primary node for an instance" $
1118
  optionalNEStringField "pnode"
1119

    
1120
pPrimaryNodeUuid :: Field
1121
pPrimaryNodeUuid =
1122
  withDoc "Primary node UUID for an instance" $
1123
  optionalNEStringField "pnode_uuid"
1124

    
1125
pSecondaryNode :: Field
1126
pSecondaryNode =
1127
  withDoc "Secondary node for an instance" $
1128
  optionalNEStringField "snode"
1129

    
1130
pSecondaryNodeUuid :: Field
1131
pSecondaryNodeUuid =
1132
  withDoc "Secondary node UUID for an instance" $
1133
  optionalNEStringField "snode_uuid"
1134

    
1135
pSourceHandshake :: Field
1136
pSourceHandshake =
1137
  withDoc "Signed handshake from source (remote import only)" .
1138
  optionalField $ simpleField "source_handshake" [t| [JSValue] |]
1139

    
1140
pSourceInstance :: Field
1141
pSourceInstance =
1142
  withDoc "Source instance name (remote import only)" $
1143
  optionalNEStringField "source_instance_name"
1144

    
1145
-- FIXME: non-negative int, whereas the constant is a plain int.
1146
pSourceShutdownTimeout :: Field
1147
pSourceShutdownTimeout =
1148
  withDoc "How long source instance was given to shut down (remote import\
1149
          \ only)" .
1150
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1151
  simpleField "source_shutdown_timeout" [t| NonNegative Int |]
1152

    
1153
pSourceX509Ca :: Field
1154
pSourceX509Ca =
1155
  withDoc "Source X509 CA in PEM format (remote import only)" $
1156
  optionalNEStringField "source_x509_ca"
1157

    
1158
pSrcNode :: Field
1159
pSrcNode =
1160
  withDoc "Source node for import" $
1161
  optionalNEStringField "src_node"
1162

    
1163
pSrcNodeUuid :: Field
1164
pSrcNodeUuid =
1165
  withDoc "Source node UUID for import" $
1166
  optionalNEStringField "src_node_uuid"
1167

    
1168
pSrcPath :: Field
1169
pSrcPath =
1170
  withDoc "Source directory for import" $
1171
  optionalNEStringField "src_path"
1172

    
1173
pStartInstance :: Field
1174
pStartInstance =
1175
  withDoc "Whether to start instance after creation" $
1176
  defaultTrue "start"
1177

    
1178
-- FIXME: unify/simplify with pTags, once that migrates to NonEmpty String"
1179
pInstTags :: Field
1180
pInstTags =
1181
  withDoc "Instance tags" .
1182
  renameField "InstTags" .
1183
  defaultField [| [] |] $
1184
  simpleField "tags" [t| [NonEmptyString] |]
1185

    
1186
pMultiAllocInstances :: Field
1187
pMultiAllocInstances =
1188
  withDoc "List of instance create opcodes describing the instances to\
1189
          \ allocate" .
1190
  renameField "InstMultiAlloc" .
1191
  defaultField [| [] |] $
1192
  simpleField "instances"[t| [JSValue] |]
1193

    
1194
pOpportunisticLocking :: Field
1195
pOpportunisticLocking =
1196
  withDoc "Whether to employ opportunistic locking for nodes, meaning\
1197
          \ nodes already locked by another opcode won't be considered for\
1198
          \ instance allocation (only when an iallocator is used)" $
1199
  defaultFalse "opportunistic_locking"
1200

    
1201
pInstanceUuid :: Field
1202
pInstanceUuid =
1203
  withDoc "An instance UUID (for single-instance LUs)" .
1204
  optionalField $ simpleField "instance_uuid" [t| NonEmptyString |]
1205

    
1206
pTempOsParams :: Field
1207
pTempOsParams =
1208
  withDoc "Temporary OS parameters (currently only in reinstall, might be\
1209
          \ added to install as well)" .
1210
  renameField "TempOsParams" .
1211
  optionalField $ simpleField "osparams" [t| JSObject JSValue |]
1212

    
1213
pShutdownTimeout :: Field
1214
pShutdownTimeout =
1215
  withDoc "How long to wait for instance to shut down" .
1216
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1217
  simpleField "shutdown_timeout" [t| NonNegative Int |]
1218

    
1219
-- | Another name for the shutdown timeout, because we like to be
1220
-- inconsistent.
1221
pShutdownTimeout' :: Field
1222
pShutdownTimeout' =
1223
  withDoc "How long to wait for instance to shut down" .
1224
  renameField "InstShutdownTimeout" .
1225
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1226
  simpleField "timeout" [t| NonNegative Int |]
1227

    
1228
pIgnoreFailures :: Field
1229
pIgnoreFailures =
1230
  withDoc "Whether to ignore failures during removal" $
1231
  defaultFalse "ignore_failures"
1232

    
1233
pNewName :: Field
1234
pNewName =
1235
  withDoc "New group or instance name" $
1236
  simpleField "new_name" [t| NonEmptyString |]
1237

    
1238
pIgnoreOfflineNodes :: Field
1239
pIgnoreOfflineNodes =
1240
  withDoc "Whether to ignore offline nodes" $
1241
  defaultFalse "ignore_offline_nodes"
1242

    
1243
pTempHvParams :: Field
1244
pTempHvParams =
1245
  withDoc "Temporary hypervisor parameters, hypervisor-dependent" .
1246
  renameField "TempHvParams" .
1247
  defaultField [| toJSObject [] |] $
1248
  simpleField "hvparams" [t| JSObject JSValue |]
1249

    
1250
pTempBeParams :: Field
1251
pTempBeParams =
1252
  withDoc "Temporary backend parameters" .
1253
  renameField "TempBeParams" .
1254
  defaultField [| toJSObject [] |] $
1255
  simpleField "beparams" [t| JSObject JSValue |]
1256

    
1257
pNoRemember :: Field
1258
pNoRemember =
1259
  withDoc "Do not remember instance state changes" $
1260
  defaultFalse "no_remember"
1261

    
1262
pStartupPaused :: Field
1263
pStartupPaused =
1264
  withDoc "Pause instance at startup" $
1265
  defaultFalse "startup_paused"
1266

    
1267
pIgnoreSecondaries :: Field
1268
pIgnoreSecondaries =
1269
  withDoc "Whether to start the instance even if secondary disks are failing" $
1270
  defaultFalse "ignore_secondaries"
1271

    
1272
pRebootType :: Field
1273
pRebootType =
1274
  withDoc "How to reboot the instance" $
1275
  simpleField "reboot_type" [t| RebootType |]
1276

    
1277
pReplaceDisksMode :: Field
1278
pReplaceDisksMode =
1279
  withDoc "Replacement mode" .
1280
  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1281

    
1282
pReplaceDisksList :: Field
1283
pReplaceDisksList =
1284
  withDoc "List of disk indices" .
1285
  renameField "ReplaceDisksList" .
1286
  defaultField [| [] |] $
1287
  simpleField "disks" [t| [DiskIndex] |]
1288

    
1289
pMigrationCleanup :: Field
1290
pMigrationCleanup =
1291
  withDoc "Whether a previously failed migration should be cleaned up" .
1292
  renameField "MigrationCleanup" $ defaultFalse "cleanup"
1293

    
1294
pAllowFailover :: Field
1295
pAllowFailover =
1296
  withDoc "Whether we can fallback to failover if migration is not possible" $
1297
  defaultFalse "allow_failover"
1298

    
1299
pMoveTargetNode :: Field
1300
pMoveTargetNode =
1301
  withDoc "Target node for instance move" .
1302
  renameField "MoveTargetNode" $
1303
  simpleField "target_node" [t| NonEmptyString |]
1304

    
1305
pMoveTargetNodeUuid :: Field
1306
pMoveTargetNodeUuid =
1307
  withDoc "Target node UUID for instance move" .
1308
  renameField "MoveTargetNodeUuid" . optionalField $
1309
  simpleField "target_node_uuid" [t| NonEmptyString |]
1310

    
1311
pMoveCompress :: Field
1312
pMoveCompress =
1313
  withDoc "Compression mode to use during instance moves" .
1314
  defaultField [| None |] $
1315
  simpleField "compress" [t| ImportExportCompression |]
1316

    
1317
pBackupCompress :: Field
1318
pBackupCompress =
1319
  withDoc "Compression mode to use for moves during backups/imports" .
1320
  defaultField [| None |] $
1321
  simpleField "compress" [t| ImportExportCompression |]
1322

    
1323
pIgnoreDiskSize :: Field
1324
pIgnoreDiskSize =
1325
  withDoc "Whether to ignore recorded disk size" $
1326
  defaultFalse "ignore_size"
1327

    
1328
pWaitForSyncFalse :: Field
1329
pWaitForSyncFalse =
1330
  withDoc "Whether to wait for the disk to synchronize (defaults to false)" $
1331
  defaultField [| False |] pWaitForSync
1332

    
1333
pRecreateDisksInfo :: Field
1334
pRecreateDisksInfo =
1335
  withDoc "Disk list for recreate disks" .
1336
  renameField "RecreateDisksInfo" .
1337
  defaultField [| RecreateDisksAll |] $
1338
  simpleField "disks" [t| RecreateDisksInfo |]
1339

    
1340
pStatic :: Field
1341
pStatic =
1342
  withDoc "Whether to only return configuration data without querying nodes" $
1343
  defaultFalse "static"
1344

    
1345
pInstParamsNicChanges :: Field
1346
pInstParamsNicChanges =
1347
  withDoc "List of NIC changes" .
1348
  renameField "InstNicChanges" .
1349
  defaultField [| SetParamsEmpty |] $
1350
  simpleField "nics" [t| SetParamsMods INicParams |]
1351

    
1352
pInstParamsDiskChanges :: Field
1353
pInstParamsDiskChanges =
1354
  withDoc "List of disk changes" .
1355
  renameField "InstDiskChanges" .
1356
  defaultField [| SetParamsEmpty |] $
1357
  simpleField "disks" [t| SetParamsMods IDiskParams |]
1358

    
1359
pRuntimeMem :: Field
1360
pRuntimeMem =
1361
  withDoc "New runtime memory" .
1362
  optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1363

    
1364
pOptDiskTemplate :: Field
1365
pOptDiskTemplate =
1366
  withDoc "Instance disk template" .
1367
  optionalField .
1368
  renameField "OptDiskTemplate" $
1369
  simpleField "disk_template" [t| DiskTemplate |]
1370

    
1371
pOsNameChange :: Field
1372
pOsNameChange =
1373
  withDoc "Change the instance's OS without reinstalling the instance" $
1374
  optionalNEStringField "os_name"
1375

    
1376
pDiskIndex :: Field
1377
pDiskIndex =
1378
  withDoc "Disk index for e.g. grow disk" .
1379
  renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
1380

    
1381
pDiskChgAmount :: Field
1382
pDiskChgAmount =
1383
  withDoc "Disk amount to add or grow to" .
1384
  renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
1385

    
1386
pDiskChgAbsolute :: Field
1387
pDiskChgAbsolute =
1388
  withDoc
1389
    "Whether the amount parameter is an absolute target or a relative one" .
1390
  renameField "DiskChkAbsolute" $ defaultFalse "absolute"
1391

    
1392
pTargetGroups :: Field
1393
pTargetGroups =
1394
  withDoc
1395
    "Destination group names or UUIDs (defaults to \"all but current group\")" .
1396
  optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
1397

    
1398
pNodeGroupAllocPolicy :: Field
1399
pNodeGroupAllocPolicy =
1400
  withDoc "Instance allocation policy" .
1401
  optionalField $
1402
  simpleField "alloc_policy" [t| AllocPolicy |]
1403

    
1404
pGroupNodeParams :: Field
1405
pGroupNodeParams =
1406
  withDoc "Default node parameters for group" .
1407
  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
1408

    
1409
pExportMode :: Field
1410
pExportMode =
1411
  withDoc "Export mode" .
1412
  renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1413

    
1414
-- FIXME: Rename target_node as it changes meaning for different
1415
-- export modes (e.g. "destination")
1416
pExportTargetNode :: Field
1417
pExportTargetNode =
1418
  withDoc "Target node (depends on export mode)" .
1419
  renameField "ExportTarget" $
1420
  simpleField "target_node" [t| ExportTarget |]
1421

    
1422
pExportTargetNodeUuid :: Field
1423
pExportTargetNodeUuid =
1424
  withDoc "Target node UUID (if local export)" .
1425
  renameField "ExportTargetNodeUuid" . optionalField $
1426
  simpleField "target_node_uuid" [t| NonEmptyString |]
1427

    
1428
pShutdownInstance :: Field
1429
pShutdownInstance =
1430
  withDoc "Whether to shutdown the instance before export" $
1431
  defaultTrue "shutdown"
1432

    
1433
pRemoveInstance :: Field
1434
pRemoveInstance =
1435
  withDoc "Whether to remove instance after export" $
1436
  defaultFalse "remove_instance"
1437

    
1438
pIgnoreRemoveFailures :: Field
1439
pIgnoreRemoveFailures =
1440
  withDoc "Whether to ignore failures while removing instances" $
1441
  defaultFalse "ignore_remove_failures"
1442

    
1443
pX509KeyName :: Field
1444
pX509KeyName =
1445
  withDoc "Name of X509 key (remote export only)" .
1446
  optionalField $ simpleField "x509_key_name" [t| [JSValue] |]
1447

    
1448
pX509DestCA :: Field
1449
pX509DestCA =
1450
  withDoc "Destination X509 CA (remote export only)" $
1451
  optionalNEStringField "destination_x509_ca"
1452

    
1453
pTagsObject :: Field
1454
pTagsObject =
1455
  withDoc "Tag kind" $
1456
  simpleField "kind" [t| TagKind |]
1457

    
1458
pTagsName :: Field
1459
pTagsName =
1460
  withDoc "Name of object" .
1461
  renameField "TagsGetName" .
1462
  optionalField $ simpleField "name" [t| String |]
1463

    
1464
pTagsList :: Field
1465
pTagsList =
1466
  withDoc "List of tag names" $
1467
  simpleField "tags" [t| [String] |]
1468

    
1469
-- FIXME: this should be compiled at load time?
1470
pTagSearchPattern :: Field
1471
pTagSearchPattern =
1472
  withDoc "Search pattern (regular expression)" .
1473
  renameField "TagSearchPattern" $
1474
  simpleField "pattern" [t| NonEmptyString |]
1475

    
1476
pDelayDuration :: Field
1477
pDelayDuration =
1478
  withDoc "Duration parameter for 'OpTestDelay'" .
1479
  renameField "DelayDuration" $
1480
  simpleField "duration" [t| Double |]
1481

    
1482
pDelayOnMaster :: Field
1483
pDelayOnMaster =
1484
  withDoc "on_master field for 'OpTestDelay'" .
1485
  renameField "DelayOnMaster" $
1486
  defaultTrue "on_master"
1487

    
1488
pDelayOnNodes :: Field
1489
pDelayOnNodes =
1490
  withDoc "on_nodes field for 'OpTestDelay'" .
1491
  renameField "DelayOnNodes" .
1492
  defaultField [| [] |] $
1493
  simpleField "on_nodes" [t| [NonEmptyString] |]
1494

    
1495
pDelayOnNodeUuids :: Field
1496
pDelayOnNodeUuids =
1497
  withDoc "on_node_uuids field for 'OpTestDelay'" .
1498
  renameField "DelayOnNodeUuids" . optionalField $
1499
  simpleField "on_node_uuids" [t| [NonEmptyString] |]
1500

    
1501
pDelayRepeat :: Field
1502
pDelayRepeat =
1503
  withDoc "Repeat parameter for OpTestDelay" .
1504
  renameField "DelayRepeat" .
1505
  defaultField [| forceNonNeg (0::Int) |] $
1506
  simpleField "repeat" [t| NonNegative Int |]
1507

    
1508
pIAllocatorDirection :: Field
1509
pIAllocatorDirection =
1510
  withDoc "IAllocator test direction" .
1511
  renameField "IAllocatorDirection" $
1512
  simpleField "direction" [t| IAllocatorTestDir |]
1513

    
1514
pIAllocatorMode :: Field
1515
pIAllocatorMode =
1516
  withDoc "IAllocator test mode" .
1517
  renameField "IAllocatorMode" $
1518
  simpleField "mode" [t| IAllocatorMode |]
1519

    
1520
pIAllocatorReqName :: Field
1521
pIAllocatorReqName =
1522
  withDoc "IAllocator target name (new instance, node to evac, etc.)" .
1523
  renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
1524

    
1525
pIAllocatorNics :: Field
1526
pIAllocatorNics =
1527
  withDoc "Custom OpTestIAllocator nics" .
1528
  renameField "IAllocatorNics" .
1529
  optionalField $ simpleField "nics" [t| [INicParams] |]
1530

    
1531
pIAllocatorDisks :: Field
1532
pIAllocatorDisks =
1533
  withDoc "Custom OpTestAllocator disks" .
1534
  renameField "IAllocatorDisks" .
1535
  optionalField $ simpleField "disks" [t| [JSValue] |]
1536

    
1537
pIAllocatorMemory :: Field
1538
pIAllocatorMemory =
1539
  withDoc "IAllocator memory field" .
1540
  renameField "IAllocatorMem" .
1541
  optionalField $
1542
  simpleField "memory" [t| NonNegative Int |]
1543

    
1544
pIAllocatorVCpus :: Field
1545
pIAllocatorVCpus =
1546
  withDoc "IAllocator vcpus field" .
1547
  renameField "IAllocatorVCpus" .
1548
  optionalField $
1549
  simpleField "vcpus" [t| NonNegative Int |]
1550

    
1551
pIAllocatorOs :: Field
1552
pIAllocatorOs =
1553
  withDoc "IAllocator os field" .
1554
  renameField "IAllocatorOs" $ optionalNEStringField "os"
1555

    
1556
pIAllocatorInstances :: Field
1557
pIAllocatorInstances =
1558
  withDoc "IAllocator instances field" .
1559
  renameField "IAllocatorInstances " .
1560
  optionalField $
1561
  simpleField "instances" [t| [NonEmptyString] |]
1562

    
1563
pIAllocatorEvacMode :: Field
1564
pIAllocatorEvacMode =
1565
  withDoc "IAllocator evac mode" .
1566
  renameField "IAllocatorEvacMode" .
1567
  optionalField $
1568
  simpleField "evac_mode" [t| EvacMode |]
1569

    
1570
pIAllocatorSpindleUse :: Field
1571
pIAllocatorSpindleUse =
1572
  withDoc "IAllocator spindle use" .
1573
  renameField "IAllocatorSpindleUse" .
1574
  defaultField [| forceNonNeg (1::Int) |] $
1575
  simpleField "spindle_use" [t| NonNegative Int |]
1576

    
1577
pIAllocatorCount :: Field
1578
pIAllocatorCount =
1579
  withDoc "IAllocator count field" .
1580
  renameField "IAllocatorCount" .
1581
  defaultField [| forceNonNeg (1::Int) |] $
1582
  simpleField "count" [t| NonNegative Int |]
1583

    
1584
pJQueueNotifyWaitLock :: Field
1585
pJQueueNotifyWaitLock =
1586
  withDoc "'OpTestJqueue' notify_waitlock" $
1587
  defaultFalse "notify_waitlock"
1588

    
1589
pJQueueNotifyExec :: Field
1590
pJQueueNotifyExec =
1591
  withDoc "'OpTestJQueue' notify_exec" $
1592
  defaultFalse "notify_exec"
1593

    
1594
pJQueueLogMessages :: Field
1595
pJQueueLogMessages =
1596
  withDoc "'OpTestJQueue' log_messages" .
1597
  defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
1598

    
1599
pJQueueFail :: Field
1600
pJQueueFail =
1601
  withDoc "'OpTestJQueue' fail attribute" .
1602
  renameField "JQueueFail" $ defaultFalse "fail"
1603

    
1604
pTestDummyResult :: Field
1605
pTestDummyResult =
1606
  withDoc "'OpTestDummy' result field" .
1607
  renameField "TestDummyResult" $ simpleField "result" [t| JSValue |]
1608

    
1609
pTestDummyMessages :: Field
1610
pTestDummyMessages =
1611
  withDoc "'OpTestDummy' messages field" .
1612
  renameField "TestDummyMessages" $
1613
  simpleField "messages" [t| JSValue |]
1614

    
1615
pTestDummyFail :: Field
1616
pTestDummyFail =
1617
  withDoc "'OpTestDummy' fail field" .
1618
  renameField "TestDummyFail" $ simpleField "fail" [t| JSValue |]
1619

    
1620
pTestDummySubmitJobs :: Field
1621
pTestDummySubmitJobs =
1622
  withDoc "'OpTestDummy' submit_jobs field" .
1623
  renameField "TestDummySubmitJobs" $
1624
  simpleField "submit_jobs" [t| JSValue |]
1625

    
1626
pNetworkName :: Field
1627
pNetworkName =
1628
  withDoc "Network name" $
1629
  simpleField "network_name" [t| NonEmptyString |]
1630

    
1631
pNetworkAddress4 :: Field
1632
pNetworkAddress4 =
1633
  withDoc "Network address (IPv4 subnet)" .
1634
  renameField "NetworkAddress4" $
1635
  simpleField "network" [t| IPv4Network |]
1636

    
1637
pNetworkGateway4 :: Field
1638
pNetworkGateway4 =
1639
  withDoc "Network gateway (IPv4 address)" .
1640
  renameField "NetworkGateway4" .
1641
  optionalField $ simpleField "gateway" [t| IPv4Address |]
1642

    
1643
pNetworkAddress6 :: Field
1644
pNetworkAddress6 =
1645
  withDoc "Network address (IPv6 subnet)" .
1646
  renameField "NetworkAddress6" .
1647
  optionalField $ simpleField "network6" [t| IPv6Network |]
1648

    
1649
pNetworkGateway6 :: Field
1650
pNetworkGateway6 =
1651
  withDoc "Network gateway (IPv6 address)" .
1652
  renameField "NetworkGateway6" .
1653
  optionalField $ simpleField "gateway6" [t| IPv6Address |]
1654

    
1655
pNetworkMacPrefix :: Field
1656
pNetworkMacPrefix =
1657
  withDoc "Network specific mac prefix (that overrides the cluster one)" .
1658
  renameField "NetMacPrefix" $
1659
  optionalNEStringField "mac_prefix"
1660

    
1661
pNetworkAddRsvdIps :: Field
1662
pNetworkAddRsvdIps =
1663
  withDoc "Which IP addresses to reserve" .
1664
  renameField "NetworkAddRsvdIps" .
1665
  optionalField $
1666
  simpleField "add_reserved_ips" [t| [IPv4Address] |]
1667

    
1668
pNetworkRemoveRsvdIps :: Field
1669
pNetworkRemoveRsvdIps =
1670
  withDoc "Which external IP addresses to release" .
1671
  renameField "NetworkRemoveRsvdIps" .
1672
  optionalField $
1673
  simpleField "remove_reserved_ips" [t| [IPv4Address] |]
1674

    
1675
pNetworkMode :: Field
1676
pNetworkMode =
1677
  withDoc "Network mode when connecting to a group" $
1678
  simpleField "network_mode" [t| NICMode |]
1679

    
1680
pNetworkLink :: Field
1681
pNetworkLink =
1682
  withDoc "Network link when connecting to a group" $
1683
  simpleField "network_link" [t| NonEmptyString |]