Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ ad756c77

History | View | Annotate | Download (46.4 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

    
3
{-| Implementation of opcodes parameters.
4

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

    
11
-}
12

    
13
{-
14

    
15
Copyright (C) 2012 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
  , pMoveCompress
87
  , pBackupCompress
88
  , pStartupPaused
89
  , pVerbose
90
  , pDebugSimulateErrors
91
  , pErrorCodes
92
  , pSkipChecks
93
  , pIgnoreErrors
94
  , pOptGroupName
95
  , pDiskParams
96
  , pHvState
97
  , pDiskState
98
  , pIgnoreIpolicy
99
  , pHotplug
100
  , pHotplugIfPossible
101
  , pAllowRuntimeChgs
102
  , pInstDisks
103
  , pDiskTemplate
104
  , pOptDiskTemplate
105
  , pFileDriver
106
  , pFileStorageDir
107
  , pClusterFileStorageDir
108
  , pClusterSharedFileStorageDir
109
  , pClusterGlusterStorageDir
110
  , pVgName
111
  , pEnabledHypervisors
112
  , pHypervisor
113
  , pClusterHvParams
114
  , pInstHvParams
115
  , pClusterBeParams
116
  , pInstBeParams
117
  , pResetDefaults
118
  , pOsHvp
119
  , pClusterOsParams
120
  , pInstOsParams
121
  , pCandidatePoolSize
122
  , pMaxRunningJobs
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
  , pDefaultIAllocatorParams
136
  , pMasterNetdev
137
  , pMasterNetmask
138
  , pReservedLvs
139
  , pHiddenOs
140
  , pBlacklistedOs
141
  , pUseExternalMipScript
142
  , pQueryFields
143
  , pQueryFilter
144
  , pQueryFieldsFields
145
  , pOobCommand
146
  , pOobTimeout
147
  , pIgnoreStatus
148
  , pPowerDelay
149
  , pPrimaryIp
150
  , pSecondaryIp
151
  , pReadd
152
  , pNodeGroup
153
  , pMasterCapable
154
  , pVmCapable
155
  , pNames
156
  , pNodes
157
  , pRequiredNodes
158
  , pRequiredNodeUuids
159
  , pStorageType
160
  , pStorageTypeOptional
161
  , pStorageChanges
162
  , pMasterCandidate
163
  , pOffline
164
  , pDrained
165
  , pAutoPromote
166
  , pPowered
167
  , pIallocator
168
  , pRemoteNode
169
  , pRemoteNodeUuid
170
  , pEvacMode
171
  , pInstCreateMode
172
  , pNoInstall
173
  , pInstOs
174
  , pPrimaryNode
175
  , pPrimaryNodeUuid
176
  , pSecondaryNode
177
  , pSecondaryNodeUuid
178
  , pSourceHandshake
179
  , pSourceInstance
180
  , pSourceShutdownTimeout
181
  , pSourceX509Ca
182
  , pSrcNode
183
  , pSrcNodeUuid
184
  , pSrcPath
185
  , pStartInstance
186
  , pInstTags
187
  , pMultiAllocInstances
188
  , pTempOsParams
189
  , pTempHvParams
190
  , pTempBeParams
191
  , pIgnoreFailures
192
  , pNewName
193
  , pIgnoreSecondaries
194
  , pRebootType
195
  , pIgnoreDiskSize
196
  , pRecreateDisksInfo
197
  , pStatic
198
  , pInstParamsNicChanges
199
  , pInstParamsDiskChanges
200
  , pRuntimeMem
201
  , pOsNameChange
202
  , pDiskIndex
203
  , pDiskChgAmount
204
  , pDiskChgAbsolute
205
  , pTargetGroups
206
  , pExportMode
207
  , pExportTargetNode
208
  , pExportTargetNodeUuid
209
  , pRemoveInstance
210
  , pIgnoreRemoveFailures
211
  , pX509KeyName
212
  , pX509DestCA
213
  , pTagSearchPattern
214
  , pRestrictedCommand
215
  , pReplaceDisksMode
216
  , pReplaceDisksList
217
  , pAllowFailover
218
  , pDelayDuration
219
  , pDelayOnMaster
220
  , pDelayOnNodes
221
  , pDelayOnNodeUuids
222
  , pDelayRepeat
223
  , pIAllocatorDirection
224
  , pIAllocatorMode
225
  , pIAllocatorReqName
226
  , pIAllocatorNics
227
  , pIAllocatorDisks
228
  , pIAllocatorMemory
229
  , pIAllocatorVCpus
230
  , pIAllocatorOs
231
  , pIAllocatorInstances
232
  , pIAllocatorEvacMode
233
  , pIAllocatorSpindleUse
234
  , pIAllocatorCount
235
  , pJQueueNotifyWaitLock
236
  , pJQueueNotifyExec
237
  , pJQueueLogMessages
238
  , pJQueueFail
239
  , pTestDummyResult
240
  , pTestDummyMessages
241
  , pTestDummyFail
242
  , pTestDummySubmitJobs
243
  , pNetworkName
244
  , pNetworkAddress4
245
  , pNetworkGateway4
246
  , pNetworkAddress6
247
  , pNetworkGateway6
248
  , pNetworkMacPrefix
249
  , pNetworkAddRsvdIps
250
  , pNetworkRemoveRsvdIps
251
  , pNetworkMode
252
  , pNetworkLink
253
  , pDryRun
254
  , pDebugLevel
255
  , pOpPriority
256
  , pDependencies
257
  , pComment
258
  , pReason
259
  , pEnabledDiskTemplates
260
  ) where
261

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

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

    
276
-- * Helper functions and types
277

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

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

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

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

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

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

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

    
311
-- ** Disks
312

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

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

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

    
329
-- ** I* param types
330

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

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

    
349
-- | Disk modification definition.
350
$(buildObject "IDiskParams" "idisk"
351
  [ specialNumericalField 'parseUnitAssumeBinary . optionalField
352
      $ 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.idiskSpindles [t| Int          |]
359
  ])
360

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

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

    
383
instance JSON RecreateDisksInfo where
384
  readJSON = readRecreateDisks
385
  showJSON  RecreateDisksAll            = showJSON ()
386
  showJSON (RecreateDisksIndices idx)   = showJSON idx
387
  showJSON (RecreateDisksParams params) = showJSON params
388

    
389
-- | Simple type for old-style ddm changes.
390
data DdmOldChanges = DdmOldIndex (NonNegative Int)
391
                   | DdmOldMod DdmSimple
392
                     deriving (Eq, Show)
393

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

    
403
instance JSON DdmOldChanges where
404
  showJSON (DdmOldIndex i) = showJSON i
405
  showJSON (DdmOldMod m)   = showJSON m
406
  readJSON = readDdmOldChanges
407

    
408
-- | Instance disk or nic modifications.
409
data SetParamsMods a
410
  = SetParamsEmpty
411
  | SetParamsDeprecated (NonEmpty (DdmOldChanges, a))
412
  | SetParamsNew (NonEmpty (DdmFull, Int, a))
413
  | SetParamsNewName (NonEmpty (DdmFull, String, a))
414
    deriving (Eq, Show)
415

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

    
424
instance (JSON a) => JSON (SetParamsMods a) where
425
  showJSON SetParamsEmpty = showJSON ()
426
  showJSON (SetParamsDeprecated v) = showJSON v
427
  showJSON (SetParamsNew v) = showJSON v
428
  showJSON (SetParamsNewName v) = showJSON v
429
  readJSON = readSetParams
430

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

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

    
447
instance JSON ExportTarget where
448
  showJSON (ExportTargetLocal s)  = showJSON s
449
  showJSON (ExportTargetRemote l) = showJSON l
450
  readJSON = readExportTarget
451

    
452
-- * Common opcode parameters
453

    
454
pDryRun :: Field
455
pDryRun =
456
  withDoc "Run checks only, don't execute" .
457
  optionalField $ booleanField "dry_run"
458

    
459
pDebugLevel :: Field
460
pDebugLevel =
461
  withDoc "Debug level" .
462
  optionalField $ simpleField "debug_level" [t| NonNegative Int |]
463

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

    
471
pDependencies :: Field
472
pDependencies =
473
  withDoc "Job dependencies" .
474
  optionalNullSerField $ simpleField "depends" [t| [JobDependency] |]
475

    
476
pComment :: Field
477
pComment =
478
  withDoc "Comment field" .
479
  optionalNullSerField $ stringField "comment"
480

    
481
pReason :: Field
482
pReason =
483
  withDoc "Reason trail field" $
484
  simpleField C.opcodeReason [t| ReasonTrail |]
485

    
486
-- * Parameters
487

    
488
pDebugSimulateErrors :: Field
489
pDebugSimulateErrors =
490
  withDoc "Whether to simulate errors (useful for debugging)" $
491
  defaultFalse "debug_simulate_errors"
492

    
493
pErrorCodes :: Field
494
pErrorCodes =
495
  withDoc "Error codes" $
496
  defaultFalse "error_codes"
497

    
498
pSkipChecks :: Field
499
pSkipChecks =
500
  withDoc "Which checks to skip" .
501
  defaultField [| emptyListSet |] $
502
  simpleField "skip_checks" [t| ListSet VerifyOptionalChecks |]
503

    
504
pIgnoreErrors :: Field
505
pIgnoreErrors =
506
  withDoc "List of error codes that should be treated as warnings" .
507
  defaultField [| emptyListSet |] $
508
  simpleField "ignore_errors" [t| ListSet CVErrorCode |]
509

    
510
pVerbose :: Field
511
pVerbose =
512
  withDoc "Verbose mode" $
513
  defaultFalse "verbose"
514

    
515
pOptGroupName :: Field
516
pOptGroupName =
517
  withDoc "Optional group name" .
518
  renameField "OptGroupName" .
519
  optionalField $ simpleField "group_name" [t| NonEmptyString |]
520

    
521
pGroupName :: Field
522
pGroupName =
523
  withDoc "Group name" $
524
  simpleField "group_name" [t| NonEmptyString |]
525

    
526
-- | Whether to hotplug device.
527
pHotplug :: Field
528
pHotplug = defaultFalse "hotplug"
529

    
530
pHotplugIfPossible :: Field
531
pHotplugIfPossible = defaultFalse "hotplug_if_possible"
532

    
533
pInstances :: Field
534
pInstances =
535
  withDoc "List of instances" .
536
  defaultField [| [] |] $
537
  simpleField "instances" [t| [NonEmptyString] |]
538

    
539
pOutputFields :: Field
540
pOutputFields =
541
  withDoc "Selected output fields" $
542
  simpleField "output_fields" [t| [NonEmptyString] |]
543

    
544
pName :: Field
545
pName =
546
  withDoc "A generic name" $
547
  simpleField "name" [t| NonEmptyString |]
548

    
549
pForce :: Field
550
pForce =
551
  withDoc "Whether to force the operation" $
552
  defaultFalse "force"
553

    
554
pHvState :: Field
555
pHvState =
556
  withDoc "Set hypervisor states" .
557
  optionalField $ simpleField "hv_state" [t| JSObject JSValue |]
558

    
559
pDiskState :: Field
560
pDiskState =
561
  withDoc "Set disk states" .
562
  optionalField $ simpleField "disk_state" [t| JSObject JSValue |]
563

    
564
-- | Cluster-wide default directory for storing file-backed disks.
565
pClusterFileStorageDir :: Field
566
pClusterFileStorageDir =
567
  renameField "ClusterFileStorageDir" $
568
  optionalStringField "file_storage_dir"
569

    
570
-- | Cluster-wide default directory for storing shared-file-backed disks.
571
pClusterSharedFileStorageDir :: Field
572
pClusterSharedFileStorageDir =
573
  renameField "ClusterSharedFileStorageDir" $
574
  optionalStringField "shared_file_storage_dir"
575

    
576
-- | Cluster-wide default directory for storing Gluster-backed disks.
577
pClusterGlusterStorageDir :: Field
578
pClusterGlusterStorageDir =
579
  renameField "ClusterGlusterStorageDir" $
580
  optionalStringField "gluster_storage_dir"
581

    
582
-- | Volume group name.
583
pVgName :: Field
584
pVgName =
585
  withDoc "Volume group name" $
586
  optionalStringField "vg_name"
587

    
588
pEnabledHypervisors :: Field
589
pEnabledHypervisors =
590
  withDoc "List of enabled hypervisors" .
591
  optionalField $
592
  simpleField "enabled_hypervisors" [t| [Hypervisor] |]
593

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

    
601
pClusterBeParams :: Field
602
pClusterBeParams =
603
  withDoc "Cluster-wide backend parameter defaults" .
604
  renameField "ClusterBeParams" .
605
  optionalField $ simpleField "beparams" [t| JSObject JSValue |]
606

    
607
pOsHvp :: Field
608
pOsHvp =
609
  withDoc "Cluster-wide per-OS hypervisor parameter defaults" .
610
  optionalField $
611
  simpleField "os_hvp" [t| GenericContainer String (JSObject JSValue) |]
612

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

    
620
pDiskParams :: Field
621
pDiskParams =
622
  withDoc "Disk templates' parameter defaults" .
623
  optionalField $
624
  simpleField "diskparams"
625
              [t| GenericContainer DiskTemplate (JSObject JSValue) |]
626

    
627
pCandidatePoolSize :: Field
628
pCandidatePoolSize =
629
  withDoc "Master candidate pool size" .
630
  optionalField $ simpleField "candidate_pool_size" [t| Positive Int |]
631

    
632
pMaxRunningJobs :: Field
633
pMaxRunningJobs =
634
  withDoc "Maximal number of jobs to run simultaneously" .
635
  optionalField $ simpleField "max_running_jobs" [t| Positive Int |]
636

    
637
pUidPool :: Field
638
pUidPool =
639
  withDoc "Set UID pool, must be list of lists describing UID ranges\
640
          \ (two items, start and end inclusive)" .
641
  optionalField $ simpleField "uid_pool" [t| [(Int, Int)] |]
642

    
643
pAddUids :: Field
644
pAddUids =
645
  withDoc "Extend UID pool, must be list of lists describing UID\
646
          \ ranges (two items, start and end inclusive)" .
647
  optionalField $ simpleField "add_uids" [t| [(Int, Int)] |]
648

    
649
pRemoveUids :: Field
650
pRemoveUids =
651
  withDoc "Shrink UID pool, must be list of lists describing UID\
652
          \ ranges (two items, start and end inclusive) to be removed" .
653
  optionalField $ simpleField "remove_uids" [t| [(Int, Int)] |]
654

    
655
pMaintainNodeHealth :: Field
656
pMaintainNodeHealth =
657
  withDoc "Whether to automatically maintain node health" .
658
  optionalField $ booleanField "maintain_node_health"
659

    
660
-- | Whether to modify and keep in sync the @/etc/hosts@ files of nodes.
661
pModifyEtcHosts :: Field
662
pModifyEtcHosts = optionalField $ booleanField "modify_etc_hosts"
663

    
664
-- | Whether to wipe disks before allocating them to instances.
665
pPreallocWipeDisks :: Field
666
pPreallocWipeDisks =
667
  withDoc "Whether to wipe disks before allocating them to instances" .
668
  optionalField $ booleanField "prealloc_wipe_disks"
669

    
670
pNicParams :: Field
671
pNicParams =
672
  withDoc "Cluster-wide NIC parameter defaults" .
673
  optionalField $ simpleField "nicparams" [t| INicParams |]
674

    
675
pIpolicy :: Field
676
pIpolicy =
677
  withDoc "Ipolicy specs" .
678
  optionalField $ simpleField "ipolicy" [t| JSObject JSValue |]
679

    
680
pDrbdHelper :: Field
681
pDrbdHelper =
682
  withDoc "DRBD helper program" $
683
  optionalStringField "drbd_helper"
684

    
685
pDefaultIAllocator :: Field
686
pDefaultIAllocator =
687
  withDoc "Default iallocator for cluster" $
688
  optionalStringField "default_iallocator"
689

    
690
pDefaultIAllocatorParams :: Field
691
pDefaultIAllocatorParams =
692
  withDoc "Default iallocator parameters for cluster" . optionalField
693
    $ simpleField "default_iallocator_params" [t| JSObject JSValue |]
694

    
695
pMasterNetdev :: Field
696
pMasterNetdev =
697
  withDoc "Master network device" $
698
  optionalStringField "master_netdev"
699

    
700
pMasterNetmask :: Field
701
pMasterNetmask =
702
  withDoc "Netmask of the master IP" .
703
  optionalField $ simpleField "master_netmask" [t| NonNegative Int |]
704

    
705
pReservedLvs :: Field
706
pReservedLvs =
707
  withDoc "List of reserved LVs" .
708
  optionalField $ simpleField "reserved_lvs" [t| [NonEmptyString] |]
709

    
710
pHiddenOs :: Field
711
pHiddenOs =
712
  withDoc "Modify list of hidden operating systems: each modification\
713
          \ must have two items, the operation and the OS name; the operation\
714
          \ can be add or remove" .
715
  optionalField $ simpleField "hidden_os" [t| [(DdmSimple, NonEmptyString)] |]
716

    
717
pBlacklistedOs :: Field
718
pBlacklistedOs =
719
  withDoc "Modify list of blacklisted operating systems: each\
720
          \ modification must have two items, the operation and the OS name;\
721
          \ the operation can be add or remove" .
722
  optionalField $
723
  simpleField "blacklisted_os" [t| [(DdmSimple, NonEmptyString)] |]
724

    
725
pUseExternalMipScript :: Field
726
pUseExternalMipScript =
727
  withDoc "Whether to use an external master IP address setup script" .
728
  optionalField $ booleanField "use_external_mip_script"
729

    
730
pEnabledDiskTemplates :: Field
731
pEnabledDiskTemplates =
732
  withDoc "List of enabled disk templates" .
733
  optionalField $
734
  simpleField "enabled_disk_templates" [t| [DiskTemplate] |]
735

    
736
pQueryWhat :: Field
737
pQueryWhat =
738
  withDoc "Resource(s) to query for" $
739
  simpleField "what" [t| Qlang.QueryTypeOp |]
740

    
741
pUseLocking :: Field
742
pUseLocking =
743
  withDoc "Whether to use synchronization" $
744
  defaultFalse "use_locking"
745

    
746
pQueryFields :: Field
747
pQueryFields =
748
  withDoc "Requested fields" $
749
  simpleField "fields" [t| [NonEmptyString] |]
750

    
751
pQueryFilter :: Field
752
pQueryFilter =
753
  withDoc "Query filter" .
754
  optionalField $ simpleField "qfilter" [t| [JSValue] |]
755

    
756
pQueryFieldsFields :: Field
757
pQueryFieldsFields =
758
  withDoc "Requested fields; if not given, all are returned" .
759
  renameField "QueryFieldsFields" $
760
  optionalField pQueryFields
761

    
762
pNodeNames :: Field
763
pNodeNames =
764
  withDoc "List of node names to run the OOB command against" .
765
  defaultField [| [] |] $ simpleField "node_names" [t| [NonEmptyString] |]
766

    
767
pNodeUuids :: Field
768
pNodeUuids =
769
  withDoc "List of node UUIDs" .
770
  optionalField $ simpleField "node_uuids" [t| [NonEmptyString] |]
771

    
772
pOobCommand :: Field
773
pOobCommand =
774
  withDoc "OOB command to run" $
775
  simpleField "command" [t| OobCommand |]
776

    
777
pOobTimeout :: Field
778
pOobTimeout =
779
  withDoc "Timeout before the OOB helper will be terminated" .
780
  defaultField [| C.oobTimeout |] $
781
  simpleField "timeout" [t| Int |]
782

    
783
pIgnoreStatus :: Field
784
pIgnoreStatus =
785
  withDoc "Ignores the node offline status for power off" $
786
  defaultFalse "ignore_status"
787

    
788
pPowerDelay :: Field
789
pPowerDelay =
790
  -- FIXME: we can't use the proper type "NonNegative Double", since
791
  -- the default constant is a plain Double, not a non-negative one.
792
  -- And trying to fix the constant introduces a cyclic import.
793
  withDoc "Time in seconds to wait between powering on nodes" .
794
  defaultField [| C.oobPowerDelay |] $
795
  simpleField "power_delay" [t| Double |]
796

    
797
pRequiredNodes :: Field
798
pRequiredNodes =
799
  withDoc "Required list of node names" .
800
  renameField "ReqNodes " $ simpleField "nodes" [t| [NonEmptyString] |]
801

    
802
pRequiredNodeUuids :: Field
803
pRequiredNodeUuids =
804
  withDoc "Required list of node UUIDs" .
805
  renameField "ReqNodeUuids " . optionalField $
806
  simpleField "node_uuids" [t| [NonEmptyString] |]
807

    
808
pRestrictedCommand :: Field
809
pRestrictedCommand =
810
  withDoc "Restricted command name" .
811
  renameField "RestrictedCommand" $
812
  simpleField "command" [t| NonEmptyString |]
813

    
814
pNodeName :: Field
815
pNodeName =
816
  withDoc "A required node name (for single-node LUs)" $
817
  simpleField "node_name" [t| NonEmptyString |]
818

    
819
pNodeUuid :: Field
820
pNodeUuid =
821
  withDoc "A node UUID (for single-node LUs)" .
822
  optionalField $ simpleField "node_uuid" [t| NonEmptyString |]
823

    
824
pPrimaryIp :: Field
825
pPrimaryIp =
826
  withDoc "Primary IP address" .
827
  optionalField $
828
  simpleField "primary_ip" [t| NonEmptyString |]
829

    
830
pSecondaryIp :: Field
831
pSecondaryIp =
832
  withDoc "Secondary IP address" $
833
  optionalNEStringField "secondary_ip"
834

    
835
pReadd :: Field
836
pReadd =
837
  withDoc "Whether node is re-added to cluster" $
838
  defaultFalse "readd"
839

    
840
pNodeGroup :: Field
841
pNodeGroup =
842
  withDoc "Initial node group" $
843
  optionalNEStringField "group"
844

    
845
pMasterCapable :: Field
846
pMasterCapable =
847
  withDoc "Whether node can become master or master candidate" .
848
  optionalField $ booleanField "master_capable"
849

    
850
pVmCapable :: Field
851
pVmCapable =
852
  withDoc "Whether node can host instances" .
853
  optionalField $ booleanField "vm_capable"
854

    
855
pNdParams :: Field
856
pNdParams =
857
  withDoc "Node parameters" .
858
  renameField "genericNdParams" .
859
  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
860

    
861
pNames :: Field
862
pNames =
863
  withDoc "List of names" .
864
  defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
865

    
866
pNodes :: Field
867
pNodes =
868
  withDoc "List of nodes" .
869
  defaultField [| [] |] $ simpleField "nodes" [t| [NonEmptyString] |]
870

    
871
pStorageType :: Field
872
pStorageType =
873
  withDoc "Storage type" $ simpleField "storage_type" [t| StorageType |]
874

    
875
pStorageTypeOptional :: Field
876
pStorageTypeOptional =
877
  withDoc "Storage type" .
878
  renameField "StorageTypeOptional" .
879
  optionalField $ simpleField "storage_type" [t| StorageType |]
880

    
881
pStorageName :: Field
882
pStorageName =
883
  withDoc "Storage name" .
884
  renameField "StorageName" .
885
  optionalField $ simpleField "name" [t| NonEmptyString |]
886

    
887
pStorageChanges :: Field
888
pStorageChanges =
889
  withDoc "Requested storage changes" $
890
  simpleField "changes" [t| JSObject JSValue |]
891

    
892
pIgnoreConsistency :: Field
893
pIgnoreConsistency =
894
  withDoc "Whether to ignore disk consistency" $
895
  defaultFalse "ignore_consistency"
896

    
897
pMasterCandidate :: Field
898
pMasterCandidate =
899
  withDoc "Whether the node should become a master candidate" .
900
  optionalField $ booleanField "master_candidate"
901

    
902
pOffline :: Field
903
pOffline =
904
  withDoc "Whether to mark the node or instance offline" .
905
  optionalField $ booleanField "offline"
906

    
907
pDrained ::Field
908
pDrained =
909
  withDoc "Whether to mark the node as drained" .
910
  optionalField $ booleanField "drained"
911

    
912
pAutoPromote :: Field
913
pAutoPromote =
914
  withDoc "Whether node(s) should be promoted to master candidate if\
915
          \ necessary" $
916
  defaultFalse "auto_promote"
917

    
918
pPowered :: Field
919
pPowered =
920
  withDoc "Whether the node should be marked as powered" .
921
  optionalField $ booleanField "powered"
922

    
923
pMigrationMode :: Field
924
pMigrationMode =
925
  withDoc "Migration type (live/non-live)" .
926
  renameField "MigrationMode" .
927
  optionalField $
928
  simpleField "mode" [t| MigrationMode |]
929

    
930
pMigrationLive :: Field
931
pMigrationLive =
932
  withDoc "Obsolete \'live\' migration mode (do not use)" .
933
  renameField "OldLiveMode" . optionalField $ booleanField "live"
934

    
935
pMigrationTargetNode :: Field
936
pMigrationTargetNode =
937
  withDoc "Target node for instance migration/failover" $
938
  optionalNEStringField "target_node"
939

    
940
pMigrationTargetNodeUuid :: Field
941
pMigrationTargetNodeUuid =
942
  withDoc "Target node UUID for instance migration/failover" $
943
  optionalNEStringField "target_node_uuid"
944

    
945
pAllowRuntimeChgs :: Field
946
pAllowRuntimeChgs =
947
  withDoc "Whether to allow runtime changes while migrating" $
948
  defaultTrue "allow_runtime_changes"
949

    
950
pIgnoreIpolicy :: Field
951
pIgnoreIpolicy =
952
  withDoc "Whether to ignore ipolicy violations" $
953
  defaultFalse "ignore_ipolicy"
954

    
955
pIallocator :: Field
956
pIallocator =
957
  withDoc "Iallocator for deciding the target node for shared-storage\
958
          \ instances" $
959
  optionalNEStringField "iallocator"
960

    
961
pEarlyRelease :: Field
962
pEarlyRelease =
963
  withDoc "Whether to release locks as soon as possible" $
964
  defaultFalse "early_release"
965

    
966
pRemoteNode :: Field
967
pRemoteNode =
968
  withDoc "New secondary node" $
969
  optionalNEStringField "remote_node"
970

    
971
pRemoteNodeUuid :: Field
972
pRemoteNodeUuid =
973
  withDoc "New secondary node UUID" $
974
  optionalNEStringField "remote_node_uuid"
975

    
976
pEvacMode :: Field
977
pEvacMode =
978
  withDoc "Node evacuation mode" .
979
  renameField "EvacMode" $ simpleField "mode" [t| EvacMode |]
980

    
981
pInstanceName :: Field
982
pInstanceName =
983
  withDoc "A required instance name (for single-instance LUs)" $
984
  simpleField "instance_name" [t| String |]
985

    
986
pForceVariant :: Field
987
pForceVariant =
988
  withDoc "Whether to force an unknown OS variant" $
989
  defaultFalse "force_variant"
990

    
991
pWaitForSync :: Field
992
pWaitForSync =
993
  withDoc "Whether to wait for the disk to synchronize" $
994
  defaultTrue "wait_for_sync"
995

    
996
pNameCheck :: Field
997
pNameCheck =
998
  withDoc "Whether to check name" $
999
  defaultTrue "name_check"
1000

    
1001
pInstBeParams :: Field
1002
pInstBeParams =
1003
  withDoc "Backend parameters for instance" .
1004
  renameField "InstBeParams" .
1005
  defaultField [| toJSObject [] |] $
1006
  simpleField "beparams" [t| JSObject JSValue |]
1007

    
1008
pInstDisks :: Field
1009
pInstDisks =
1010
  withDoc "List of instance disks" .
1011
  renameField "instDisks" $ simpleField "disks" [t| [IDiskParams] |]
1012

    
1013
pDiskTemplate :: Field
1014
pDiskTemplate =
1015
  withDoc "Disk template" $
1016
  simpleField "disk_template" [t| DiskTemplate |]
1017

    
1018
pFileDriver :: Field
1019
pFileDriver =
1020
  withDoc "Driver for file-backed disks" .
1021
  optionalField $ simpleField "file_driver" [t| FileDriver |]
1022

    
1023
pFileStorageDir :: Field
1024
pFileStorageDir =
1025
  withDoc "Directory for storing file-backed disks" $
1026
  optionalNEStringField "file_storage_dir"
1027

    
1028
pInstHvParams :: Field
1029
pInstHvParams =
1030
  withDoc "Hypervisor parameters for instance, hypervisor-dependent" .
1031
  renameField "InstHvParams" .
1032
  defaultField [| toJSObject [] |] $
1033
  simpleField "hvparams" [t| JSObject JSValue |]
1034

    
1035
pHypervisor :: Field
1036
pHypervisor =
1037
  withDoc "Selected hypervisor for an instance" .
1038
  optionalField $
1039
  simpleField "hypervisor" [t| Hypervisor |]
1040

    
1041
pResetDefaults :: Field
1042
pResetDefaults =
1043
  withDoc "Reset instance parameters to default if equal" $
1044
  defaultFalse "identify_defaults"
1045

    
1046
pIpCheck :: Field
1047
pIpCheck =
1048
  withDoc "Whether to ensure instance's IP address is inactive" $
1049
  defaultTrue "ip_check"
1050

    
1051
pIpConflictsCheck :: Field
1052
pIpConflictsCheck =
1053
  withDoc "Whether to check for conflicting IP addresses" $
1054
  defaultTrue "conflicts_check"
1055

    
1056
pInstCreateMode :: Field
1057
pInstCreateMode =
1058
  withDoc "Instance creation mode" .
1059
  renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
1060

    
1061
pInstNics :: Field
1062
pInstNics =
1063
  withDoc "List of NIC (network interface) definitions" $
1064
  simpleField "nics" [t| [INicParams] |]
1065

    
1066
pNoInstall :: Field
1067
pNoInstall =
1068
  withDoc "Do not install the OS (will disable automatic start)" .
1069
  optionalField $ booleanField "no_install"
1070

    
1071
pInstOs :: Field
1072
pInstOs =
1073
  withDoc "OS type for instance installation" $
1074
  optionalNEStringField "os_type"
1075

    
1076
pInstOsParams :: Field
1077
pInstOsParams =
1078
  withDoc "OS parameters for instance" .
1079
  renameField "InstOsParams" .
1080
  defaultField [| toJSObject [] |] $
1081
  simpleField "osparams" [t| JSObject JSValue |]
1082

    
1083
pPrimaryNode :: Field
1084
pPrimaryNode =
1085
  withDoc "Primary node for an instance" $
1086
  optionalNEStringField "pnode"
1087

    
1088
pPrimaryNodeUuid :: Field
1089
pPrimaryNodeUuid =
1090
  withDoc "Primary node UUID for an instance" $
1091
  optionalNEStringField "pnode_uuid"
1092

    
1093
pSecondaryNode :: Field
1094
pSecondaryNode =
1095
  withDoc "Secondary node for an instance" $
1096
  optionalNEStringField "snode"
1097

    
1098
pSecondaryNodeUuid :: Field
1099
pSecondaryNodeUuid =
1100
  withDoc "Secondary node UUID for an instance" $
1101
  optionalNEStringField "snode_uuid"
1102

    
1103
pSourceHandshake :: Field
1104
pSourceHandshake =
1105
  withDoc "Signed handshake from source (remote import only)" .
1106
  optionalField $ simpleField "source_handshake" [t| [JSValue] |]
1107

    
1108
pSourceInstance :: Field
1109
pSourceInstance =
1110
  withDoc "Source instance name (remote import only)" $
1111
  optionalNEStringField "source_instance_name"
1112

    
1113
-- FIXME: non-negative int, whereas the constant is a plain int.
1114
pSourceShutdownTimeout :: Field
1115
pSourceShutdownTimeout =
1116
  withDoc "How long source instance was given to shut down (remote import\
1117
          \ only)" .
