Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ cc5ab470

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

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

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

    
275
-- * Helper functions and types
276

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

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

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

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

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

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

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

    
310
-- ** Disks
311

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

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

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

    
328
-- ** I* param types
329

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

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

    
348
-- | Disk modification definition.
349
$(buildObject "IDiskParams" "idisk"
350
  [ specialNumericalField 'parseUnitAssumeBinary . optionalField
351
      $ simpleField C.idiskSize               [t| Int            |]
352
  , optionalField $ simpleField C.idiskMode   [t| DiskAccess     |]
353
  , optionalField $ simpleField C.idiskAdopt  [t| NonEmptyString |]
354
  , optionalField $ simpleField C.idiskVg     [t| NonEmptyString |]
355
  , optionalField $ simpleField C.idiskMetavg [t| NonEmptyString |]
356
  , optionalField $ simpleField C.idiskName   [t| NonEmptyString |]
357
  , optionalField $ simpleField C.idiskSpindles [t| Int          |]
358
  ])
359

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

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

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

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

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

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

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

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

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

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

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

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

    
451
-- * Common opcode parameters
452

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

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

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

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

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

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

    
485
-- * Parameters
486

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
631
pUidPool :: Field
632
pUidPool =
633
  withDoc "Set UID pool, must be list of lists describing UID ranges\
634
          \ (two items, start and end inclusive)" .
635
  optionalField $ simpleField "uid_pool" [t| [(Int, Int)] |]
636

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

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

    
649
pMaintainNodeHealth :: Field
650
pMaintainNodeHealth =
651
  withDoc "Whether to automatically maintain node health" .
652
  optionalField $ booleanField "maintain_node_health"
653

    
654
-- | Whether to modify and keep in sync the @/etc/hosts@ files of nodes.
655
pModifyEtcHosts :: Field
656
pModifyEtcHosts = optionalField $ booleanField "modify_etc_hosts"
657

    
658
-- | Whether to wipe disks before allocating them to instances.
659
pPreallocWipeDisks :: Field
660
pPreallocWipeDisks =
661
  withDoc "Whether to wipe disks before allocating them to instances" .
662
  optionalField $ booleanField "prealloc_wipe_disks"
663

    
664
pNicParams :: Field
665
pNicParams =
666
  withDoc "Cluster-wide NIC parameter defaults" .
667
  optionalField $ simpleField "nicparams" [t| INicParams |]
668

    
669
pIpolicy :: Field
670
pIpolicy =
671
  withDoc "Ipolicy specs" .
672
  optionalField $ simpleField "ipolicy" [t| JSObject JSValue |]
673

    
674
pDrbdHelper :: Field
675
pDrbdHelper =
676
  withDoc "DRBD helper program" $
677
  optionalStringField "drbd_helper"
678

    
679
pDefaultIAllocator :: Field
680
pDefaultIAllocator =
681
  withDoc "Default iallocator for cluster" $
682
  optionalStringField "default_iallocator"
683

    
684
pDefaultIAllocatorParams :: Field
685
pDefaultIAllocatorParams =
686
  withDoc "Default iallocator parameters for cluster" . optionalField
687
    $ simpleField "default_iallocator_params" [t| JSObject JSValue |]
688

    
689
pMasterNetdev :: Field
690
pMasterNetdev =
691
  withDoc "Master network device" $
692
  optionalStringField "master_netdev"
693

    
694
pMasterNetmask :: Field
695
pMasterNetmask =
696
  withDoc "Netmask of the master IP" .
697
  optionalField $ simpleField "master_netmask" [t| NonNegative Int |]
698

    
699
pReservedLvs :: Field
700
pReservedLvs =
701
  withDoc "List of reserved LVs" .
702
  optionalField $ simpleField "reserved_lvs" [t| [NonEmptyString] |]
703

    
704
pHiddenOs :: Field
705
pHiddenOs =
706
  withDoc "Modify list of hidden operating systems: each modification\
707
          \ must have two items, the operation and the OS name; the operation\
708
          \ can be add or remove" .
709
  optionalField $ simpleField "hidden_os" [t| [(DdmSimple, NonEmptyString)] |]
710

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

    
719
pUseExternalMipScript :: Field
720
pUseExternalMipScript =
721
  withDoc "Whether to use an external master IP address setup script" .
722
  optionalField $ booleanField "use_external_mip_script"
723

    
724
pEnabledDiskTemplates :: Field
725
pEnabledDiskTemplates =
726
  withDoc "List of enabled disk templates" .
727
  optionalField $
728
  simpleField "enabled_disk_templates" [t| [DiskTemplate] |]
729

    
730
pQueryWhat :: Field
731
pQueryWhat =
732
  withDoc "Resource(s) to query for" $
733
  simpleField "what" [t| Qlang.QueryTypeOp |]
734

    
735
pUseLocking :: Field
736
pUseLocking =
737
  withDoc "Whether to use synchronization" $
738
  defaultFalse "use_locking"
739

    
740
pQueryFields :: Field
741
pQueryFields =
742
  withDoc "Requested fields" $
743
  simpleField "fields" [t| [NonEmptyString] |]
