Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ 07e3c124

History | View | Annotate | Download (47 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
  , pCandidatePoolSize
124
  , pMaxRunningJobs
125
  , pUidPool
126
  , pAddUids
127
  , pRemoveUids
128
  , pMaintainNodeHealth
129
  , pModifyEtcHosts
130
  , pPreallocWipeDisks
131
  , pNicParams
132
  , pInstNics
133
  , pNdParams
134
  , pIpolicy
135
  , pDrbdHelper
136
  , pDefaultIAllocator
137
  , pDefaultIAllocatorParams
138
  , pMasterNetdev
139
  , pMasterNetmask
140
  , pReservedLvs
141
  , pHiddenOs
142
  , pBlacklistedOs
143
  , pUseExternalMipScript
144
  , pQueryFields
145
  , pQueryFilter
146
  , pQueryFieldsFields
147
  , pOobCommand
148
  , pOobTimeout
149
  , pIgnoreStatus
150
  , pPowerDelay
151
  , pPrimaryIp
152
  , pSecondaryIp
153
  , pReadd
154
  , pNodeGroup
155
  , pMasterCapable
156
  , pVmCapable
157
  , pNames
158
  , pNodes
159
  , pRequiredNodes
160
  , pRequiredNodeUuids
161
  , pStorageType
162
  , pStorageTypeOptional
163
  , pStorageChanges
164
  , pMasterCandidate
165
  , pOffline
166
  , pDrained
167
  , pAutoPromote
168
  , pPowered
169
  , pIallocator
170
  , pRemoteNode
171
  , pRemoteNodeUuid
172
  , pEvacMode
173
  , pInstCreateMode
174
  , pNoInstall
175
  , pInstOs
176
  , pPrimaryNode
177
  , pPrimaryNodeUuid
178
  , pSecondaryNode
179
  , pSecondaryNodeUuid
180
  , pSourceHandshake
181
  , pSourceInstance
182
  , pSourceShutdownTimeout
183
  , pSourceX509Ca
184
  , pSrcNode
185
  , pSrcNodeUuid
186
  , pSrcPath
187
  , pStartInstance
188
  , pInstTags
189
  , pMultiAllocInstances
190
  , pTempOsParams
191
  , pTempHvParams
192
  , pTempBeParams
193
  , pIgnoreFailures
194
  , pNewName
195
  , pIgnoreSecondaries
196
  , pRebootType
197
  , pIgnoreDiskSize
198
  , pRecreateDisksInfo
199
  , pStatic
200
  , pInstParamsNicChanges
201
  , pInstParamsDiskChanges
202
  , pRuntimeMem
203
  , pOsNameChange
204
  , pDiskIndex
205
  , pDiskChgAmount
206
  , pDiskChgAbsolute
207
  , pTargetGroups
208
  , pExportMode
209
  , pExportTargetNode
210
  , pExportTargetNodeUuid
211
  , pRemoveInstance
212
  , pIgnoreRemoveFailures
213
  , pX509KeyName
214
  , pX509DestCA
215
  , pTagSearchPattern
216
  , pRestrictedCommand
217
  , pReplaceDisksMode
218
  , pReplaceDisksList
219
  , pAllowFailover
220
  , pDelayDuration
221
  , pDelayOnMaster
222
  , pDelayOnNodes
223
  , pDelayOnNodeUuids
224
  , pDelayRepeat
225
  , pIAllocatorDirection
226
  , pIAllocatorMode
227
  , pIAllocatorReqName
228
  , pIAllocatorNics
229
  , pIAllocatorDisks
230
  , pIAllocatorMemory
231
  , pIAllocatorVCpus
232
  , pIAllocatorOs
233
  , pIAllocatorInstances
234
  , pIAllocatorEvacMode
235
  , pIAllocatorSpindleUse
236
  , pIAllocatorCount
237
  , pJQueueNotifyWaitLock
238
  , pJQueueNotifyExec
239
  , pJQueueLogMessages
240
  , pJQueueFail
241
  , pTestDummyResult
242
  , pTestDummyMessages
243
  , pTestDummyFail
244
  , pTestDummySubmitJobs
245
  , pNetworkName
246
  , pNetworkAddress4
247
  , pNetworkGateway4
248
  , pNetworkAddress6
249
  , pNetworkGateway6
250
  , pNetworkMacPrefix
251
  , pNetworkAddRsvdIps
252
  , pNetworkRemoveRsvdIps
253
  , pNetworkMode
254
  , pNetworkLink
255
  , pDryRun
256
  , pDebugLevel
257
  , pOpPriority
258
  , pDependencies
259
  , pComment
260
  , pReason
261
  , pEnabledDiskTemplates
262
  ) where