1118
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1119
  simpleField "source_shutdown_timeout" [t| NonNegative Int |]
1120

    
1121
pSourceX509Ca :: Field
1122
pSourceX509Ca =
1123
  withDoc "Source X509 CA in PEM format (remote import only)" $
1124
  optionalNEStringField "source_x509_ca"
1125

    
1126
pSrcNode :: Field
1127
pSrcNode =
1128
  withDoc "Source node for import" $
1129
  optionalNEStringField "src_node"
1130

    
1131
pSrcNodeUuid :: Field
1132
pSrcNodeUuid =
1133
  withDoc "Source node UUID for import" $
1134
  optionalNEStringField "src_node_uuid"
1135

    
1136
pSrcPath :: Field
1137
pSrcPath =
1138
  withDoc "Source directory for import" $
1139
  optionalNEStringField "src_path"
1140

    
1141
pStartInstance :: Field
1142
pStartInstance =
1143
  withDoc "Whether to start instance after creation" $
1144
  defaultTrue "start"
1145

    
1146
-- FIXME: unify/simplify with pTags, once that migrates to NonEmpty String"
1147
pInstTags :: Field
1148
pInstTags =
1149
  withDoc "Instance tags" .
1150
  renameField "InstTags" .
1151
  defaultField [| [] |] $
