Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ d3e6fd0e

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

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

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

    
274
-- * Helper functions and types
275

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

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

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

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

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

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

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

    
309
-- ** Disks
310

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

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

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

    
327
-- ** I* param types
328

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
450
-- * Common opcode parameters
451

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

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

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

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

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

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

    
484
-- * Parameters
485

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
571
-- | Cluster-wide default directory for storing Gluster-backed disks.
572
pClusterGlusterStorageDir :: Field
573
pClusterGlusterStorageDir =
574
  renameField "ClusterGlusterStorageDir" $
575
  optionalStringField "gluster_storage_dir"
576

    
577
-- | Volume group name.
578
pVgName :: Field
579
pVgName =
580
  withDoc "Volume group name" $
581
  optionalStringField "vg_name"
582

    
583
pEnabledHypervisors :: Field
584
pEnabledHypervisors =
585
  withDoc "List of enabled hypervisors" .
586
  optionalField $
587
  simpleField "enabled_hypervisors" [t| [Hypervisor] |]
588

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

    
596
pClusterBeParams :: Field
597
pClusterBeParams =
598
  withDoc "Cluster-wide backend parameter defaults" .
599
  renameField "ClusterBeParams" .
600
  optionalField $ simpleField "beparams" [t| JSObject JSValue |]
601

    
602
pOsHvp :: Field
603
pOsHvp =
604
  withDoc "Cluster-wide per-OS hypervisor parameter defaults" .
605
  optionalField $
606
  simpleField "os_hvp" [t| GenericContainer String (JSObject JSValue) |]
607

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

    
615
pDiskParams :: Field
616
pDiskParams =
617
  withDoc "Disk templates' parameter defaults" .
618
  optionalField $
619
  simpleField "diskparams"
620
              [t| GenericContainer DiskTemplate (JSObject JSValue) |]
621

    
622
pCandidatePoolSize :: Field
623
pCandidatePoolSize =
624
  withDoc "Master candidate pool size" .
625
  optionalField $ simpleField "candidate_pool_size" [t| Positive Int |]
626

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

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

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

    
645
pMaintainNodeHealth :: Field
646
pMaintainNodeHealth =
647
  withDoc "Whether to automatically maintain node health" .
648
  optionalField $ booleanField "maintain_node_health"
649

    
650
-- | Whether to modify and keep in sync the @/etc/hosts@ files of nodes.
651
pModifyEtcHosts :: Field
652
pModifyEtcHosts = optionalField $ booleanField "modify_etc_hosts"
653

    
654
-- | Whether to wipe disks before allocating them to instances.
655
pPreallocWipeDisks :: Field
656
pPreallocWipeDisks =
657
  withDoc "Whether to wipe disks before allocating them to instances" .
658
  optionalField $ booleanField "prealloc_wipe_disks"
659

    
660
pNicParams :: Field
661
pNicParams =
662
  withDoc "Cluster-wide NIC parameter defaults" .
663
  optionalField $ simpleField "nicparams" [t| INicParams |]
664

    
665
pIpolicy :: Field
666
pIpolicy =
667
  withDoc "Ipolicy specs" .
668
  optionalField $ simpleField "ipolicy" [t| JSObject JSValue |]
669

    
670
pDrbdHelper :: Field
671
pDrbdHelper =
672
  withDoc "DRBD helper program" $
673
  optionalStringField "drbd_helper"
674

    
675
pDefaultIAllocator :: Field
676
pDefaultIAllocator =
677
  withDoc "Default iallocator for cluster" $
678
  optionalStringField "default_iallocator"
679

    
680
pDefaultIAllocatorParams :: Field
681
pDefaultIAllocatorParams =
682
  withDoc "Default iallocator parameters for cluster" . optionalField
683
    $ simpleField "default_iallocator_params" [t| JSObject JSValue |]
684

    
685
pMasterNetdev :: Field
686
pMasterNetdev =
687
  withDoc "Master network device" $
688
  optionalStringField "master_netdev"
689

    
690
pMasterNetmask :: Field
691
pMasterNetmask =
692
  withDoc "Netmask of the master IP" .
693
  optionalField $ simpleField "master_netmask" [t| NonNegative Int |]
694

    
695
pReservedLvs :: Field
696
pReservedLvs =
697
  withDoc "List of reserved LVs" .
698
  optionalField $ simpleField "reserved_lvs" [t| [NonEmptyString] |]
699

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

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

    
715
pUseExternalMipScript :: Field
716
pUseExternalMipScript =
717
  withDoc "Whether to use an external master IP address setup script" .
718
  optionalField $ booleanField "use_external_mip_script"
719

    
720
pEnabledDiskTemplates :: Field
721
pEnabledDiskTemplates =
722
  withDoc "List of enabled disk templates" .
723
  optionalField $
724
  simpleField "enabled_disk_templates" [t| [DiskTemplate] |]