263

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

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

    
278
-- * Helper functions and types
279

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

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

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

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

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

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

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

    
313
-- ** Disks
314

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

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

    
327
instance JSON DiskIndex where
328
  readJSON v = readJSON v >>= mkDiskIndex
329
  showJSON = showJSON . unDiskIndex
330

    
331
-- ** I* param types
332

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
456
-- * Common opcode parameters
457

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

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

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

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

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

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

    
490
-- * Parameters
491

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

    
497
pErrorCodes :: Field
498
pErrorCodes =
499
  withDoc "Error codes" $
500
  defaultFalse "error_codes"
501

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

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

    
514
pVerbose :: Field
515
pVerbose =
516
  withDoc "Verbose mode" $
517
  defaultFalse "verbose"
518

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

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

    
530
-- | Whether to hotplug device.
531
pHotplug :: Field
532
pHotplug = defaultFalse "hotplug"
533

    
534
pHotplugIfPossible :: Field
535
pHotplugIfPossible = defaultFalse "hotplug_if_possible"
536

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
693
pDrbdHelper :: Field
694
pDrbdHelper =
695
  withDoc "DRBD helper program" $
696
  optionalStringField "drbd_helper"
697

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

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

    
708
pMasterNetdev :: Field
709
pMasterNetdev =
710
  withDoc "Master network device" $
711
  optionalStringField "master_netdev"
712

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
843
pSecondaryIp :: Field
844
pSecondaryIp =
845
  withDoc "Secondary IP address" $
846
  optionalNEStringField "secondary_ip"
847

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

    
853
pNodeGroup :: Field
854
pNodeGroup =
855
  withDoc "Initial node group" $
856
  optionalNEStringField "group"
857

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
979
pRemoteNode :: Field
980
pRemoteNode =
981
  withDoc "New secondary node" $
982
  optionalNEStringField "remote_node"
983

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

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

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

    
999
pInstanceCommunication :: Field
1000
pInstanceCommunication =
1001
  withDoc C.instanceCommunicationDoc $
1002
  defaultFalse "instance_communication"
1003

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
1101
pPrimaryNode :: Field
1102
pPrimaryNode =
1103
  withDoc "Primary node for an instance" $
1104
  optionalNEStringField "pnode"
1105

    
1106
pPrimaryNodeUuid :: Field
1107
pPrimaryNodeUuid =
1108
  withDoc "Primary node UUID for an instance" $
1109
  optionalNEStringField "pnode_uuid"
1110

    
1111
pSecondaryNode :: Field
1112
pSecondaryNode =
1113
  withDoc "Secondary node for an instance" $
1114
  optionalNEStringField "snode"
1115

    
1116
pSecondaryNodeUuid :: Field
1117
pSecondaryNodeUuid =
1118
  withDoc "Secondary node UUID for an instance" $
1119
  optionalNEStringField "snode_uuid"
1120

    
1121
pSourceHandshake :: Field
1122
pSourceHandshake =
1123
  withDoc "Signed handshake from source (remote import only)" .
1124
  optionalField $ simpleField "source_handshake" [t| [JSValue] |]