1152
  simpleField "tags" [t| [NonEmptyString] |]
1153

    
1154
pMultiAllocInstances :: Field
1155
pMultiAllocInstances =
1156
  withDoc "List of instance create opcodes describing the instances to\
1157
          \ allocate" .
1158
  renameField "InstMultiAlloc" .
1159
  defaultField [| [] |] $
1160
  simpleField "instances"[t| [JSValue] |]
1161

    
1162
pOpportunisticLocking :: Field
1163
pOpportunisticLocking =
1164
  withDoc "Whether to employ opportunistic locking for nodes, meaning\
1165
          \ nodes already locked by another opcode won't be considered for\
1166
          \ instance allocation (only when an iallocator is used)" $
1167
  defaultFalse "opportunistic_locking"
1168

    
1169
pInstanceUuid :: Field
1170
pInstanceUuid =
1171
  withDoc "An instance UUID (for single-instance LUs)" .
1172
  optionalField $ simpleField "instance_uuid" [t| NonEmptyString |]
1173

    
1174
pTempOsParams :: Field
1175
pTempOsParams =
1176
  withDoc "Temporary OS parameters (currently only in reinstall, might be\
1177
          \ added to install as well)" .
1178
  renameField "TempOsParams" .
1179
  optionalField $ simpleField "osparams" [t| JSObject JSValue |]