725

    
726
pQueryWhat :: Field
727
pQueryWhat =
728
  withDoc "Resource(s) to query for" $
729
  simpleField "what" [t| Qlang.QueryTypeOp |]
730

    
731
pUseLocking :: Field
732
pUseLocking =
733
  withDoc "Whether to use synchronization" $
734
  defaultFalse "use_locking"
735

    
736
pQueryFields :: Field
737
pQueryFields =
738
  withDoc "Requested fields" $
739
  simpleField "fields" [t| [NonEmptyString] |]
740

    
741
pQueryFilter :: Field
742
pQueryFilter =
743
  withDoc "Query filter" .
744
  optionalField $ simpleField "qfilter" [t| [JSValue] |]
745

    
746
pQueryFieldsFields :: Field
747
pQueryFieldsFields =
748
  withDoc "Requested fields; if not given, all are returned" .
749
  renameField "QueryFieldsFields" $
750
  optionalField pQueryFields
751

    
752
pNodeNames :: Field
753
pNodeNames =
754
  withDoc "List of node names to run the OOB command against" .
755
  defaultField [| [] |] $ simpleField "node_names" [t| [NonEmptyString] |]
756

    
757
pNodeUuids :: Field
758
pNodeUuids =
759
  withDoc "List of node UUIDs" .
760
  optionalField $ simpleField "node_uuids" [t| [NonEmptyString] |]
761

    
762
pOobCommand :: Field
763
pOobCommand =
764
  withDoc "OOB command to run" $
765
  simpleField "command" [t| OobCommand |]
766

    
767
pOobTimeout :: Field
768
pOobTimeout =
769
  withDoc "Timeout before the OOB helper will be terminated" .
770
  defaultField [| C.oobTimeout |] $
771
  simpleField "timeout" [t| Int |]
772

    
773
pIgnoreStatus :: Field
774
pIgnoreStatus =
775
  withDoc "Ignores the node offline status for power off" $
776
  defaultFalse "ignore_status"
777

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

    
787
pRequiredNodes :: Field
788
pRequiredNodes =
789
  withDoc "Required list of node names" .
790
  renameField "ReqNodes " $ simpleField "nodes" [t| [NonEmptyString] |]
791

    
792
pRequiredNodeUuids :: Field
793
pRequiredNodeUuids =
794
  withDoc "Required list of node UUIDs" .
795
  renameField "ReqNodeUuids " . optionalField $
796
  simpleField "node_uuids" [t| [NonEmptyString] |]
797

    
798
pRestrictedCommand :: Field
799
pRestrictedCommand =
800
  withDoc "Restricted command name" .
801
  renameField "RestrictedCommand" $
802
  simpleField "command" [t| NonEmptyString |]
803

    
804
pNodeName :: Field
805
pNodeName =
806
  withDoc "A required node name (for single-node LUs)" $
807
  simpleField "node_name" [t| NonEmptyString |]
808

    
809
pNodeUuid :: Field
810
pNodeUuid =
811
  withDoc "A node UUID (for single-node LUs)" .
812
  optionalField $ simpleField "node_uuid" [t| NonEmptyString |]
813

    
814
pPrimaryIp :: Field
815
pPrimaryIp =
816
  withDoc "Primary IP address" .
817
  optionalField $
818
  simpleField "primary_ip" [t| NonEmptyString |]
819

    
820
pSecondaryIp :: Field
821
pSecondaryIp =
822
  withDoc "Secondary IP address" $
823
  optionalNEStringField "secondary_ip"
824

    
825
pReadd :: Field
826
pReadd =
827
  withDoc "Whether node is re-added to cluster" $
828
  defaultFalse "readd"
829

    
830
pNodeGroup :: Field
831
pNodeGroup =
832
  withDoc "Initial node group" $
833
  optionalNEStringField "group"
834

    
835
pMasterCapable :: Field
836
pMasterCapable =
837
  withDoc "Whether node can become master or master candidate" .
838
  optionalField $ booleanField "master_capable"
839

    
840
pVmCapable :: Field
841
pVmCapable =
842
  withDoc "Whether node can host instances" .
843
  optionalField $ booleanField "vm_capable"
844

    
845
pNdParams :: Field
846
pNdParams =
847
  withDoc "Node parameters" .
848
  renameField "genericNdParams" .
849
  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
850

    
851
pNames :: Field
852
pNames =
853
  withDoc "List of names" .
854
  defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
855

    
856
pNodes :: Field
857
pNodes =
858
  withDoc "List of nodes" .
859
  defaultField [| [] |] $ simpleField "nodes" [t| [NonEmptyString] |]
860

    
861
pStorageType :: Field
862
pStorageType =
863
  withDoc "Storage type" $ simpleField "storage_type" [t| StorageType |]
864

    
865
pStorageTypeOptional :: Field
866
pStorageTypeOptional =
867
  withDoc "Storage type" .
