Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ f665d9de

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

    
264
import Control.Monad (liftM)
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.JSON
274
import Ganeti.Types
275
import qualified Ganeti.Query.Language as Qlang
276

    
277
-- * Helper functions and types
278

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

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

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

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

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

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

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

    
312
-- ** Disks
313

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

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

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

    
330
-- ** I* param types
331

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

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

    
350
-- | Disk modification definition. FIXME: disksize should be VTYPE_UNIT.
351
$(buildObject "IDiskParams" "idisk"
352
  [ optionalField $ simpleField C.idiskSize   [t| Int            |]
353
  , optionalField $ simpleField C.idiskMode   [t| DiskAccess     |]
354
  , optionalField $ simpleField C.idiskAdopt  [t| NonEmptyString |]
355
  , optionalField $ simpleField C.idiskVg     [t| NonEmptyString |]
356
  , optionalField $ simpleField C.idiskMetavg [t| NonEmptyString |]
357
  , optionalField $ simpleField C.idiskName   [t| NonEmptyString |]
358
  , optionalField $ simpleField C.idiskProvider [t| NonEmptyString |]
359
  , optionalField $ simpleField C.idiskAccess   [t| NonEmptyString |]
360
  , andRestArguments "opaque"
361
  ])
362

    
363
-- | Disk snapshot definition.
364
$(buildObject "ISnapParams" "idisk"
365
  [ simpleField C.idiskSnapshotName [t| NonEmptyString |]])
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
    deriving (Eq, Show)
420

    
421
-- | Custom deserialiser for 'SetParamsMods'.
422
readSetParams :: (JSON a) => JSValue -> Text.JSON.Result (SetParamsMods a)
423
readSetParams (JSArray []) = return SetParamsEmpty
424
readSetParams v =
425
  case readJSON v::Text.JSON.Result [(DdmOldChanges, JSValue)] of
426
    Text.JSON.Ok _ -> liftM SetParamsDeprecated $ readJSON v
427
    _ -> liftM SetParamsNew $ readJSON v
428

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

    
435
-- | Instance snapshot params
436
data SetSnapParams a
437
  = SetSnapParamsEmpty
438
  | SetSnapParamsValid (NonEmpty (Int, a))
439
    deriving (Eq, Show)
440

    
441
readSetSnapParams :: (JSON a) => JSValue -> Text.JSON.Result (SetSnapParams a)
442
readSetSnapParams (JSArray []) = return SetSnapParamsEmpty
443
readSetSnapParams v =
444
  case readJSON v::Text.JSON.Result [(Int, JSValue)] of
445
    Text.JSON.Ok _ -> liftM SetSnapParamsValid $ readJSON v
446
    _ -> fail "Cannot parse snapshot params."
447

    
448
instance (JSON a) => JSON (SetSnapParams a) where
449
  showJSON SetSnapParamsEmpty = showJSON ()
450
  showJSON (SetSnapParamsValid v) = showJSON v
451
  readJSON = readSetSnapParams
452

    
453
-- | Custom type for target_node parameter of OpBackupExport, which
454
-- varies depending on mode. FIXME: this uses an [JSValue] since
455
-- we don't care about individual rows (just like the Python code
456
-- tests). But the proper type could be parsed if we wanted.
457
data ExportTarget = ExportTargetLocal NonEmptyString
458
                  | ExportTargetRemote [JSValue]
459
                    deriving (Eq, Show)
460

    
461
-- | Custom reader for 'ExportTarget'.
462
readExportTarget :: JSValue -> Text.JSON.Result ExportTarget
463
readExportTarget (JSString s) = liftM ExportTargetLocal $
464
                                mkNonEmpty (fromJSString s)
465
readExportTarget (JSArray arr) = return $ ExportTargetRemote arr
466
readExportTarget v = fail $ "Invalid value received for 'target_node': " ++
467
                     show (pp_value v)
468

    
469
instance JSON ExportTarget where
470
  showJSON (ExportTargetLocal s)  = showJSON s
471
  showJSON (ExportTargetRemote l) = showJSON l
472
  readJSON = readExportTarget