744

    
745
pQueryFilter :: Field
746
pQueryFilter =
747
  withDoc "Query filter" .
748
  optionalField $ simpleField "qfilter" [t| [JSValue] |]
749

    
750
pQueryFieldsFields :: Field
751
pQueryFieldsFields =
752
  withDoc "Requested fields; if not given, all are returned" .
753
  renameField "QueryFieldsFields" $
754
  optionalField pQueryFields
755

    
756
pNodeNames :: Field
757
pNodeNames =
758
  withDoc "List of node names to run the OOB command against" .
759
  defaultField [| [] |] $ simpleField "node_names" [t| [NonEmptyString] |]
760

    
761
pNodeUuids :: Field
762
pNodeUuids =
763
  withDoc "List of node UUIDs" .
764
  optionalField $ simpleField "node_uuids" [t| [NonEmptyString] |]
765

    
766
pOobCommand :: Field
767
pOobCommand =
768
  withDoc "OOB command to run" $
769
  simpleField "command" [t| OobCommand |]
770

    
771
pOobTimeout :: Field
772
pOobTimeout =
773
  withDoc "Timeout before the OOB helper will be terminated" .
774
  defaultField [| C.oobTimeout |] $
775
  simpleField "timeout" [t| Int |]
776

    
777
pIgnoreStatus :: Field
778
pIgnoreStatus =
779
  withDoc "Ignores the node offline status for power off" $
780
  defaultFalse "ignore_status"
781

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

    
791
pRequiredNodes :: Field
792
pRequiredNodes =
793
  withDoc "Required list of node names" .
794
  renameField "ReqNodes " $ simpleField "nodes" [t| [NonEmptyString] |]
795

    
796
pRequiredNodeUuids :: Field
797
pRequiredNodeUuids =
798
  withDoc "Required list of node UUIDs" .
799
  renameField "ReqNodeUuids " . optionalField $
800
  simpleField "node_uuids" [t| [NonEmptyString] |]
801

    
802
pRestrictedCommand :: Field
803
pRestrictedCommand =
804
  withDoc "Restricted command name" .
805
  renameField "RestrictedCommand" $
806
  simpleField "command" [t| NonEmptyString |]
807

    
808
pNodeName :: Field
809
pNodeName =
810
  withDoc "A required node name (for single-node LUs)" $
811
  simpleField "node_name" [t| NonEmptyString |]
812

    
813
pNodeUuid :: Field
814
pNodeUuid =
815
  withDoc "A node UUID (for single-node LUs)" .
816
  optionalField $ simpleField "node_uuid" [t| NonEmptyString |]
817

    
818
pPrimaryIp :: Field
819
pPrimaryIp =
820
  withDoc "Primary IP address" .
821
  optionalField $
822
  simpleField "primary_ip" [t| NonEmptyString |]
823

    
824
pSecondaryIp :: Field
825
pSecondaryIp =
826
  withDoc "Secondary IP address" $
827
  optionalNEStringField "secondary_ip"
828

    
829
pReadd :: Field
830
pReadd =
831
  withDoc "Whether node is re-added to cluster" $
832
  defaultFalse "readd"
833

    
834
pNodeGroup :: Field
835
pNodeGroup =
836
  withDoc "Initial node group" $
837
  optionalNEStringField "group"
838

    
839
pMasterCapable :: Field
840
pMasterCapable =
841
  withDoc "Whether node can become master or master candidate" .
842
  optionalField $ booleanField "master_capable"
843

    
844
pVmCapable :: Field
845
pVmCapable =
846
  withDoc "Whether node can host instances" .
847
  optionalField $ booleanField "vm_capable"
848

    
849
pNdParams :: Field
850
pNdParams =
851
  withDoc "Node parameters" .
852
  renameField "genericNdParams" .
853
  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
854

    
855
pNames :: Field
856
pNames =
857
  withDoc "List of names" .
858
  defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
859

    
860
pNodes :: Field
861
pNodes =
862
  withDoc "List of nodes" .
863
  defaultField [| [] |] $ simpleField "nodes" [t| [NonEmptyString] |]
864

    
865
pStorageType :: Field
866
pStorageType =
867
  withDoc "Storage type" $ simpleField "storage_type" [t| StorageType |]
868

    
869
pStorageTypeOptional :: Field
870
pStorageTypeOptional =
871
  withDoc "Storage type" .
872
  renameField "StorageTypeOptional" .
873
  optionalField $ simpleField "storage_type" [t| StorageType |]
874

    
875
pStorageName :: Field
876
pStorageName =
877
  withDoc "Storage name" .
878
  renameField "StorageName" .
879
  optionalField $ simpleField "name" [t| NonEmptyString |]
880

    
881
pStorageChanges :: Field
882
pStorageChanges =
883
  withDoc "Requested storage changes" $
884
  simpleField "changes" [t| JSObject JSValue |]
885

    
886
pIgnoreConsistency :: Field
887
pIgnoreConsistency =
888
  withDoc "Whether to ignore disk consistency" $
889
  defaultFalse "ignore_consistency"