868
  renameField "StorageTypeOptional" .
869
  optionalField $ simpleField "storage_type" [t| StorageType |]
870

    
871
pStorageName :: Field
872
pStorageName =
873
  withDoc "Storage name" .
874
  renameField "StorageName" .
875
  optionalField $ simpleField "name" [t| NonEmptyString |]
876

    
877
pStorageChanges :: Field
878
pStorageChanges =
879
  withDoc "Requested storage changes" $
880
  simpleField "changes" [t| JSObject JSValue |]
881

    
882
pIgnoreConsistency :: Field
883
pIgnoreConsistency =
884
  withDoc "Whether to ignore disk consistency" $
885
  defaultFalse "ignore_consistency"
886

    
887
pMasterCandidate :: Field
888
pMasterCandidate =
889
  withDoc "Whether the node should become a master candidate" .
890
  optionalField $ booleanField "master_candidate"
891

    
892
pOffline :: Field
893
pOffline =
894
  withDoc "Whether to mark the node or instance offline" .
895
  optionalField $ booleanField "offline"
896

    
897
pDrained ::Field
898
pDrained =
899
  withDoc "Whether to mark the node as drained" .
900
  optionalField $ booleanField "drained"
901

    
902
pAutoPromote :: Field
903
pAutoPromote =
904
  withDoc "Whether node(s) should be promoted to master candidate if\
905
          \ necessary" $
906
  defaultFalse "auto_promote"
907

    
908
pPowered :: Field
909
pPowered =
910
  withDoc "Whether the node should be marked as powered" .
911
  optionalField $ booleanField "powered"
912

    
913
pMigrationMode :: Field
914
pMigrationMode =
915
  withDoc "Migration type (live/non-live)" .
916
  renameField "MigrationMode" .
917
  optionalField $
918
  simpleField "mode" [t| MigrationMode |]
919

    
920
pMigrationLive :: Field
921
pMigrationLive =
922
  withDoc "Obsolete \'live\' migration mode (do not use)" .
923
  renameField "OldLiveMode" . optionalField $ booleanField "live"
924

    
925
pMigrationTargetNode :: Field
926
pMigrationTargetNode =
927
  withDoc "Target node for instance migration/failover" $
928
  optionalNEStringField "target_node"
929

    
930
pMigrationTargetNodeUuid :: Field
931
pMigrationTargetNodeUuid =
932
  withDoc "Target node UUID for instance migration/failover" $
933
  optionalNEStringField "target_node_uuid"
934

    
935
pAllowRuntimeChgs :: Field
936
pAllowRuntimeChgs =
937
  withDoc "Whether to allow runtime changes while migrating" $
938
  defaultTrue "allow_runtime_changes"
939

    
940
pIgnoreIpolicy :: Field
941
pIgnoreIpolicy =
942
  withDoc "Whether to ignore ipolicy violations" $
943
  defaultFalse "ignore_ipolicy"
944

    
945
pIallocator :: Field
946
pIallocator =
947
  withDoc "Iallocator for deciding the target node for shared-storage\
948
          \ instances" $
949
  optionalNEStringField "iallocator"
950

    
951
pEarlyRelease :: Field
952
pEarlyRelease =
953
  withDoc "Whether to release locks as soon as possible" $
954
  defaultFalse "early_release"
955

    
956
pRemoteNode :: Field
957
pRemoteNode =
958
  withDoc "New secondary node" $
959
  optionalNEStringField "remote_node"
960

    
961
pRemoteNodeUuid :: Field
962
pRemoteNodeUuid =
963
  withDoc "New secondary node UUID" $
964
  optionalNEStringField "remote_node_uuid"
965

    
966
pEvacMode :: Field
967
pEvacMode =
968
  withDoc "Node evacuation mode" .
969
  renameField "EvacMode" $ simpleField "mode" [t| EvacMode |]
970

    
971
pInstanceName :: Field
972
pInstanceName =
973
  withDoc "A required instance name (for single-instance LUs)" $
974
  simpleField "instance_name" [t| String |]
975

    
976
pForceVariant :: Field
977
pForceVariant =
978
  withDoc "Whether to force an unknown OS variant" $
979
  defaultFalse "force_variant"
980

    
981
pWaitForSync :: Field
982
pWaitForSync =
983
  withDoc "Whether to wait for the disk to synchronize" $
984
  defaultTrue "wait_for_sync"
985

    
986
pNameCheck :: Field
987
pNameCheck =
988
  withDoc "Whether to check name" $
989
  defaultTrue "name_check"
990

    
991
pInstBeParams :: Field
992
pInstBeParams =
993
  withDoc "Backend parameters for instance" .
994
  renameField "InstBeParams" .
995
  defaultField [| toJSObject [] |] $
996
  simpleField "beparams" [t| JSObject JSValue |]
997

    
998
pInstDisks :: Field
999
pInstDisks =
1000
  withDoc "List of instance disks" .