473

    
474
-- * Common opcode parameters
475

    
476
pDryRun :: Field
477
pDryRun =
478
  withDoc "Run checks only, don't execute" .
479
  optionalField $ booleanField "dry_run"
480

    
481
pDebugLevel :: Field
482
pDebugLevel =
483
  withDoc "Debug level" .
484
  optionalField $ simpleField "debug_level" [t| NonNegative Int |]
485

    
486
pOpPriority :: Field
487
pOpPriority =
488
  withDoc "Opcode priority. Note: python uses a separate constant,\
489
          \ we're using the actual value we know it's the default" .
490
  defaultField [| OpPrioNormal |] $
491
  simpleField "priority" [t| OpSubmitPriority |]
492

    
493
pDependencies :: Field
494
pDependencies =
495
  withDoc "Job dependencies" .
496
  optionalNullSerField $ simpleField "depends" [t| [JobDependency] |]
497

    
498
pComment :: Field
499
pComment =
500
  withDoc "Comment field" .
501
  optionalNullSerField $ stringField "comment"
502

    
503
pReason :: Field
504
pReason =
505
  withDoc "Reason trail field" $
506
  simpleField C.opcodeReason [t| ReasonTrail |]
507

    
508
pSequential :: Field
509
pSequential =
510
  withDoc "Sequential job execution" $
511
  defaultFalse C.opcodeSequential
512

    
513
-- * Parameters
514

    
515
pDebugSimulateErrors :: Field
516
pDebugSimulateErrors =
517
  withDoc "Whether to simulate errors (useful for debugging)" $
518
  defaultFalse "debug_simulate_errors"
519

    
520
pErrorCodes :: Field
521
pErrorCodes = 
522
  withDoc "Error codes" $
523
  defaultFalse "error_codes"
524

    
525
pSkipChecks :: Field
526
pSkipChecks = 
527
  withDoc "Which checks to skip" .
528
  defaultField [| emptyListSet |] $
529
  simpleField "skip_checks" [t| ListSet VerifyOptionalChecks |]
530

    
531
pIgnoreErrors :: Field
532
pIgnoreErrors =
533
  withDoc "List of error codes that should be treated as warnings" .
534
  defaultField [| emptyListSet |] $
535
  simpleField "ignore_errors" [t| ListSet CVErrorCode |]
536

    
537
pVerbose :: Field
538
pVerbose =
539
  withDoc "Verbose mode" $
540
  defaultFalse "verbose"
541

    
542
pOptGroupName :: Field
543
pOptGroupName =
544
  withDoc "Optional group name" .
545
  renameField "OptGroupName" .
546
  optionalField $ simpleField "group_name" [t| NonEmptyString |]
547

    
548
pGroupName :: Field
549
pGroupName =
550
  withDoc "Group name" $
551
  simpleField "group_name" [t| NonEmptyString |]
552

    
553
-- | Whether to hotplug device.
554
pHotplug :: Field
555
pHotplug = defaultFalse "hotplug"
556

    
557
pHotplugIfPossible :: Field
558
pHotplugIfPossible = defaultFalse "hotplug_if_possible"
559

    
560
pInstances :: Field
561
pInstances =
562
  withDoc "List of instances" .
563
  defaultField [| [] |] $
564
  simpleField "instances" [t| [NonEmptyString] |]
565

    
566
-- | Whether to remove disks.
567
pKeepDisks :: Field
568
pKeepDisks = defaultFalse "keep_disks"
569

    
570
pOutputFields :: Field
571
pOutputFields =
572
  withDoc "Selected output fields" $
573
  simpleField "output_fields" [t| [NonEmptyString] |]
574

    
575
pName :: Field
576
pName =
577
  withDoc "A generic name" $
578
  simpleField "name" [t| NonEmptyString |]
579

    
580
-- | List of instance snaps.
581
pInstSnaps :: Field
582
pInstSnaps =
583
  renameField "instSnaps" $
584
  simpleField "disks" [t| SetSnapParams ISnapParams |]
585

    
586
pForce :: Field
587
pForce =
588
  withDoc "Whether to force the operation" $
589
  defaultFalse "force"