890

    
891
pMasterCandidate :: Field
892
pMasterCandidate =
893
  withDoc "Whether the node should become a master candidate" .
894
  optionalField $ booleanField "master_candidate"
895

    
896
pOffline :: Field
897
pOffline =
898
  withDoc "Whether to mark the node or instance offline" .
899
  optionalField $ booleanField "offline"
900

    
901
pDrained ::Field
902
pDrained =
903
  withDoc "Whether to mark the node as drained" .
904
  optionalField $ booleanField "drained"
905

    
906
pAutoPromote :: Field
907
pAutoPromote =
908
  withDoc "Whether node(s) should be promoted to master candidate if\
909
          \ necessary" $
910
  defaultFalse "auto_promote"
911

    
912
pPowered :: Field
913
pPowered =
914
  withDoc "Whether the node should be marked as powered" .
915
  optionalField $ booleanField "powered"
916

    
917
pMigrationMode :: Field
918
pMigrationMode =
919
  withDoc "Migration type (live/non-live)" .
920
  renameField "MigrationMode" .
921
  optionalField $
922
  simpleField "mode" [t| MigrationMode |]
923

    
924
pMigrationLive :: Field
925
pMigrationLive =
926
  withDoc "Obsolete \'live\' migration mode (do not use)" .
927
  renameField "OldLiveMode" . optionalField $ booleanField "live"
928

    
929
pMigrationTargetNode :: Field
930
pMigrationTargetNode =
931
  withDoc "Target node for instance migration/failover" $
932
  optionalNEStringField "target_node"
933

    
934
pMigrationTargetNodeUuid :: Field
935
pMigrationTargetNodeUuid =
936
  withDoc "Target node UUID for instance migration/failover" $
937
  optionalNEStringField "target_node_uuid"
938

    
939
pAllowRuntimeChgs :: Field
940
pAllowRuntimeChgs =
941
  withDoc "Whether to allow runtime changes while migrating" $
942
  defaultTrue "allow_runtime_changes"
943

    
944
pIgnoreIpolicy :: Field
945
pIgnoreIpolicy =
946
  withDoc "Whether to ignore ipolicy violations" $
947
  defaultFalse "ignore_ipolicy"
948

    
949
pIallocator :: Field
950
pIallocator =
951
  withDoc "Iallocator for deciding the target node for shared-storage\
952
          \ instances" $
953
  optionalNEStringField "iallocator"
954

    
955
pEarlyRelease :: Field
956
pEarlyRelease =
957
  withDoc "Whether to release locks as soon as possible" $
958
  defaultFalse "early_release"
959

    
960
pRemoteNode :: Field
961
pRemoteNode =
962
  withDoc "New secondary node" $
963
  optionalNEStringField "remote_node"
964

    
965
pRemoteNodeUuid :: Field
966
pRemoteNodeUuid =
967
  withDoc "New secondary node UUID" $
968
  optionalNEStringField "remote_node_uuid"
969

    
970
pEvacMode :: Field
971
pEvacMode =
972
  withDoc "Node evacuation mode" .
973
  renameField "EvacMode" $ simpleField "mode" [t| EvacMode |]
974

    
975
pInstanceName :: Field
976
pInstanceName =
977
  withDoc "A required instance name (for single-instance LUs)" $
978
  simpleField "instance_name" [t| String |]
979

    
980
pForceVariant :: Field
981
pForceVariant =
982
  withDoc "Whether to force an unknown OS variant" $
983
  defaultFalse "force_variant"
984

    
985
pWaitForSync :: Field
986
pWaitForSync =
987
  withDoc "Whether to wait for the disk to synchronize" $
988
  defaultTrue "wait_for_sync"
989

    
990
pNameCheck :: Field
991
pNameCheck =
992
  withDoc "Whether to check name" $
993
  defaultTrue "name_check"
994

    
995
pInstBeParams :: Field
996
pInstBeParams =
997
  withDoc "Backend parameters for instance" .
998
  renameField "InstBeParams" .
999
  defaultField [| toJSObject [] |] $
1000
  simpleField "beparams" [t| JSObject JSValue |]
1001

    
1002
pInstDisks :: Field
1003
pInstDisks =
1004
  withDoc "List of instance disks" .
1005
  renameField "instDisks" $ simpleField "disks" [t| [IDiskParams] |]
1006

    
1007
pDiskTemplate :: Field
1008
pDiskTemplate =
1009
  withDoc "Disk template" $
1010
  simpleField "disk_template" [t| DiskTemplate |]
1011

    
1012
pFileDriver :: Field
1013
pFileDriver =
1014
  withDoc "Driver for file-backed disks" .
1015
  optionalField $ simpleField "file_driver" [t| FileDriver |]
1016

    
1017
pFileStorageDir :: Field
1018
pFileStorageDir =
1019
  withDoc "Directory for storing file-backed disks" $
1020
  optionalNEStringField "file_storage_dir"
1021

    
1022
pInstHvParams :: Field
1023
pInstHvParams =
1024
  withDoc "Hypervisor parameters for instance, hypervisor-dependent" .
1025
  renameField "InstHvParams" .