1180

    
1181
pShutdownTimeout :: Field
1182
pShutdownTimeout =
1183
  withDoc "How long to wait for instance to shut down" .
1184
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1185
  simpleField "shutdown_timeout" [t| NonNegative Int |]
1186

    
1187
-- | Another name for the shutdown timeout, because we like to be
1188
-- inconsistent.
1189
pShutdownTimeout' :: Field
1190
pShutdownTimeout' =
1191
  withDoc "How long to wait for instance to shut down" .
1192
  renameField "InstShutdownTimeout" .
1193
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1194
  simpleField "timeout" [t| NonNegative Int |]
1195

    
1196
pIgnoreFailures :: Field
1197
pIgnoreFailures =
1198
  withDoc "Whether to ignore failures during removal" $
1199
  defaultFalse "ignore_failures"
1200

    
1201
pNewName :: Field
1202
pNewName =
1203
  withDoc "New group or instance name" $
1204
  simpleField "new_name" [t| NonEmptyString |]
1205

    
1206
pIgnoreOfflineNodes :: Field
1207
pIgnoreOfflineNodes =
1208
  withDoc "Whether to ignore offline nodes" $
1209
  defaultFalse "ignore_offline_nodes"
1210

    
1211
pTempHvParams :: Field
1212
pTempHvParams =
1213
  withDoc "Temporary hypervisor parameters, hypervisor-dependent" .