590

    
591
pHvState :: Field
592
pHvState =
593
  withDoc "Set hypervisor states" .
594
  optionalField $ simpleField "hv_state" [t| JSObject JSValue |]
595

    
596
pDiskState :: Field
597
pDiskState =
598
  withDoc "Set disk states" .
599
  optionalField $ simpleField "disk_state" [t| JSObject JSValue |]
600

    
601
-- | Cluster-wide default directory for storing file-backed disks.
602
pClusterFileStorageDir :: Field
603
pClusterFileStorageDir =
604
  renameField "ClusterFileStorageDir" $
605
  optionalStringField "file_storage_dir"
606

    
607
-- | Cluster-wide default directory for storing shared-file-backed disks.
608
pClusterSharedFileStorageDir :: Field
609
pClusterSharedFileStorageDir =
610
  renameField "ClusterSharedFileStorageDir" $
611
  optionalStringField "shared_file_storage_dir"
612

    
613
-- | Volume group name.
614
pVgName :: Field
615
pVgName =
616
  withDoc "Volume group name" $
617
  optionalStringField "vg_name"
618

    
619
pEnabledHypervisors :: Field
620
pEnabledHypervisors =
621
  withDoc "List of enabled hypervisors" .
622
  optionalField $
623
  simpleField "enabled_hypervisors" [t| [Hypervisor] |]
624

    
625
pClusterHvParams :: Field
626
pClusterHvParams =
627
  withDoc "Cluster-wide hypervisor parameters, hypervisor-dependent" .
628
  renameField "ClusterHvParams" .
629
  optionalField $
630
  simpleField "hvparams" [t| GenericContainer String (JSObject JSValue) |]
631

    
632
pClusterBeParams :: Field
633
pClusterBeParams =
634
  withDoc "Cluster-wide backend parameter defaults" .
635
  renameField "ClusterBeParams" .
636
  optionalField $ simpleField "beparams" [t| JSObject JSValue |]
637

    
638
pOsHvp :: Field
639
pOsHvp =
640
  withDoc "Cluster-wide per-OS hypervisor parameter defaults" .
641
  optionalField $
642
  simpleField "os_hvp" [t| GenericContainer String (JSObject JSValue) |]
643

    
644
pClusterOsParams :: Field
645
pClusterOsParams =
646
  withDoc "Cluster-wide OS parameter defaults" .
647
  renameField "ClusterOsParams" .
648
  optionalField $
649
  simpleField "osparams" [t| GenericContainer String (JSObject JSValue) |]
650

    
651
pGroupDiskParams :: Field
652
pGroupDiskParams =
653
  withDoc "Disk templates' parameter defaults" .
654
  optionalField $
655
  simpleField "diskparams"
656
              [t| GenericContainer DiskTemplate (JSObject JSValue) |]
657

    
658
pCandidatePoolSize :: Field
659
pCandidatePoolSize =
660
  withDoc "Master candidate pool size" .
661
  optionalField $ simpleField "candidate_pool_size" [t| Positive Int |]
662

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
876
pNdParams :: Field
877
pNdParams =
878
  withDoc "Node parameters" .
879
  renameField "genericNdParams" .
880
  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
881
  
882
pNames :: Field
883
pNames =
884
  withDoc "List of names" .
885
  defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
886

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

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

    
896
pStorageTypeOptional :: Field
897
pStorageTypeOptional =
898
  withDoc "Storage type" .
899
  renameField "StorageTypeOptional" .
900
  optionalField $ simpleField "storage_type" [t| StorageType |]
901

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

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

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

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

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

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

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

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

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

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

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

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

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

    
971
pIgnoreIpolicy :: Field
972
pIgnoreIpolicy =
973
  withDoc "Whether to ignore ipolicy violations" $
974
  defaultFalse "ignore_ipolicy"
975
  
976
pIallocator :: Field
977
pIallocator =
978
  withDoc "Iallocator for deciding the target node for shared-storage\
979
          \ instances" $
980
  optionalNEStringField "iallocator"
981

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
1104
pPrimaryNode :: Field
1105
pPrimaryNode =
1106
  withDoc "Primary node for an instance" $
