Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ eabbda6f

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

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

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

    
273
-- * Helper functions and types
274

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

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

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

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

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

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

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

    
308
-- ** Disks
309

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

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

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

    
326
-- ** I* param types
327

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
449
-- * Common opcode parameters
450

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

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

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

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

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

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

    
483
-- * Parameters
484

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
663
pDrbdHelper :: Field
664
pDrbdHelper =
665
  withDoc "DRBD helper program" $
666
  optionalStringField "drbd_helper"
667

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

    
673
pDefaultIAllocatorParams :: Field
674
pDefaultIAllocatorParams =
675
  withDoc "Default iallocator parameters for cluster" . optionalField
676
    $ simpleField "default_iallocator_params" [t| JSObject JSValue |]
677

    
678
pMasterNetdev :: Field
679
pMasterNetdev =
680
  withDoc "Master network device" $
681
  optionalStringField "master_netdev"
682

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

    
688
pReservedLvs :: Field
689
pReservedLvs =
690
  withDoc "List of reserved LVs" .
691
  optionalField $ simpleField "reserved_lvs" [t| [NonEmptyString] |]
692

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

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

    
708
pUseExternalMipScript :: Field
709
pUseExternalMipScript =
710
  withDoc "Whether to use an external master IP address setup script" .
711
  optionalField $ booleanField "use_external_mip_script"
712

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

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

    
724
pUseLocking :: Field
725
pUseLocking =
726
  withDoc "Whether to use synchronization" $
727
  defaultFalse "use_locking"
728

    
729
pQueryFields :: Field
730
pQueryFields =
731
  withDoc "Requested fields" $
732
  simpleField "fields" [t| [NonEmptyString] |]
733

    
734
pQueryFilter :: Field
735
pQueryFilter =
736
  withDoc "Query filter" .
737
  optionalField $ simpleField "qfilter" [t| [JSValue] |]
738

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

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

    
750
pNodeUuids :: Field
751
pNodeUuids =
752
  withDoc "List of node UUIDs" .
753
  optionalField $ simpleField "node_uuids" [t| [NonEmptyString] |]
754

    
755
pOobCommand :: Field
756
pOobCommand =
757
  withDoc "OOB command to run" $
758
  simpleField "command" [t| OobCommand |]
759

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

    
766
pIgnoreStatus :: Field
767
pIgnoreStatus =
768
  withDoc "Ignores the node offline status for power off" $
769
  defaultFalse "ignore_status"
770

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

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

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

    
791
pRestrictedCommand :: Field
792
pRestrictedCommand =
793
  withDoc "Restricted command name" .
794
  renameField "RestrictedCommand" $
795
  simpleField "command" [t| NonEmptyString |]
796

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

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

    
807
pPrimaryIp :: Field
808
pPrimaryIp =
809
  withDoc "Primary IP address" .
810
  optionalField $
811
  simpleField "primary_ip" [t| NonEmptyString |]
812

    
813
pSecondaryIp :: Field
814
pSecondaryIp =
815
  withDoc "Secondary IP address" $
816
  optionalNEStringField "secondary_ip"
817

    
818
pReadd :: Field
819
pReadd =
820
  withDoc "Whether node is re-added to cluster" $
821
  defaultFalse "readd"
822

    
823
pNodeGroup :: Field
824
pNodeGroup =
825
  withDoc "Initial node group" $
826
  optionalNEStringField "group"
827

    
828
pMasterCapable :: Field
829
pMasterCapable =
830
  withDoc "Whether node can become master or master candidate" .
831
  optionalField $ booleanField "master_capable"
832

    
833
pVmCapable :: Field
834
pVmCapable =
835
  withDoc "Whether node can host instances" .
836
  optionalField $ booleanField "vm_capable"
837

    
838
pNdParams :: Field
839
pNdParams =
840
  withDoc "Node parameters" .
841
  renameField "genericNdParams" .
842
  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
843

    
844
pNames :: Field
845
pNames =
846
  withDoc "List of names" .
847
  defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
848

    
849
pNodes :: Field
850
pNodes =
851
  withDoc "List of nodes" .
852
  defaultField [| [] |] $ simpleField "nodes" [t| [NonEmptyString] |]