1026
  defaultField [| toJSObject [] |] $
1027
  simpleField "hvparams" [t| JSObject JSValue |]
1028

    
1029
pHypervisor :: Field
1030
pHypervisor =
1031
  withDoc "Selected hypervisor for an instance" .
1032
  optionalField $
1033
  simpleField "hypervisor" [t| Hypervisor |]
1034

    
1035
pResetDefaults :: Field
1036
pResetDefaults =
1037
  withDoc "Reset instance parameters to default if equal" $
1038
  defaultFalse "identify_defaults"
1039

    
1040
pIpCheck :: Field
1041
pIpCheck =
1042
  withDoc "Whether to ensure instance's IP address is inactive" $
1043
  defaultTrue "ip_check"
1044

    
1045
pIpConflictsCheck :: Field
1046
pIpConflictsCheck =
1047
  withDoc "Whether to check for conflicting IP addresses" $
1048
  defaultTrue "conflicts_check"
1049

    
1050
pInstCreateMode :: Field
1051
pInstCreateMode =
1052
  withDoc "Instance creation mode" .
1053
  renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
1054

    
1055
pInstNics :: Field
1056
pInstNics =
1057
  withDoc "List of NIC (network interface) definitions" $
1058
  simpleField "nics" [t| [INicParams] |]
1059

    
1060
pNoInstall :: Field
1061
pNoInstall =
1062
  withDoc "Do not install the OS (will disable automatic start)" .
1063
  optionalField $ booleanField "no_install"
1064

    
1065
pInstOs :: Field
1066
pInstOs =
1067
  withDoc "OS type for instance installation" $
1068
  optionalNEStringField "os_type"
1069

    
1070
pInstOsParams :: Field
1071
pInstOsParams =
1072
  withDoc "OS parameters for instance" .
1073
  renameField "InstOsParams" .
1074
  defaultField [| toJSObject [] |] $
1075
  simpleField "osparams" [t| JSObject JSValue |]
1076

    
1077
pPrimaryNode :: Field
1078
pPrimaryNode =
1079
  withDoc "Primary node for an instance" $
1080
  optionalNEStringField "pnode"
1081

    
1082
pPrimaryNodeUuid :: Field
1083
pPrimaryNodeUuid =
1084
  withDoc "Primary node UUID for an instance" $
1085
  optionalNEStringField "pnode_uuid"
1086

    
1087
pSecondaryNode :: Field
1088
pSecondaryNode =
1089
  withDoc "Secondary node for an instance" $
1090
  optionalNEStringField "snode"
1091

    
1092
pSecondaryNodeUuid :: Field
1093
pSecondaryNodeUuid =
1094
  withDoc "Secondary node UUID for an instance" $
1095
  optionalNEStringField "snode_uuid"
1096

    
1097
pSourceHandshake :: Field
1098
pSourceHandshake =
1099
  withDoc "Signed handshake from source (remote import only)" .
1100
  optionalField $ simpleField "source_handshake" [t| [JSValue] |]
1101

    
1102
pSourceInstance :: Field
1103
pSourceInstance =
1104
  withDoc "Source instance name (remote import only)" $
1105
  optionalNEStringField "source_instance_name"
1106

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

    
1115
pSourceX509Ca :: Field
1116
pSourceX509Ca =
1117
  withDoc "Source X509 CA in PEM format (remote import only)" $
1118
  optionalNEStringField "source_x509_ca"
1119

    
1120
pSrcNode :: Field
1121
pSrcNode =
1122
  withDoc "Source node for import" $
1123
  optionalNEStringField "src_node"
1124

    
1125
pSrcNodeUuid :: Field
1126
pSrcNodeUuid =
1127
  withDoc "Source node UUID for import" $
1128
  optionalNEStringField "src_node_uuid"
1129

    
1130
pSrcPath :: Field
1131
pSrcPath =
1132
  withDoc "Source directory for import" $
1133
  optionalNEStringField "src_path"
1134

    
1135
pStartInstance :: Field
1136
pStartInstance =
1137
  withDoc "Whether to start instance after creation" $
1138
  defaultTrue "start"
1139

    
1140
-- FIXME: unify/simplify with pTags, once that migrates to NonEmpty String"
1141
pInstTags :: Field
1142
pInstTags =
1143
  withDoc "Instance tags" .
1144
  renameField "InstTags" .
1145
  defaultField [| [] |] $
1146
  simpleField "tags" [t| [NonEmptyString] |]
1147

    
1148
pMultiAllocInstances :: Field
1149
pMultiAllocInstances =
1150
  withDoc "List of instance create opcodes describing the instances to\
1151
          \ allocate" .
1152
  renameField "InstMultiAlloc" .
1153
  defaultField [| [] |] $
1154
  simpleField "instances"[t| [JSValue] |]
1155

    
1156
pOpportunisticLocking :: Field
1157
pOpportunisticLocking =
1158
  withDoc "Whether to employ opportunistic locking for nodes, meaning\
1159
          \ nodes already locked by another opcode won't be considered for\
1160
          \ instance allocation (only when an iallocator is used)" $
1161
  defaultFalse "opportunistic_locking"
