Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ d0b60d3a

History | View | Annotate | Download (46.1 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

    
3
{-| Implementation of opcodes parameters.
4

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

    
11
-}
12

    
13
{-
14

    
15
Copyright (C) 2012 Google Inc.
16

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

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

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

    
32
-}
33

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

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

    
266
import Ganeti.BasicTypes
267
import qualified Ganeti.Constants as C
268
import Ganeti.THH
269
import Ganeti.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| NonEmptyString |]
343
  , optionalField $ simpleField C.inicBridge [t| NonEmptyString |]
344
  ])
345

    
346
-- | Disk modification definition. FIXME: disksize should be VTYPE_UNIT.
347
$(buildObject "IDiskParams" "idisk"
348
  [ optionalField $ simpleField C.idiskSize   [t| Int            |]
349
  , optionalField $ simpleField C.idiskMode   [t| DiskAccess     |]
350
  , optionalField $ simpleField C.idiskAdopt  [t| NonEmptyString |]
351
  , optionalField $ simpleField C.idiskVg     [t| NonEmptyString |]
352
  , optionalField $ simpleField C.idiskMetavg [t| NonEmptyString |]
353
  , optionalField $ simpleField C.idiskName   [t| NonEmptyString |]
354
  ])
355

    
356
-- | Disk snapshot definition.
357
$(buildObject "ISnapParams" "idisk"
358
  [ simpleField C.idiskSnapshotName [t| NonEmptyString |]])
359

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

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

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

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

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

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

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

    
414
-- | Custom deserialiser for 'SetParamsMods'.
415
readSetParams :: (JSON a) => JSValue -> Text.JSON.Result (SetParamsMods a)
416
readSetParams (JSArray []) = return SetParamsEmpty
417
readSetParams v =
418
  case readJSON v::Text.JSON.Result [(DdmOldChanges, JSValue)] of
419
    Text.JSON.Ok _ -> liftM SetParamsDeprecated $ readJSON v
420
    _ -> liftM SetParamsNew $ readJSON v
421

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

    
428
-- | Instance snapshot params
429
data SetSnapParams a
430
  = SetSnapParamsEmpty
431
  | SetSnapParamsValid (NonEmpty (Int, a))
432
    deriving (Eq, Show)
433

    
434
readSetSnapParams :: (JSON a) => JSValue -> Text.JSON.Result (SetSnapParams a)
435
readSetSnapParams (JSArray []) = return SetSnapParamsEmpty
436
readSetSnapParams v =
437
  case readJSON v::Text.JSON.Result [(Int, JSValue)] of
438
    Text.JSON.Ok _ -> liftM SetSnapParamsValid $ readJSON v
439
    _ -> fail "Cannot parse snapshot params."
440

    
441
instance (JSON a) => JSON (SetSnapParams a) where
442
  showJSON SetSnapParamsEmpty = showJSON ()
443
  showJSON (SetSnapParamsValid v) = showJSON v
444
  readJSON = readSetSnapParams
445

    
446
-- | Custom type for target_node parameter of OpBackupExport, which
447
-- varies depending on mode. FIXME: this uses an [JSValue] since
448
-- we don't care about individual rows (just like the Python code
449
-- tests). But the proper type could be parsed if we wanted.
450
data ExportTarget = ExportTargetLocal NonEmptyString
451
                  | ExportTargetRemote [JSValue]
452
                    deriving (Eq, Show)
453

    
454
-- | Custom reader for 'ExportTarget'.
455
readExportTarget :: JSValue -> Text.JSON.Result ExportTarget
456
readExportTarget (JSString s) = liftM ExportTargetLocal $
457
                                mkNonEmpty (fromJSString s)
458
readExportTarget (JSArray arr) = return $ ExportTargetRemote arr
459
readExportTarget v = fail $ "Invalid value received for 'target_node': " ++
460
                     show (pp_value v)
461

    
462
instance JSON ExportTarget where
463
  showJSON (ExportTargetLocal s)  = showJSON s
464
  showJSON (ExportTargetRemote l) = showJSON l
465
  readJSON = readExportTarget
466

    
467
-- * Common opcode parameters
468

    
469
pDryRun :: Field
470
pDryRun =
471
  withDoc "Run checks only, don't execute" .