1001
  renameField "instDisks" $ simpleField "disks" [t| [IDiskParams] |]
1002

    
1003
pDiskTemplate :: Field
1004
pDiskTemplate =
1005
  withDoc "Disk template" $
1006
  simpleField "disk_template" [t| DiskTemplate |]
1007

    
1008
pFileDriver :: Field
1009
pFileDriver =
1010
  withDoc "Driver for file-backed disks" .
1011
  optionalField $ simpleField "file_driver" [t| FileDriver |]
1012

    
1013
pFileStorageDir :: Field
1014
pFileStorageDir =
1015
  withDoc "Directory for storing file-backed disks" $
1016
  optionalNEStringField "file_storage_dir"
1017

    
1018
pInstHvParams :: Field
1019
pInstHvParams =
1020
  withDoc "Hypervisor parameters for instance, hypervisor-dependent" .
1021
  renameField "InstHvParams" .
1022
  defaultField [| toJSObject [] |] $
1023
  simpleField "hvparams" [t| JSObject JSValue |]
1024

    
1025
pHypervisor :: Field
1026
pHypervisor =
1027
  withDoc "Selected hypervisor for an instance" .
1028
  optionalField $
1029
  simpleField "hypervisor" [t| Hypervisor |]
1030

    
1031
pResetDefaults :: Field
1032
pResetDefaults =
1033
  withDoc "Reset instance parameters to default if equal" $
1034
  defaultFalse "identify_defaults"
1035

    
1036
pIpCheck :: Field
1037
pIpCheck =
1038
  withDoc "Whether to ensure instance's IP address is inactive" $
1039
  defaultTrue "ip_check"
1040

    
1041
pIpConflictsCheck :: Field
1042
pIpConflictsCheck =
1043
  withDoc "Whether to check for conflicting IP addresses" $
1044
  defaultTrue "conflicts_check"
1045

    
1046
pInstCreateMode :: Field
1047
pInstCreateMode =
1048
  withDoc "Instance creation mode" .
1049
  renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
1050

    
1051
pInstNics :: Field
1052
pInstNics =
1053
  withDoc "List of NIC (network interface) definitions" $
1054
  simpleField "nics" [t| [INicParams] |]
1055

    
1056
pNoInstall :: Field
1057
pNoInstall =
1058
  withDoc "Do not install the OS (will disable automatic start)" .
1059
  optionalField $ booleanField "no_install"
1060

    
1061
pInstOs :: Field
1062
pInstOs =
1063
  withDoc "OS type for instance installation" $
1064
  optionalNEStringField "os_type"
1065

    
1066
pInstOsParams :: Field
1067
pInstOsParams =
1068
  withDoc "OS parameters for instance" .
1069
  renameField "InstOsParams" .
1070
  defaultField [| toJSObject [] |] $
1071
  simpleField "osparams" [t| JSObject JSValue |]
1072

    
1073
pPrimaryNode :: Field
1074
pPrimaryNode =
1075
  withDoc "Primary node for an instance" $
1076
  optionalNEStringField "pnode"
1077

    
1078
pPrimaryNodeUuid :: Field
1079
pPrimaryNodeUuid =
1080
  withDoc "Primary node UUID for an instance" $
1081
  optionalNEStringField "pnode_uuid"
1082

    
1083
pSecondaryNode :: Field
1084
pSecondaryNode =
1085
  withDoc "Secondary node for an instance" $
1086
  optionalNEStringField "snode"
1087

    
1088
pSecondaryNodeUuid :: Field
1089
pSecondaryNodeUuid =
1090
  withDoc "Secondary node UUID for an instance" $
1091
  optionalNEStringField "snode_uuid"
1092

    
1093
pSourceHandshake :: Field
1094
pSourceHandshake =
1095
  withDoc "Signed handshake from source (remote import only)" .
1096
  optionalField $ simpleField "source_handshake" [t| [JSValue] |]
1097

    
1098
pSourceInstance :: Field
1099
pSourceInstance =
1100
  withDoc "Source instance name (remote import only)" $
1101
  optionalNEStringField "source_instance_name"
1102

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

    
1111
pSourceX509Ca :: Field
1112
pSourceX509Ca =
1113
  withDoc "Source X509 CA in PEM format (remote import only)" $
1114
  optionalNEStringField "source_x509_ca"
1115

    
1116
pSrcNode :: Field
1117
pSrcNode =
1118
  withDoc "Source node for import" $
1119
  optionalNEStringField "src_node"
1120

    
1121
pSrcNodeUuid :: Field
1122
pSrcNodeUuid =
1123
  withDoc "Source node UUID for import" $
1124
  optionalNEStringField "src_node_uuid"
1125

    
1126
pSrcPath :: Field
1127
pSrcPath =
1128
  withDoc "Source directory for import" $
1129
  optionalNEStringField "src_path"