1125

    
1126
pSourceInstance :: Field
1127
pSourceInstance =
1128
  withDoc "Source instance name (remote import only)" $
1129
  optionalNEStringField "source_instance_name"
1130

    
1131
-- FIXME: non-negative int, whereas the constant is a plain int.
1132
pSourceShutdownTimeout :: Field
1133
pSourceShutdownTimeout =
1134
  withDoc "How long source instance was given to shut down (remote import\
1135
          \ only)" .
1136
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1137
  simpleField "source_shutdown_timeout" [t| NonNegative Int |]
1138

    
1139
pSourceX509Ca :: Field
1140
pSourceX509Ca =
1141
  withDoc "Source X509 CA in PEM format (remote import only)" $
1142
  optionalNEStringField "source_x509_ca"
1143

    
1144
pSrcNode :: Field
1145
pSrcNode =
1146
  withDoc "Source node for import" $
1147
  optionalNEStringField "src_node"
1148

    
1149
pSrcNodeUuid :: Field
1150
pSrcNodeUuid =
1151
  withDoc "Source node UUID for import" $
1152
  optionalNEStringField "src_node_uuid"
1153

    
1154
pSrcPath :: Field
1155
pSrcPath =
1156
  withDoc "Source directory for import" $
1157
  optionalNEStringField "src_path"
1158

    
1159
pStartInstance :: Field
1160
pStartInstance =
1161
  withDoc "Whether to start instance after creation" $
1162
  defaultTrue "start"
1163

    
1164
-- FIXME: unify/simplify with pTags, once that migrates to NonEmpty String"
1165
pInstTags :: Field
1166
pInstTags =
1167
  withDoc "Instance tags" .
1168
  renameField "InstTags" .
1169
  defaultField [| [] |] $
1170
  simpleField "tags" [t| [NonEmptyString] |]
1171

    
1172
pMultiAllocInstances :: Field
1173
pMultiAllocInstances =
1174
  withDoc "List of instance create opcodes describing the instances to\
1175
          \ allocate" .
1176
  renameField "InstMultiAlloc" .
1177
  defaultField [| [] |] $
1178
  simpleField "instances"[t| [JSValue] |]
1179

    
1180
pOpportunisticLocking :: Field
1181
pOpportunisticLocking =
1182
  withDoc "Whether to employ opportunistic locking for nodes, meaning\
1183
          \ nodes already locked by another opcode won't be considered for\
1184
          \ instance allocation (only when an iallocator is used)" $
1185
  defaultFalse "opportunistic_locking"
1186

    
1187
pInstanceUuid :: Field
1188
pInstanceUuid =
1189
  withDoc "An instance UUID (for single-instance LUs)" .
1190
  optionalField $ simpleField "instance_uuid" [t| NonEmptyString |]
1191

    
1192
pTempOsParams :: Field
1193
pTempOsParams =
1194
  withDoc "Temporary OS parameters (currently only in reinstall, might be\
1195
          \ added to install as well)" .
1196
  renameField "TempOsParams" .
1197
  optionalField $ simpleField "osparams" [t| JSObject JSValue |]
1198

    
1199
pShutdownTimeout :: Field
1200
pShutdownTimeout =
1201
  withDoc "How long to wait for instance to shut down" .
1202
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1203
  simpleField "shutdown_timeout" [t| NonNegative Int |]
1204

    
1205
-- | Another name for the shutdown timeout, because we like to be
1206
-- inconsistent.
1207
pShutdownTimeout' :: Field
1208
pShutdownTimeout' =
1209
  withDoc "How long to wait for instance to shut down" .
1210
  renameField "InstShutdownTimeout" .
1211
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1212
  simpleField "timeout" [t| NonNegative Int |]
1213

    
1214
pIgnoreFailures :: Field
1215
pIgnoreFailures =
1216
  withDoc "Whether to ignore failures during removal" $