1214
  renameField "TempHvParams" .
1215
  defaultField [| toJSObject [] |] $
1216
  simpleField "hvparams" [t| JSObject JSValue |]
1217

    
1218
pTempBeParams :: Field
1219
pTempBeParams =
1220
  withDoc "Temporary backend parameters" .
1221
  renameField "TempBeParams" .
1222
  defaultField [| toJSObject [] |] $
1223
  simpleField "beparams" [t| JSObject JSValue |]
1224

    
1225
pNoRemember :: Field
1226
pNoRemember =
1227
  withDoc "Do not remember instance state changes" $
1228
  defaultFalse "no_remember"
1229

    
1230
pStartupPaused :: Field
1231
pStartupPaused =
1232
  withDoc "Pause instance at startup" $
1233
  defaultFalse "startup_paused"
1234

    
1235
pIgnoreSecondaries :: Field
1236
pIgnoreSecondaries =
1237
  withDoc "Whether to start the instance even if secondary disks are failing" $
1238
  defaultFalse "ignore_secondaries"
1239

    
1240
pRebootType :: Field
1241
pRebootType =
1242
  withDoc "How to reboot the instance" $
1243
  simpleField "reboot_type" [t| RebootType |]
1244

    
1245
pReplaceDisksMode :: Field
1246
pReplaceDisksMode =
1247
  withDoc "Replacement mode" .