1130

    
1131
pStartInstance :: Field
1132
pStartInstance =
1133
  withDoc "Whether to start instance after creation" $
1134
  defaultTrue "start"
1135

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

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

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

    
1159
pInstanceUuid :: Field
1160
pInstanceUuid =
1161
  withDoc "An instance UUID (for single-instance LUs)" .
1162
  optionalField $ simpleField "instance_uuid" [t| NonEmptyString |]
1163

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

    
1171
pShutdownTimeout :: Field
1172
pShutdownTimeout =
1173
  withDoc "How long to wait for instance to shut down" .
1174
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1175
  simpleField "shutdown_timeout" [t| NonNegative Int |]
1176

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

    
1186
pIgnoreFailures :: Field
1187
pIgnoreFailures =
1188
  withDoc "Whether to ignore failures during removal" $
1189
  defaultFalse "ignore_failures"
1190

    
1191
pNewName :: Field
1192
pNewName =
1193
  withDoc "New group or instance name" $
1194
  simpleField "new_name" [t| NonEmptyString |]
1195

    
1196
pIgnoreOfflineNodes :: Field
1197
pIgnoreOfflineNodes =
1198
  withDoc "Whether to ignore offline nodes" $
1199
  defaultFalse "ignore_offline_nodes"
1200

    
1201
pTempHvParams :: Field
1202
pTempHvParams =
1203
  withDoc "Temporary hypervisor parameters, hypervisor-dependent" .
1204
  renameField "TempHvParams" .
1205
  defaultField [| toJSObject [] |] $
1206
  simpleField "hvparams" [t| JSObject JSValue |]
1207

    
1208
pTempBeParams :: Field
1209
pTempBeParams =
1210
  withDoc "Temporary backend parameters" .
1211
  renameField "TempBeParams" .
1212
  defaultField [| toJSObject [] |] $
1213
  simpleField "beparams" [t| JSObject JSValue |]
1214

    
1215
pNoRemember :: Field
1216
pNoRemember =
1217
  withDoc "Do not remember instance state changes" $
1218
  defaultFalse "no_remember"
1219

    
1220
pStartupPaused :: Field
1221
pStartupPaused =
1222
  withDoc "Pause instance at startup" $
1223
  defaultFalse "startup_paused"
1224

    
1225
pIgnoreSecondaries :: Field
1226
pIgnoreSecondaries =
1227
  withDoc "Whether to start the instance even if secondary disks are failing" $
1228
  defaultFalse "ignore_secondaries"
1229

    
1230
pRebootType :: Field
1231
pRebootType =
1232
  withDoc "How to reboot the instance" $
1233
  simpleField "reboot_type" [t| RebootType |]
1234

    
1235
pReplaceDisksMode :: Field
1236
pReplaceDisksMode =
1237
  withDoc "Replacement mode" .
1238
  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1239

    
1240
pReplaceDisksList :: Field
1241
pReplaceDisksList =
1242
  withDoc "List of disk indices" .
1243
  renameField "ReplaceDisksList" .
1244
  defaultField [| [] |] $
1245
  simpleField "disks" [t| [DiskIndex] |]
1246

    
1247
pMigrationCleanup :: Field
1248
pMigrationCleanup =
1249
  withDoc "Whether a previously failed migration should be cleaned up" .
1250
  renameField "MigrationCleanup" $ defaultFalse "cleanup"
1251

    
1252
pAllowFailover :: Field
1253
pAllowFailover =
1254
  withDoc "Whether we can fallback to failover if migration is not possible" $
1255
  defaultFalse "allow_failover"
1256

    
1257
pMoveTargetNode :: Field
1258
pMoveTargetNode =
1259
  withDoc "Target node for instance move" .
1260
  renameField "MoveTargetNode" $
1261
  simpleField "target_node" [t| NonEmptyString |]
1262

    
1263
pMoveTargetNodeUuid :: Field
1264
pMoveTargetNodeUuid =
1265
  withDoc "Target node UUID for instance move" .
1266
  renameField "MoveTargetNodeUuid" . optionalField $
1267
  simpleField "target_node_uuid" [t| NonEmptyString |]
1268

    
1269
pMoveCompress :: Field
1270
pMoveCompress =
1271
  withDoc "Compression mode to use during instance moves" .
1272
  defaultField [| None |] $
1273
  simpleField "compress" [t| ImportExportCompression |]
1274

    
1275
pBackupCompress :: Field
1276
pBackupCompress =
1277
  withDoc "Compression mode to use for moves during backups/imports" .
1278
  defaultField [| None |] $
1279
  simpleField "compress" [t| ImportExportCompression |]
1280

    
1281
pIgnoreDiskSize :: Field
1282
pIgnoreDiskSize =
1283
  withDoc "Whether to ignore recorded disk size" $
1284
  defaultFalse "ignore_size"
