Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ 593fd115

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

    
258
import Control.Monad (liftM)
259
import Text.JSON (JSON, JSValue(..), JSObject (..), readJSON, showJSON,
260
                  fromJSString, toJSObject)
261
import qualified Text.JSON
262
import Text.JSON.Pretty (pp_value)
263

    
264
import Ganeti.BasicTypes
265
import qualified Ganeti.Constants as C
266
import Ganeti.THH
267
import Ganeti.JSON
268
import Ganeti.Types
269
import qualified Ganeti.Query.Language as Qlang
270

    
271
-- * Helper functions and types
272

    
273
-- | Build a boolean field.
274
booleanField :: String -> Field
275
booleanField = flip simpleField [t| Bool |]
276

    
277
-- | Default a field to 'False'.
278
defaultFalse :: String -> Field
279
defaultFalse = defaultField [| False |] . booleanField
280

    
281
-- | Default a field to 'True'.
282
defaultTrue :: String -> Field
283
defaultTrue = defaultField [| True |] . booleanField
284

    
285
-- | An alias for a 'String' field.
286
stringField :: String -> Field
287
stringField = flip simpleField [t| String |]
288

    
289
-- | An alias for an optional string field.
290
optionalStringField :: String -> Field
291
optionalStringField = optionalField . stringField
292

    
293
-- | An alias for an optional non-empty string field.
294
optionalNEStringField :: String -> Field
295
optionalNEStringField = optionalField . flip simpleField [t| NonEmptyString |]
296

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

    
306
-- ** Disks
307

    
308
-- | Disk index type (embedding constraints on the index value via a
309
-- smart constructor).
310
newtype DiskIndex = DiskIndex { unDiskIndex :: Int }
311
  deriving (Show, Eq, Ord)
312

    
313
-- | Smart constructor for 'DiskIndex'.
314
mkDiskIndex :: (Monad m) => Int -> m DiskIndex
315
mkDiskIndex i | i >= 0 && i < C.maxDisks = return (DiskIndex i)
316
              | otherwise = fail $ "Invalid value for disk index '" ++
317
                            show i ++ "', required between 0 and " ++
318
                            show C.maxDisks
319

    
320
instance JSON DiskIndex where
321
  readJSON v = readJSON v >>= mkDiskIndex
322
  showJSON = showJSON . unDiskIndex