1248
  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1249

    
1250
pReplaceDisksList :: Field
1251
pReplaceDisksList =
1252
  withDoc "List of disk indices" .
1253
  renameField "ReplaceDisksList" .
1254
  defaultField [| [] |] $
1255
  simpleField "disks" [t| [DiskIndex] |]
1256

    
1257
pMigrationCleanup :: Field
1258
pMigrationCleanup =
1259
  withDoc "Whether a previously failed migration should be cleaned up" .
1260
  renameField "MigrationCleanup" $ defaultFalse "cleanup"
1261

    
1262
pAllowFailover :: Field
1263
pAllowFailover =
1264
  withDoc "Whether we can fallback to failover if migration is not possible" $
1265
  defaultFalse "allow_failover"
1266

    
1267
pMoveTargetNode :: Field
1268
pMoveTargetNode =
1269
  withDoc "Target node for instance move" .
1270
  renameField "MoveTargetNode" $
1271
  simpleField "target_node" [t| NonEmptyString |]
1272

    
1273
pMoveTargetNodeUuid :: Field
1274
pMoveTargetNodeUuid =
1275
  withDoc "Target node UUID for instance move" .
1276
  renameField "MoveTargetNodeUuid" . optionalField $
1277
  simpleField "target_node_uuid" [t| NonEmptyString |]
1278

    
1279
pMoveCompress :: Field
1280
pMoveCompress =
1281
  withDoc "Compression mode to use during instance moves" .
1282
  defaultField [| None |] $
1283
  simpleField "compress" [t| ImportExportCompression |]
1284

    
1285
pBackupCompress :: Field
1286
pBackupCompress =
1287
  withDoc "Compression mode to use for moves during backups/imports" .
1288
  defaultField [| None |] $
1289
  simpleField "compress" [t| ImportExportCompression |]
1290

    
1291
pIgnoreDiskSize :: Field
1292
pIgnoreDiskSize =
1293
  withDoc "Whether to ignore recorded disk size" $
1294
  defaultFalse "ignore_size"
1295

    
1296
pWaitForSyncFalse :: Field
1297
pWaitForSyncFalse =
1298
  withDoc "Whether to wait for the disk to synchronize (defaults to false)" $
1299
  defaultField [| False |] pWaitForSync
1300

    
1301
pRecreateDisksInfo :: Field
1302
pRecreateDisksInfo =
1303
  withDoc "Disk list for recreate disks" .
1304
  renameField "RecreateDisksInfo" .
1305
  defaultField [| RecreateDisksAll |] $
1306
  simpleField "disks" [t| RecreateDisksInfo |]
1307

    
1308
pStatic :: Field
1309
pStatic =
1310
  withDoc "Whether to only return configuration data without querying nodes" $
1311
  defaultFalse "static"
1312

    
1313
pInstParamsNicChanges :: Field
1314
pInstParamsNicChanges =
1315
  withDoc "List of NIC changes" .
1316
  renameField "InstNicChanges" .
1317
  defaultField [| SetParamsEmpty |] $
1318
  simpleField "nics" [t| SetParamsMods INicParams |]
1319

    
1320
pInstParamsDiskChanges :: Field
1321
pInstParamsDiskChanges =
1322
  withDoc "List of disk changes" .
1323
  renameField "InstDiskChanges" .
1324
  defaultField [| SetParamsEmpty |] $
1325
  simpleField "disks" [t| SetParamsMods IDiskParams |]