472
  optionalField $ booleanField "dry_run"
473

    
474
pDebugLevel :: Field
475
pDebugLevel =
476
  withDoc "Debug level" .
477
  optionalField $ simpleField "debug_level" [t| NonNegative Int |]
478

    
479
pOpPriority :: Field
480
pOpPriority =
481
  withDoc "Opcode priority. Note: python uses a separate constant,\
482
          \ we're using the actual value we know it's the default" .
483
  defaultField [| OpPrioNormal |] $
484
  simpleField "priority" [t| OpSubmitPriority |]
485

    
486
pDependencies :: Field
487
pDependencies =
488
  withDoc "Job dependencies" .
489
  optionalNullSerField $ simpleField "depends" [t| [JobDependency] |]
490

    
491
pComment :: Field
492
pComment =
493
  withDoc "Comment field" .
494
  optionalNullSerField $ stringField "comment"
495

    
496
pReason :: Field
497
pReason =
498
  withDoc "Reason trail field" $
499
  simpleField C.opcodeReason [t| ReasonTrail |]
500

    
501
-- * Parameters
502

    
503
pDebugSimulateErrors :: Field
504
pDebugSimulateErrors =
505
  withDoc "Whether to simulate errors (useful for debugging)" $
506
  defaultFalse "debug_simulate_errors"
507

    
508
pErrorCodes :: Field
509
pErrorCodes = 
510
  withDoc "Error codes" $
511
  defaultFalse "error_codes"
512

    
513
pSkipChecks :: Field
514
pSkipChecks = 
515
  withDoc "Which checks to skip" .
516
  defaultField [| emptyListSet |] $
517
  simpleField "skip_checks" [t| ListSet VerifyOptionalChecks |]
518

    
519
pIgnoreErrors :: Field
520
pIgnoreErrors =
521
  withDoc "List of error codes that should be treated as warnings" .
522
  defaultField [| emptyListSet |] $
523
  simpleField "ignore_errors" [t| ListSet CVErrorCode |]
524

    
525
pVerbose :: Field
526
pVerbose =
527
  withDoc "Verbose mode" $
528
  defaultFalse "verbose"
529

    
530
pOptGroupName :: Field
531
pOptGroupName =
532
  withDoc "Optional group name" .
533
  renameField "OptGroupName" .
534
  optionalField $ simpleField "group_name" [t| NonEmptyString |]
535

    
536
pGroupName :: Field
537
pGroupName =
538
  withDoc "Group name" $
539
  simpleField "group_name" [t| NonEmptyString |]
540

    
541
-- | Whether to hotplug device.
542
pHotplug :: Field
543
pHotplug = defaultFalse "hotplug"
544

    
545
pHotplugIfPossible :: Field
546
pHotplugIfPossible = defaultFalse "hotplug_if_possible"
547

    
548
pInstances :: Field
549
pInstances =
550
  withDoc "List of instances" .
551
  defaultField [| [] |] $
552
  simpleField "instances" [t| [NonEmptyString] |]
553

    
554
pOutputFields :: Field
555
pOutputFields =
556
  withDoc "Selected output fields" $
557
  simpleField "output_fields" [t| [NonEmptyString] |]
558

    
559
pName :: Field
560
pName =
561
  withDoc "A generic name" $
562
  simpleField "name" [t| NonEmptyString |]
563

    
564
-- | List of instance snaps.
565
pInstSnaps :: Field
566
pInstSnaps =
567
  renameField "instSnaps" $
568
  simpleField "disks" [t| SetSnapParams ISnapParams |]
569

    
570
pForce :: Field
571
pForce =
572
  withDoc "Whether to force the operation" $
573
  defaultFalse "force"
574

    
575
pHvState :: Field
576
pHvState =
577
  withDoc "Set hypervisor states" .
578
  optionalField $ simpleField "hv_state" [t| JSObject JSValue |]
579

    
580
pDiskState :: Field
581
pDiskState =
582
  withDoc "Set disk states" .
583
  optionalField $ simpleField "disk_state" [t| JSObject JSValue |]
584

    
585
-- | Cluster-wide default directory for storing file-backed disks.
586
pClusterFileStorageDir :: Field
587
pClusterFileStorageDir =
588
  renameField "ClusterFileStorageDir" $