1217
  defaultFalse "ignore_failures"
1218

    
1219
pNewName :: Field
1220
pNewName =
1221
  withDoc "New group or instance name" $
1222
  simpleField "new_name" [t| NonEmptyString |]
1223

    
1224
pIgnoreOfflineNodes :: Field
1225
pIgnoreOfflineNodes =
1226
  withDoc "Whether to ignore offline nodes" $
1227
  defaultFalse "ignore_offline_nodes"
1228

    
1229
pTempHvParams :: Field
1230
pTempHvParams =
1231
  withDoc "Temporary hypervisor parameters, hypervisor-dependent" .
1232
  renameField "TempHvParams" .
1233
  defaultField [| toJSObject [] |] $
1234
  simpleField "hvparams" [t| JSObject JSValue |]
1235

    
1236
pTempBeParams :: Field
1237
pTempBeParams =
1238
  withDoc "Temporary backend parameters" .
1239
  renameField "TempBeParams" .
1240
  defaultField [| toJSObject [] |] $
1241
  simpleField "beparams" [t| JSObject JSValue |]
1242

    
1243
pNoRemember :: Field
1244
pNoRemember =
1245
  withDoc "Do not remember instance state changes" $
1246
  defaultFalse "no_remember"
1247

    
1248
pStartupPaused :: Field
1249
pStartupPaused =
1250
  withDoc "Pause instance at startup" $
1251
  defaultFalse "startup_paused"
1252

    
1253
pIgnoreSecondaries :: Field
1254
pIgnoreSecondaries =
1255
  withDoc "Whether to start the instance even if secondary disks are failing" $
1256
  defaultFalse "ignore_secondaries"
1257

    
1258
pRebootType :: Field
1259
pRebootType =
1260
  withDoc "How to reboot the instance" $
1261
  simpleField "reboot_type" [t| RebootType |]
1262

    
1263
pReplaceDisksMode :: Field
1264
pReplaceDisksMode =
1265
  withDoc "Replacement mode" .
1266
  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1267

    
1268
pReplaceDisksList :: Field
1269
pReplaceDisksList =
1270
  withDoc "List of disk indices" .
1271
  renameField "ReplaceDisksList" .
1272
  defaultField [| [] |] $
1273
  simpleField "disks" [t| [DiskIndex] |]
1274

    
1275
pMigrationCleanup :: Field
1276
pMigrationCleanup =
1277
  withDoc "Whether a previously failed migration should be cleaned up" .
1278
  renameField "MigrationCleanup" $ defaultFalse "cleanup"
1279

    
1280
pAllowFailover :: Field
1281
pAllowFailover =
1282
  withDoc "Whether we can fallback to failover if migration is not possible" $
1283
  defaultFalse "allow_failover"
1284

    
1285
pMoveTargetNode :: Field
1286
pMoveTargetNode =
1287
  withDoc "Target node for instance move" .
1288
  renameField "MoveTargetNode" $
1289
  simpleField "target_node" [t| NonEmptyString |]
1290

    
1291
pMoveTargetNodeUuid :: Field
1292
pMoveTargetNodeUuid =
1293
  withDoc "Target node UUID for instance move" .
1294
  renameField "MoveTargetNodeUuid" . optionalField $
1295
  simpleField "target_node_uuid" [t| NonEmptyString |]
1296

    
1297
pMoveCompress :: Field
1298
pMoveCompress =
1299
  withDoc "Compression mode to use during instance moves" .
1300
  defaultField [| None |] $
1301
  simpleField "compress" [t| ImportExportCompression |]
1302

    
1303
pBackupCompress :: Field
1304
pBackupCompress =
1305
  withDoc "Compression mode to use for moves during backups/imports" .
1306
  defaultField [| None |] $
1307
  simpleField "compress" [t| ImportExportCompression |]
