Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ b75430d9

History | View | Annotate | Download (46.5 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

    
3
{-| Implementation of opcodes parameters.
4

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

    
11
-}
12

    
13
{-
14

    
15
Copyright (C) 2012 Google Inc.
16

    
17
This program is free software; you can redistribute it and/or modify
18
it under the terms of the GNU General Public License as published by
19
the Free Software Foundation; either version 2 of the License, or
20
(at your option) any later version.
21

    
22
This program is distributed in the hope that it will be useful, but
23
WITHOUT ANY WARRANTY; without even the implied warranty of
24
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
25
General Public License for more details.
26

    
27
You should have received a copy of the GNU General Public License
28
along with this program; if not, write to the Free Software
29
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
30
02110-1301, USA.
31

    
32
-}
33

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

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

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

    
276
-- * Helper functions and types
277

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

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

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

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

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

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

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

    
311
-- ** Disks
312

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

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

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

    
329
-- ** I* param types
330

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
453
-- * Common opcode parameters
454

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

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

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

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

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

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

    
487
-- * Parameters
488

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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