853

    
854
pStorageType :: Field
855
pStorageType =
856
  withDoc "Storage type" $ simpleField "storage_type" [t| StorageType |]
857

    
858
pStorageTypeOptional :: Field
859
pStorageTypeOptional =
860
  withDoc "Storage type" .
861
  renameField "StorageTypeOptional" .
862
  optionalField $ simpleField "storage_type" [t| StorageType |]
863

    
864
pStorageName :: Field
865
pStorageName =
866
  withDoc "Storage name" .
867
  renameField "StorageName" .
868
  optionalField $ simpleField "name" [t| NonEmptyString |]
869

    
870
pStorageChanges :: Field
871
pStorageChanges =
872
  withDoc "Requested storage changes" $
873
  simpleField "changes" [t| JSObject JSValue |]
874

    
875
pIgnoreConsistency :: Field
876
pIgnoreConsistency =
877
  withDoc "Whether to ignore disk consistency" $
878
  defaultFalse "ignore_consistency"
879

    
880
pMasterCandidate :: Field
881
pMasterCandidate =
882
  withDoc "Whether the node should become a master candidate" .
883
  optionalField $ booleanField "master_candidate"
884

    
885
pOffline :: Field
886
pOffline =
887
  withDoc "Whether to mark the node or instance offline" .
888
  optionalField $ booleanField "offline"
889

    
890
pDrained ::Field
891
pDrained =
892
  withDoc "Whether to mark the node as drained" .
893
  optionalField $ booleanField "drained"
894

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

    
901
pPowered :: Field
902
pPowered =
903
  withDoc "Whether the node should be marked as powered" .
904
  optionalField $ booleanField "powered"
905

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

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

    
918
pMigrationTargetNode :: Field
919
pMigrationTargetNode =
920
  withDoc "Target node for instance migration/failover" $
921
  optionalNEStringField "target_node"
922

    
923
pMigrationTargetNodeUuid :: Field
924
pMigrationTargetNodeUuid =
925
  withDoc "Target node UUID for instance migration/failover" $
926
  optionalNEStringField "target_node_uuid"
927

    
928
pAllowRuntimeChgs :: Field
929
pAllowRuntimeChgs =
930
  withDoc "Whether to allow runtime changes while migrating" $
931
  defaultTrue "allow_runtime_changes"
932

    
933
pIgnoreIpolicy :: Field
934
pIgnoreIpolicy =
935
  withDoc "Whether to ignore ipolicy violations" $
936
  defaultFalse "ignore_ipolicy"
937

    
938
pIallocator :: Field
939
pIallocator =
940
  withDoc "Iallocator for deciding the target node for shared-storage\
941
          \ instances" $
942
  optionalNEStringField "iallocator"
943

    
944
pEarlyRelease :: Field
945
pEarlyRelease =
946
  withDoc "Whether to release locks as soon as possible" $
947
  defaultFalse "early_release"
948

    
949
pRemoteNode :: Field
950
pRemoteNode =
951
  withDoc "New secondary node" $
952
  optionalNEStringField "remote_node"
953

    
954
pRemoteNodeUuid :: Field
955
pRemoteNodeUuid =
956
  withDoc "New secondary node UUID" $
957
  optionalNEStringField "remote_node_uuid"
958

    
959
pEvacMode :: Field
960
pEvacMode =
961
  withDoc "Node evacuation mode" .
962
  renameField "EvacMode" $ simpleField "mode" [t| EvacMode |]
963

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

    
969
pForceVariant :: Field
970
pForceVariant =
971
  withDoc "Whether to force an unknown OS variant" $
972
  defaultFalse "force_variant"
973

    
974
pWaitForSync :: Field
975
pWaitForSync =
976
  withDoc "Whether to wait for the disk to synchronize" $
977
  defaultTrue "wait_for_sync"
978

    
979
pNameCheck :: Field
980
pNameCheck =
981
  withDoc "Whether to check name" $
982
  defaultTrue "name_check"
983

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

    
991
pInstDisks :: Field
992
pInstDisks =
993
  withDoc "List of instance disks" .
994
  renameField "instDisks" $ simpleField "disks" [t| [IDiskParams] |]
995

    
996
pDiskTemplate :: Field
997
pDiskTemplate =
998
  withDoc "Disk template" $