1107
  optionalNEStringField "pnode"
1108

    
1109
pPrimaryNodeUuid :: Field
1110
pPrimaryNodeUuid =
1111
  withDoc "Primary node UUID for an instance" $
1112
  optionalNEStringField "pnode_uuid"
1113

    
1114
pSecondaryNode :: Field
1115
pSecondaryNode =
1116
  withDoc "Secondary node for an instance" $
1117
  optionalNEStringField "snode"
1118

    
1119
pSecondaryNodeUuid :: Field
1120
pSecondaryNodeUuid =
1121
  withDoc "Secondary node UUID for an instance" $
1122
  optionalNEStringField "snode_uuid"
1123

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

    
1129
pSourceInstance :: Field
1130
pSourceInstance =
1131
  withDoc "Source instance name (remote import only)" $
1132
  optionalNEStringField "source_instance_name"
1133

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

    
1142
pSourceX509Ca :: Field
1143
pSourceX509Ca =
1144
  withDoc "Source X509 CA in PEM format (remote import only)" $
1145
  optionalNEStringField "source_x509_ca"
1146

    
1147
pSrcNode :: Field
1148
pSrcNode =
1149
  withDoc "Source node for import" $
1150
  optionalNEStringField "src_node"
1151

    
1152
pSrcNodeUuid :: Field
1153
pSrcNodeUuid =
1154
  withDoc "Source node UUID for import" $
1155
  optionalNEStringField "src_node_uuid"
1156

    
1157
pSrcPath :: Field
1158
pSrcPath =
1159
  withDoc "Source directory for import" $
1160
  optionalNEStringField "src_path"
1161

    
1162
pStartInstance :: Field
1163
pStartInstance =
1164
  withDoc "Whether to start instance after creation" $
1165
  defaultTrue "start"
1166

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

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

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

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

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

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

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

    
1217
pIgnoreFailures :: Field
1218
pIgnoreFailures =
1219
  withDoc "Whether to ignore failures during removal" $
1220
  defaultFalse "ignore_failures"
1221

    
1222
pNewName :: Field
1223
pNewName =
1224
  withDoc "New group or instance name" $
1225
  simpleField "new_name" [t| NonEmptyString |]
1226
  
1227
pIgnoreOfflineNodes :: Field
1228
pIgnoreOfflineNodes =
1229
  withDoc "Whether to ignore offline nodes" $
1230
  defaultFalse "ignore_offline_nodes"
1231

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

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

    
1246
pNoRemember :: Field
1247
pNoRemember =
1248
  withDoc "Do not remember instance state changes" $
1249
  defaultFalse "no_remember"
1250

    
1251
pStartupPaused :: Field
1252
pStartupPaused =
1253
  withDoc "Pause instance at startup" $
1254
  defaultFalse "startup_paused"
1255

    
1256
pIgnoreSecondaries :: Field
1257
pIgnoreSecondaries =
1258
  withDoc "Whether to start the instance even if secondary disks are failing" $
1259
  defaultFalse "ignore_secondaries"
1260

    
1261
pRebootType :: Field
1262
pRebootType =
1263
  withDoc "How to reboot the instance" $
1264
  simpleField "reboot_type" [t| RebootType |]
1265

    
1266
pReplaceDisksMode :: Field
1267
pReplaceDisksMode =
1268
  withDoc "Replacement mode" .
1269
  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1270

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

    
1278
pMigrationCleanup :: Field
1279
pMigrationCleanup =
1280
  withDoc "Whether a previously failed migration should be cleaned up" .
1281
  renameField "MigrationCleanup" $ defaultFalse "cleanup"
1282

    
1283
pAllowFailover :: Field
1284
pAllowFailover =
1285
  withDoc "Whether we can fallback to failover if migration is not possible" $
1286
  defaultFalse "allow_failover"
1287

    
1288
pForceFailover :: Field
1289
pForceFailover =
1290
  withDoc "Disallow migration moves and always use failovers" $
1291
  defaultFalse "force_failover"
1292

    
1293
pMoveTargetNode :: Field
1294
pMoveTargetNode =
1295
  withDoc "Target node for instance move" .