589
  optionalStringField "file_storage_dir"
590

    
591
-- | Cluster-wide default directory for storing shared-file-backed disks.
592
pClusterSharedFileStorageDir :: Field
593
pClusterSharedFileStorageDir =
594
  renameField "ClusterSharedFileStorageDir" $
595
  optionalStringField "shared_file_storage_dir"
596

    
597
-- | Volume group name.
598
pVgName :: Field
599
pVgName =
600
  withDoc "Volume group name" $
601
  optionalStringField "vg_name"
602

    
603
pEnabledHypervisors :: Field
604
pEnabledHypervisors =
605
  withDoc "List of enabled hypervisors" .
606
  optionalField $
607
  simpleField "enabled_hypervisors" [t| [Hypervisor] |]
608

    
609
pClusterHvParams :: Field
610
pClusterHvParams =
611
  withDoc "Cluster-wide hypervisor parameters, hypervisor-dependent" .
612
  renameField "ClusterHvParams" .
613
  optionalField $
614
  simpleField "hvparams" [t| GenericContainer String (JSObject JSValue) |]
615

    
616
pClusterBeParams :: Field
617
pClusterBeParams =
618
  withDoc "Cluster-wide backend parameter defaults" .
619
  renameField "ClusterBeParams" .
620
  optionalField $ simpleField "beparams" [t| JSObject JSValue |]
621

    
622
pOsHvp :: Field
623
pOsHvp =
624
  withDoc "Cluster-wide per-OS hypervisor parameter defaults" .
625
  optionalField $
626
  simpleField "os_hvp" [t| GenericContainer String (JSObject JSValue) |]
627

    
628
pClusterOsParams :: Field
629
pClusterOsParams =
630
  withDoc "Cluster-wide OS parameter defaults" .
631
  renameField "ClusterOsParams" .
632
  optionalField $
633
  simpleField "osparams" [t| GenericContainer String (JSObject JSValue) |]
634

    
635
pDiskParams :: Field
636
pDiskParams =
637
  withDoc "Disk templates' parameter defaults" .
638
  optionalField $
639
  simpleField "diskparams"
640
              [t| GenericContainer DiskTemplate (JSObject JSValue) |]
641

    
642
pCandidatePoolSize :: Field
643
pCandidatePoolSize =
644
  withDoc "Master candidate pool size" .
645
  optionalField $ simpleField "candidate_pool_size" [t| Positive Int |]
646

    
647
pUidPool :: Field
648
pUidPool =
649
  withDoc "Set UID pool, must be list of lists describing UID ranges\
650
          \ (two items, start and end inclusive)" .
651
  optionalField $ simpleField "uid_pool" [t| [(Int, Int)] |]
652

    
653
pAddUids :: Field
654
pAddUids =
655
  withDoc "Extend UID pool, must be list of lists describing UID\
656
          \ ranges (two items, start and end inclusive)" .
657
  optionalField $ simpleField "add_uids" [t| [(Int, Int)] |]
658

    
659
pRemoveUids :: Field
660
pRemoveUids =
661
  withDoc "Shrink UID pool, must be list of lists describing UID\
662
          \ ranges (two items, start and end inclusive) to be removed" .
663
  optionalField $ simpleField "remove_uids" [t| [(Int, Int)] |]
664

    
665
pMaintainNodeHealth :: Field
666
pMaintainNodeHealth =
667
  withDoc "Whether to automatically maintain node health" .
668
  optionalField $ booleanField "maintain_node_health"
669

    
670
-- | Whether to modify and keep in sync the @/etc/hosts@ files of nodes.
671
pModifyEtcHosts :: Field
672
pModifyEtcHosts = optionalField $ booleanField "modify_etc_hosts"
673

    
674
-- | Whether to wipe disks before allocating them to instances.
675
pPreallocWipeDisks :: Field
676
pPreallocWipeDisks =
677
  withDoc "Whether to wipe disks before allocating them to instances" .
678
  optionalField $ booleanField "prealloc_wipe_disks"
679

    
680
pNicParams :: Field
681
pNicParams =
682
  withDoc "Cluster-wide NIC parameter defaults" .
683
  optionalField $ simpleField "nicparams" [t| INicParams |]