999
  simpleField "disk_template" [t| DiskTemplate |]
1000

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

    
1006
pFileStorageDir :: Field
1007
pFileStorageDir =
1008
  withDoc "Directory for storing file-backed disks" $
1009
  optionalNEStringField "file_storage_dir"
1010

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

    
1018
pHypervisor :: Field
1019
pHypervisor =
1020
  withDoc "Selected hypervisor for an instance" .
1021
  optionalField $
1022
  simpleField "hypervisor" [t| Hypervisor |]
1023

    
1024
pResetDefaults :: Field
1025
pResetDefaults =
1026
  withDoc "Reset instance parameters to default if equal" $
1027
  defaultFalse "identify_defaults"
1028

    
1029
pIpCheck :: Field
1030
pIpCheck =
1031
  withDoc "Whether to ensure instance's IP address is inactive" $
1032
  defaultTrue "ip_check"
1033

    
1034
pIpConflictsCheck :: Field
1035
pIpConflictsCheck =
1036
  withDoc "Whether to check for conflicting IP addresses" $
1037
  defaultTrue "conflicts_check"
1038

    
1039
pInstCreateMode :: Field
1040
pInstCreateMode =
1041
  withDoc "Instance creation mode" .
1042
  renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
1043

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

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

    
1054
pInstOs :: Field
1055
pInstOs =
1056
  withDoc "OS type for instance installation" $
1057
  optionalNEStringField "os_type"
1058

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

    
1066
pPrimaryNode :: Field
1067
pPrimaryNode =
1068
  withDoc "Primary node for an instance" $
1069
  optionalNEStringField "pnode"
1070

    
1071
pPrimaryNodeUuid :: Field
1072
pPrimaryNodeUuid =
1073
  withDoc "Primary node UUID for an instance" $
1074
  optionalNEStringField "pnode_uuid"
1075

    
1076
pSecondaryNode :: Field
1077
pSecondaryNode =
1078
  withDoc "Secondary node for an instance" $
1079
  optionalNEStringField "snode"
1080

    
1081
pSecondaryNodeUuid :: Field
1082
pSecondaryNodeUuid =
1083
  withDoc "Secondary node UUID for an instance" $
1084
  optionalNEStringField "snode_uuid"
1085

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

    
1091
pSourceInstance :: Field
1092
pSourceInstance =
1093
  withDoc "Source instance name (remote import only)" $
1094
  optionalNEStringField "source_instance_name"
1095

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

    
1104
pSourceX509Ca :: Field
1105
pSourceX509Ca =
1106
  withDoc "Source X509 CA in PEM format (remote import only)" $
1107
  optionalNEStringField "source_x509_ca"
1108

    
1109
pSrcNode :: Field
1110
pSrcNode =
1111
  withDoc "Source node for import" $
1112
  optionalNEStringField "src_node"
1113

    
1114
pSrcNodeUuid :: Field
1115
pSrcNodeUuid =
1116
  withDoc "Source node UUID for import" $
1117
  optionalNEStringField "src_node_uuid"
1118

    
1119
pSrcPath :: Field
1120
pSrcPath =
1121
  withDoc "Source directory for import" $
1122
  optionalNEStringField "src_path"
1123

    
1124
pStartInstance :: Field
1125
pStartInstance =
1126
  withDoc "Whether to start instance after creation" $
1127
  defaultTrue "start"
1128

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

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

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

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

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

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

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

    
1179
pIgnoreFailures :: Field
1180
pIgnoreFailures =
1181
  withDoc "Whether to ignore failures during removal" $
1182
  defaultFalse "ignore_failures"
1183

    
1184
pNewName :: Field
1185
pNewName =
1186
  withDoc "New group or instance name" $
1187
  simpleField "new_name" [t| NonEmptyString |]
1188

    
1189
pIgnoreOfflineNodes :: Field
1190
pIgnoreOfflineNodes =
1191
  withDoc "Whether to ignore offline nodes" $
1192
  defaultFalse "ignore_offline_nodes"
1193

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

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

    
1208
pNoRemember :: Field
1209
pNoRemember =
1210
  withDoc "Do not remember instance state changes" $
1211
  defaultFalse "no_remember"