1285

    
1286
pWaitForSyncFalse :: Field
1287
pWaitForSyncFalse =
1288
  withDoc "Whether to wait for the disk to synchronize (defaults to false)" $
1289
  defaultField [| False |] pWaitForSync
1290

    
1291
pRecreateDisksInfo :: Field
1292
pRecreateDisksInfo =
1293
  withDoc "Disk list for recreate disks" .
1294
  renameField "RecreateDisksInfo" .
1295
  defaultField [| RecreateDisksAll |] $
1296
  simpleField "disks" [t| RecreateDisksInfo |]
1297

    
1298
pStatic :: Field
1299
pStatic =
1300
  withDoc "Whether to only return configuration data without querying nodes" $
1301
  defaultFalse "static"
1302

    
1303
pInstParamsNicChanges :: Field
1304
pInstParamsNicChanges =
1305
  withDoc "List of NIC changes" .
1306
  renameField "InstNicChanges" .
1307
  defaultField [| SetParamsEmpty |] $
1308
  simpleField "nics" [t| SetParamsMods INicParams |]
1309

    
1310
pInstParamsDiskChanges :: Field
1311
pInstParamsDiskChanges =
1312
  withDoc "List of disk changes" .
1313
  renameField "InstDiskChanges" .
1314
  defaultField [| SetParamsEmpty |] $
1315
  simpleField "disks" [t| SetParamsMods IDiskParams |]
1316

    
1317
pRuntimeMem :: Field
1318
pRuntimeMem =
1319
  withDoc "New runtime memory" .
1320
  optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1321

    
1322
pOptDiskTemplate :: Field
1323
pOptDiskTemplate =
1324
  withDoc "Instance disk template" .
1325
  optionalField .
1326
  renameField "OptDiskTemplate" $
1327
  simpleField "disk_template" [t| DiskTemplate |]
1328

    
1329
pOsNameChange :: Field
1330
pOsNameChange =
1331
  withDoc "Change the instance's OS without reinstalling the instance" $
1332
  optionalNEStringField "os_name"
1333

    
1334
pDiskIndex :: Field
1335
pDiskIndex =
1336
  withDoc "Disk index for e.g. grow disk" .
1337
  renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
1338

    
1339
pDiskChgAmount :: Field
1340
pDiskChgAmount =
1341
  withDoc "Disk amount to add or grow to" .
1342
  renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
1343

    
1344
pDiskChgAbsolute :: Field
1345
pDiskChgAbsolute =
1346
  withDoc
1347
    "Whether the amount parameter is an absolute target or a relative one" .
1348
  renameField "DiskChkAbsolute" $ defaultFalse "absolute"
1349

    
1350
pTargetGroups :: Field
1351
pTargetGroups =
1352
  withDoc
1353
    "Destination group names or UUIDs (defaults to \"all but current group\")" .
1354
  optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
1355

    
1356
pNodeGroupAllocPolicy :: Field
1357
pNodeGroupAllocPolicy =
1358
  withDoc "Instance allocation policy" .
1359
  optionalField $
1360
  simpleField "alloc_policy" [t| AllocPolicy |]
1361

    
1362
pGroupNodeParams :: Field
1363
pGroupNodeParams =
1364
  withDoc "Default node parameters for group" .
1365
  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
1366

    
1367
pExportMode :: Field
1368
pExportMode =
1369
  withDoc "Export mode" .
1370
  renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1371

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

    
1380
pExportTargetNodeUuid :: Field
1381
pExportTargetNodeUuid =
1382
  withDoc "Target node UUID (if local export)" .
1383
  renameField "ExportTargetNodeUuid" . optionalField $
1384
  simpleField "target_node_uuid" [t| NonEmptyString |]
1385

    
1386
pShutdownInstance :: Field
1387
pShutdownInstance =
1388
  withDoc "Whether to shutdown the instance before export" $
1389
  defaultTrue "shutdown"
1390

    
1391
pRemoveInstance :: Field
1392
pRemoveInstance =
1393
  withDoc "Whether to remove instance after export" $
1394
  defaultFalse "remove_instance"
1395

    
1396
pIgnoreRemoveFailures :: Field
1397
pIgnoreRemoveFailures =
1398
  withDoc "Whether to ignore failures while removing instances" $
1399
  defaultFalse "ignore_remove_failures"
1400

    
1401
pX509KeyName :: Field
1402
pX509KeyName =
1403
  withDoc "Name of X509 key (remote export only)" .
1404
  optionalField $ simpleField "x509_key_name" [t| [JSValue] |]
1405

    
1406
pX509DestCA :: Field
1407
pX509DestCA =
1408
  withDoc "Destination X509 CA (remote export only)" $
1409
  optionalNEStringField "destination_x509_ca"
1410

    
1411
pTagsObject :: Field
1412
pTagsObject =
1413
  withDoc "Tag kind" $
1414
  simpleField "kind" [t| TagKind |]