684

    
685
pIpolicy :: Field
686
pIpolicy =
687
  withDoc "Ipolicy specs" .
688
  optionalField $ simpleField "ipolicy" [t| JSObject JSValue |]
689

    
690
pDrbdHelper :: Field
691
pDrbdHelper =
692
  withDoc "DRBD helper program" $
693
  optionalStringField "drbd_helper"
694

    
695
pDefaultIAllocator :: Field
696
pDefaultIAllocator =
697
  withDoc "Default iallocator for cluster" $
698
  optionalStringField "default_iallocator"
699

    
700
pMasterNetdev :: Field
701
pMasterNetdev =
702
  withDoc "Master network device" $
703
  optionalStringField "master_netdev"
704

    
705
pMasterNetmask :: Field
706
pMasterNetmask =
707
  withDoc "Netmask of the master IP" .
708
  optionalField $ simpleField "master_netmask" [t| NonNegative Int |]
709

    
710
pReservedLvs :: Field
711
pReservedLvs =
712
  withDoc "List of reserved LVs" .
713
  optionalField $ simpleField "reserved_lvs" [t| [NonEmptyString] |]
714

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

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

    
730
pUseExternalMipScript :: Field
731
pUseExternalMipScript =
732
  withDoc "Whether to use an external master IP address setup script" .
733
  optionalField $ booleanField "use_external_mip_script"
734

    
735
pEnabledDiskTemplates :: Field
736
pEnabledDiskTemplates =
737
  withDoc "List of enabled disk templates" .
738
  optionalField $
739
  simpleField "enabled_disk_templates" [t| [DiskTemplate] |]
740

    
741
pQueryWhat :: Field
742
pQueryWhat =
743
  withDoc "Resource(s) to query for" $
744
  simpleField "what" [t| Qlang.QueryTypeOp |]
745

    
746
pUseLocking :: Field
747
pUseLocking =
748
  withDoc "Whether to use synchronization" $
749
  defaultFalse "use_locking"
750

    
751
pQueryFields :: Field
752
pQueryFields =
753
  withDoc "Requested fields" $
754
  simpleField "fields" [t| [NonEmptyString] |]
755

    
756
pQueryFilter :: Field
757
pQueryFilter =
758
  withDoc "Query filter" .
759
  optionalField $ simpleField "qfilter" [t| [JSValue] |]
760

    
761
pQueryFieldsFields :: Field
762
pQueryFieldsFields =
763
  withDoc "Requested fields; if not given, all are returned" .
764
  renameField "QueryFieldsFields" $
765
  optionalField pQueryFields
766

    
767
pNodeNames :: Field
768
pNodeNames =
769
  withDoc "List of node names to run the OOB command against" .
770
  defaultField [| [] |] $ simpleField "node_names" [t| [NonEmptyString] |]
771

    
772
pNodeUuids :: Field
773
pNodeUuids =
774
  withDoc "List of node UUIDs" .
775
  optionalField $ simpleField "node_uuids" [t| [NonEmptyString] |]
776

    
777
pOobCommand :: Field
778
pOobCommand =
779
  withDoc "OOB command to run" $
780
  simpleField "command" [t| OobCommand |]
781

    
782
pOobTimeout :: Field
783
pOobTimeout =
784
  withDoc "Timeout before the OOB helper will be terminated" .
785
  defaultField [| C.oobTimeout |] $
786
  simpleField "timeout" [t| Int |]
787

    
788
pIgnoreStatus :: Field
789
pIgnoreStatus =
790
  withDoc "Ignores the node offline status for power off" $
791
  defaultFalse "ignore_status"
792

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

    
802
pRequiredNodes :: Field
803
pRequiredNodes =
804
  withDoc "Required list of node names" .
805
  renameField "ReqNodes " $ simpleField "nodes" [t| [NonEmptyString] |]
806

    
807
pRequiredNodeUuids :: Field
808
pRequiredNodeUuids =
809
  withDoc "Required list of node UUIDs" .
810
  renameField "ReqNodeUuids " . optionalField $
811
  simpleField "node_uuids" [t| [NonEmptyString] |]
812

    
813
pRestrictedCommand :: Field
814
pRestrictedCommand =
815
  withDoc "Restricted command name" .
816
  renameField "RestrictedCommand" $