1212

    
1213
pStartupPaused :: Field
1214
pStartupPaused =
1215
  withDoc "Pause instance at startup" $
1216
  defaultFalse "startup_paused"
1217

    
1218
pIgnoreSecondaries :: Field
1219
pIgnoreSecondaries =
1220
  withDoc "Whether to start the instance even if secondary disks are failing" $
1221
  defaultFalse "ignore_secondaries"
1222

    
1223
pRebootType :: Field
1224
pRebootType =
1225
  withDoc "How to reboot the instance" $
1226
  simpleField "reboot_type" [t| RebootType |]
1227

    
1228
pReplaceDisksMode :: Field
1229
pReplaceDisksMode =
1230
  withDoc "Replacement mode" .
1231
  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1232

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

    
1240
pMigrationCleanup :: Field
1241
pMigrationCleanup =
1242
  withDoc "Whether a previously failed migration should be cleaned up" .
1243
  renameField "MigrationCleanup" $ defaultFalse "cleanup"
1244

    
1245
pAllowFailover :: Field
1246
pAllowFailover =
1247
  withDoc "Whether we can fallback to failover if migration is not possible" $
1248
  defaultFalse "allow_failover"
1249

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

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

    
1262
pMoveCompress :: Field
1263
pMoveCompress =
1264
  withDoc "Compression mode to use during instance moves" .
1265
  defaultField [| None |] $
1266
  simpleField "compress" [t| ImportExportCompression |]
1267

    
1268
pBackupCompress :: Field
1269
pBackupCompress =
1270
  withDoc "Compression mode to use for moves during backups/imports" .
1271
  defaultField [| None |] $
1272
  simpleField "compress" [t| ImportExportCompression |]
1273

    
1274
pIgnoreDiskSize :: Field
1275
pIgnoreDiskSize =
1276
  withDoc "Whether to ignore recorded disk size" $
1277
  defaultFalse "ignore_size"
1278

    
1279
pWaitForSyncFalse :: Field
1280
pWaitForSyncFalse =
1281
  withDoc "Whether to wait for the disk to synchronize (defaults to false)" $
1282
  defaultField [| False |] pWaitForSync
1283

    
1284
pRecreateDisksInfo :: Field
1285
pRecreateDisksInfo =
1286
  withDoc "Disk list for recreate disks" .
1287
  renameField "RecreateDisksInfo" .
1288
  defaultField [| RecreateDisksAll |] $
1289
  simpleField "disks" [t| RecreateDisksInfo |]
1290

    
1291
pStatic :: Field
1292
pStatic =
1293
  withDoc "Whether to only return configuration data without querying nodes" $
1294
  defaultFalse "static"
1295

    
1296
pInstParamsNicChanges :: Field
1297
pInstParamsNicChanges =
1298
  withDoc "List of NIC changes" .
1299
  renameField "InstNicChanges" .
1300
  defaultField [| SetParamsEmpty |] $
1301
  simpleField "nics" [t| SetParamsMods INicParams |]
1302

    
1303
pInstParamsDiskChanges :: Field
1304
pInstParamsDiskChanges =
1305
  withDoc "List of disk changes" .
1306
  renameField "InstDiskChanges" .
1307
  defaultField [| SetParamsEmpty |] $
1308
  simpleField "disks" [t| SetParamsMods IDiskParams |]
1309

    
1310
pRuntimeMem :: Field
1311
pRuntimeMem =
1312
  withDoc "New runtime memory" .
1313
  optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1314

    
1315
pOptDiskTemplate :: Field
1316
pOptDiskTemplate =
1317
  withDoc "Instance disk template" .
1318
  optionalField .
1319
  renameField "OptDiskTemplate" $
1320
  simpleField "disk_template" [t| DiskTemplate |]
1321

    
1322
pOsNameChange :: Field
1323
pOsNameChange =
1324
  withDoc "Change the instance's OS without reinstalling the instance" $
1325
  optionalNEStringField "os_name"
1326

    
1327
pDiskIndex :: Field
1328
pDiskIndex =
1329
  withDoc "Disk index for e.g. grow disk" .
1330
  renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
1331

    
1332
pDiskChgAmount :: Field
1333
pDiskChgAmount =
1334
  withDoc "Disk amount to add or grow to" .
1335
  renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