1162

    
1163
pInstanceUuid :: Field
1164
pInstanceUuid =
1165
  withDoc "An instance UUID (for single-instance LUs)" .
1166
  optionalField $ simpleField "instance_uuid" [t| NonEmptyString |]
1167

    
1168
pTempOsParams :: Field
1169
pTempOsParams =
1170
  withDoc "Temporary OS parameters (currently only in reinstall, might be\
1171
          \ added to install as well)" .
1172
  renameField "TempOsParams" .
1173
  optionalField $ simpleField "osparams" [t| JSObject JSValue |]
1174

    
1175
pShutdownTimeout :: Field
1176
pShutdownTimeout =
1177
  withDoc "How long to wait for instance to shut down" .
1178
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1179
  simpleField "shutdown_timeout" [t| NonNegative Int |]
1180

    
1181
-- | Another name for the shutdown timeout, because we like to be
1182
-- inconsistent.
1183
pShutdownTimeout' :: Field
1184
pShutdownTimeout' =
1185
  withDoc "How long to wait for instance to shut down" .
1186
  renameField "InstShutdownTimeout" .
1187
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1188
  simpleField "timeout" [t| NonNegative Int |]
1189

    
1190
pIgnoreFailures :: Field
1191
pIgnoreFailures =
1192
  withDoc "Whether to ignore failures during removal" $
1193
  defaultFalse "ignore_failures"
1194

    
1195
pNewName :: Field
1196
pNewName =
1197
  withDoc "New group or instance name" $
1198
  simpleField "new_name" [t| NonEmptyString |]
1199

    
1200
pIgnoreOfflineNodes :: Field
1201
pIgnoreOfflineNodes =
1202
  withDoc "Whether to ignore offline nodes" $
1203
  defaultFalse "ignore_offline_nodes"
1204

    
1205
pTempHvParams :: Field
1206
pTempHvParams =
1207
  withDoc "Temporary hypervisor parameters, hypervisor-dependent" .
1208
  renameField "TempHvParams" .
1209
  defaultField [| toJSObject [] |] $
1210
  simpleField "hvparams" [t| JSObject JSValue |]
1211

    
1212
pTempBeParams :: Field
1213
pTempBeParams =
1214
  withDoc "Temporary backend parameters" .
1215
  renameField "TempBeParams" .
1216
  defaultField [| toJSObject [] |] $
1217
  simpleField "beparams" [t| JSObject JSValue |]
1218

    
1219
pNoRemember :: Field
1220
pNoRemember =
1221
  withDoc "Do not remember instance state changes" $
1222
  defaultFalse "no_remember"
1223

    
1224
pStartupPaused :: Field
1225
pStartupPaused =
1226
  withDoc "Pause instance at startup" $
1227
  defaultFalse "startup_paused"
1228

    
1229
pIgnoreSecondaries :: Field
1230
pIgnoreSecondaries =
1231
  withDoc "Whether to start the instance even if secondary disks are failing" $
1232
  defaultFalse "ignore_secondaries"
1233

    
1234
pRebootType :: Field
1235
pRebootType =
1236
  withDoc "How to reboot the instance" $
1237
  simpleField "reboot_type" [t| RebootType |]
1238

    
1239
pReplaceDisksMode :: Field
1240
pReplaceDisksMode =
1241
  withDoc "Replacement mode" .
1242
  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1243

    
1244
pReplaceDisksList :: Field
1245
pReplaceDisksList =
1246
  withDoc "List of disk indices" .
1247
  renameField "ReplaceDisksList" .
1248
  defaultField [| [] |] $
1249
  simpleField "disks" [t| [DiskIndex] |]
1250

    
1251
pMigrationCleanup :: Field
1252
pMigrationCleanup =
1253
  withDoc "Whether a previously failed migration should be cleaned up" .
1254
  renameField "MigrationCleanup" $ defaultFalse "cleanup"
1255

    
1256
pAllowFailover :: Field
1257
pAllowFailover =
1258
  withDoc "Whether we can fallback to failover if migration is not possible" $
1259
  defaultFalse "allow_failover"
1260

    
1261
pMoveTargetNode :: Field
1262
pMoveTargetNode =
1263
  withDoc "Target node for instance move" .
1264
  renameField "MoveTargetNode" $
1265
  simpleField "target_node" [t| NonEmptyString |]
1266

    
1267
pMoveTargetNodeUuid :: Field
1268
pMoveTargetNodeUuid =
1269
  withDoc "Target node UUID for instance move" .
1270
  renameField "MoveTargetNodeUuid" . optionalField $
1271
  simpleField "target_node_uuid" [t| NonEmptyString |]
1272

    
1273
pMoveCompress :: Field
1274
pMoveCompress =
1275
  withDoc "Compression mode to use during instance moves" .
1276
  defaultField [| None |] $
1277
  simpleField "compress" [t| ImportExportCompression |]
1278

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

    
1285
pIgnoreDiskSize :: Field
1286
pIgnoreDiskSize =
1287
  withDoc "Whether to ignore recorded disk size" $
1288
  defaultFalse "ignore_size"