817
  simpleField "command" [t| NonEmptyString |]
818

    
819
pNodeName :: Field
820
pNodeName =
821
  withDoc "A required node name (for single-node LUs)" $
822
  simpleField "node_name" [t| NonEmptyString |]
823

    
824
pNodeUuid :: Field
825
pNodeUuid =
826
  withDoc "A node UUID (for single-node LUs)" .
827
  optionalField $ simpleField "node_uuid" [t| NonEmptyString |]
828

    
829
pPrimaryIp :: Field
830
pPrimaryIp =
831
  withDoc "Primary IP address" .
832
  optionalField $
833
  simpleField "primary_ip" [t| NonEmptyString |]
834

    
835
pSecondaryIp :: Field
836
pSecondaryIp =
837
  withDoc "Secondary IP address" $
838
  optionalNEStringField "secondary_ip"
839

    
840
pReadd :: Field
841
pReadd =
842
  withDoc "Whether node is re-added to cluster" $
843
  defaultFalse "readd"
844

    
845
pNodeGroup :: Field
846
pNodeGroup =
847
  withDoc "Initial node group" $
848
  optionalNEStringField "group"
849

    
850
pMasterCapable :: Field
851
pMasterCapable =
852
  withDoc "Whether node can become master or master candidate" .
853
  optionalField $ booleanField "master_capable"
854

    
855
pVmCapable :: Field
856
pVmCapable =
857
  withDoc "Whether node can host instances" .
858
  optionalField $ booleanField "vm_capable"
859

    
860
pNdParams :: Field
861
pNdParams =
862
  withDoc "Node parameters" .
863
  renameField "genericNdParams" .
864
  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
865
  
866
pNames :: Field
867
pNames =
868
  withDoc "List of names" .
869
  defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
870

    
871
pNodes :: Field
872
pNodes =
873
  withDoc "List of nodes" .
874
  defaultField [| [] |] $ simpleField "nodes" [t| [NonEmptyString] |]
875

    
876
pStorageType :: Field
877
pStorageType =
878
  withDoc "Storage type" $ simpleField "storage_type" [t| StorageType |]
879

    
880
pStorageTypeOptional :: Field
881
pStorageTypeOptional =
882
  withDoc "Storage type" .
883
  renameField "StorageTypeOptional" .
884
  optionalField $ simpleField "storage_type" [t| StorageType |]
885

    
886
pStorageName :: Field
887
pStorageName =
888
  withDoc "Storage name" .
889
  renameField "StorageName" .
890
  optionalField $ simpleField "name" [t| NonEmptyString |]
891

    
892
pStorageChanges :: Field
893
pStorageChanges =
894
  withDoc "Requested storage changes" $
895
  simpleField "changes" [t| JSObject JSValue |]
896

    
897
pIgnoreConsistency :: Field
898
pIgnoreConsistency =
899
  withDoc "Whether to ignore disk consistency" $
900
  defaultFalse "ignore_consistency"
901

    
902
pMasterCandidate :: Field
903
pMasterCandidate =
904
  withDoc "Whether the node should become a master candidate" .
905
  optionalField $ booleanField "master_candidate"
906

    
907
pOffline :: Field
908
pOffline =
909
  withDoc "Whether to mark the node or instance offline" .
910
  optionalField $ booleanField "offline"
911

    
912
pDrained ::Field
913
pDrained =
914
  withDoc "Whether to mark the node as drained" .
915
  optionalField $ booleanField "drained"
916

    
917
pAutoPromote :: Field
918
pAutoPromote =
919
  withDoc "Whether node(s) should be promoted to master candidate if\
920
          \ necessary" $
921
  defaultFalse "auto_promote"
922

    
923
pPowered :: Field
924
pPowered =
925
  withDoc "Whether the node should be marked as powered" .
926
  optionalField $ booleanField "powered"
927

    
928
pMigrationMode :: Field
929
pMigrationMode =
930
  withDoc "Migration type (live/non-live)" .
931
  renameField "MigrationMode" .
932
  optionalField $
933
  simpleField "mode" [t| MigrationMode |]
934

    
935
pMigrationLive :: Field
936
pMigrationLive =
937
  withDoc "Obsolete \'live\' migration mode (do not use)" .