323

    
324
-- ** I* param types
325

    
326
-- | Type holding disk access modes.
327
$(declareSADT "DiskAccess"
328
  [ ("DiskReadOnly",  'C.diskRdonly)
329
  , ("DiskReadWrite", 'C.diskRdwr)
330
  ])
331
$(makeJSONInstance ''DiskAccess)
332

    
333
-- | NIC modification definition.
334
$(buildObject "INicParams" "inic"
335
  [ optionalField $ simpleField C.inicMac    [t| NonEmptyString |]
336
  , optionalField $ simpleField C.inicIp     [t| String         |]
337
  , optionalField $ simpleField C.inicMode   [t| NonEmptyString |]
338
  , optionalField $ simpleField C.inicLink   [t| NonEmptyString |]
339
  , optionalField $ simpleField C.inicName   [t| NonEmptyString |]
340
  , optionalField $ simpleField C.inicVlan   [t| NonEmptyString |]
341
  , optionalField $ simpleField C.inicBridge [t| NonEmptyString |]
342
  ])
343

    
344
-- | Disk modification definition. FIXME: disksize should be VTYPE_UNIT.
345
$(buildObject "IDiskParams" "idisk"
346
  [ optionalField $ simpleField C.idiskSize   [t| Int            |]
347
  , optionalField $ simpleField C.idiskMode   [t| DiskAccess     |]
348
  , optionalField $ simpleField C.idiskAdopt  [t| NonEmptyString |]
349
  , optionalField $ simpleField C.idiskVg     [t| NonEmptyString |]
350
  , optionalField $ simpleField C.idiskMetavg [t| NonEmptyString |]
351
  , optionalField $ simpleField C.idiskName   [t| NonEmptyString |]
352
  ])
353

    
354
-- | Disk changes type for OpInstanceRecreateDisks. This is a bit
355
-- strange, because the type in Python is something like Either
356
-- [DiskIndex] [DiskChanges], but we can't represent the type of an
357
-- empty list in JSON, so we have to add a custom case for the empty
358
-- list.
359
data RecreateDisksInfo
360
  = RecreateDisksAll
361
  | RecreateDisksIndices (NonEmpty DiskIndex)
362
  | RecreateDisksParams (NonEmpty (DiskIndex, IDiskParams))
363
    deriving (Eq, Show)
364

    
365
readRecreateDisks :: JSValue -> Text.JSON.Result RecreateDisksInfo
366
readRecreateDisks (JSArray []) = return RecreateDisksAll
367
readRecreateDisks v =
368
  case readJSON v::Text.JSON.Result [DiskIndex] of
369
    Text.JSON.Ok indices -> liftM RecreateDisksIndices (mkNonEmpty indices)
370
    _ -> case readJSON v::Text.JSON.Result [(DiskIndex, IDiskParams)] of
371
           Text.JSON.Ok params -> liftM RecreateDisksParams (mkNonEmpty params)
372
           _ -> fail $ "Can't parse disk information as either list of disk"
373
                ++ " indices or list of disk parameters; value received:"
374
                ++ show (pp_value v)
375

    
376
instance JSON RecreateDisksInfo where
377
  readJSON = readRecreateDisks
378
  showJSON  RecreateDisksAll            = showJSON ()
379
  showJSON (RecreateDisksIndices idx)   = showJSON idx
380
  showJSON (RecreateDisksParams params) = showJSON params
381

    
382
-- | Simple type for old-style ddm changes.
383
data DdmOldChanges = DdmOldIndex (NonNegative Int)
384
                   | DdmOldMod DdmSimple
385
                     deriving (Eq, Show)
386

    
387
readDdmOldChanges :: JSValue -> Text.JSON.Result DdmOldChanges
388
readDdmOldChanges v =
389
  case readJSON v::Text.JSON.Result (NonNegative Int) of
390
    Text.JSON.Ok nn -> return $ DdmOldIndex nn
391
    _ -> case readJSON v::Text.JSON.Result DdmSimple of
392
           Text.JSON.Ok ddms -> return $ DdmOldMod ddms
393
           _ -> fail $ "Can't parse value '" ++ show (pp_value v) ++ "' as"
394
                ++ " either index or modification"
395

    
396
instance JSON DdmOldChanges where
397
  showJSON (DdmOldIndex i) = showJSON i
398
  showJSON (DdmOldMod m)   = showJSON m
399
  readJSON = readDdmOldChanges
400

    
401
-- | Instance disk or nic modifications.
402
data SetParamsMods a
403
  = SetParamsEmpty
404
  | SetParamsDeprecated (NonEmpty (DdmOldChanges, a))
405
  | SetParamsNew (NonEmpty (DdmFull, Int, a))
406
    deriving (Eq, Show)
407

    
408
-- | Custom deserialiser for 'SetParamsMods'.
409
readSetParams :: (JSON a) => JSValue -> Text.JSON.Result (SetParamsMods a)
410
readSetParams (JSArray []) = return SetParamsEmpty
411
readSetParams v =
412
  case readJSON v::Text.JSON.Result [(DdmOldChanges, JSValue)] of
413
    Text.JSON.Ok _ -> liftM SetParamsDeprecated $ readJSON v
414
    _ -> liftM SetParamsNew $ readJSON v
415

    
416
instance (JSON a) => JSON (SetParamsMods a) where
417
  showJSON SetParamsEmpty = showJSON ()
418
  showJSON (SetParamsDeprecated v) = showJSON v
419
  showJSON (SetParamsNew v) = showJSON v
420
  readJSON = readSetParams
421

    
422
-- | Custom type for target_node parameter of OpBackupExport, which
423
-- varies depending on mode. FIXME: this uses an [JSValue] since
424
-- we don't care about individual rows (just like the Python code
425
-- tests). But the proper type could be parsed if we wanted.
426
data ExportTarget = ExportTargetLocal NonEmptyString
427
                  | ExportTargetRemote [JSValue]
428
                    deriving (Eq, Show)
429

    
430
-- | Custom reader for 'ExportTarget'.
431
readExportTarget :: JSValue -> Text.JSON.Result ExportTarget
432
readExportTarget (JSString s) = liftM ExportTargetLocal $
433
                                mkNonEmpty (fromJSString s)
434
readExportTarget (JSArray arr) = return $ ExportTargetRemote arr
435
readExportTarget v = fail $ "Invalid value received for 'target_node': " ++
436
                     show (pp_value v)
437

    
438
instance JSON ExportTarget where
439
  showJSON (ExportTargetLocal s)  = showJSON s
440
  showJSON (ExportTargetRemote l) = showJSON l
441
  readJSON = readExportTarget
442

    
443
-- * Common opcode parameters
444

    
445
pDryRun :: Field
446
pDryRun =
447
  withDoc "Run checks only, don't execute" .
448
  optionalField $ booleanField "dry_run"
449

    
450
pDebugLevel :: Field
451
pDebugLevel =
452
  withDoc "Debug level" .
453
  optionalField $ simpleField "debug_level" [t| NonNegative Int |]
454

    
455
pOpPriority :: Field
456
pOpPriority =
457
  withDoc "Opcode priority. Note: python uses a separate constant,\
458
          \ we're using the actual value we know it's the default" .
459
  defaultField [| OpPrioNormal |] $
460
  simpleField "priority" [t| OpSubmitPriority |]
461

    
462
pDependencies :: Field
463
pDependencies =
464
  withDoc "Job dependencies" .
465
  optionalNullSerField $ simpleField "depends" [t| [JobDependency] |]
466

    
467
pComment :: Field
468
pComment =
469
  withDoc "Comment field" .
470
  optionalNullSerField $ stringField "comment"
471

    
472
pReason :: Field
473
pReason =
474
  withDoc "Reason trail field" $
475
  simpleField C.opcodeReason [t| ReasonTrail |]
476

    
477
pSequential :: Field
478
pSequential =
479
  withDoc "Sequential job execution" $
480
  defaultFalse C.opcodeSequential
481

    
482
-- * Parameters
483

    
484
pDebugSimulateErrors :: Field
485
pDebugSimulateErrors =
486
  withDoc "Whether to simulate errors (useful for debugging)" $
487
  defaultFalse "debug_simulate_errors"
488

    
489
pErrorCodes :: Field
490
pErrorCodes = 
491
  withDoc "Error codes" $
492
  defaultFalse "error_codes"
493

    
494
pSkipChecks :: Field
495
pSkipChecks = 
496
  withDoc "Which checks to skip" .
497
  defaultField [| emptyListSet |] $
498
  simpleField "skip_checks" [t| ListSet VerifyOptionalChecks |]
499

    
500
pIgnoreErrors :: Field
501
pIgnoreErrors =
502
  withDoc "List of error codes that should be treated as warnings" .
503
  defaultField [| emptyListSet |] $
504
  simpleField "ignore_errors" [t| ListSet CVErrorCode |]
505

    
506
pVerbose :: Field
507
pVerbose =
508
  withDoc "Verbose mode" $
509
  defaultFalse "verbose"
510

    
511
pOptGroupName :: Field
512
pOptGroupName =
513
  withDoc "Optional group name" .
514
  renameField "OptGroupName" .
515
  optionalField $ simpleField "group_name" [t| NonEmptyString |]
516

    
517
pGroupName :: Field
518
pGroupName =
519
  withDoc "Group name" $
520
  simpleField "group_name" [t| NonEmptyString |]
521

    
522
-- | Whether to hotplug device.
523
pHotplug :: Field
524
pHotplug = defaultFalse "hotplug"
525

    
526
pHotplugIfPossible :: Field
527
pHotplugIfPossible = defaultFalse "hotplug_if_possible"
528

    
529
pInstances :: Field
530
pInstances =
531
  withDoc "List of instances" .
532
  defaultField [| [] |] $
533
  simpleField "instances" [t| [NonEmptyString] |]
534

    
535
pOutputFields :: Field
536
pOutputFields =
537
  withDoc "Selected output fields" $
538
  simpleField "output_fields" [t| [NonEmptyString] |]
539

    
540
pName :: Field
541
pName =
542
  withDoc "A generic name" $
543
  simpleField "name" [t| NonEmptyString |]
544

    
545
pForce :: Field
546
pForce =
547
  withDoc "Whether to force the operation" $
548
  defaultFalse "force"
549

    
550
pHvState :: Field
551
pHvState =
552
  withDoc "Set hypervisor states" .
553
  optionalField $ simpleField "hv_state" [t| JSObject JSValue |]
554

    
555
pDiskState :: Field
556
pDiskState =
557
  withDoc "Set disk states" .
558
  optionalField $ simpleField "disk_state" [t| JSObject JSValue |]
559

    
560
-- | Cluster-wide default directory for storing file-backed disks.
561
pClusterFileStorageDir :: Field
562
pClusterFileStorageDir =
563
  renameField "ClusterFileStorageDir" $
564
  optionalStringField "file_storage_dir"
565

    
566
-- | Cluster-wide default directory for storing shared-file-backed disks.
567
pClusterSharedFileStorageDir :: Field
568
pClusterSharedFileStorageDir =
569
  renameField "ClusterSharedFileStorageDir" $
570
  optionalStringField "shared_file_storage_dir"
571

    
572
-- | Volume group name.
573
pVgName :: Field
574
pVgName =
575
  withDoc "Volume group name" $
576
  optionalStringField "vg_name"
577

    
578
pEnabledHypervisors :: Field
579
pEnabledHypervisors =
580
  withDoc "List of enabled hypervisors" .
581
  optionalField $
582
  simpleField "enabled_hypervisors" [t| [Hypervisor] |]
583

    
584
pClusterHvParams :: Field
585
pClusterHvParams =
586
  withDoc "Cluster-wide hypervisor parameters, hypervisor-dependent" .
587
  renameField "ClusterHvParams" .
588
  optionalField $
589
  simpleField "hvparams" [t| GenericContainer String (JSObject JSValue) |]
590

    
591
pClusterBeParams :: Field
592
pClusterBeParams =
593
  withDoc "Cluster-wide backend parameter defaults" .
594
  renameField "ClusterBeParams" .
595
  optionalField $ simpleField "beparams" [t| JSObject JSValue |]
596

    
597
pOsHvp :: Field
598
pOsHvp =
599
  withDoc "Cluster-wide per-OS hypervisor parameter defaults" .
600
  optionalField $
601
  simpleField "os_hvp" [t| GenericContainer String (JSObject JSValue) |]
602

    
603
pClusterOsParams :: Field
604
pClusterOsParams =
605
  withDoc "Cluster-wide OS parameter defaults" .
606
  renameField "ClusterOsParams" .
607
  optionalField $
608
  simpleField "osparams" [t| GenericContainer String (JSObject JSValue) |]
609

    
610
pDiskParams :: Field
611
pDiskParams =
612
  withDoc "Disk templates' parameter defaults" .
613
  optionalField $
614
  simpleField "diskparams"
615
              [t| GenericContainer DiskTemplate (JSObject JSValue) |]
616

    
617
pCandidatePoolSize :: Field
618
pCandidatePoolSize =
619
  withDoc "Master candidate pool size" .
620
  optionalField $ simpleField "candidate_pool_size" [t| Positive Int |]
621

    
622
pUidPool :: Field
623
pUidPool =
624
  withDoc "Set UID pool, must be list of lists describing UID ranges\
625
          \ (two items, start and end inclusive)" .
626
  optionalField $ simpleField "uid_pool" [t| [(Int, Int)] |]
627

    
628
pAddUids :: Field
629
pAddUids =
630
  withDoc "Extend UID pool, must be list of lists describing UID\
631
          \ ranges (two items, start and end inclusive)" .
632
  optionalField $ simpleField "add_uids" [t| [(Int, Int)] |]
633

    
634
pRemoveUids :: Field
635
pRemoveUids =
636
  withDoc "Shrink UID pool, must be list of lists describing UID\
637
          \ ranges (two items, start and end inclusive) to be removed" .
638
  optionalField $ simpleField "remove_uids" [t| [(Int, Int)] |]
639

    
640
pMaintainNodeHealth :: Field
641
pMaintainNodeHealth =
642
  withDoc "Whether to automatically maintain node health" .
643
  optionalField $ booleanField "maintain_node_health"
644

    
645
-- | Whether to modify and keep in sync the @/etc/hosts@ files of nodes.
646
pModifyEtcHosts :: Field
647
pModifyEtcHosts = optionalField $ booleanField "modify_etc_hosts"
648

    
649
-- | Whether to wipe disks before allocating them to instances.
650
pPreallocWipeDisks :: Field
651
pPreallocWipeDisks =
652
  withDoc "Whether to wipe disks before allocating them to instances" .
653
  optionalField $ booleanField "prealloc_wipe_disks"
654

    
655
pNicParams :: Field
656
pNicParams =
657
  withDoc "Cluster-wide NIC parameter defaults" .
658
  optionalField $ simpleField "nicparams" [t| INicParams |]
659

    
660
pIpolicy :: Field
661
pIpolicy =
662
  withDoc "Ipolicy specs" .
663
  optionalField $ simpleField "ipolicy" [t| JSObject JSValue |]
664

    
665
pDrbdHelper :: Field
666
pDrbdHelper =
667
  withDoc "DRBD helper program" $
668
  optionalStringField "drbd_helper"
669

    
670
pDefaultIAllocator :: Field
671
pDefaultIAllocator =
672
  withDoc "Default iallocator for cluster" $
673
  optionalStringField "default_iallocator"
674

    
675
pMasterNetdev :: Field
676
pMasterNetdev =
677
  withDoc "Master network device" $
678
  optionalStringField "master_netdev"
679

    
680
pMasterNetmask :: Field
681
pMasterNetmask =
682
  withDoc "Netmask of the master IP" .
683
  optionalField $ simpleField "master_netmask" [t| NonNegative Int |]
684

    
685
pReservedLvs :: Field
686
pReservedLvs =
687
  withDoc "List of reserved LVs" .
688
  optionalField $ simpleField "reserved_lvs" [t| [NonEmptyString] |]
689

    
690
pHiddenOs :: Field
691
pHiddenOs =
692
  withDoc "Modify list of hidden operating systems: each modification\
693
          \ must have two items, the operation and the OS name; the operation\
694
          \ can be add or remove" .
695
  optionalField $ simpleField "hidden_os" [t| [(DdmSimple, NonEmptyString)] |]
696

    
697
pBlacklistedOs :: Field
698
pBlacklistedOs =
699
  withDoc "Modify list of blacklisted operating systems: each\
700
          \ modification must have two items, the operation and the OS name;\
701
          \ the operation can be add or remove" .
702
  optionalField $
703
  simpleField "blacklisted_os" [t| [(DdmSimple, NonEmptyString)] |]
704

    
705
pUseExternalMipScript :: Field
706
pUseExternalMipScript =
707
  withDoc "Whether to use an external master IP address setup script" .
708
  optionalField $ booleanField "use_external_mip_script"
709

    
710
pEnabledDiskTemplates :: Field
711
pEnabledDiskTemplates =
712
  withDoc "List of enabled disk templates" .
713
  optionalField $
714
  simpleField "enabled_disk_templates" [t| [DiskTemplate] |]
715

    
716
pQueryWhat :: Field
717
pQueryWhat =
718
  withDoc "Resource(s) to query for" $
719
  simpleField "what" [t| Qlang.QueryTypeOp |]
720

    
721
pUseLocking :: Field
722
pUseLocking =
723
  withDoc "Whether to use synchronization" $
724
  defaultFalse "use_locking"
725

    
726
pQueryFields :: Field
727
pQueryFields =
728
  withDoc "Requested fields" $
729
  simpleField "fields" [t| [NonEmptyString] |]
730

    
731
pQueryFilter :: Field
732
pQueryFilter =
733
  withDoc "Query filter" .
734
  optionalField $ simpleField "qfilter" [t| [JSValue] |]
735

    
736
pQueryFieldsFields :: Field
737
pQueryFieldsFields =
738
  withDoc "Requested fields; if not given, all are returned" .
739
  renameField "QueryFieldsFields" $
740
  optionalField pQueryFields
741

    
742
pNodeNames :: Field
743
pNodeNames =
744
  withDoc "List of node names to run the OOB command against" .
745
  defaultField [| [] |] $ simpleField "node_names" [t| [NonEmptyString] |]
746

    
747
pNodeUuids :: Field
748
pNodeUuids =
749
  withDoc "List of node UUIDs" .
750
  optionalField $ simpleField "node_uuids" [t| [NonEmptyString] |]
751

    
752
pOobCommand :: Field
753
pOobCommand =
754
  withDoc "OOB command to run" $
755
  simpleField "command" [t| OobCommand |]
756

    
757
pOobTimeout :: Field
758
pOobTimeout =
759
  withDoc "Timeout before the OOB helper will be terminated" .
760
  defaultField [| C.oobTimeout |] $
761
  simpleField "timeout" [t| Int |]
762

    
763
pIgnoreStatus :: Field
764
pIgnoreStatus =
765
  withDoc "Ignores the node offline status for power off" $
766
  defaultFalse "ignore_status"
767

    
768
pPowerDelay :: Field
769
pPowerDelay =
770
  -- FIXME: we can't use the proper type "NonNegative Double", since
771
  -- the default constant is a plain Double, not a non-negative one.
772
  -- And trying to fix the constant introduces a cyclic import.
773
  withDoc "Time in seconds to wait between powering on nodes" .
774
  defaultField [| C.oobPowerDelay |] $
775
  simpleField "power_delay" [t| Double |]
776

    
777
pRequiredNodes :: Field
778
pRequiredNodes =
779
  withDoc "Required list of node names" .
780
  renameField "ReqNodes " $ simpleField "nodes" [t| [NonEmptyString] |]
781

    
782
pRequiredNodeUuids :: Field
783
pRequiredNodeUuids =
784
  withDoc "Required list of node UUIDs" .
785
  renameField "ReqNodeUuids " . optionalField $
786
  simpleField "node_uuids" [t| [NonEmptyString] |]
787

    
788
pRestrictedCommand :: Field
789
pRestrictedCommand =
790
  withDoc "Restricted command name" .
791
  renameField "RestrictedCommand" $
792
  simpleField "command" [t| NonEmptyString |]
793

    
794
pNodeName :: Field
795
pNodeName =
796
  withDoc "A required node name (for single-node LUs)" $
797
  simpleField "node_name" [t| NonEmptyString |]
798

    
799
pNodeUuid :: Field
800
pNodeUuid =
801
  withDoc "A node UUID (for single-node LUs)" .
802
  optionalField $ simpleField "node_uuid" [t| NonEmptyString |]
803

    
804
pPrimaryIp :: Field
805
pPrimaryIp =
806
  withDoc "Primary IP address" .
807
  optionalField $
808
  simpleField "primary_ip" [t| NonEmptyString |]
809

    
810
pSecondaryIp :: Field
811
pSecondaryIp =
812
  withDoc "Secondary IP address" $
813
  optionalNEStringField "secondary_ip"
814

    
815
pReadd :: Field
816
pReadd =
817
  withDoc "Whether node is re-added to cluster" $
818
  defaultFalse "readd"
819

    
820
pNodeGroup :: Field
821
pNodeGroup =
822
  withDoc "Initial node group" $
823
  optionalNEStringField "group"
824

    
825
pMasterCapable :: Field
826
pMasterCapable =
827
  withDoc "Whether node can become master or master candidate" .
828
  optionalField $ booleanField "master_capable"
829

    
830
pVmCapable :: Field
831
pVmCapable =
832
  withDoc "Whether node can host instances" .
833
  optionalField $ booleanField "vm_capable"
834

    
835
pNdParams :: Field
836
pNdParams =
837
  withDoc "Node parameters" .
838
  renameField "genericNdParams" .
839
  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
840
  
841
pNames :: Field
842
pNames =
843
  withDoc "List of names" .
844
  defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
845

    
846
pNodes :: Field
847
pNodes =
848
  withDoc "List of nodes" .
849
  defaultField [| [] |] $ simpleField "nodes" [t| [NonEmptyString] |]
850

    
851
pStorageType :: Field
852
pStorageType =
853
  withDoc "Storage type" $ simpleField "storage_type" [t| StorageType |]
854

    
855
pStorageTypeOptional :: Field
856
pStorageTypeOptional =
857
  withDoc "Storage type" .
858
  renameField "StorageTypeOptional" .
859
  optionalField $ simpleField "storage_type" [t| StorageType |]
860

    
861
pStorageName :: Field
862
pStorageName =
863
  withDoc "Storage name" .
864
  renameField "StorageName" .
865
  optionalField $ simpleField "name" [t| NonEmptyString |]
866

    
867
pStorageChanges :: Field
868
pStorageChanges =
869
  withDoc "Requested storage changes" $
870
  simpleField "changes" [t| JSObject JSValue |]
871

    
872
pIgnoreConsistency :: Field
873
pIgnoreConsistency =
874
  withDoc "Whether to ignore disk consistency" $
875
  defaultFalse "ignore_consistency"
876

    
877
pMasterCandidate :: Field
878
pMasterCandidate =
879
  withDoc "Whether the node should become a master candidate" .
880
  optionalField $ booleanField "master_candidate"
881

    
882
pOffline :: Field
883
pOffline =
884
  withDoc "Whether to mark the node or instance offline" .
885
  optionalField $ booleanField "offline"
886

    
887
pDrained ::Field
888
pDrained =
889
  withDoc "Whether to mark the node as drained" .
890
  optionalField $ booleanField "drained"
891

    
892
pAutoPromote :: Field
893
pAutoPromote =
894
  withDoc "Whether node(s) should be promoted to master candidate if\
895
          \ necessary" $
896
  defaultFalse "auto_promote"
897

    
898
pPowered :: Field
899
pPowered =
900
  withDoc "Whether the node should be marked as powered" .
901
  optionalField $ booleanField "powered"
902

    
903
pMigrationMode :: Field
904
pMigrationMode =
905
  withDoc "Migration type (live/non-live)" .
906
  renameField "MigrationMode" .
907
  optionalField $
908
  simpleField "mode" [t| MigrationMode |]
909

    
910
pMigrationLive :: Field
911
pMigrationLive =
912
  withDoc "Obsolete \'live\' migration mode (do not use)" .
913
  renameField "OldLiveMode" . optionalField $ booleanField "live"
914

    
915
pMigrationTargetNode :: Field
916
pMigrationTargetNode =
917
  withDoc "Target node for instance migration/failover" $
918
  optionalNEStringField "target_node"
919

    
920
pMigrationTargetNodeUuid :: Field
921
pMigrationTargetNodeUuid =
922
  withDoc "Target node UUID for instance migration/failover" $
923
  optionalNEStringField "target_node_uuid"
924

    
925
pAllowRuntimeChgs :: Field
926
pAllowRuntimeChgs =
927
  withDoc "Whether to allow runtime changes while migrating" $
928
  defaultTrue "allow_runtime_changes"
929

    
930
pIgnoreIpolicy :: Field
931
pIgnoreIpolicy =
932
  withDoc "Whether to ignore ipolicy violations" $
933
  defaultFalse "ignore_ipolicy"
934
  
935
pIallocator :: Field
936
pIallocator =
937
  withDoc "Iallocator for deciding the target node for shared-storage\
938
          \ instances" $
939
  optionalNEStringField "iallocator"
940

    
941
pEarlyRelease :: Field
942
pEarlyRelease =
943
  withDoc "Whether to release locks as soon as possible" $
944
  defaultFalse "early_release"
945

    
946
pRemoteNode :: Field
947
pRemoteNode =
948
  withDoc "New secondary node" $
949
  optionalNEStringField "remote_node"
950

    
951
pRemoteNodeUuid :: Field
952
pRemoteNodeUuid =
953
  withDoc "New secondary node UUID" $
954
  optionalNEStringField "remote_node_uuid"
955

    
956
pEvacMode :: Field
957
pEvacMode =
958
  withDoc "Node evacuation mode" .
959
  renameField "EvacMode" $ simpleField "mode" [t| EvacMode |]
960

    
961
pInstanceName :: Field
962
pInstanceName =
963
  withDoc "A required instance name (for single-instance LUs)" $
964
  simpleField "instance_name" [t| String |]
965

    
966
pForceVariant :: Field
967
pForceVariant =
968
  withDoc "Whether to force an unknown OS variant" $
969
  defaultFalse "force_variant"
970

    
971
pWaitForSync :: Field
972
pWaitForSync =
973
  withDoc "Whether to wait for the disk to synchronize" $
974
  defaultTrue "wait_for_sync"
975

    
976
pNameCheck :: Field
977
pNameCheck =
978
  withDoc "Whether to check name" $
979
  defaultTrue "name_check"
980

    
981
pInstBeParams :: Field
982
pInstBeParams =
983
  withDoc "Backend parameters for instance" .
984
  renameField "InstBeParams" .
985
  defaultField [| toJSObject [] |] $
986
  simpleField "beparams" [t| JSObject JSValue |]
987

    
988
pInstDisks :: Field
989
pInstDisks =
990
  withDoc "List of instance disks" .
991
  renameField "instDisks" $ simpleField "disks" [t| [IDiskParams] |]
992

    
993
pDiskTemplate :: Field
994
pDiskTemplate =
995
  withDoc "Disk template" $
996
  simpleField "disk_template" [t| DiskTemplate |]
997

    
998
pFileDriver :: Field
999
pFileDriver =
1000
  withDoc "Driver for file-backed disks" .
1001
  optionalField $ simpleField "file_driver" [t| FileDriver |]
1002

    
1003
pFileStorageDir :: Field
1004
pFileStorageDir =
1005
  withDoc "Directory for storing file-backed disks" $
1006
  optionalNEStringField "file_storage_dir"
1007

    
1008
pInstHvParams :: Field
1009
pInstHvParams =
1010
  withDoc "Hypervisor parameters for instance, hypervisor-dependent" .
1011
  renameField "InstHvParams" .
1012
  defaultField [| toJSObject [] |] $
1013
  simpleField "hvparams" [t| JSObject JSValue |]
1014

    
1015
pHypervisor :: Field
1016
pHypervisor =
1017
  withDoc "Selected hypervisor for an instance" .
1018
  optionalField $
1019
  simpleField "hypervisor" [t| Hypervisor |]
1020

    
1021
pResetDefaults :: Field
1022
pResetDefaults =
1023
  withDoc "Reset instance parameters to default if equal" $
1024
  defaultFalse "identify_defaults"
1025

    
1026
pIpCheck :: Field
1027
pIpCheck =
1028
  withDoc "Whether to ensure instance's IP address is inactive" $
1029
  defaultTrue "ip_check"
1030

    
1031
pIpConflictsCheck :: Field
1032
pIpConflictsCheck =
1033
  withDoc "Whether to check for conflicting IP addresses" $
1034
  defaultTrue "conflicts_check"
1035

    
1036
pInstCreateMode :: Field
1037
pInstCreateMode =
1038
  withDoc "Instance creation mode" .
1039
  renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
1040

    
1041
pInstNics :: Field
1042
pInstNics =
1043
  withDoc "List of NIC (network interface) definitions" $
1044
  simpleField "nics" [t| [INicParams] |]
1045

    
1046
pNoInstall :: Field
1047
pNoInstall =
1048
  withDoc "Do not install the OS (will disable automatic start)" .
1049
  optionalField $ booleanField "no_install"
1050

    
1051
pInstOs :: Field
1052
pInstOs =
1053
  withDoc "OS type for instance installation" $
1054
  optionalNEStringField "os_type"
1055

    
1056
pInstOsParams :: Field
1057
pInstOsParams =
1058
  withDoc "OS parameters for instance" .
1059
  renameField "InstOsParams" .
1060
  defaultField [| toJSObject [] |] $
1061
  simpleField "osparams" [t| JSObject JSValue |]
1062

    
1063
pPrimaryNode :: Field
1064
pPrimaryNode =
1065
  withDoc "Primary node for an instance" $
1066
  optionalNEStringField "pnode"
1067

    
1068
pPrimaryNodeUuid :: Field
1069
pPrimaryNodeUuid =
1070
  withDoc "Primary node UUID for an instance" $
1071
  optionalNEStringField "pnode_uuid"
1072

    
1073
pSecondaryNode :: Field
1074
pSecondaryNode =
1075
  withDoc "Secondary node for an instance" $
1076
  optionalNEStringField "snode"
1077

    
1078
pSecondaryNodeUuid :: Field
1079
pSecondaryNodeUuid =
1080
  withDoc "Secondary node UUID for an instance" $
1081
  optionalNEStringField "snode_uuid"
1082

    
1083
pSourceHandshake :: Field
1084
pSourceHandshake =
1085
  withDoc "Signed handshake from source (remote import only)" .
1086
  optionalField $ simpleField "source_handshake" [t| [JSValue] |]
1087

    
1088
pSourceInstance :: Field
1089
pSourceInstance =
1090
  withDoc "Source instance name (remote import only)" $
1091
  optionalNEStringField "source_instance_name"
1092

    
1093
-- FIXME: non-negative int, whereas the constant is a plain int.
1094
pSourceShutdownTimeout :: Field
1095
pSourceShutdownTimeout =
1096
  withDoc "How long source instance was given to shut down (remote import\
1097
          \ only)" .