1336

    
1337
pDiskChgAbsolute :: Field
1338
pDiskChgAbsolute =
1339
  withDoc
1340
    "Whether the amount parameter is an absolute target or a relative one" .
1341
  renameField "DiskChkAbsolute" $ defaultFalse "absolute"
1342

    
1343
pTargetGroups :: Field
1344
pTargetGroups =
1345
  withDoc
1346
    "Destination group names or UUIDs (defaults to \"all but current group\")" .
1347
  optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
1348

    
1349
pNodeGroupAllocPolicy :: Field
1350
pNodeGroupAllocPolicy =
1351
  withDoc "Instance allocation policy" .
1352
  optionalField $
1353
  simpleField "alloc_policy" [t| AllocPolicy |]
1354

    
1355
pGroupNodeParams :: Field
1356
pGroupNodeParams =
1357
  withDoc "Default node parameters for group" .
1358
  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
1359

    
1360
pExportMode :: Field
1361
pExportMode =
1362
  withDoc "Export mode" .
1363
  renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1364

    
1365
-- FIXME: Rename target_node as it changes meaning for different
1366
-- export modes (e.g. "destination")
1367
pExportTargetNode :: Field
1368
pExportTargetNode =
1369
  withDoc "Target node (depends on export mode)" .
1370
  renameField "ExportTarget" $
1371
  simpleField "target_node" [t| ExportTarget |]
1372

    
1373
pExportTargetNodeUuid :: Field
1374
pExportTargetNodeUuid =
1375
  withDoc "Target node UUID (if local export)" .
1376
  renameField "ExportTargetNodeUuid" . optionalField $
1377
  simpleField "target_node_uuid" [t| NonEmptyString |]
1378

    
1379
pShutdownInstance :: Field
1380
pShutdownInstance =
1381
  withDoc "Whether to shutdown the instance before export" $
1382
  defaultTrue "shutdown"
1383

    
1384
pRemoveInstance :: Field
1385
pRemoveInstance =
1386
  withDoc "Whether to remove instance after export" $
1387
  defaultFalse "remove_instance"
1388

    
1389
pIgnoreRemoveFailures :: Field
1390
pIgnoreRemoveFailures =
1391
  withDoc "Whether to ignore failures while removing instances" $
1392
  defaultFalse "ignore_remove_failures"
1393

    
1394
pX509KeyName :: Field
1395
pX509KeyName =
1396
  withDoc "Name of X509 key (remote export only)" .
1397
  optionalField $ simpleField "x509_key_name" [t| [JSValue] |]
1398

    
1399
pX509DestCA :: Field
1400
pX509DestCA =
1401
  withDoc "Destination X509 CA (remote export only)" $
1402
  optionalNEStringField "destination_x509_ca"
1403

    
1404
pTagsObject :: Field
1405
pTagsObject =
1406
  withDoc "Tag kind" $
1407
  simpleField "kind" [t| TagKind |]
1408

    
1409
pTagsName :: Field
1410
pTagsName =
1411
  withDoc "Name of object" .
1412
  renameField "TagsGetName" .
1413
  optionalField $ simpleField "name" [t| String |]
1414

    
1415
pTagsList :: Field
1416
pTagsList =
1417
  withDoc "List of tag names" $
1418
  simpleField "tags" [t| [String] |]
1419

    
1420
-- FIXME: this should be compiled at load time?
1421
pTagSearchPattern :: Field
1422
pTagSearchPattern =
1423
  withDoc "Search pattern (regular expression)" .
1424
  renameField "TagSearchPattern" $
1425
  simpleField "pattern" [t| NonEmptyString |]
1426

    
1427
pDelayDuration :: Field
1428
pDelayDuration =
1429
  withDoc "Duration parameter for 'OpTestDelay'" .
1430
  renameField "DelayDuration" $
1431
  simpleField "duration" [t| Double |]
1432

    
1433
pDelayOnMaster :: Field
1434
pDelayOnMaster =
1435
  withDoc "on_master field for 'OpTestDelay'" .
1436
  renameField "DelayOnMaster" $
1437
  defaultTrue "on_master"
1438

    
1439
pDelayOnNodes :: Field
1440
pDelayOnNodes =
1441
  withDoc "on_nodes field for 'OpTestDelay'" .