1296
  renameField "MoveTargetNode" $
1297
  simpleField "target_node" [t| NonEmptyString |]
1298

    
1299
pMoveTargetNodeUuid :: Field
1300
pMoveTargetNodeUuid =
1301
  withDoc "Target node UUID for instance move" .
1302
  renameField "MoveTargetNodeUuid" . optionalField $
1303
  simpleField "target_node_uuid" [t| NonEmptyString |]
1304

    
1305
pIgnoreDiskSize :: Field
1306
pIgnoreDiskSize =
1307
  withDoc "Whether to ignore recorded disk size" $
1308
  defaultFalse "ignore_size"
1309
  
1310
pWaitForSyncFalse :: Field
1311
pWaitForSyncFalse =
1312
  withDoc "Whether to wait for the disk to synchronize (defaults to false)" $
1313
  defaultField [| False |] pWaitForSync
1314
  
1315
pRecreateDisksInfo :: Field
1316
pRecreateDisksInfo =
1317
  withDoc "Disk list for recreate disks" .
1318
  renameField "RecreateDisksInfo" .
1319
  defaultField [| RecreateDisksAll |] $
1320
  simpleField "disks" [t| RecreateDisksInfo |]
1321

    
1322
pStatic :: Field
1323
pStatic =
1324
  withDoc "Whether to only return configuration data without querying nodes" $
1325
  defaultFalse "static"
1326

    
1327
pInstParamsNicChanges :: Field
1328
pInstParamsNicChanges =
1329
  withDoc "List of NIC changes" .
1330
  renameField "InstNicChanges" .
1331
  defaultField [| SetParamsEmpty |] $
1332
  simpleField "nics" [t| SetParamsMods INicParams |]
1333

    
1334
pInstParamsDiskChanges :: Field
1335
pInstParamsDiskChanges =
1336
  withDoc "List of disk changes" .
1337
  renameField "InstDiskChanges" .
1338
  defaultField [| SetParamsEmpty |] $
1339
  simpleField "disks" [t| SetParamsMods IDiskParams |]
1340

    
1341
pRuntimeMem :: Field
1342
pRuntimeMem =
1343
  withDoc "New runtime memory" .
1344
  optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1345

    
1346
pOptDiskTemplate :: Field
1347
pOptDiskTemplate =
1348
  withDoc "Instance disk template" .
1349
  optionalField .
1350
  renameField "OptDiskTemplate" $
1351
  simpleField "disk_template" [t| DiskTemplate |]
1352

    
1353
pOsNameChange :: Field
1354
pOsNameChange =
1355
  withDoc "Change the instance's OS without reinstalling the instance" $
1356
  optionalNEStringField "os_name"
1357

    
1358
pDiskIndex :: Field
1359
pDiskIndex =
1360
  withDoc "Disk index for e.g. grow disk" .
1361
  renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
1362

    
1363
pDiskChgAmount :: Field
1364
pDiskChgAmount =
1365
  withDoc "Disk amount to add or grow to" .
1366
  renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
1367

    
1368
pDiskChgAbsolute :: Field
1369
pDiskChgAbsolute =
1370
  withDoc
1371
    "Whether the amount parameter is an absolute target or a relative one" .
1372
  renameField "DiskChkAbsolute" $ defaultFalse "absolute"
1373

    
1374
pTargetGroups :: Field
1375
pTargetGroups =
1376
  withDoc
1377
    "Destination group names or UUIDs (defaults to \"all but current group\")" .
1378
  optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
1379

    
1380
pNodeGroupAllocPolicy :: Field
1381
pNodeGroupAllocPolicy =
1382
  withDoc "Instance allocation policy" .
1383
  optionalField $
1384
  simpleField "alloc_policy" [t| AllocPolicy |]
1385

    
1386
pGroupNodeParams :: Field
1387
pGroupNodeParams =
1388
  withDoc "Default node parameters for group" .
1389
  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
1390

    
1391
pExportMode :: Field
1392
pExportMode =
1393
  withDoc "Export mode" .