1289

    
1290
pWaitForSyncFalse :: Field
1291
pWaitForSyncFalse =
1292
  withDoc "Whether to wait for the disk to synchronize (defaults to false)" $
1293
  defaultField [| False |] pWaitForSync
1294

    
1295
pRecreateDisksInfo :: Field
1296
pRecreateDisksInfo =
1297
  withDoc "Disk list for recreate disks" .
1298
  renameField "RecreateDisksInfo" .
1299
  defaultField [| RecreateDisksAll |] $
1300
  simpleField "disks" [t| RecreateDisksInfo |]
1301

    
1302
pStatic :: Field
1303
pStatic =
1304
  withDoc "Whether to only return configuration data without querying nodes" $
1305
  defaultFalse "static"
1306

    
1307
pInstParamsNicChanges :: Field
1308
pInstParamsNicChanges =
1309
  withDoc "List of NIC changes" .
1310
  renameField "InstNicChanges" .
1311
  defaultField [| SetParamsEmpty |] $
1312
  simpleField "nics" [t| SetParamsMods INicParams |]
1313

    
1314
pInstParamsDiskChanges :: Field
1315
pInstParamsDiskChanges =
1316
  withDoc "List of disk changes" .
1317
  renameField "InstDiskChanges" .
1318
  defaultField [| SetParamsEmpty |] $
1319
  simpleField "disks" [t| SetParamsMods IDiskParams |]
1320

    
1321
pRuntimeMem :: Field
1322
pRuntimeMem =
1323
  withDoc "New runtime memory" .
1324
  optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1325

    
1326
pOptDiskTemplate :: Field
1327
pOptDiskTemplate =
1328
  withDoc "Instance disk template" .
1329
  optionalField .
1330
  renameField "OptDiskTemplate" $
1331
  simpleField "disk_template" [t| DiskTemplate |]
1332

    
1333
pOsNameChange :: Field
1334
pOsNameChange =
1335
  withDoc "Change the instance's OS without reinstalling the instance" $
1336
  optionalNEStringField "os_name"
1337

    
1338
pDiskIndex :: Field
1339
pDiskIndex =
1340
  withDoc "Disk index for e.g. grow disk" .
1341
  renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
1342

    
1343
pDiskChgAmount :: Field
1344
pDiskChgAmount =
1345
  withDoc "Disk amount to add or grow to" .
1346
  renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
1347

    
1348
pDiskChgAbsolute :: Field
1349
pDiskChgAbsolute =
1350
  withDoc
1351
    "Whether the amount parameter is an absolute target or a relative one" .
1352
  renameField "DiskChkAbsolute" $ defaultFalse "absolute"
1353

    
1354
pTargetGroups :: Field
1355
pTargetGroups =
1356
  withDoc
1357
    "Destination group names or UUIDs (defaults to \"all but current group\")" .
1358
  optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
1359

    
1360
pNodeGroupAllocPolicy :: Field
1361
pNodeGroupAllocPolicy =
1362
  withDoc "Instance allocation policy" .
1363
  optionalField $
1364
  simpleField "alloc_policy" [t| AllocPolicy |]
1365

    
1366
pGroupNodeParams :: Field
1367
pGroupNodeParams =
1368
  withDoc "Default node parameters for group" .
1369
  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
1370

    
1371
pExportMode :: Field
1372
pExportMode =
1373
  withDoc "Export mode" .
1374
  renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1375

    
1376
-- FIXME: Rename target_node as it changes meaning for different
1377
-- export modes (e.g. "destination")
1378
pExportTargetNode :: Field
1379
pExportTargetNode =
1380
  withDoc "Target node (depends on export mode)" .
1381
  renameField "ExportTarget" $
1382
  simpleField "target_node" [t| ExportTarget |]
1383

    
1384
pExportTargetNodeUuid :: Field
1385
pExportTargetNodeUuid =
1386
  withDoc "Target node UUID (if local export)" .
1387
  renameField "ExportTargetNodeUuid" . optionalField $
1388
  simpleField "target_node_uuid" [t| NonEmptyString |]
1389

    
1390
pShutdownInstance :: Field
1391
pShutdownInstance =
1392
  withDoc "Whether to shutdown the instance before export" $
1393
  defaultTrue "shutdown"
1394

    
1395
pRemoveInstance :: Field
1396
pRemoveInstance =
1397
  withDoc "Whether to remove instance after export" $
1398
  defaultFalse "remove_instance"
1399

    
1400
pIgnoreRemoveFailures :: Field
1401
pIgnoreRemoveFailures =
1402
  withDoc "Whether to ignore failures while removing instances" $
1403
  defaultFalse "ignore_remove_failures"
1404

    
1405
pX509KeyName :: Field
1406
pX509KeyName =
1407
  withDoc "Name of X509 key (remote export only)" .
1408
  optionalField $ simpleField "x509_key_name" [t| [JSValue] |]
1409

    
1410
pX509DestCA :: Field
1411
pX509DestCA =
1412
  withDoc "Destination X509 CA (remote export only)" $
1413
  optionalNEStringField "destination_x509_ca"