1442
  renameField "DelayOnNodes" .
1443
  defaultField [| [] |] $
1444
  simpleField "on_nodes" [t| [NonEmptyString] |]
1445

    
1446
pDelayOnNodeUuids :: Field
1447
pDelayOnNodeUuids =
1448
  withDoc "on_node_uuids field for 'OpTestDelay'" .
1449
  renameField "DelayOnNodeUuids" . optionalField $
1450
  simpleField "on_node_uuids" [t| [NonEmptyString] |]
1451

    
1452
pDelayRepeat :: Field
1453
pDelayRepeat =
1454
  withDoc "Repeat parameter for OpTestDelay" .
1455
  renameField "DelayRepeat" .
1456
  defaultField [| forceNonNeg (0::Int) |] $
1457
  simpleField "repeat" [t| NonNegative Int |]
1458

    
1459
pIAllocatorDirection :: Field
1460
pIAllocatorDirection =
1461
  withDoc "IAllocator test direction" .
1462
  renameField "IAllocatorDirection" $
1463
  simpleField "direction" [t| IAllocatorTestDir |]
1464

    
1465
pIAllocatorMode :: Field
1466
pIAllocatorMode =
1467
  withDoc "IAllocator test mode" .
1468
  renameField "IAllocatorMode" $
1469
  simpleField "mode" [t| IAllocatorMode |]
1470

    
1471
pIAllocatorReqName :: Field
1472
pIAllocatorReqName =
1473
  withDoc "IAllocator target name (new instance, node to evac, etc.)" .
1474
  renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
1475

    
1476
pIAllocatorNics :: Field
1477
pIAllocatorNics =
1478
  withDoc "Custom OpTestIAllocator nics" .
1479
  renameField "IAllocatorNics" .
1480
  optionalField $ simpleField "nics" [t| [INicParams] |]
1481

    
1482
pIAllocatorDisks :: Field
1483
pIAllocatorDisks =
1484
  withDoc "Custom OpTestAllocator disks" .
1485
  renameField "IAllocatorDisks" .
1486
  optionalField $ simpleField "disks" [t| [JSValue] |]
1487

    
1488
pIAllocatorMemory :: Field
1489
pIAllocatorMemory =
1490
  withDoc "IAllocator memory field" .
1491
  renameField "IAllocatorMem" .
1492
  optionalField $
1493
  simpleField "memory" [t| NonNegative Int |]
1494

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

    
1502
pIAllocatorOs :: Field
1503
pIAllocatorOs =
1504
  withDoc "IAllocator os field" .
1505
  renameField "IAllocatorOs" $ optionalNEStringField "os"
1506

    
1507
pIAllocatorInstances :: Field
1508
pIAllocatorInstances =
1509
  withDoc "IAllocator instances field" .
1510
  renameField "IAllocatorInstances " .
1511
  optionalField $
1512
  simpleField "instances" [t| [NonEmptyString] |]
1513

    
1514
pIAllocatorEvacMode :: Field
1515
pIAllocatorEvacMode =
1516
  withDoc "IAllocator evac mode" .
1517
  renameField "IAllocatorEvacMode" .
1518
  optionalField $
1519
  simpleField "evac_mode" [t| EvacMode |]
1520

    
1521
pIAllocatorSpindleUse :: Field
1522
pIAllocatorSpindleUse =
1523
  withDoc "IAllocator spindle use" .
1524
  renameField "IAllocatorSpindleUse" .
1525
  defaultField [| forceNonNeg (1::Int) |] $
1526
  simpleField "spindle_use" [t| NonNegative Int |]
1527

    
1528
pIAllocatorCount :: Field
1529
pIAllocatorCount =
1530
  withDoc "IAllocator count field" .
1531
  renameField "IAllocatorCount" .
1532
  defaultField [| forceNonNeg (1::Int) |] $
1533
  simpleField "count" [t| NonNegative Int |]
1534

    
1535
pJQueueNotifyWaitLock :: Field
1536
pJQueueNotifyWaitLock =
1537
  withDoc "'OpTestJqueue' notify_waitlock" $
1538
  defaultFalse "notify_waitlock"