1326

    
1327
pRuntimeMem :: Field
1328
pRuntimeMem =
1329
  withDoc "New runtime memory" .
1330
  optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1331

    
1332
pOptDiskTemplate :: Field
1333
pOptDiskTemplate =
1334
  withDoc "Instance disk template" .
1335
  optionalField .
1336
  renameField "OptDiskTemplate" $
1337
  simpleField "disk_template" [t| DiskTemplate |]
1338

    
1339
pOsNameChange :: Field
1340
pOsNameChange =
1341
  withDoc "Change the instance's OS without reinstalling the instance" $
1342
  optionalNEStringField "os_name"
1343

    
1344
pDiskIndex :: Field
1345
pDiskIndex =
1346
  withDoc "Disk index for e.g. grow disk" .
1347
  renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
1348

    
1349
pDiskChgAmount :: Field
1350
pDiskChgAmount =
1351
  withDoc "Disk amount to add or grow to" .
1352
  renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
1353

    
1354
pDiskChgAbsolute :: Field
1355
pDiskChgAbsolute =
1356
  withDoc
1357
    "Whether the amount parameter is an absolute target or a relative one" .
1358
  renameField "DiskChkAbsolute" $ defaultFalse "absolute"
1359

    
1360
pTargetGroups :: Field
1361
pTargetGroups =
1362
  withDoc
1363
    "Destination group names or UUIDs (defaults to \"all but current group\")" .
1364
  optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
1365

    
1366
pNodeGroupAllocPolicy :: Field
1367
pNodeGroupAllocPolicy =
1368
  withDoc "Instance allocation policy" .
1369
  optionalField $
1370
  simpleField "alloc_policy" [t| AllocPolicy |]
1371

    
1372
pGroupNodeParams :: Field
1373
pGroupNodeParams =
1374
  withDoc "Default node parameters for group" .
1375
  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
1376

    
1377
pExportMode :: Field
1378
pExportMode =
1379
  withDoc "Export mode" .
1380
  renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1381

    
1382
-- FIXME: Rename target_node as it changes meaning for different
1383
-- export modes (e.g. "destination")
1384
pExportTargetNode :: Field
1385
pExportTargetNode =
1386
  withDoc "Target node (depends on export mode)" .
1387
  renameField "ExportTarget" $
1388
  simpleField "target_node" [t| ExportTarget |]
1389

    
1390
pExportTargetNodeUuid :: Field
1391
pExportTargetNodeUuid =
1392
  withDoc "Target node UUID (if local export)" .
1393
  renameField "ExportTargetNodeUuid" . optionalField $
1394
  simpleField "target_node_uuid" [t| NonEmptyString |]
1395

    
1396
pShutdownInstance :: Field
1397
pShutdownInstance =
1398
  withDoc "Whether to shutdown the instance before export" $
1399
  defaultTrue "shutdown"
1400

    
1401
pRemoveInstance :: Field
1402
pRemoveInstance =
1403
  withDoc "Whether to remove instance after export" $
1404
  defaultFalse "remove_instance"
1405

    
1406
pIgnoreRemoveFailures :: Field
1407
pIgnoreRemoveFailures =
1408
  withDoc "Whether to ignore failures while removing instances" $
1409
  defaultFalse "ignore_remove_failures"
1410

    
1411
pX509KeyName :: Field
1412
pX509KeyName =
1413
  withDoc "Name of X509 key (remote export only)" .
1414
  optionalField $ simpleField "x509_key_name" [t| [JSValue] |]
1415

    
1416
pX509DestCA :: Field
1417
pX509DestCA =
1418
  withDoc "Destination X509 CA (remote export only)" $
1419
  optionalNEStringField "destination_x509_ca"
1420

    
1421
pTagsObject :: Field
1422
pTagsObject =
1423
  withDoc "Tag kind" $
1424
  simpleField "kind" [t| TagKind |]
1425

    
1426
pTagsName :: Field
1427
pTagsName =
1428
  withDoc "Name of object" .
1429
  renameField "TagsGetName" .
1430
  optionalField $ simpleField "name" [t| String |]
1431

    
1432
pTagsList :: Field
1433
pTagsList =
1434
  withDoc "List of tag names" $
1435
  simpleField "tags" [t| [String] |]
1436

    
1437
-- FIXME: this should be compiled at load time?
1438
pTagSearchPattern :: Field
1439
pTagSearchPattern =
1440
  withDoc "Search pattern (regular expression)" .
1441
  renameField "TagSearchPattern" $
1442
  simpleField "pattern" [t| NonEmptyString |]
1443

    
1444
pDelayDuration :: Field
1445
pDelayDuration =
1446
  withDoc "Duration parameter for 'OpTestDelay'" .
1447
  renameField "DelayDuration" $
1448
  simpleField "duration" [t| Double |]
1449

    
1450
pDelayOnMaster :: Field
1451
pDelayOnMaster =
1452
  withDoc "on_master field for 'OpTestDelay'" .
1453
  renameField "DelayOnMaster" $
1454
  defaultTrue "on_master"
1455

    
1456
pDelayOnNodes :: Field
1457
pDelayOnNodes =
1458
  withDoc "on_nodes field for 'OpTestDelay'" .
1459
  renameField "DelayOnNodes" .
1460
  defaultField [| [] |] $
1461
  simpleField "on_nodes" [t| [NonEmptyString] |]
1462

    
1463
pDelayOnNodeUuids :: Field
1464
pDelayOnNodeUuids =
1465
  withDoc "on_node_uuids field for 'OpTestDelay'" .
1466
  renameField "DelayOnNodeUuids" . optionalField $
1467
  simpleField "on_node_uuids" [t| [NonEmptyString] |]
1468

    
1469
pDelayRepeat :: Field
1470
pDelayRepeat =
1471
  withDoc "Repeat parameter for OpTestDelay" .
1472
  renameField "DelayRepeat" .
1473
  defaultField [| forceNonNeg (0::Int) |] $
1474
  simpleField "repeat" [t| NonNegative Int |]
1475

    
1476
pIAllocatorDirection :: Field
1477
pIAllocatorDirection =
1478
  withDoc "IAllocator test direction" .
1479
  renameField "IAllocatorDirection" $
1480
  simpleField "direction" [t| IAllocatorTestDir |]
1481

    
1482
pIAllocatorMode :: Field
1483
pIAllocatorMode =
1484
  withDoc "IAllocator test mode" .
1485
  renameField "IAllocatorMode" $
1486
  simpleField "mode" [t| IAllocatorMode |]
1487

    
1488
pIAllocatorReqName :: Field
1489
pIAllocatorReqName =
1490
  withDoc "IAllocator target name (new instance, node to evac, etc.)" .
1491
  renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
1492

    
1493
pIAllocatorNics :: Field
1494
pIAllocatorNics =
1495
  withDoc "Custom OpTestIAllocator nics" .
1496
  renameField "IAllocatorNics" .