1308

    
1309
pIgnoreDiskSize :: Field
1310
pIgnoreDiskSize =
1311
  withDoc "Whether to ignore recorded disk size" $
1312
  defaultFalse "ignore_size"
1313

    
1314
pWaitForSyncFalse :: Field
1315
pWaitForSyncFalse =
1316
  withDoc "Whether to wait for the disk to synchronize (defaults to false)" $
1317
  defaultField [| False |] pWaitForSync
1318

    
1319
pRecreateDisksInfo :: Field
1320
pRecreateDisksInfo =
1321
  withDoc "Disk list for recreate disks" .
1322
  renameField "RecreateDisksInfo" .
1323
  defaultField [| RecreateDisksAll |] $
1324
  simpleField "disks" [t| RecreateDisksInfo |]
1325

    
1326
pStatic :: Field
1327
pStatic =
1328
  withDoc "Whether to only return configuration data without querying nodes" $
1329
  defaultFalse "static"
1330

    
1331
pInstParamsNicChanges :: Field
1332
pInstParamsNicChanges =
1333
  withDoc "List of NIC changes" .
1334
  renameField "InstNicChanges" .
1335
  defaultField [| SetParamsEmpty |] $
1336
  simpleField "nics" [t| SetParamsMods INicParams |]
1337

    
1338
pInstParamsDiskChanges :: Field
1339
pInstParamsDiskChanges =
1340
  withDoc "List of disk changes" .
1341
  renameField "InstDiskChanges" .
1342
  defaultField [| SetParamsEmpty |] $
1343
  simpleField "disks" [t| SetParamsMods IDiskParams |]
1344

    
1345
pRuntimeMem :: Field
1346
pRuntimeMem =
1347
  withDoc "New runtime memory" .
1348
  optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1349

    
1350
pOptDiskTemplate :: Field
1351
pOptDiskTemplate =
1352
  withDoc "Instance disk template" .
1353
  optionalField .
1354
  renameField "OptDiskTemplate" $
1355
  simpleField "disk_template" [t| DiskTemplate |]
1356

    
1357
pOsNameChange :: Field
1358
pOsNameChange =
1359
  withDoc "Change the instance's OS without reinstalling the instance" $
1360
  optionalNEStringField "os_name"
1361

    
1362
pDiskIndex :: Field
1363
pDiskIndex =
1364
  withDoc "Disk index for e.g. grow disk" .
1365
  renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
1366

    
1367
pDiskChgAmount :: Field
1368
pDiskChgAmount =
1369
  withDoc "Disk amount to add or grow to" .
1370
  renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
1371

    
1372
pDiskChgAbsolute :: Field
1373
pDiskChgAbsolute =
1374
  withDoc
1375
    "Whether the amount parameter is an absolute target or a relative one" .
1376
  renameField "DiskChkAbsolute" $ defaultFalse "absolute"
1377

    
1378
pTargetGroups :: Field
1379
pTargetGroups =
1380
  withDoc
1381
    "Destination group names or UUIDs (defaults to \"all but current group\")" .
1382
  optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
1383

    
1384
pNodeGroupAllocPolicy :: Field
1385
pNodeGroupAllocPolicy =
1386
  withDoc "Instance allocation policy" .
1387
  optionalField $
1388
  simpleField "alloc_policy" [t| AllocPolicy |]
1389

    
1390
pGroupNodeParams :: Field
1391
pGroupNodeParams =
1392
  withDoc "Default node parameters for group" .
1393
  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
1394

    
1395
pExportMode :: Field
1396
pExportMode =
1397
  withDoc "Export mode" .
1398
  renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1399

    
1400
-- FIXME: Rename target_node as it changes meaning for different
1401
-- export modes (e.g. "destination")
1402
pExportTargetNode :: Field
1403
pExportTargetNode =
1404
  withDoc "Target node (depends on export mode)" .
1405
  renameField "ExportTarget" $