1098
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1099
  simpleField "source_shutdown_timeout" [t| NonNegative Int |]
1100

    
1101
pSourceX509Ca :: Field
1102
pSourceX509Ca =
1103
  withDoc "Source X509 CA in PEM format (remote import only)" $
1104
  optionalNEStringField "source_x509_ca"
1105

    
1106
pSrcNode :: Field
1107
pSrcNode =
1108
  withDoc "Source node for import" $
1109
  optionalNEStringField "src_node"
1110

    
1111
pSrcNodeUuid :: Field
1112
pSrcNodeUuid =
1113
  withDoc "Source node UUID for import" $
1114
  optionalNEStringField "src_node_uuid"
1115

    
1116
pSrcPath :: Field
1117
pSrcPath =
1118
  withDoc "Source directory for import" $
1119
  optionalNEStringField "src_path"
1120

    
1121
pStartInstance :: Field
1122
pStartInstance =
1123
  withDoc "Whether to start instance after creation" $
1124
  defaultTrue "start"
1125

    
1126
-- FIXME: unify/simplify with pTags, once that migrates to NonEmpty String"
1127
pInstTags :: Field
1128
pInstTags =
1129
  withDoc "Instance tags" .
1130
  renameField "InstTags" .
1131
  defaultField [| [] |] $