938
  renameField "OldLiveMode" . optionalField $ booleanField "live"
939

    
940
pMigrationTargetNode :: Field
941
pMigrationTargetNode =
942
  withDoc "Target node for instance migration/failover" $
943
  optionalNEStringField "target_node"
944

    
945
pMigrationTargetNodeUuid :: Field
946
pMigrationTargetNodeUuid =
947
  withDoc "Target node UUID for instance migration/failover" $
948
  optionalNEStringField "target_node_uuid"
949

    
950
pAllowRuntimeChgs :: Field
951
pAllowRuntimeChgs =
952
  withDoc "Whether to allow runtime changes while migrating" $
953
  defaultTrue "allow_runtime_changes"
954

    
955
pIgnoreIpolicy :: Field
956
pIgnoreIpolicy =
957
  withDoc "Whether to ignore ipolicy violations" $
958
  defaultFalse "ignore_ipolicy"
959
  
960
pIallocator :: Field
961
pIallocator =
962
  withDoc "Iallocator for deciding the target node for shared-storage\
963
          \ instances" $
964
  optionalNEStringField "iallocator"
965

    
966
pEarlyRelease :: Field
967
pEarlyRelease =
968
  withDoc "Whether to release locks as soon as possible" $
969
  defaultFalse "early_release"
970

    
971
pRemoteNode :: Field
972
pRemoteNode =
973
  withDoc "New secondary node" $
974
  optionalNEStringField "remote_node"
975

    
976
pRemoteNodeUuid :: Field
977
pRemoteNodeUuid =
978
  withDoc "New secondary node UUID" $
979
  optionalNEStringField "remote_node_uuid"
980

    
981
pEvacMode :: Field
982
pEvacMode =
983
  withDoc "Node evacuation mode" .
984
  renameField "EvacMode" $ simpleField "mode" [t| EvacMode |]
985

    
986
pInstanceName :: Field
987
pInstanceName =
988
  withDoc "A required instance name (for single-instance LUs)" $
989
  simpleField "instance_name" [t| String |]
990

    
991
pForceVariant :: Field
992
pForceVariant =
993
  withDoc "Whether to force an unknown OS variant" $
994
  defaultFalse "force_variant"
995

    
996
pWaitForSync :: Field
997
pWaitForSync =
998
  withDoc "Whether to wait for the disk to synchronize" $
999
  defaultTrue "wait_for_sync"
1000

    
1001
pNameCheck :: Field
1002
pNameCheck =
1003
  withDoc "Whether to check name" $
1004
  defaultTrue "name_check"
1005

    
1006
pInstBeParams :: Field
1007
pInstBeParams =
1008
  withDoc "Backend parameters for instance" .
1009
  renameField "InstBeParams" .
1010
  defaultField [| toJSObject [] |] $
1011
  simpleField "beparams" [t| JSObject JSValue |]
1012

    
1013
pInstDisks :: Field
1014
pInstDisks =
1015
  withDoc "List of instance disks" .
1016
  renameField "instDisks" $ simpleField "disks" [t| [IDiskParams] |]
1017

    
1018
pDiskTemplate :: Field
1019
pDiskTemplate =
1020
  withDoc "Disk template" $
1021
  simpleField "disk_template" [t| DiskTemplate |]
1022

    
1023
pFileDriver :: Field
1024
pFileDriver =
1025
  withDoc "Driver for file-backed disks" .
1026
  optionalField $ simpleField "file_driver" [t| FileDriver |]
1027

    
1028
pFileStorageDir :: Field
1029
pFileStorageDir =
1030
  withDoc "Directory for storing file-backed disks" $
1031
  optionalNEStringField "file_storage_dir"
1032

    
1033
pInstHvParams :: Field
1034
pInstHvParams =
1035
  withDoc "Hypervisor parameters for instance, hypervisor-dependent" .
1036
  renameField "InstHvParams" .
1037
  defaultField [| toJSObject [] |] $
1038
  simpleField "hvparams" [t| JSObject JSValue |]
1039

    
1040
pHypervisor :: Field
1041
pHypervisor =
1042
  withDoc "Selected hypervisor for an instance" .
1043
  optionalField $
1044
  simpleField "hypervisor" [t| Hypervisor |]