1406
  simpleField "target_node" [t| ExportTarget |]
1407

    
1408
pExportTargetNodeUuid :: Field
1409
pExportTargetNodeUuid =
1410
  withDoc "Target node UUID (if local export)" .
1411
  renameField "ExportTargetNodeUuid" . optionalField $
1412
  simpleField "target_node_uuid" [t| NonEmptyString |]
1413

    
1414
pShutdownInstance :: Field
1415
pShutdownInstance =
1416
  withDoc "Whether to shutdown the instance before export" $
1417
  defaultTrue "shutdown"
1418

    
1419
pRemoveInstance :: Field
1420
pRemoveInstance =
1421
  withDoc "Whether to remove instance after export" $
1422
  defaultFalse "remove_instance"
1423

    
1424
pIgnoreRemoveFailures :: Field
1425
pIgnoreRemoveFailures =
1426
  withDoc "Whether to ignore failures while removing instances" $
1427
  defaultFalse "ignore_remove_failures"
1428

    
1429
pX509KeyName :: Field
1430
pX509KeyName =
1431
  withDoc "Name of X509 key (remote export only)" .
1432
  optionalField $ simpleField "x509_key_name" [t| [JSValue] |]
1433

    
1434
pX509DestCA :: Field
1435
pX509DestCA =
1436
  withDoc "Destination X509 CA (remote export only)" $
1437
  optionalNEStringField "destination_x509_ca"
1438

    
1439
pTagsObject :: Field
1440
pTagsObject =
1441
  withDoc "Tag kind" $
1442
  simpleField "kind" [t| TagKind |]
1443

    
1444
pTagsName :: Field
1445
pTagsName =
1446
  withDoc "Name of object" .
1447
  renameField "TagsGetName" .
1448
  optionalField $ simpleField "name" [t| String |]
1449

    
1450
pTagsList :: Field
1451
pTagsList =
1452
  withDoc "List of tag names" $
1453
  simpleField "tags" [t| [String] |]
1454

    
1455
-- FIXME: this should be compiled at load time?
1456
pTagSearchPattern :: Field
1457
pTagSearchPattern =
1458
  withDoc "Search pattern (regular expression)" .
1459
  renameField "TagSearchPattern" $
1460
  simpleField "pattern" [t| NonEmptyString |]
1461

    
1462
pDelayDuration :: Field
1463
pDelayDuration =
1464
  withDoc "Duration parameter for 'OpTestDelay'" .
1465
  renameField "DelayDuration" $
1466
  simpleField "duration" [t| Double |]
1467

    
1468
pDelayOnMaster :: Field
1469
pDelayOnMaster =
1470
  withDoc "on_master field for 'OpTestDelay'" .
1471
  renameField "DelayOnMaster" $
1472
  defaultTrue "on_master"
1473

    
1474
pDelayOnNodes :: Field
1475
pDelayOnNodes =
1476
  withDoc "on_nodes field for 'OpTestDelay'" .
1477
  renameField "DelayOnNodes" .
1478
  defaultField [| [] |] $
1479
  simpleField "on_nodes" [t| [NonEmptyString] |]
1480

    
1481
pDelayOnNodeUuids :: Field
1482
pDelayOnNodeUuids =
1483
  withDoc "on_node_uuids field for 'OpTestDelay'" .
1484
  renameField "DelayOnNodeUuids" . optionalField $
1485
  simpleField "on_node_uuids" [t| [NonEmptyString] |]
1486

    
1487
pDelayRepeat :: Field
1488
pDelayRepeat =
1489
  withDoc "Repeat parameter for OpTestDelay" .
1490
  renameField "DelayRepeat" .
1491
  defaultField [| forceNonNeg (0::Int) |] $
1492
  simpleField "repeat" [t| NonNegative Int |]
1493

    
1494
pIAllocatorDirection :: Field
1495
pIAllocatorDirection =
1496
  withDoc "IAllocator test direction" .