1132
  simpleField "tags" [t| [NonEmptyString] |]
1133

    
1134
pMultiAllocInstances :: Field
1135
pMultiAllocInstances =
1136
  withDoc "List of instance create opcodes describing the instances to\
1137
          \ allocate" .
1138
  renameField "InstMultiAlloc" .
1139
  defaultField [| [] |] $
1140
  simpleField "instances"[t| [JSValue] |]
1141

    
1142
pOpportunisticLocking :: Field
1143
pOpportunisticLocking =
1144
  withDoc "Whether to employ opportunistic locking for nodes, meaning\
1145
          \ nodes already locked by another opcode won't be considered for\
1146
          \ instance allocation (only when an iallocator is used)" $
1147
  defaultFalse "opportunistic_locking"
1148

    
1149
pInstanceUuid :: Field
1150
pInstanceUuid =
1151
  withDoc "An instance UUID (for single-instance LUs)" .
1152
  optionalField $ simpleField "instance_uuid" [t| NonEmptyString |]
1153

    
1154
pTempOsParams :: Field
1155
pTempOsParams =
1156
  withDoc "Temporary OS parameters (currently only in reinstall, might be\
1157
          \ added to install as well)" .
1158
  renameField "TempOsParams" .
1159
  optionalField $ simpleField "osparams" [t| JSObject JSValue |]