1414

    
1415
pTagsObject :: Field
1416
pTagsObject =
1417
  withDoc "Tag kind" $
1418
  simpleField "kind" [t| TagKind |]
1419

    
1420
pTagsName :: Field
1421
pTagsName =
1422
  withDoc "Name of object" .
1423
  renameField "TagsGetName" .
1424
  optionalField $ simpleField "name" [t| String |]
1425

    
1426
pTagsList :: Field
1427
pTagsList =
1428
  withDoc "List of tag names" $
1429
  simpleField "tags" [t| [String] |]
1430

    
1431
-- FIXME: this should be compiled at load time?
1432
pTagSearchPattern :: Field
1433
pTagSearchPattern =
1434
  withDoc "Search pattern (regular expression)" .
1435
  renameField "TagSearchPattern" $
1436
  simpleField "pattern" [t| NonEmptyString |]
1437

    
1438
pDelayDuration :: Field
1439
pDelayDuration =
1440
  withDoc "Duration parameter for 'OpTestDelay'" .
1441
  renameField "DelayDuration" $
1442
  simpleField "duration" [t| Double |]
1443

    
1444
pDelayOnMaster :: Field
1445
pDelayOnMaster =
1446
  withDoc "on_master field for 'OpTestDelay'" .
1447
  renameField "DelayOnMaster" $
1448
  defaultTrue "on_master"
1449

    
1450
pDelayOnNodes :: Field
1451
pDelayOnNodes =
1452
  withDoc "on_nodes field for 'OpTestDelay'" .
1453
  renameField "DelayOnNodes" .
1454
  defaultField [| [] |] $
1455
  simpleField "on_nodes" [t| [NonEmptyString] |]
1456

    
1457
pDelayOnNodeUuids :: Field
1458
pDelayOnNodeUuids =
1459
  withDoc "on_node_uuids field for 'OpTestDelay'" .
1460
  renameField "DelayOnNodeUuids" . optionalField $
1461
  simpleField "on_node_uuids" [t| [NonEmptyString] |]
1462

    
1463
pDelayRepeat :: Field
1464
pDelayRepeat =
1465
  withDoc "Repeat parameter for OpTestDelay" .
1466
  renameField "DelayRepeat" .
1467
  defaultField [| forceNonNeg (0::Int) |] $
1468
  simpleField "repeat" [t| NonNegative Int |]
1469

    
1470
pIAllocatorDirection :: Field
1471
pIAllocatorDirection =
1472
  withDoc "IAllocator test direction" .
1473
  renameField "IAllocatorDirection" $
1474
  simpleField "direction" [t| IAllocatorTestDir |]
1475

    
1476
pIAllocatorMode :: Field
1477
pIAllocatorMode =
1478
  withDoc "IAllocator test mode" .
1479
  renameField "IAllocatorMode" $
1480
  simpleField "mode" [t| IAllocatorMode |]
1481

    
1482
pIAllocatorReqName :: Field
1483
pIAllocatorReqName =
1484
  withDoc "IAllocator target name (new instance, node to evac, etc.)" .
1485
  renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
1486

    
1487
pIAllocatorNics :: Field
1488
pIAllocatorNics =
1489
  withDoc "Custom OpTestIAllocator nics" .
1490
  renameField "IAllocatorNics" .
1491
  optionalField $ simpleField "nics" [t| [INicParams] |]
1492

    
1493
pIAllocatorDisks :: Field
1494
pIAllocatorDisks =
1495
  withDoc "Custom OpTestAllocator disks" .
1496
  renameField "IAllocatorDisks" .
1497
  optionalField $ simpleField "disks" [t| [JSValue] |]
1498

    
1499
pIAllocatorMemory :: Field
1500
pIAllocatorMemory =
1501
  withDoc "IAllocator memory field" .
1502
  renameField "IAllocatorMem" .
1503
  optionalField $
1504
  simpleField "memory" [t| NonNegative Int |]
1505

    
1506
pIAllocatorVCpus :: Field
1507
pIAllocatorVCpus =
1508
  withDoc "IAllocator vcpus field" .
1509
  renameField "IAllocatorVCpus" .
1510
  optionalField $
1511
  simpleField "vcpus" [t| NonNegative Int |]
1512

    
1513
pIAllocatorOs :: Field
1514
pIAllocatorOs =
1515
  withDoc "IAllocator os field" .
1516
  renameField "IAllocatorOs" $ optionalNEStringField "os"
1517

    
1518
pIAllocatorInstances :: Field
1519
pIAllocatorInstances =
1520
  withDoc "IAllocator instances field" .
1521
  renameField "IAllocatorInstances " .
1522
  optionalField $
1523
  simpleField "instances" [t| [NonEmptyString] |]
1524

    
1525
pIAllocatorEvacMode :: Field
1526
pIAllocatorEvacMode =
1527
  withDoc "IAllocator evac mode" .
1528
  renameField "IAllocatorEvacMode" .
1529
  optionalField $
1530
  simpleField "evac_mode" [t| EvacMode |]
1531

    
1532
pIAllocatorSpindleUse :: Field
1533
pIAllocatorSpindleUse =
1534
  withDoc "IAllocator spindle use" .