1497
  renameField "IAllocatorDirection" $
1498
  simpleField "direction" [t| IAllocatorTestDir |]
1499

    
1500
pIAllocatorMode :: Field
1501
pIAllocatorMode =
1502
  withDoc "IAllocator test mode" .
1503
  renameField "IAllocatorMode" $
1504
  simpleField "mode" [t| IAllocatorMode |]
1505

    
1506
pIAllocatorReqName :: Field
1507
pIAllocatorReqName =
1508
  withDoc "IAllocator target name (new instance, node to evac, etc.)" .
1509
  renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
1510

    
1511
pIAllocatorNics :: Field
1512
pIAllocatorNics =
1513
  withDoc "Custom OpTestIAllocator nics" .
1514
  renameField "IAllocatorNics" .
1515
  optionalField $ simpleField "nics" [t| [INicParams] |]
1516

    
1517
pIAllocatorDisks :: Field
1518
pIAllocatorDisks =
1519
  withDoc "Custom OpTestAllocator disks" .
1520
  renameField "IAllocatorDisks" .
1521
  optionalField $ simpleField "disks" [t| [JSValue] |]
1522

    
1523
pIAllocatorMemory :: Field
1524
pIAllocatorMemory =
1525
  withDoc "IAllocator memory field" .
1526
  renameField "IAllocatorMem" .
1527
  optionalField $
1528
  simpleField "memory" [t| NonNegative Int |]
1529

    
1530
pIAllocatorVCpus :: Field
1531
pIAllocatorVCpus =
1532
  withDoc "IAllocator vcpus field" .
1533
  renameField "IAllocatorVCpus" .
1534
  optionalField $
1535
  simpleField "vcpus" [t| NonNegative Int |]
1536

    
1537
pIAllocatorOs :: Field
1538
pIAllocatorOs =
1539
  withDoc "IAllocator os field" .
1540
  renameField "IAllocatorOs" $ optionalNEStringField "os"
1541

    
1542
pIAllocatorInstances :: Field
1543
pIAllocatorInstances =
1544
  withDoc "IAllocator instances field" .
1545
  renameField "IAllocatorInstances " .
1546
  optionalField $
1547
  simpleField "instances" [t| [NonEmptyString] |]
1548

    
1549
pIAllocatorEvacMode :: Field
1550
pIAllocatorEvacMode =
1551
  withDoc "IAllocator evac mode" .
1552
  renameField "IAllocatorEvacMode" .
1553
  optionalField $
1554
  simpleField "evac_mode" [t| EvacMode |]
1555

    
1556
pIAllocatorSpindleUse :: Field
1557
pIAllocatorSpindleUse =
1558
  withDoc "IAllocator spindle use" .
1559
  renameField "IAllocatorSpindleUse" .
1560
  defaultField [| forceNonNeg (1::Int) |] $
1561
  simpleField "spindle_use" [t| NonNegative Int |]
1562

    
1563
pIAllocatorCount :: Field
1564
pIAllocatorCount =
1565
  withDoc "IAllocator count field" .
1566
  renameField "IAllocatorCount" .
1567
  defaultField [| forceNonNeg (1::Int) |] $
1568
  simpleField "count" [t| NonNegative Int |]
1569

    
1570
pJQueueNotifyWaitLock :: Field
1571
pJQueueNotifyWaitLock =
1572
  withDoc "'OpTestJqueue' notify_waitlock" $
1573
  defaultFalse "notify_waitlock"
1574

    
1575
pJQueueNotifyExec :: Field
1576
pJQueueNotifyExec =
1577
  withDoc "'OpTestJQueue' notify_exec" $
1578
  defaultFalse "notify_exec"
1579

    
1580
pJQueueLogMessages :: Field
1581
pJQueueLogMessages =
1582
  withDoc "'OpTestJQueue' log_messages" .
1583
  defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