1160

    
1161
pShutdownTimeout :: Field
1162
pShutdownTimeout =
1163
  withDoc "How long to wait for instance to shut down" .
1164
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1165
  simpleField "shutdown_timeout" [t| NonNegative Int |]
1166

    
1167
-- | Another name for the shutdown timeout, because we like to be
1168
-- inconsistent.
1169
pShutdownTimeout' :: Field
1170
pShutdownTimeout' =
1171
  withDoc "How long to wait for instance to shut down" .
1172
  renameField "InstShutdownTimeout" .
1173
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1174
  simpleField "timeout" [t| NonNegative Int |]
1175

    
1176
pIgnoreFailures :: Field
1177
pIgnoreFailures =
1178
  withDoc "Whether to ignore failures during removal" $
1179
  defaultFalse "ignore_failures"
1180

    
1181
pNewName :: Field
1182
pNewName =
1183
  withDoc "New group or instance name" $
1184
  simpleField "new_name" [t| NonEmptyString |]
1185
  
1186
pIgnoreOfflineNodes :: Field
1187
pIgnoreOfflineNodes =
1188
  withDoc "Whether to ignore offline nodes" $
1189
  defaultFalse "ignore_offline_nodes"
1190

    
1191
pTempHvParams :: Field
1192
pTempHvParams =
1193
  withDoc "Temporary hypervisor parameters, hypervisor-dependent" .