1415

    
1416
pTagsName :: Field
1417
pTagsName =
1418
  withDoc "Name of object" .
1419
  renameField "TagsGetName" .
1420
  optionalField $ simpleField "name" [t| String |]
1421

    
1422
pTagsList :: Field
1423
pTagsList =
1424
  withDoc "List of tag names" $
1425
  simpleField "tags" [t| [String] |]
1426

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

    
1434
pDelayDuration :: Field
1435
pDelayDuration =
1436
  withDoc "Duration parameter for 'OpTestDelay'" .
1437
  renameField "DelayDuration" $
1438
  simpleField "duration" [t| Double |]
1439

    
1440
pDelayOnMaster :: Field
1441
pDelayOnMaster =
1442
  withDoc "on_master field for 'OpTestDelay'" .
1443
  renameField "DelayOnMaster" $
1444
  defaultTrue "on_master"
1445

    
1446
pDelayOnNodes :: Field
1447
pDelayOnNodes =
1448
  withDoc "on_nodes field for 'OpTestDelay'" .
1449
  renameField "DelayOnNodes" .
1450
  defaultField [| [] |] $
1451
  simpleField "on_nodes" [t| [NonEmptyString] |]
1452

    
1453
pDelayOnNodeUuids :: Field
1454
pDelayOnNodeUuids =
1455
  withDoc "on_node_uuids field for 'OpTestDelay'" .
1456
  renameField "DelayOnNodeUuids" . optionalField $
1457
  simpleField "on_node_uuids" [t| [NonEmptyString] |]
1458

    
1459
pDelayRepeat :: Field
1460
pDelayRepeat =
1461
  withDoc "Repeat parameter for OpTestDelay" .
1462
  renameField "DelayRepeat" .
1463
  defaultField [| forceNonNeg (0::Int) |] $
1464
  simpleField "repeat" [t| NonNegative Int |]
1465

    
1466
pIAllocatorDirection :: Field
1467
pIAllocatorDirection =
1468
  withDoc "IAllocator test direction" .
1469
  renameField "IAllocatorDirection" $
1470
  simpleField "direction" [t| IAllocatorTestDir |]
1471

    
1472
pIAllocatorMode :: Field
1473
pIAllocatorMode =
1474
  withDoc "IAllocator test mode" .
1475
  renameField "IAllocatorMode" $
1476
  simpleField "mode" [t| IAllocatorMode |]
1477

    
1478
pIAllocatorReqName :: Field
1479
pIAllocatorReqName =
1480
  withDoc "IAllocator target name (new instance, node to evac, etc.)" .
1481
  renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
1482

    
1483
pIAllocatorNics :: Field
1484
pIAllocatorNics =
1485
  withDoc "Custom OpTestIAllocator nics" .
1486
  renameField "IAllocatorNics" .
1487
  optionalField $ simpleField "nics" [t| [INicParams] |]
1488

    
1489
pIAllocatorDisks :: Field
1490
pIAllocatorDisks =
1491
  withDoc "Custom OpTestAllocator disks" .
1492
  renameField "IAllocatorDisks" .
1493
  optionalField $ simpleField "disks" [t| [JSValue] |]
1494

    
1495
pIAllocatorMemory :: Field
1496
pIAllocatorMemory =
1497
  withDoc "IAllocator memory field" .
1498
  renameField "IAllocatorMem" .
1499
  optionalField $
1500
  simpleField "memory" [t| NonNegative Int |]
1501

    
1502
pIAllocatorVCpus :: Field
1503
pIAllocatorVCpus =
1504
  withDoc "IAllocator vcpus field" .
1505
  renameField "IAllocatorVCpus" .
1506
  optionalField $
1507
  simpleField "vcpus" [t| NonNegative Int |]
1508

    
1509
pIAllocatorOs :: Field
1510
pIAllocatorOs =
1511
  withDoc "IAllocator os field" .
1512
  renameField "IAllocatorOs" $ optionalNEStringField "os"
1513

    
1514
pIAllocatorInstances :: Field
1515
pIAllocatorInstances =
1516
  withDoc "IAllocator instances field" .
1517
  renameField "IAllocatorInstances " .
1518
  optionalField $
1519
  simpleField "instances" [t| [NonEmptyString] |]
1520

    
1521
pIAllocatorEvacMode :: Field
1522
pIAllocatorEvacMode =
1523
  withDoc "IAllocator evac mode" .
1524
  renameField "IAllocatorEvacMode" .
1525
  optionalField $
1526
  simpleField "evac_mode" [t| EvacMode |]
1527

    
1528
pIAllocatorSpindleUse :: Field
1529
pIAllocatorSpindleUse =
1530
  withDoc "IAllocator spindle use" .
1531
  renameField "IAllocatorSpindleUse" .
1532
  defaultField [| forceNonNeg (1::Int) |] $