1535
  renameField "IAllocatorSpindleUse" .
1536
  defaultField [| forceNonNeg (1::Int) |] $
1537
  simpleField "spindle_use" [t| NonNegative Int |]
1538

    
1539
pIAllocatorCount :: Field
1540
pIAllocatorCount =
1541
  withDoc "IAllocator count field" .
1542
  renameField "IAllocatorCount" .
1543
  defaultField [| forceNonNeg (1::Int) |] $
1544
  simpleField "count" [t| NonNegative Int |]
1545

    
1546
pJQueueNotifyWaitLock :: Field
1547
pJQueueNotifyWaitLock =
1548
  withDoc "'OpTestJqueue' notify_waitlock" $
1549
  defaultFalse "notify_waitlock"
1550

    
1551
pJQueueNotifyExec :: Field
1552
pJQueueNotifyExec =
1553
  withDoc "'OpTestJQueue' notify_exec" $
1554
  defaultFalse "notify_exec"
1555

    
1556
pJQueueLogMessages :: Field
1557
pJQueueLogMessages =
1558
  withDoc "'OpTestJQueue' log_messages" .
1559
  defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
1560

    
1561
pJQueueFail :: Field
1562
pJQueueFail =
1563
  withDoc "'OpTestJQueue' fail attribute" .
1564
  renameField "JQueueFail" $ defaultFalse "fail"
1565

    
1566
pTestDummyResult :: Field
1567
pTestDummyResult =
1568
  withDoc "'OpTestDummy' result field" .
1569
  renameField "TestDummyResult" $ simpleField "result" [t| JSValue |]
1570

    
1571
pTestDummyMessages :: Field
1572
pTestDummyMessages =
1573
  withDoc "'OpTestDummy' messages field" .
1574
  renameField "TestDummyMessages" $
1575
  simpleField "messages" [t| JSValue |]
1576

    
1577
pTestDummyFail :: Field
1578
pTestDummyFail =
1579
  withDoc "'OpTestDummy' fail field" .
1580
  renameField "TestDummyFail" $ simpleField "fail" [t| JSValue |]
1581

    
1582
pTestDummySubmitJobs :: Field
1583
pTestDummySubmitJobs =
1584
  withDoc "'OpTestDummy' submit_jobs field" .
1585
  renameField "TestDummySubmitJobs" $
1586
  simpleField "submit_jobs" [t| JSValue |]
1587

    
1588
pNetworkName :: Field
1589
pNetworkName =
1590
  withDoc "Network name" $
1591
  simpleField "network_name" [t| NonEmptyString |]
1592

    
1593
pNetworkAddress4 :: Field
1594
pNetworkAddress4 =
1595
  withDoc "Network address (IPv4 subnet)" .
1596
  renameField "NetworkAddress4" $
1597
  simpleField "network" [t| IPv4Network |]
1598

    
1599
pNetworkGateway4 :: Field
1600
pNetworkGateway4 =
1601
  withDoc "Network gateway (IPv4 address)" .
1602
  renameField "NetworkGateway4" .
1603
  optionalField $ simpleField "gateway" [t| IPv4Address |]
1604

    
1605
pNetworkAddress6 :: Field
1606
pNetworkAddress6 =
1607
  withDoc "Network address (IPv6 subnet)" .
1608
  renameField "NetworkAddress6" .
1609
  optionalField $ simpleField "network6" [t| IPv6Network |]
1610

    
1611
pNetworkGateway6 :: Field
1612
pNetworkGateway6 =
1613
  withDoc "Network gateway (IPv6 address)" .
1614
  renameField "NetworkGateway6" .
1615
  optionalField $ simpleField "gateway6" [t| IPv6Address |]
1616

    
1617
pNetworkMacPrefix :: Field
1618
pNetworkMacPrefix =
1619
  withDoc "Network specific mac prefix (that overrides the cluster one)" .
1620
  renameField "NetMacPrefix" $
1621
  optionalNEStringField "mac_prefix"
1622

    
1623
pNetworkAddRsvdIps :: Field
1624
pNetworkAddRsvdIps =
1625
  withDoc "Which IP addresses to reserve" .
1626
  renameField "NetworkAddRsvdIps" .
1627
  optionalField $
1628
  simpleField "add_reserved_ips" [t| [IPv4Address] |]
1629

    
1630
pNetworkRemoveRsvdIps :: Field
1631
pNetworkRemoveRsvdIps =
1632
  withDoc "Which external IP addresses to release" .
1633
  renameField "NetworkRemoveRsvdIps" .
1634
  optionalField $
1635
  simpleField "remove_reserved_ips" [t| [IPv4Address] |]
1636

    
1637
pNetworkMode :: Field
1638
pNetworkMode =
1639
  withDoc "Network mode when connecting to a group" $
1640
  simpleField "network_mode" [t| NICMode |]
1641

    
1642
pNetworkLink :: Field
1643
pNetworkLink =
1644
  withDoc "Network link when connecting to a group" $
1645
  simpleField "network_link" [t| NonEmptyString |]