1194
  renameField "TempHvParams" .
1195
  defaultField [| toJSObject [] |] $
1196
  simpleField "hvparams" [t| JSObject JSValue |]
1197

    
1198
pTempBeParams :: Field
1199
pTempBeParams =
1200
  withDoc "Temporary backend parameters" .
1201
  renameField "TempBeParams" .
1202
  defaultField [| toJSObject [] |] $
1203
  simpleField "beparams" [t| JSObject JSValue |]
1204

    
1205
pNoRemember :: Field
1206
pNoRemember =
1207
  withDoc "Do not remember instance state changes" $
1208
  defaultFalse "no_remember"
1209

    
1210
pStartupPaused :: Field
1211
pStartupPaused =
1212
  withDoc "Pause instance at startup" $
1213
  defaultFalse "startup_paused"
1214

    
1215
pIgnoreSecondaries :: Field
1216
pIgnoreSecondaries =
1217
  withDoc "Whether to start the instance even if secondary disks are failing" $
1218
  defaultFalse "ignore_secondaries"
1219

    
1220
pRebootType :: Field
1221
pRebootType =
1222
  withDoc "How to reboot the instance" $
1223
  simpleField "reboot_type" [t| RebootType |]
1224

    
1225
pReplaceDisksMode :: Field
1226
pReplaceDisksMode =
1227
  withDoc "Replacement mode" .
1228
  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1229

    
1230
pReplaceDisksList :: Field
1231
pReplaceDisksList =
1232
  withDoc "List of disk indices" .
1233
  renameField "ReplaceDisksList" .
1234
  defaultField [| [] |] $
1235
  simpleField "disks" [t| [DiskIndex] |]
1236

    
1237
pMigrationCleanup :: Field
1238
pMigrationCleanup =
1239
  withDoc "Whether a previously failed migration should be cleaned up" .
1240
  renameField "MigrationCleanup" $ defaultFalse "cleanup"
1241

    
1242
pAllowFailover :: Field
1243
pAllowFailover =
1244
  withDoc "Whether we can fallback to failover if migration is not possible" $
1245
  defaultFalse "allow_failover"
1246

    
1247
pMoveTargetNode :: Field
1248
pMoveTargetNode =
1249
  withDoc "Target node for instance move" .
1250
  renameField "MoveTargetNode" $
1251
  simpleField "target_node" [t| NonEmptyString |]
1252

    
1253
pMoveTargetNodeUuid :: Field
1254
pMoveTargetNodeUuid =
1255
  withDoc "Target node UUID for instance move" .
1256
  renameField "MoveTargetNodeUuid" . optionalField $
1257
  simpleField "target_node_uuid" [t| NonEmptyString |]
1258

    
1259
pIgnoreDiskSize :: Field
1260
pIgnoreDiskSize =
1261
  withDoc "Whether to ignore recorded disk size" $
1262
  defaultFalse "ignore_size"
1263
  
1264
pWaitForSyncFalse :: Field
1265
pWaitForSyncFalse =
1266
  withDoc "Whether to wait for the disk to synchronize (defaults to false)" $
1267
  defaultField [| False |] pWaitForSync
1268
  
1269
pRecreateDisksInfo :: Field
1270
pRecreateDisksInfo =
1271
  withDoc "Disk list for recreate disks" .
1272
  renameField "RecreateDisksInfo" .
1273
  defaultField [| RecreateDisksAll |] $
1274
  simpleField "disks" [t| RecreateDisksInfo |]
1275

    
1276
pStatic :: Field
1277
pStatic =
1278
  withDoc "Whether to only return configuration data without querying nodes" $
1279
  defaultFalse "static"
1280

    
1281
pInstParamsNicChanges :: Field
1282
pInstParamsNicChanges =
1283
  withDoc "List of NIC changes" .
1284
  renameField "InstNicChanges" .
1285
  defaultField [| SetParamsEmpty |] $
1286
  simpleField "nics" [t| SetParamsMods INicParams |]
1287

    
1288
pInstParamsDiskChanges :: Field
1289
pInstParamsDiskChanges =
1290
  withDoc "List of disk changes" .