1045

    
1046
pResetDefaults :: Field
1047
pResetDefaults =
1048
  withDoc "Reset instance parameters to default if equal" $
1049
  defaultFalse "identify_defaults"
1050

    
1051
pIpCheck :: Field
1052
pIpCheck =
1053
  withDoc "Whether to ensure instance's IP address is inactive" $
1054
  defaultTrue "ip_check"
1055

    
1056
pIpConflictsCheck :: Field
1057
pIpConflictsCheck =
1058
  withDoc "Whether to check for conflicting IP addresses" $
1059
  defaultTrue "conflicts_check"
1060

    
1061
pInstCreateMode :: Field
1062
pInstCreateMode =
1063
  withDoc "Instance creation mode" .
1064
  renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
1065

    
1066
pInstNics :: Field
1067
pInstNics =
1068
  withDoc "List of NIC (network interface) definitions" $
1069
  simpleField "nics" [t| [INicParams] |]
1070

    
1071
pNoInstall :: Field
1072
pNoInstall =
1073
  withDoc "Do not install the OS (will disable automatic start)" .
1074
  optionalField $ booleanField "no_install"
1075

    
1076
pInstOs :: Field
1077
pInstOs =
1078
  withDoc "OS type for instance installation" $
1079
  optionalNEStringField "os_type"
1080

    
1081
pInstOsParams :: Field
1082
pInstOsParams =
1083
  withDoc "OS parameters for instance" .
1084
  renameField "InstOsParams" .
1085
  defaultField [| toJSObject [] |] $
1086
  simpleField "osparams" [t| JSObject JSValue |]
1087

    
1088
pPrimaryNode :: Field
1089
pPrimaryNode =
1090
  withDoc "Primary node for an instance" $
1091
  optionalNEStringField "pnode"
1092

    
1093
pPrimaryNodeUuid :: Field
1094
pPrimaryNodeUuid =
1095
  withDoc "Primary node UUID for an instance" $
1096
  optionalNEStringField "pnode_uuid"
1097

    
1098
pSecondaryNode :: Field
1099
pSecondaryNode =
1100
  withDoc "Secondary node for an instance" $
1101
  optionalNEStringField "snode"
1102

    
1103
pSecondaryNodeUuid :: Field
1104
pSecondaryNodeUuid =
1105
  withDoc "Secondary node UUID for an instance" $
1106
  optionalNEStringField "snode_uuid"
1107

    
1108
pSourceHandshake :: Field
1109
pSourceHandshake =
1110
  withDoc "Signed handshake from source (remote import only)" .
1111
  optionalField $ simpleField "source_handshake" [t| [JSValue] |]
1112

    
1113
pSourceInstance :: Field
1114
pSourceInstance =
1115
  withDoc "Source instance name (remote import only)" $
1116
  optionalNEStringField "source_instance_name"
1117

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

    
1126
pSourceX509Ca :: Field
1127
pSourceX509Ca =
1128
  withDoc "Source X509 CA in PEM format (remote import only)" $
1129
  optionalNEStringField "source_x509_ca"
1130

    
1131
pSrcNode :: Field
1132
pSrcNode =
1133
  withDoc "Source node for import" $
1134
  optionalNEStringField "src_node"
1135

    
1136
pSrcNodeUuid :: Field
1137
pSrcNodeUuid =
1138
  withDoc "Source node UUID for import" $
1139
  optionalNEStringField "src_node_uuid"
1140

    
1141
pSrcPath :: Field
1142
pSrcPath =
1143
  withDoc "Source directory for import" $
1144
  optionalNEStringField "src_path"
1145

    
1146
pStartInstance :: Field
1147
pStartInstance =
1148
  withDoc "Whether to start instance after creation" $
1149
  defaultTrue "start"
1150

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

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

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

    
1174
pInstanceUuid :: Field
1175
pInstanceUuid =
1176
  withDoc "An instance UUID (for single-instance LUs)" .
1177
  optionalField $ simpleField "instance_uuid" [t| NonEmptyString |]
1178

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

    
1186
pShutdownTimeout :: Field
1187
pShutdownTimeout =
1188
  withDoc "How long to wait for instance to shut down" .
1189
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1190
  simpleField "shutdown_timeout" [t| NonNegative Int |]