1533
  simpleField "spindle_use" [t| NonNegative Int |]
1534

    
1535
pIAllocatorCount :: Field
1536
pIAllocatorCount =
1537
  withDoc "IAllocator count field" .
1538
  renameField "IAllocatorCount" .
1539
  defaultField [| forceNonNeg (1::Int) |] $
1540
  simpleField "count" [t| NonNegative Int |]
1541

    
1542
pJQueueNotifyWaitLock :: Field
1543
pJQueueNotifyWaitLock =
1544
  withDoc "'OpTestJqueue' notify_waitlock" $
1545
  defaultFalse "notify_waitlock"
1546

    
1547
pJQueueNotifyExec :: Field
1548
pJQueueNotifyExec =
1549
  withDoc "'OpTestJQueue' notify_exec" $
1550
  defaultFalse "notify_exec"
1551

    
1552
pJQueueLogMessages :: Field
1553
pJQueueLogMessages =
1554
  withDoc "'OpTestJQueue' log_messages" .
1555
  defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
1556

    
1557
pJQueueFail :: Field
1558
pJQueueFail =
1559
  withDoc "'OpTestJQueue' fail attribute" .
1560
  renameField "JQueueFail" $ defaultFalse "fail"
1561

    
1562
pTestDummyResult :: Field
1563
pTestDummyResult =
1564
  withDoc "'OpTestDummy' result field" .
1565
  renameField "TestDummyResult" $ simpleField "result" [t| JSValue |]
1566

    
1567
pTestDummyMessages :: Field
1568
pTestDummyMessages =
1569
  withDoc "'OpTestDummy' messages field" .
1570
  renameField "TestDummyMessages" $
1571
  simpleField "messages" [t| JSValue |]
1572

    
1573
pTestDummyFail :: Field
1574
pTestDummyFail =
1575
  withDoc "'OpTestDummy' fail field" .
1576
  renameField "TestDummyFail" $ simpleField "fail" [t| JSValue |]
1577

    
1578
pTestDummySubmitJobs :: Field
1579
pTestDummySubmitJobs =
1580
  withDoc "'OpTestDummy' submit_jobs field" .
1581
  renameField "TestDummySubmitJobs" $
1582
  simpleField "submit_jobs" [t| JSValue |]
1583

    
1584
pNetworkName :: Field
1585
pNetworkName =
1586
  withDoc "Network name" $
1587
  simpleField "network_name" [t| NonEmptyString |]
1588

    
1589
pNetworkAddress4 :: Field
1590
pNetworkAddress4 =
1591
  withDoc "Network address (IPv4 subnet)" .
1592
  renameField "NetworkAddress4" $
1593
  simpleField "network" [t| IPv4Network |]
1594

    
1595
pNetworkGateway4 :: Field
1596
pNetworkGateway4 =
1597
  withDoc "Network gateway (IPv4 address)" .
1598
  renameField "NetworkGateway4" .
1599
  optionalField $ simpleField "gateway" [t| IPv4Address |]
1600

    
1601
pNetworkAddress6 :: Field
1602
pNetworkAddress6 =
1603
  withDoc "Network address (IPv6 subnet)" .
1604
  renameField "NetworkAddress6" .
1605
  optionalField $ simpleField "network6" [t| IPv6Network |]
1606

    
1607
pNetworkGateway6 :: Field
1608
pNetworkGateway6 =
1609
  withDoc "Network gateway (IPv6 address)" .
1610
  renameField "NetworkGateway6" .
1611
  optionalField $ simpleField "gateway6" [t| IPv6Address |]
1612

    
1613
pNetworkMacPrefix :: Field
1614
pNetworkMacPrefix =
1615
  withDoc "Network specific mac prefix (that overrides the cluster one)" .
1616
  renameField "NetMacPrefix" $
1617
  optionalNEStringField "mac_prefix"
1618

    
1619
pNetworkAddRsvdIps :: Field
1620
pNetworkAddRsvdIps =
1621
  withDoc "Which IP addresses to reserve" .
1622
  renameField "NetworkAddRsvdIps" .
1623
  optionalField $
1624
  simpleField "add_reserved_ips" [t| [IPv4Address] |]
1625

    
1626
pNetworkRemoveRsvdIps :: Field
1627
pNetworkRemoveRsvdIps =
1628
  withDoc "Which external IP addresses to release" .
1629
  renameField "NetworkRemoveRsvdIps" .
1630
  optionalField $
1631
  simpleField "remove_reserved_ips" [t| [IPv4Address] |]
1632

    
1633
pNetworkMode :: Field
1634
pNetworkMode =
1635
  withDoc "Network mode when connecting to a group" $
1636
  simpleField "network_mode" [t| NICMode |]
1637

    
1638
pNetworkLink :: Field
1639
pNetworkLink =
1640
  withDoc "Network link when connecting to a group" $
1641
  simpleField "network_link" [t| NonEmptyString |]