1291
  renameField "InstDiskChanges" .
1292
  defaultField [| SetParamsEmpty |] $
1293
  simpleField "disks" [t| SetParamsMods IDiskParams |]
1294

    
1295
pRuntimeMem :: Field
1296
pRuntimeMem =
1297
  withDoc "New runtime memory" .
1298
  optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1299

    
1300
pOptDiskTemplate :: Field
1301
pOptDiskTemplate =
1302
  withDoc "Instance disk template" .
1303
  optionalField .
1304
  renameField "OptDiskTemplate" $
1305
  simpleField "disk_template" [t| DiskTemplate |]
1306

    
1307
pOsNameChange :: Field
1308
pOsNameChange =
1309
  withDoc "Change the instance's OS without reinstalling the instance" $
1310
  optionalNEStringField "os_name"
1311

    
1312
pDiskIndex :: Field
1313
pDiskIndex =
1314
  withDoc "Disk index for e.g. grow disk" .
1315
  renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
1316

    
1317
pDiskChgAmount :: Field
1318
pDiskChgAmount =
1319
  withDoc "Disk amount to add or grow to" .
1320
  renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
1321

    
1322
pDiskChgAbsolute :: Field
1323
pDiskChgAbsolute =
1324
  withDoc
1325
    "Whether the amount parameter is an absolute target or a relative one" .
1326
  renameField "DiskChkAbsolute" $ defaultFalse "absolute"
1327

    
1328
pTargetGroups :: Field
1329
pTargetGroups =
1330
  withDoc
1331
    "Destination group names or UUIDs (defaults to \"all but current group\")" .
1332
  optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
1333

    
1334
pNodeGroupAllocPolicy :: Field
1335
pNodeGroupAllocPolicy =
1336
  withDoc "Instance allocation policy" .
1337
  optionalField $
1338
  simpleField "alloc_policy" [t| AllocPolicy |]
1339

    
1340
pGroupNodeParams :: Field
1341
pGroupNodeParams =
1342
  withDoc "Default node parameters for group" .
1343
  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
1344

    
1345
pExportMode :: Field
1346
pExportMode =
1347
  withDoc "Export mode" .
1348
  renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1349

    
1350
-- FIXME: Rename target_node as it changes meaning for different
1351
-- export modes (e.g. "destination")
1352
pExportTargetNode :: Field
1353
pExportTargetNode =
1354
  withDoc "Target node (depends on export mode)" .
1355
  renameField "ExportTarget" $
1356
  simpleField "target_node" [t| ExportTarget |]
1357

    
1358
pExportTargetNodeUuid :: Field
1359
pExportTargetNodeUuid =
1360
  withDoc "Target node UUID (if local export)" .
1361
  renameField "ExportTargetNodeUuid" . optionalField $
1362
  simpleField "target_node_uuid" [t| NonEmptyString |]
1363

    
1364
pShutdownInstance :: Field
1365
pShutdownInstance =
1366
  withDoc "Whether to shutdown the instance before export" $
1367
  defaultTrue "shutdown"
1368

    
1369
pRemoveInstance :: Field
1370
pRemoveInstance =
1371
  withDoc "Whether to remove instance after export" $
1372
  defaultFalse "remove_instance"
1373

    
1374
pIgnoreRemoveFailures :: Field
1375
pIgnoreRemoveFailures =
1376
  withDoc "Whether to ignore failures while removing instances" $
1377
  defaultFalse "ignore_remove_failures"
1378

    
1379
pX509KeyName :: Field
1380
pX509KeyName =
1381
  withDoc "Name of X509 key (remote export only)" .
1382
  optionalField $ simpleField "x509_key_name" [t| [JSValue] |]
1383

    
1384
pX509DestCA :: Field
1385
pX509DestCA =
1386
  withDoc "Destination X509 CA (remote export only)" $
1387
  optionalNEStringField "destination_x509_ca"
1388

    
1389
pTagsObject :: Field
1390
pTagsObject =
1391
  withDoc "Tag kind" $
1392
  simpleField "kind" [t| TagKind |]
1393

    
1394
pTagsName :: Field
1395
pTagsName =
1396
  withDoc "Name of object" .
1397
  renameField "TagsGetName" .
1398
  optionalField $ simpleField "name" [t| String |]
1399

    
1400
pTagsList :: Field
1401
pTagsList =
1402
  withDoc "List of tag names" $
1403
  simpleField "tags" [t| [String] |]
1404

    
1405
-- FIXME: this should be compiled at load time?
1406
pTagSearchPattern :: Field
1407
pTagSearchPattern =
1408
  withDoc "Search pattern (regular expression)" .
1409
  renameField "TagSearchPattern" $
1410
  simpleField "pattern" [t| NonEmptyString |]
1411

    
1412
pDelayDuration :: Field
1413
pDelayDuration =
1414
  withDoc "Duration parameter for 'OpTestDelay'" .
1415
  renameField "DelayDuration" $
1416
  simpleField "duration" [t| Double |]
1417

    
1418
pDelayOnMaster :: Field
1419
pDelayOnMaster =
1420
  withDoc "on_master field for 'OpTestDelay'" .
1421
  renameField "DelayOnMaster" $
1422
  defaultTrue "on_master"
1423

    
1424
pDelayOnNodes :: Field
1425
pDelayOnNodes =
1426
  withDoc "on_nodes field for 'OpTestDelay'" .
1427
  renameField "DelayOnNodes" .
1428
  defaultField [| [] |] $
1429
  simpleField "on_nodes" [t| [NonEmptyString] |]
1430

    
1431
pDelayOnNodeUuids :: Field
1432
pDelayOnNodeUuids =
1433
  withDoc "on_node_uuids field for 'OpTestDelay'" .
1434
  renameField "DelayOnNodeUuids" . optionalField $
1435
  simpleField "on_node_uuids" [t| [NonEmptyString] |]
1436

    
1437
pDelayRepeat :: Field
1438
pDelayRepeat =
1439
  withDoc "Repeat parameter for OpTestDelay" .
1440
  renameField "DelayRepeat" .
1441
  defaultField [| forceNonNeg (0::Int) |] $
1442
  simpleField "repeat" [t| NonNegative Int |]
1443

    
1444
pIAllocatorDirection :: Field
1445
pIAllocatorDirection =
1446
  withDoc "IAllocator test direction" .
1447
  renameField "IAllocatorDirection" $
1448
  simpleField "direction" [t| IAllocatorTestDir |]
1449

    
1450
pIAllocatorMode :: Field
1451
pIAllocatorMode =
1452
  withDoc "IAllocator test mode" .
1453
  renameField "IAllocatorMode" $
1454
  simpleField "mode" [t| IAllocatorMode |]
1455

    
1456
pIAllocatorReqName :: Field
1457
pIAllocatorReqName =
1458
  withDoc "IAllocator target name (new instance, node to evac, etc.)" .
1459
  renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