1539

    
1540
pJQueueNotifyExec :: Field
1541
pJQueueNotifyExec =
1542
  withDoc "'OpTestJQueue' notify_exec" $
1543
  defaultFalse "notify_exec"
1544

    
1545
pJQueueLogMessages :: Field
1546
pJQueueLogMessages =
1547
  withDoc "'OpTestJQueue' log_messages" .
1548
  defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
1549

    
1550
pJQueueFail :: Field
1551
pJQueueFail =
1552
  withDoc "'OpTestJQueue' fail attribute" .
1553
  renameField "JQueueFail" $ defaultFalse "fail"
1554

    
1555
pTestDummyResult :: Field
1556
pTestDummyResult =
1557
  withDoc "'OpTestDummy' result field" .
1558
  renameField "TestDummyResult" $ simpleField "result" [t| JSValue |]
1559

    
1560
pTestDummyMessages :: Field
1561
pTestDummyMessages =
1562
  withDoc "'OpTestDummy' messages field" .
1563
  renameField "TestDummyMessages" $
1564
  simpleField "messages" [t| JSValue |]
1565

    
1566
pTestDummyFail :: Field
1567
pTestDummyFail =
1568
  withDoc "'OpTestDummy' fail field" .
1569
  renameField "TestDummyFail" $ simpleField "fail" [t| JSValue |]
1570

    
1571
pTestDummySubmitJobs :: Field
1572
pTestDummySubmitJobs =
1573
  withDoc "'OpTestDummy' submit_jobs field" .
1574
  renameField "TestDummySubmitJobs" $
1575
  simpleField "submit_jobs" [t| JSValue |]
1576

    
1577
pNetworkName :: Field
1578
pNetworkName =
1579
  withDoc "Network name" $
1580
  simpleField "network_name" [t| NonEmptyString |]
1581

    
1582
pNetworkAddress4 :: Field
1583
pNetworkAddress4 =
1584
  withDoc "Network address (IPv4 subnet)" .
1585
  renameField "NetworkAddress4" $
1586
  simpleField "network" [t| IPv4Network |]
1587

    
1588
pNetworkGateway4 :: Field
1589
pNetworkGateway4 =
1590
  withDoc "Network gateway (IPv4 address)" .
1591
  renameField "NetworkGateway4" .
1592
  optionalField $ simpleField "gateway" [t| IPv4Address |]
1593

    
1594
pNetworkAddress6 :: Field
1595
pNetworkAddress6 =
1596
  withDoc "Network address (IPv6 subnet)" .
1597
  renameField "NetworkAddress6" .
1598
  optionalField $ simpleField "network6" [t| IPv6Network |]
1599

    
1600
pNetworkGateway6 :: Field
1601
pNetworkGateway6 =
1602
  withDoc "Network gateway (IPv6 address)" .
1603
  renameField "NetworkGateway6" .
1604
  optionalField $ simpleField "gateway6" [t| IPv6Address |]
1605

    
1606
pNetworkMacPrefix :: Field
1607
pNetworkMacPrefix =
1608
  withDoc "Network specific mac prefix (that overrides the cluster one)" .
1609
  renameField "NetMacPrefix" $
1610
  optionalNEStringField "mac_prefix"
1611

    
1612
pNetworkAddRsvdIps :: Field
1613
pNetworkAddRsvdIps =
1614
  withDoc "Which IP addresses to reserve" .
1615
  renameField "NetworkAddRsvdIps" .
1616
  optionalField $
1617
  simpleField "add_reserved_ips" [t| [IPv4Address] |]
1618

    
1619
pNetworkRemoveRsvdIps :: Field
1620
pNetworkRemoveRsvdIps =
1621
  withDoc "Which external IP addresses to release" .
1622
  renameField "NetworkRemoveRsvdIps" .
1623
  optionalField $
1624
  simpleField "remove_reserved_ips" [t| [IPv4Address] |]
1625

    
1626
pNetworkMode :: Field
1627
pNetworkMode =
1628
  withDoc "Network mode when connecting to a group" $
1629
  simpleField "network_mode" [t| NICMode |]
1630

    
1631
pNetworkLink :: Field
1632
pNetworkLink =
1633
  withDoc "Network link when connecting to a group" $
1634
  simpleField "network_link" [t| NonEmptyString |]