1394
  renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1395

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

    
1404
pExportTargetNodeUuid :: Field
1405
pExportTargetNodeUuid =
1406
  withDoc "Target node UUID (if local export)" .
1407
  renameField "ExportTargetNodeUuid" . optionalField $
1408
  simpleField "target_node_uuid" [t| NonEmptyString |]
1409

    
1410
pShutdownInstance :: Field
1411
pShutdownInstance =
1412
  withDoc "Whether to shutdown the instance before export" $
1413
  defaultTrue "shutdown"
1414

    
1415
pRemoveInstance :: Field
1416
pRemoveInstance =
1417
  withDoc "Whether to remove instance after export" $
1418
  defaultFalse "remove_instance"
1419

    
1420
pIgnoreRemoveFailures :: Field
1421
pIgnoreRemoveFailures =
1422
  withDoc "Whether to ignore failures while removing instances" $
1423
  defaultFalse "ignore_remove_failures"
1424

    
1425
pX509KeyName :: Field
1426
pX509KeyName =
1427
  withDoc "Name of X509 key (remote export only)" .
1428
  optionalField $ simpleField "x509_key_name" [t| [JSValue] |]
1429

    
1430
pX509DestCA :: Field
1431
pX509DestCA =
1432
  withDoc "Destination X509 CA (remote export only)" $
1433
  optionalNEStringField "destination_x509_ca"
1434

    
1435
pTagsObject :: Field
1436
pTagsObject =
1437
  withDoc "Tag kind" $
1438
  simpleField "kind" [t| TagKind |]
1439

    
1440
pTagsName :: Field
1441
pTagsName =
1442
  withDoc "Name of object" .
1443
  renameField "TagsGetName" .
1444
  optionalField $ simpleField "name" [t| String |]
1445

    
1446
pTagsList :: Field
1447
pTagsList =
1448
  withDoc "List of tag names" $
1449
  simpleField "tags" [t| [String] |]
1450

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

    
1458
pDelayDuration :: Field
1459
pDelayDuration =
1460
  withDoc "Duration parameter for 'OpTestDelay'" .
1461
  renameField "DelayDuration" $
1462
  simpleField "duration" [t| Double |]
1463

    
1464
pDelayOnMaster :: Field
1465
pDelayOnMaster =
1466
  withDoc "on_master field for 'OpTestDelay'" .
1467
  renameField "DelayOnMaster" $
1468
  defaultTrue "on_master"
1469

    
1470
pDelayOnNodes :: Field
1471
pDelayOnNodes =
1472
  withDoc "on_nodes field for 'OpTestDelay'" .
1473
  renameField "DelayOnNodes" .
1474
  defaultField [| [] |] $
1475
  simpleField "on_nodes" [t| [NonEmptyString] |]
1476

    
1477
pDelayOnNodeUuids :: Field
1478
pDelayOnNodeUuids =
1479
  withDoc "on_node_uuids field for 'OpTestDelay'" .
1480
  renameField "DelayOnNodeUuids" . optionalField $
1481
  simpleField "on_node_uuids" [t| [NonEmptyString] |]
1482

    
1483
pDelayRepeat :: Field
1484
pDelayRepeat =
1485
  withDoc "Repeat parameter for OpTestDelay" .
1486
  renameField "DelayRepeat" .
1487
  defaultField [| forceNonNeg (0::Int) |] $
1488
  simpleField "repeat" [t| NonNegative Int |]
1489

    
1490
pDelayNoLocks :: Field
1491
pDelayNoLocks =
1492
  withDoc "Don't take locks during the delay" .
1493
  renameField "DelayNoLocks" $
1494
  defaultTrue "no_locks"
1495

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

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

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

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

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

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

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

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

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

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

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

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

    
1572
pJQueueNotifyWaitLock :: Field
1573
pJQueueNotifyWaitLock =
1574
  withDoc "'OpTestJqueue' notify_waitlock" $
1575
  defaultFalse "notify_waitlock"
1576

    
1577
pJQueueNotifyExec :: Field
1578
pJQueueNotifyExec =
1579
  withDoc "'OpTestJQueue' notify_exec" $
1580
  defaultFalse "notify_exec"
1581

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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