1460

    
1461
pIAllocatorNics :: Field
1462
pIAllocatorNics =
1463
  withDoc "Custom OpTestIAllocator nics" .
1464
  renameField "IAllocatorNics" .
1465
  optionalField $ simpleField "nics" [t| [INicParams] |]
1466

    
1467
pIAllocatorDisks :: Field
1468
pIAllocatorDisks =
1469
  withDoc "Custom OpTestAllocator disks" .
1470
  renameField "IAllocatorDisks" .
1471
  optionalField $ simpleField "disks" [t| [JSValue] |]
1472

    
1473
pIAllocatorMemory :: Field
1474
pIAllocatorMemory =
1475
  withDoc "IAllocator memory field" .
1476
  renameField "IAllocatorMem" .
1477
  optionalField $
1478
  simpleField "memory" [t| NonNegative Int |]
1479

    
1480
pIAllocatorVCpus :: Field
1481
pIAllocatorVCpus =
1482
  withDoc "IAllocator vcpus field" .
1483
  renameField "IAllocatorVCpus" .
1484
  optionalField $
1485
  simpleField "vcpus" [t| NonNegative Int |]
1486

    
1487
pIAllocatorOs :: Field
1488
pIAllocatorOs =
1489
  withDoc "IAllocator os field" .
1490
  renameField "IAllocatorOs" $ optionalNEStringField "os"
1491

    
1492
pIAllocatorInstances :: Field
1493
pIAllocatorInstances =
1494
  withDoc "IAllocator instances field" .
1495
  renameField "IAllocatorInstances " .
1496
  optionalField $
1497
  simpleField "instances" [t| [NonEmptyString] |]
1498

    
1499
pIAllocatorEvacMode :: Field
1500
pIAllocatorEvacMode =
1501
  withDoc "IAllocator evac mode" .
1502
  renameField "IAllocatorEvacMode" .
1503
  optionalField $
1504
  simpleField "evac_mode" [t| EvacMode |]
1505

    
1506
pIAllocatorSpindleUse :: Field
1507
pIAllocatorSpindleUse =
1508
  withDoc "IAllocator spindle use" .
1509
  renameField "IAllocatorSpindleUse" .
1510
  defaultField [| forceNonNeg (1::Int) |] $
1511
  simpleField "spindle_use" [t| NonNegative Int |]
1512

    
1513
pIAllocatorCount :: Field
1514
pIAllocatorCount =
1515
  withDoc "IAllocator count field" .
1516
  renameField "IAllocatorCount" .
1517
  defaultField [| forceNonNeg (1::Int) |] $
1518
  simpleField "count" [t| NonNegative Int |]
1519

    
1520
pJQueueNotifyWaitLock :: Field
1521
pJQueueNotifyWaitLock =
1522
  withDoc "'OpTestJqueue' notify_waitlock" $
1523
  defaultFalse "notify_waitlock"
1524

    
1525
pJQueueNotifyExec :: Field
1526
pJQueueNotifyExec =
1527
  withDoc "'OpTestJQueue' notify_exec" $
1528
  defaultFalse "notify_exec"
1529

    
1530
pJQueueLogMessages :: Field
1531
pJQueueLogMessages =
1532
  withDoc "'OpTestJQueue' log_messages" .
1533
  defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
1534

    
1535
pJQueueFail :: Field
1536
pJQueueFail =
1537
  withDoc "'OpTestJQueue' fail attribute" .
1538
  renameField "JQueueFail" $ defaultFalse "fail"
1539

    
1540
pTestDummyResult :: Field
1541
pTestDummyResult =
1542
  withDoc "'OpTestDummy' result field" .
1543
  renameField "TestDummyResult" $ simpleField "result" [t| JSValue |]
1544

    
1545
pTestDummyMessages :: Field
1546
pTestDummyMessages =
1547
  withDoc "'OpTestDummy' messages field" .
1548
  renameField "TestDummyMessages" $
1549
  simpleField "messages" [t| JSValue |]
1550

    
1551
pTestDummyFail :: Field
1552
pTestDummyFail =
1553
  withDoc "'OpTestDummy' fail field" .
1554
  renameField "TestDummyFail" $ simpleField "fail" [t| JSValue |]
1555

    
1556
pTestDummySubmitJobs :: Field
1557
pTestDummySubmitJobs =
1558
  withDoc "'OpTestDummy' submit_jobs field" .
1559
  renameField "TestDummySubmitJobs" $
1560
  simpleField "submit_jobs" [t| JSValue |]
1561

    
1562
pNetworkName :: Field
1563
pNetworkName =
1564
  withDoc "Network name" $
1565
  simpleField "network_name" [t| NonEmptyString |]
1566

    
1567
pNetworkAddress4 :: Field
1568
pNetworkAddress4 =
1569
  withDoc "Network address (IPv4 subnet)" .
1570
  renameField "NetworkAddress4" $
1571
  simpleField "network" [t| IPv4Network |]
1572

    
1573
pNetworkGateway4 :: Field
1574
pNetworkGateway4 =
1575
  withDoc "Network gateway (IPv4 address)" .
1576
  renameField "NetworkGateway4" .
1577
  optionalField $ simpleField "gateway" [t| IPv4Address |]
1578

    
1579
pNetworkAddress6 :: Field
1580
pNetworkAddress6 =
1581
  withDoc "Network address (IPv6 subnet)" .
1582
  renameField "NetworkAddress6" .
1583
  optionalField $ simpleField "network6" [t| IPv6Network |]
1584

    
1585
pNetworkGateway6 :: Field
1586
pNetworkGateway6 =
1587
  withDoc "Network gateway (IPv6 address)" .
1588
  renameField "NetworkGateway6" .
1589
  optionalField $ simpleField "gateway6" [t| IPv6Address |]
1590

    
1591
pNetworkMacPrefix :: Field
1592
pNetworkMacPrefix =
1593
  withDoc "Network specific mac prefix (that overrides the cluster one)" .
1594
  renameField "NetMacPrefix" $
1595
  optionalNEStringField "mac_prefix"
1596

    
1597
pNetworkAddRsvdIps :: Field
1598
pNetworkAddRsvdIps =
1599
  withDoc "Which IP addresses to reserve" .
1600
  renameField "NetworkAddRsvdIps" .
1601
  optionalField $
1602
  simpleField "add_reserved_ips" [t| [IPv4Address] |]
1603

    
1604
pNetworkRemoveRsvdIps :: Field
1605
pNetworkRemoveRsvdIps =
1606
  withDoc "Which external IP addresses to release" .
1607
  renameField "NetworkRemoveRsvdIps" .
1608
  optionalField $
1609
  simpleField "remove_reserved_ips" [t| [IPv4Address] |]
1610

    
1611
pNetworkMode :: Field
1612
pNetworkMode =
1613
  withDoc "Network mode when connecting to a group" $
1614
  simpleField "network_mode" [t| NICMode |]
1615

    
1616
pNetworkLink :: Field
1617
pNetworkLink =
1618
  withDoc "Network link when connecting to a group" $
1619
  simpleField "network_link" [t| NonEmptyString |]