1191

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

    
1201
pIgnoreFailures :: Field
1202
pIgnoreFailures =
1203
  withDoc "Whether to ignore failures during removal" $
1204
  defaultFalse "ignore_failures"
1205

    
1206
pNewName :: Field
1207
pNewName =
1208
  withDoc "New group or instance name" $
1209
  simpleField "new_name" [t| NonEmptyString |]
1210
  
1211
pIgnoreOfflineNodes :: Field
1212
pIgnoreOfflineNodes =
1213
  withDoc "Whether to ignore offline nodes" $
1214
  defaultFalse "ignore_offline_nodes"
1215

    
1216
pTempHvParams :: Field
1217
pTempHvParams =
1218
  withDoc "Temporary hypervisor parameters, hypervisor-dependent" .
1219
  renameField "TempHvParams" .
1220
  defaultField [| toJSObject [] |] $
1221
  simpleField "hvparams" [t| JSObject JSValue |]
1222

    
1223
pTempBeParams :: Field
1224
pTempBeParams =
1225
  withDoc "Temporary backend parameters" .
1226
  renameField "TempBeParams" .
1227
  defaultField [| toJSObject [] |] $
1228
  simpleField "beparams" [t| JSObject JSValue |]
1229

    
1230
pNoRemember :: Field
1231
pNoRemember =
1232
  withDoc "Do not remember instance state changes" $
1233
  defaultFalse "no_remember"
1234

    
1235
pStartupPaused :: Field
1236
pStartupPaused =
1237
  withDoc "Pause instance at startup" $
1238
  defaultFalse "startup_paused"
1239

    
1240
pIgnoreSecondaries :: Field
1241
pIgnoreSecondaries =
1242
  withDoc "Whether to start the instance even if secondary disks are failing" $
1243
  defaultFalse "ignore_secondaries"
1244

    
1245
pRebootType :: Field
1246
pRebootType =
1247
  withDoc "How to reboot the instance" $
1248
  simpleField "reboot_type" [t| RebootType |]
1249

    
1250
pReplaceDisksMode :: Field
1251
pReplaceDisksMode =
1252
  withDoc "Replacement mode" .
1253
  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1254

    
1255
pReplaceDisksList :: Field
1256
pReplaceDisksList =
1257
  withDoc "List of disk indices" .
1258
  renameField "ReplaceDisksList" .
1259
  defaultField [| [] |] $
1260
  simpleField "disks" [t| [DiskIndex] |]
1261

    
1262
pMigrationCleanup :: Field
1263
pMigrationCleanup =
1264
  withDoc "Whether a previously failed migration should be cleaned up" .
1265
  renameField "MigrationCleanup" $ defaultFalse "cleanup"
1266

    
1267
pAllowFailover :: Field
1268
pAllowFailover =
1269
  withDoc "Whether we can fallback to failover if migration is not possible" $
1270
  defaultFalse "allow_failover"
1271

    
1272
pMoveTargetNode :: Field
1273
pMoveTargetNode =
1274
  withDoc "Target node for instance move" .
1275
  renameField "MoveTargetNode" $
1276
  simpleField "target_node" [t| NonEmptyString |]
1277

    
1278
pMoveTargetNodeUuid :: Field
1279
pMoveTargetNodeUuid =
1280
  withDoc "Target node UUID for instance move" .
1281
  renameField "MoveTargetNodeUuid" . optionalField $
1282
  simpleField "target_node_uuid" [t| NonEmptyString |]
1283

    
1284
pIgnoreDiskSize :: Field
1285
pIgnoreDiskSize =
1286
  withDoc "Whether to ignore recorded disk size" $
1287
  defaultFalse "ignore_size"
1288
  
1289
pWaitForSyncFalse :: Field
1290
pWaitForSyncFalse =
1291
  withDoc "Whether to wait for the disk to synchronize (defaults to false)" $
1292
  defaultField [| False |] pWaitForSync
1293
  
1294
pRecreateDisksInfo :: Field
1295
pRecreateDisksInfo =
1296
  withDoc "Disk list for recreate disks" .
1297
  renameField "RecreateDisksInfo" .
1298
  defaultField [| RecreateDisksAll |] $
1299
  simpleField "disks" [t| RecreateDisksInfo |]
1300

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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