1497
  optionalField $ simpleField "nics" [t| [INicParams] |]
1498

    
1499
pIAllocatorDisks :: Field
1500
pIAllocatorDisks =
1501
  withDoc "Custom OpTestAllocator disks" .
1502
  renameField "IAllocatorDisks" .
1503
  optionalField $ simpleField "disks" [t| [JSValue] |]
1504

    
1505
pIAllocatorMemory :: Field
1506
pIAllocatorMemory =
1507
  withDoc "IAllocator memory field" .
1508
  renameField "IAllocatorMem" .
1509
  optionalField $
1510
  simpleField "memory" [t| NonNegative Int |]
1511

    
1512
pIAllocatorVCpus :: Field
1513
pIAllocatorVCpus =
1514
  withDoc "IAllocator vcpus field" .
1515
  renameField "IAllocatorVCpus" .
1516
  optionalField $
1517
  simpleField "vcpus" [t| NonNegative Int |]
1518

    
1519
pIAllocatorOs :: Field
1520
pIAllocatorOs =
1521
  withDoc "IAllocator os field" .
1522
  renameField "IAllocatorOs" $ optionalNEStringField "os"
1523

    
1524
pIAllocatorInstances :: Field
1525
pIAllocatorInstances =
1526
  withDoc "IAllocator instances field" .
1527
  renameField "IAllocatorInstances " .
1528
  optionalField $
1529
  simpleField "instances" [t| [NonEmptyString] |]
1530

    
1531
pIAllocatorEvacMode :: Field
1532
pIAllocatorEvacMode =
1533
  withDoc "IAllocator evac mode" .
1534
  renameField "IAllocatorEvacMode" .
1535
  optionalField $
1536
  simpleField "evac_mode" [t| EvacMode |]
1537

    
1538
pIAllocatorSpindleUse :: Field
1539
pIAllocatorSpindleUse =
1540
  withDoc "IAllocator spindle use" .
1541
  renameField "IAllocatorSpindleUse" .
1542
  defaultField [| forceNonNeg (1::Int) |] $
1543
  simpleField "spindle_use" [t| NonNegative Int |]
1544

    
1545
pIAllocatorCount :: Field
1546
pIAllocatorCount =
1547
  withDoc "IAllocator count field" .
1548
  renameField "IAllocatorCount" .
1549
  defaultField [| forceNonNeg (1::Int) |] $
1550
  simpleField "count" [t| NonNegative Int |]
1551

    
1552
pJQueueNotifyWaitLock :: Field
1553
pJQueueNotifyWaitLock =
1554
  withDoc "'OpTestJqueue' notify_waitlock" $
1555
  defaultFalse "notify_waitlock"
1556

    
1557
pJQueueNotifyExec :: Field
1558
pJQueueNotifyExec =
1559
  withDoc "'OpTestJQueue' notify_exec" $
1560
  defaultFalse "notify_exec"
1561

    
1562
pJQueueLogMessages :: Field
1563
pJQueueLogMessages =
1564
  withDoc "'OpTestJQueue' log_messages" .
1565
  defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
1566

    
1567
pJQueueFail :: Field
1568
pJQueueFail =
1569
  withDoc "'OpTestJQueue' fail attribute" .
1570
  renameField "JQueueFail" $ defaultFalse "fail"
1571

    
1572
pTestDummyResult :: Field
1573
pTestDummyResult =
1574
  withDoc "'OpTestDummy' result field" .
1575
  renameField "TestDummyResult" $ simpleField "result" [t| JSValue |]
1576

    
1577
pTestDummyMessages :: Field
1578
pTestDummyMessages =
1579
  withDoc "'OpTestDummy' messages field" .
1580
  renameField "TestDummyMessages" $
1581
  simpleField "messages" [t| JSValue |]
1582

    
1583
pTestDummyFail :: Field
1584
pTestDummyFail =
1585
  withDoc "'OpTestDummy' fail field" .
1586
  renameField "TestDummyFail" $ simpleField "fail" [t| JSValue |]
1587

    
1588
pTestDummySubmitJobs :: Field
1589
pTestDummySubmitJobs =
1590
  withDoc "'OpTestDummy' submit_jobs field" .
1591
  renameField "TestDummySubmitJobs" $
1592
  simpleField "submit_jobs" [t| JSValue |]
1593

    
1594
pNetworkName :: Field
1595
pNetworkName =
1596
  withDoc "Network name" $
1597
  simpleField "network_name" [t| NonEmptyString |]
1598

    
1599
pNetworkAddress4 :: Field
1600
pNetworkAddress4 =
1601
  withDoc "Network address (IPv4 subnet)" .
1602
  renameField "NetworkAddress4" $
1603
  simpleField "network" [t| IPv4Network |]
1604

    
1605
pNetworkGateway4 :: Field
1606
pNetworkGateway4 =
1607
  withDoc "Network gateway (IPv4 address)" .
1608
  renameField "NetworkGateway4" .
1609
  optionalField $ simpleField "gateway" [t| IPv4Address |]
1610

    
1611
pNetworkAddress6 :: Field
1612
pNetworkAddress6 =
1613
  withDoc "Network address (IPv6 subnet)" .
1614
  renameField "NetworkAddress6" .
1615
  optionalField $ simpleField "network6" [t| IPv6Network |]
1616

    
1617
pNetworkGateway6 :: Field
1618
pNetworkGateway6 =
1619
  withDoc "Network gateway (IPv6 address)" .
1620
  renameField "NetworkGateway6" .
1621
  optionalField $ simpleField "gateway6" [t| IPv6Address |]
1622

    
1623
pNetworkMacPrefix :: Field
1624
pNetworkMacPrefix =
1625
  withDoc "Network specific mac prefix (that overrides the cluster one)" .
1626
  renameField "NetMacPrefix" $
1627
  optionalNEStringField "mac_prefix"
1628

    
1629
pNetworkAddRsvdIps :: Field
1630
pNetworkAddRsvdIps =
1631
  withDoc "Which IP addresses to reserve" .
1632
  renameField "NetworkAddRsvdIps" .
1633
  optionalField $
1634
  simpleField "add_reserved_ips" [t| [IPv4Address] |]
1635

    
1636
pNetworkRemoveRsvdIps :: Field
1637
pNetworkRemoveRsvdIps =
1638
  withDoc "Which external IP addresses to release" .
1639
  renameField "NetworkRemoveRsvdIps" .
1640
  optionalField $
1641
  simpleField "remove_reserved_ips" [t| [IPv4Address] |]
1642

    
1643
pNetworkMode :: Field
1644
pNetworkMode =
1645
  withDoc "Network mode when connecting to a group" $
1646
  simpleField "network_mode" [t| NICMode |]
1647

    
1648
pNetworkLink :: Field
1649
pNetworkLink =
1650
  withDoc "Network link when connecting to a group" $
1651
  simpleField "network_link" [t| NonEmptyString |]