1584

    
1585
pJQueueFail :: Field
1586
pJQueueFail =
1587
  withDoc "'OpTestJQueue' fail attribute" .
1588
  renameField "JQueueFail" $ defaultFalse "fail"
1589

    
1590
pTestDummyResult :: Field
1591
pTestDummyResult =
1592
  withDoc "'OpTestDummy' result field" .
1593
  renameField "TestDummyResult" $ simpleField "result" [t| JSValue |]
1594

    
1595
pTestDummyMessages :: Field
1596
pTestDummyMessages =
1597
  withDoc "'OpTestDummy' messages field" .
1598
  renameField "TestDummyMessages" $
1599
  simpleField "messages" [t| JSValue |]
1600

    
1601
pTestDummyFail :: Field
1602
pTestDummyFail =
1603
  withDoc "'OpTestDummy' fail field" .
1604
  renameField "TestDummyFail" $ simpleField "fail" [t| JSValue |]
1605

    
1606
pTestDummySubmitJobs :: Field
1607
pTestDummySubmitJobs =
1608
  withDoc "'OpTestDummy' submit_jobs field" .
1609
  renameField "TestDummySubmitJobs" $
1610
  simpleField "submit_jobs" [t| JSValue |]
1611

    
1612
pNetworkName :: Field
1613
pNetworkName =
1614
  withDoc "Network name" $
1615
  simpleField "network_name" [t| NonEmptyString |]
1616

    
1617
pNetworkAddress4 :: Field
1618
pNetworkAddress4 =
1619
  withDoc "Network address (IPv4 subnet)" .
1620
  renameField "NetworkAddress4" $
1621
  simpleField "network" [t| IPv4Network |]
1622

    
1623
pNetworkGateway4 :: Field
1624
pNetworkGateway4 =
1625
  withDoc "Network gateway (IPv4 address)" .
1626
  renameField "NetworkGateway4" .
1627
  optionalField $ simpleField "gateway" [t| IPv4Address |]
1628

    
1629
pNetworkAddress6 :: Field
1630
pNetworkAddress6 =
1631
  withDoc "Network address (IPv6 subnet)" .
1632
  renameField "NetworkAddress6" .
1633
  optionalField $ simpleField "network6" [t| IPv6Network |]
1634

    
1635
pNetworkGateway6 :: Field
1636
pNetworkGateway6 =
1637
  withDoc "Network gateway (IPv6 address)" .
1638
  renameField "NetworkGateway6" .
1639
  optionalField $ simpleField "gateway6" [t| IPv6Address |]
1640

    
1641
pNetworkMacPrefix :: Field
1642
pNetworkMacPrefix =
1643
  withDoc "Network specific mac prefix (that overrides the cluster one)" .
1644
  renameField "NetMacPrefix" $
1645
  optionalNEStringField "mac_prefix"
1646

    
1647
pNetworkAddRsvdIps :: Field
1648
pNetworkAddRsvdIps =
1649
  withDoc "Which IP addresses to reserve" .
1650
  renameField "NetworkAddRsvdIps" .
1651
  optionalField $
1652
  simpleField "add_reserved_ips" [t| [IPv4Address] |]
1653

    
1654
pNetworkRemoveRsvdIps :: Field
1655
pNetworkRemoveRsvdIps =
1656
  withDoc "Which external IP addresses to release" .
1657
  renameField "NetworkRemoveRsvdIps" .
1658
  optionalField $
1659
  simpleField "remove_reserved_ips" [t| [IPv4Address] |]
1660

    
1661
pNetworkMode :: Field
1662
pNetworkMode =
1663
  withDoc "Network mode when connecting to a group" $
1664
  simpleField "network_mode" [t| NICMode |]
1665

    
1666
pNetworkLink :: Field
1667
pNetworkLink =
1668
  withDoc "Network link when connecting to a group" $
1669
  simpleField "network_link" [t| NonEmptyString |]