Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ 7d81bb8b

History | View | Annotate | Download (46.7 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
  , pGroupDiskParams
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
  , pForceFailover
217
  , pDelayDuration
218
  , pDelayOnMaster
219
  , pDelayOnNodes
220
  , pDelayOnNodeUuids
221
  , pDelayRepeat
222
  , pDelayNoLocks
223
  , pIAllocatorDirection
224
  , pIAllocatorMode
225
  , pIAllocatorReqName
226
  , pIAllocatorNics
227
  , pIAllocatorDisks
228
  , pIAllocatorMemory
229
  , pIAllocatorVCpus
230
  , pIAllocatorOs
231
  , pIAllocatorInstances
232
  , pIAllocatorEvacMode
233
  , pIAllocatorSpindleUse
234
  , pIAllocatorCount
235
  , pJQueueNotifyWaitLock
236
  , pJQueueNotifyExec
237
  , pJQueueLogMessages
238
  , pJQueueFail
239
  , pTestDummyResult
240
  , pTestDummyMessages
241
  , pTestDummyFail
242
  , pTestDummySubmitJobs
243
  , pNetworkName
244
  , pNetworkAddress4
245
  , pNetworkGateway4
246
  , pNetworkAddress6
247
  , pNetworkGateway6
248
  , pNetworkMacPrefix
249
  , pNetworkAddRsvdIps
250
  , pNetworkRemoveRsvdIps
251
  , pNetworkMode
252
  , pNetworkLink
253
  , pDryRun
254
  , pDebugLevel
255
  , pOpPriority
256
  , pDependencies
257
  , pComment
258
  , pReason
259
  , pSequential
260
  , pEnabledDiskTemplates
261
  ) where
262

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

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

    
276
-- * Helper functions and types
277

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

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

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

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

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

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

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

    
311
-- ** Disks
312

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

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

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

    
329
-- ** I* param types
330

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

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

    
349
-- | Disk modification definition. FIXME: disksize should be VTYPE_UNIT.
350
$(buildObject "IDiskParams" "idisk"
351
  [ optionalField $ simpleField C.idiskSize   [t| Int            |]
352
  , optionalField $ simpleField C.idiskMode   [t| DiskAccess     |]
353
  , optionalField $ simpleField C.idiskAdopt  [t| NonEmptyString |]
354
  , optionalField $ simpleField C.idiskVg     [t| NonEmptyString |]
355
  , optionalField $ simpleField C.idiskMetavg [t| NonEmptyString |]
356
  , optionalField $ simpleField C.idiskName   [t| NonEmptyString |]
357
  , optionalField $ simpleField C.idiskProvider [t| NonEmptyString |]
358
  , optionalField $ simpleField C.idiskAccess   [t| NonEmptyString |]
359
  , andRestArguments "opaque"
360
  ])
361

    
362
-- | Disk snapshot definition.
363
$(buildObject "ISnapParams" "idisk"
364
  [ simpleField C.idiskSnapshotName [t| NonEmptyString |]])
365

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

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

    
388
instance JSON RecreateDisksInfo where
389
  readJSON = readRecreateDisks
390
  showJSON  RecreateDisksAll            = showJSON ()
391
  showJSON (RecreateDisksIndices idx)   = showJSON idx
392
  showJSON (RecreateDisksParams params) = showJSON params
393

    
394
-- | Simple type for old-style ddm changes.
395
data DdmOldChanges = DdmOldIndex (NonNegative Int)
396
                   | DdmOldMod DdmSimple
397
                     deriving (Eq, Show)
398

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

    
408
instance JSON DdmOldChanges where
409
  showJSON (DdmOldIndex i) = showJSON i
410
  showJSON (DdmOldMod m)   = showJSON m
411
  readJSON = readDdmOldChanges
412

    
413
-- | Instance disk or nic modifications.
414
data SetParamsMods a
415
  = SetParamsEmpty
416
  | SetParamsDeprecated (NonEmpty (DdmOldChanges, a))
417
  | SetParamsNew (NonEmpty (DdmFull, Int, a))
418
    deriving (Eq, Show)
419

    
420
-- | Custom deserialiser for 'SetParamsMods'.
421
readSetParams :: (JSON a) => JSValue -> Text.JSON.Result (SetParamsMods a)
422
readSetParams (JSArray []) = return SetParamsEmpty
423
readSetParams v =
424
  case readJSON v::Text.JSON.Result [(DdmOldChanges, JSValue)] of
425
    Text.JSON.Ok _ -> liftM SetParamsDeprecated $ readJSON v
426
    _ -> liftM SetParamsNew $ readJSON v
427

    
428
instance (JSON a) => JSON (SetParamsMods a) where
429
  showJSON SetParamsEmpty = showJSON ()
430
  showJSON (SetParamsDeprecated v) = showJSON v
431
  showJSON (SetParamsNew v) = showJSON v
432
  readJSON = readSetParams
433

    
434
-- | Instance snapshot params
435
data SetSnapParams a
436
  = SetSnapParamsEmpty
437
  | SetSnapParamsValid (NonEmpty (Int, a))
438
    deriving (Eq, Show)
439

    
440
readSetSnapParams :: (JSON a) => JSValue -> Text.JSON.Result (SetSnapParams a)
441
readSetSnapParams (JSArray []) = return SetSnapParamsEmpty
442
readSetSnapParams v =
443
  case readJSON v::Text.JSON.Result [(Int, JSValue)] of
444
    Text.JSON.Ok _ -> liftM SetSnapParamsValid $ readJSON v
445
    _ -> fail "Cannot parse snapshot params."
446

    
447
instance (JSON a) => JSON (SetSnapParams a) where
448
  showJSON SetSnapParamsEmpty = showJSON ()
449
  showJSON (SetSnapParamsValid v) = showJSON v
450
  readJSON = readSetSnapParams
451

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

    
460
-- | Custom reader for 'ExportTarget'.
461
readExportTarget :: JSValue -> Text.JSON.Result ExportTarget
462
readExportTarget (JSString s) = liftM ExportTargetLocal $
463
                                mkNonEmpty (fromJSString s)
464
readExportTarget (JSArray arr) = return $ ExportTargetRemote arr
465
readExportTarget v = fail $ "Invalid value received for 'target_node': " ++
466
                     show (pp_value v)
467

    
468
instance JSON ExportTarget where
469
  showJSON (ExportTargetLocal s)  = showJSON s
470
  showJSON (ExportTargetRemote l) = showJSON l
471
  readJSON = readExportTarget
472

    
473
-- * Common opcode parameters
474

    
475
pDryRun :: Field
476
pDryRun =
477
  withDoc "Run checks only, don't execute" .
478
  optionalField $ booleanField "dry_run"
479

    
480
pDebugLevel :: Field
481
pDebugLevel =
482
  withDoc "Debug level" .
483
  optionalField $ simpleField "debug_level" [t| NonNegative Int |]
484

    
485
pOpPriority :: Field
486
pOpPriority =
487
  withDoc "Opcode priority. Note: python uses a separate constant,\
488
          \ we're using the actual value we know it's the default" .
489
  defaultField [| OpPrioNormal |] $
490
  simpleField "priority" [t| OpSubmitPriority |]
491

    
492
pDependencies :: Field
493
pDependencies =
494
  withDoc "Job dependencies" .
495
  optionalNullSerField $ simpleField "depends" [t| [JobDependency] |]
496

    
497
pComment :: Field
498
pComment =
499
  withDoc "Comment field" .
500
  optionalNullSerField $ stringField "comment"
501

    
502
pReason :: Field
503
pReason =
504
  withDoc "Reason trail field" $
505
  simpleField C.opcodeReason [t| ReasonTrail |]
506

    
507
pSequential :: Field
508
pSequential =
509
  withDoc "Sequential job execution" $
510
  defaultFalse C.opcodeSequential
511

    
512
-- * Parameters
513

    
514
pDebugSimulateErrors :: Field
515
pDebugSimulateErrors =
516
  withDoc "Whether to simulate errors (useful for debugging)" $
517
  defaultFalse "debug_simulate_errors"
518

    
519
pErrorCodes :: Field
520
pErrorCodes = 
521
  withDoc "Error codes" $
522
  defaultFalse "error_codes"
523

    
524
pSkipChecks :: Field
525
pSkipChecks = 
526
  withDoc "Which checks to skip" .
527
  defaultField [| emptyListSet |] $
528
  simpleField "skip_checks" [t| ListSet VerifyOptionalChecks |]
529

    
530
pIgnoreErrors :: Field
531
pIgnoreErrors =
532
  withDoc "List of error codes that should be treated as warnings" .
533
  defaultField [| emptyListSet |] $
534
  simpleField "ignore_errors" [t| ListSet CVErrorCode |]
535

    
536
pVerbose :: Field
537
pVerbose =
538
  withDoc "Verbose mode" $
539
  defaultFalse "verbose"
540

    
541
pOptGroupName :: Field
542
pOptGroupName =
543
  withDoc "Optional group name" .
544
  renameField "OptGroupName" .
545
  optionalField $ simpleField "group_name" [t| NonEmptyString |]
546

    
547
pGroupName :: Field
548
pGroupName =
549
  withDoc "Group name" $
550
  simpleField "group_name" [t| NonEmptyString |]
551

    
552
-- | Whether to hotplug device.
553
pHotplug :: Field
554
pHotplug = defaultFalse "hotplug"
555

    
556
pHotplugIfPossible :: Field
557
pHotplugIfPossible = defaultFalse "hotplug_if_possible"
558

    
559
pInstances :: Field
560
pInstances =
561
  withDoc "List of instances" .
562
  defaultField [| [] |] $
563
  simpleField "instances" [t| [NonEmptyString] |]
564

    
565
pOutputFields :: Field
566
pOutputFields =
567
  withDoc "Selected output fields" $
568
  simpleField "output_fields" [t| [NonEmptyString] |]
569

    
570
pName :: Field
571
pName =
572
  withDoc "A generic name" $
573
  simpleField "name" [t| NonEmptyString |]
574

    
575
-- | List of instance snaps.
576
pInstSnaps :: Field
577
pInstSnaps =
578
  renameField "instSnaps" $
579
  simpleField "disks" [t| SetSnapParams ISnapParams |]
580

    
581
pForce :: Field
582
pForce =
583
  withDoc "Whether to force the operation" $
584
  defaultFalse "force"
585

    
586
pHvState :: Field
587
pHvState =
588
  withDoc "Set hypervisor states" .
589
  optionalField $ simpleField "hv_state" [t| JSObject JSValue |]
590

    
591
pDiskState :: Field
592
pDiskState =
593
  withDoc "Set disk states" .
594
  optionalField $ simpleField "disk_state" [t| JSObject JSValue |]
595

    
596
-- | Cluster-wide default directory for storing file-backed disks.
597
pClusterFileStorageDir :: Field
598
pClusterFileStorageDir =
599
  renameField "ClusterFileStorageDir" $
600
  optionalStringField "file_storage_dir"
601

    
602
-- | Cluster-wide default directory for storing shared-file-backed disks.
603
pClusterSharedFileStorageDir :: Field
604
pClusterSharedFileStorageDir =
605
  renameField "ClusterSharedFileStorageDir" $
606
  optionalStringField "shared_file_storage_dir"
607

    
608
-- | Volume group name.
609
pVgName :: Field
610
pVgName =
611
  withDoc "Volume group name" $
612
  optionalStringField "vg_name"
613

    
614
pEnabledHypervisors :: Field
615
pEnabledHypervisors =
616
  withDoc "List of enabled hypervisors" .
617
  optionalField $
618
  simpleField "enabled_hypervisors" [t| [Hypervisor] |]
619

    
620
pClusterHvParams :: Field
621
pClusterHvParams =
622
  withDoc "Cluster-wide hypervisor parameters, hypervisor-dependent" .
623
  renameField "ClusterHvParams" .
624
  optionalField $
625
  simpleField "hvparams" [t| GenericContainer String (JSObject JSValue) |]
626

    
627
pClusterBeParams :: Field
628
pClusterBeParams =
629
  withDoc "Cluster-wide backend parameter defaults" .
630
  renameField "ClusterBeParams" .
631
  optionalField $ simpleField "beparams" [t| JSObject JSValue |]
632

    
633
pOsHvp :: Field
634
pOsHvp =
635
  withDoc "Cluster-wide per-OS hypervisor parameter defaults" .
636
  optionalField $
637
  simpleField "os_hvp" [t| GenericContainer String (JSObject JSValue) |]
638

    
639
pClusterOsParams :: Field
640
pClusterOsParams =
641
  withDoc "Cluster-wide OS parameter defaults" .
642
  renameField "ClusterOsParams" .
643
  optionalField $
644
  simpleField "osparams" [t| GenericContainer String (JSObject JSValue) |]
645

    
646
pGroupDiskParams :: Field
647
pGroupDiskParams =
648
  withDoc "Disk templates' parameter defaults" .
649
  optionalField $
650
  simpleField "diskparams"
651
              [t| GenericContainer DiskTemplate (JSObject JSValue) |]
652

    
653
pCandidatePoolSize :: Field
654
pCandidatePoolSize =
655
  withDoc "Master candidate pool size" .
656
  optionalField $ simpleField "candidate_pool_size" [t| Positive Int |]
657

    
658
pUidPool :: Field
659
pUidPool =
660
  withDoc "Set UID pool, must be list of lists describing UID ranges\
661
          \ (two items, start and end inclusive)" .
662
  optionalField $ simpleField "uid_pool" [t| [(Int, Int)] |]
663

    
664
pAddUids :: Field
665
pAddUids =
666
  withDoc "Extend UID pool, must be list of lists describing UID\
667
          \ ranges (two items, start and end inclusive)" .
668
  optionalField $ simpleField "add_uids" [t| [(Int, Int)] |]
669

    
670
pRemoveUids :: Field
671
pRemoveUids =
672
  withDoc "Shrink UID pool, must be list of lists describing UID\
673
          \ ranges (two items, start and end inclusive) to be removed" .
674
  optionalField $ simpleField "remove_uids" [t| [(Int, Int)] |]
675

    
676
pMaintainNodeHealth :: Field
677
pMaintainNodeHealth =
678
  withDoc "Whether to automatically maintain node health" .
679
  optionalField $ booleanField "maintain_node_health"
680

    
681
-- | Whether to modify and keep in sync the @/etc/hosts@ files of nodes.
682
pModifyEtcHosts :: Field
683
pModifyEtcHosts = optionalField $ booleanField "modify_etc_hosts"
684

    
685
-- | Whether to wipe disks before allocating them to instances.
686
pPreallocWipeDisks :: Field
687
pPreallocWipeDisks =
688
  withDoc "Whether to wipe disks before allocating them to instances" .
689
  optionalField $ booleanField "prealloc_wipe_disks"
690

    
691
pNicParams :: Field
692
pNicParams =
693
  withDoc "Cluster-wide NIC parameter defaults" .
694
  optionalField $ simpleField "nicparams" [t| INicParams |]
695

    
696
pIpolicy :: Field
697
pIpolicy =
698
  withDoc "Ipolicy specs" .
699
  optionalField $ simpleField "ipolicy" [t| JSObject JSValue |]
700

    
701
pDrbdHelper :: Field
702
pDrbdHelper =
703
  withDoc "DRBD helper program" $
704
  optionalStringField "drbd_helper"
705

    
706
pDefaultIAllocator :: Field
707
pDefaultIAllocator =
708
  withDoc "Default iallocator for cluster" $
709
  optionalStringField "default_iallocator"
710

    
711
pMasterNetdev :: Field
712
pMasterNetdev =
713
  withDoc "Master network device" $
714
  optionalStringField "master_netdev"
715

    
716
pMasterNetmask :: Field
717
pMasterNetmask =
718
  withDoc "Netmask of the master IP" .
719
  optionalField $ simpleField "master_netmask" [t| NonNegative Int |]
720

    
721
pReservedLvs :: Field
722
pReservedLvs =
723
  withDoc "List of reserved LVs" .
724
  optionalField $ simpleField "reserved_lvs" [t| [NonEmptyString] |]
725

    
726
pHiddenOs :: Field
727
pHiddenOs =
728
  withDoc "Modify list of hidden operating systems: each modification\
729
          \ must have two items, the operation and the OS name; the operation\
730
          \ can be add or remove" .
731
  optionalField $ simpleField "hidden_os" [t| [(DdmSimple, NonEmptyString)] |]
732

    
733
pBlacklistedOs :: Field
734
pBlacklistedOs =
735
  withDoc "Modify list of blacklisted operating systems: each\
736
          \ modification must have two items, the operation and the OS name;\
737
          \ the operation can be add or remove" .
738
  optionalField $
739
  simpleField "blacklisted_os" [t| [(DdmSimple, NonEmptyString)] |]
740

    
741
pUseExternalMipScript :: Field
742
pUseExternalMipScript =
743
  withDoc "Whether to use an external master IP address setup script" .
744
  optionalField $ booleanField "use_external_mip_script"
745

    
746
pEnabledDiskTemplates :: Field
747
pEnabledDiskTemplates =
748
  withDoc "List of enabled disk templates" .
749
  optionalField $
750
  simpleField "enabled_disk_templates" [t| [DiskTemplate] |]
751

    
752
pQueryWhat :: Field
753
pQueryWhat =
754
  withDoc "Resource(s) to query for" $
755
  simpleField "what" [t| Qlang.QueryTypeOp |]
756

    
757
pUseLocking :: Field
758
pUseLocking =
759
  withDoc "Whether to use synchronization" $
760
  defaultFalse "use_locking"
761

    
762
pQueryFields :: Field
763
pQueryFields =
764
  withDoc "Requested fields" $
765
  simpleField "fields" [t| [NonEmptyString] |]
766

    
767
pQueryFilter :: Field
768
pQueryFilter =
769
  withDoc "Query filter" .
770
  optionalField $ simpleField "qfilter" [t| [JSValue] |]
771

    
772
pQueryFieldsFields :: Field
773
pQueryFieldsFields =
774
  withDoc "Requested fields; if not given, all are returned" .
775
  renameField "QueryFieldsFields" $
776
  optionalField pQueryFields
777

    
778
pNodeNames :: Field
779
pNodeNames =
780
  withDoc "List of node names to run the OOB command against" .
781
  defaultField [| [] |] $ simpleField "node_names" [t| [NonEmptyString] |]
782

    
783
pNodeUuids :: Field
784
pNodeUuids =
785
  withDoc "List of node UUIDs" .
786
  optionalField $ simpleField "node_uuids" [t| [NonEmptyString] |]
787

    
788
pOobCommand :: Field
789
pOobCommand =
790
  withDoc "OOB command to run" $
791
  simpleField "command" [t| OobCommand |]
792

    
793
pOobTimeout :: Field
794
pOobTimeout =
795
  withDoc "Timeout before the OOB helper will be terminated" .
796
  defaultField [| C.oobTimeout |] $
797
  simpleField "timeout" [t| Int |]
798

    
799
pIgnoreStatus :: Field
800
pIgnoreStatus =
801
  withDoc "Ignores the node offline status for power off" $
802
  defaultFalse "ignore_status"
803

    
804
pPowerDelay :: Field
805
pPowerDelay =
806
  -- FIXME: we can't use the proper type "NonNegative Double", since
807
  -- the default constant is a plain Double, not a non-negative one.
808
  -- And trying to fix the constant introduces a cyclic import.
809
  withDoc "Time in seconds to wait between powering on nodes" .
810
  defaultField [| C.oobPowerDelay |] $
811
  simpleField "power_delay" [t| Double |]
812

    
813
pRequiredNodes :: Field
814
pRequiredNodes =
815
  withDoc "Required list of node names" .
816
  renameField "ReqNodes " $ simpleField "nodes" [t| [NonEmptyString] |]
817

    
818
pRequiredNodeUuids :: Field
819
pRequiredNodeUuids =
820
  withDoc "Required list of node UUIDs" .
821
  renameField "ReqNodeUuids " . optionalField $
822
  simpleField "node_uuids" [t| [NonEmptyString] |]
823

    
824
pRestrictedCommand :: Field
825
pRestrictedCommand =
826
  withDoc "Restricted command name" .
827
  renameField "RestrictedCommand" $
828
  simpleField "command" [t| NonEmptyString |]
829

    
830
pNodeName :: Field
831
pNodeName =
832
  withDoc "A required node name (for single-node LUs)" $
833
  simpleField "node_name" [t| NonEmptyString |]
834

    
835
pNodeUuid :: Field
836
pNodeUuid =
837
  withDoc "A node UUID (for single-node LUs)" .
838
  optionalField $ simpleField "node_uuid" [t| NonEmptyString |]
839

    
840
pPrimaryIp :: Field
841
pPrimaryIp =
842
  withDoc "Primary IP address" .
843
  optionalField $
844
  simpleField "primary_ip" [t| NonEmptyString |]
845

    
846
pSecondaryIp :: Field
847
pSecondaryIp =
848
  withDoc "Secondary IP address" $
849
  optionalNEStringField "secondary_ip"
850

    
851
pReadd :: Field
852
pReadd =
853
  withDoc "Whether node is re-added to cluster" $
854
  defaultFalse "readd"
855

    
856
pNodeGroup :: Field
857
pNodeGroup =
858
  withDoc "Initial node group" $
859
  optionalNEStringField "group"
860

    
861
pMasterCapable :: Field
862
pMasterCapable =
863
  withDoc "Whether node can become master or master candidate" .
864
  optionalField $ booleanField "master_capable"
865

    
866
pVmCapable :: Field
867
pVmCapable =
868
  withDoc "Whether node can host instances" .
869
  optionalField $ booleanField "vm_capable"
870

    
871
pNdParams :: Field
872
pNdParams =
873
  withDoc "Node parameters" .
874
  renameField "genericNdParams" .
875
  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
876
  
877
pNames :: Field
878
pNames =
879
  withDoc "List of names" .
880
  defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
881

    
882
pNodes :: Field
883
pNodes =
884
  withDoc "List of nodes" .
885
  defaultField [| [] |] $ simpleField "nodes" [t| [NonEmptyString] |]
886

    
887
pStorageType :: Field
888
pStorageType =
889
  withDoc "Storage type" $ simpleField "storage_type" [t| StorageType |]
890

    
891
pStorageTypeOptional :: Field
892
pStorageTypeOptional =
893
  withDoc "Storage type" .
894
  renameField "StorageTypeOptional" .
895
  optionalField $ simpleField "storage_type" [t| StorageType |]
896

    
897
pStorageName :: Field
898
pStorageName =
899
  withDoc "Storage name" .
900
  renameField "StorageName" .
901
  optionalField $ simpleField "name" [t| NonEmptyString |]
902

    
903
pStorageChanges :: Field
904
pStorageChanges =
905
  withDoc "Requested storage changes" $
906
  simpleField "changes" [t| JSObject JSValue |]
907

    
908
pIgnoreConsistency :: Field
909
pIgnoreConsistency =
910
  withDoc "Whether to ignore disk consistency" $
911
  defaultFalse "ignore_consistency"
912

    
913
pMasterCandidate :: Field
914
pMasterCandidate =
915
  withDoc "Whether the node should become a master candidate" .
916
  optionalField $ booleanField "master_candidate"
917

    
918
pOffline :: Field
919
pOffline =
920
  withDoc "Whether to mark the node or instance offline" .
921
  optionalField $ booleanField "offline"
922

    
923
pDrained ::Field
924
pDrained =
925
  withDoc "Whether to mark the node as drained" .
926
  optionalField $ booleanField "drained"
927

    
928
pAutoPromote :: Field
929
pAutoPromote =
930
  withDoc "Whether node(s) should be promoted to master candidate if\
931
          \ necessary" $
932
  defaultFalse "auto_promote"
933

    
934
pPowered :: Field
935
pPowered =
936
  withDoc "Whether the node should be marked as powered" .
937
  optionalField $ booleanField "powered"
938

    
939
pMigrationMode :: Field
940
pMigrationMode =
941
  withDoc "Migration type (live/non-live)" .
942
  renameField "MigrationMode" .
943
  optionalField $
944
  simpleField "mode" [t| MigrationMode |]
945

    
946
pMigrationLive :: Field
947
pMigrationLive =
948
  withDoc "Obsolete \'live\' migration mode (do not use)" .
949
  renameField "OldLiveMode" . optionalField $ booleanField "live"
950

    
951
pMigrationTargetNode :: Field
952
pMigrationTargetNode =
953
  withDoc "Target node for instance migration/failover" $
954
  optionalNEStringField "target_node"
955

    
956
pMigrationTargetNodeUuid :: Field
957
pMigrationTargetNodeUuid =
958
  withDoc "Target node UUID for instance migration/failover" $
959
  optionalNEStringField "target_node_uuid"
960

    
961
pAllowRuntimeChgs :: Field
962
pAllowRuntimeChgs =
963
  withDoc "Whether to allow runtime changes while migrating" $
964
  defaultTrue "allow_runtime_changes"
965

    
966
pIgnoreIpolicy :: Field
967
pIgnoreIpolicy =
968
  withDoc "Whether to ignore ipolicy violations" $
969
  defaultFalse "ignore_ipolicy"
970
  
971
pIallocator :: Field
972
pIallocator =
973
  withDoc "Iallocator for deciding the target node for shared-storage\
974
          \ instances" $
975
  optionalNEStringField "iallocator"
976

    
977
pEarlyRelease :: Field
978
pEarlyRelease =
979
  withDoc "Whether to release locks as soon as possible" $
980
  defaultFalse "early_release"
981

    
982
pRemoteNode :: Field
983
pRemoteNode =
984
  withDoc "New secondary node" $
985
  optionalNEStringField "remote_node"
986

    
987
pRemoteNodeUuid :: Field
988
pRemoteNodeUuid =
989
  withDoc "New secondary node UUID" $
990
  optionalNEStringField "remote_node_uuid"
991

    
992
pEvacMode :: Field
993
pEvacMode =
994
  withDoc "Node evacuation mode" .
995
  renameField "EvacMode" $ simpleField "mode" [t| EvacMode |]
996

    
997
pInstanceName :: Field
998
pInstanceName =
999
  withDoc "A required instance name (for single-instance LUs)" $
1000
  simpleField "instance_name" [t| String |]
1001

    
1002
pForceVariant :: Field
1003
pForceVariant =
1004
  withDoc "Whether to force an unknown OS variant" $
1005
  defaultFalse "force_variant"
1006

    
1007
pWaitForSync :: Field
1008
pWaitForSync =
1009
  withDoc "Whether to wait for the disk to synchronize" $
1010
  defaultTrue "wait_for_sync"
1011

    
1012
pNameCheck :: Field
1013
pNameCheck =
1014
  withDoc "Whether to check name" $
1015
  defaultTrue "name_check"
1016

    
1017
pInstBeParams :: Field
1018
pInstBeParams =
1019
  withDoc "Backend parameters for instance" .
1020
  renameField "InstBeParams" .
1021
  defaultField [| toJSObject [] |] $
1022
  simpleField "beparams" [t| JSObject JSValue |]
1023

    
1024
pInstDisks :: Field
1025
pInstDisks =
1026
  withDoc "List of instance disks" .
1027
  renameField "instDisks" $ simpleField "disks" [t| [IDiskParams] |]
1028

    
1029
pDiskTemplate :: Field
1030
pDiskTemplate =
1031
  withDoc "Disk template" $
1032
  simpleField "disk_template" [t| DiskTemplate |]
1033

    
1034
pFileDriver :: Field
1035
pFileDriver =
1036
  withDoc "Driver for file-backed disks" .
1037
  optionalField $ simpleField "file_driver" [t| FileDriver |]
1038

    
1039
pFileStorageDir :: Field
1040
pFileStorageDir =
1041
  withDoc "Directory for storing file-backed disks" $
1042
  optionalNEStringField "file_storage_dir"
1043

    
1044
pInstHvParams :: Field
1045
pInstHvParams =
1046
  withDoc "Hypervisor parameters for instance, hypervisor-dependent" .
1047
  renameField "InstHvParams" .
1048
  defaultField [| toJSObject [] |] $
1049
  simpleField "hvparams" [t| JSObject JSValue |]
1050

    
1051
pHypervisor :: Field
1052
pHypervisor =
1053
  withDoc "Selected hypervisor for an instance" .
1054
  optionalField $
1055
  simpleField "hypervisor" [t| Hypervisor |]
1056

    
1057
pResetDefaults :: Field
1058
pResetDefaults =
1059
  withDoc "Reset instance parameters to default if equal" $
1060
  defaultFalse "identify_defaults"
1061

    
1062
pIpCheck :: Field
1063
pIpCheck =
1064
  withDoc "Whether to ensure instance's IP address is inactive" $
1065
  defaultTrue "ip_check"
1066

    
1067
pIpConflictsCheck :: Field
1068
pIpConflictsCheck =
1069
  withDoc "Whether to check for conflicting IP addresses" $
1070
  defaultTrue "conflicts_check"
1071

    
1072
pInstCreateMode :: Field
1073
pInstCreateMode =
1074
  withDoc "Instance creation mode" .
1075
  renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
1076

    
1077
pInstNics :: Field
1078
pInstNics =
1079
  withDoc "List of NIC (network interface) definitions" $
1080
  simpleField "nics" [t| [INicParams] |]
1081

    
1082
pNoInstall :: Field
1083
pNoInstall =
1084
  withDoc "Do not install the OS (will disable automatic start)" .
1085
  optionalField $ booleanField "no_install"
1086

    
1087
pInstOs :: Field
1088
pInstOs =
1089
  withDoc "OS type for instance installation" $
1090
  optionalNEStringField "os_type"
1091

    
1092
pInstOsParams :: Field
1093
pInstOsParams =
1094
  withDoc "OS parameters for instance" .
1095
  renameField "InstOsParams" .
1096
  defaultField [| toJSObject [] |] $
1097
  simpleField "osparams" [t| JSObject JSValue |]
1098

    
1099
pPrimaryNode :: Field
1100
pPrimaryNode =
1101
  withDoc "Primary node for an instance" $
1102
  optionalNEStringField "pnode"
1103

    
1104
pPrimaryNodeUuid :: Field
1105
pPrimaryNodeUuid =
1106
  withDoc "Primary node UUID for an instance" $
1107
  optionalNEStringField "pnode_uuid"
1108

    
1109
pSecondaryNode :: Field
1110
pSecondaryNode =
1111
  withDoc "Secondary node for an instance" $
1112
  optionalNEStringField "snode"
1113

    
1114
pSecondaryNodeUuid :: Field
1115
pSecondaryNodeUuid =
1116
  withDoc "Secondary node UUID for an instance" $
1117
  optionalNEStringField "snode_uuid"
1118

    
1119
pSourceHandshake :: Field
1120
pSourceHandshake =
1121
  withDoc "Signed handshake from source (remote import only)" .
1122
  optionalField $ simpleField "source_handshake" [t| [JSValue] |]
1123

    
1124
pSourceInstance :: Field
1125
pSourceInstance =
1126
  withDoc "Source instance name (remote import only)" $
1127
  optionalNEStringField "source_instance_name"
1128

    
1129
-- FIXME: non-negative int, whereas the constant is a plain int.
1130
pSourceShutdownTimeout :: Field
1131
pSourceShutdownTimeout =
1132
  withDoc "How long source instance was given to shut down (remote import\
1133
          \ only)" .
1134
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1135
  simpleField "source_shutdown_timeout" [t| NonNegative Int |]
1136

    
1137
pSourceX509Ca :: Field
1138
pSourceX509Ca =
1139
  withDoc "Source X509 CA in PEM format (remote import only)" $
1140
  optionalNEStringField "source_x509_ca"
1141

    
1142
pSrcNode :: Field
1143
pSrcNode =
1144
  withDoc "Source node for import" $
1145
  optionalNEStringField "src_node"
1146

    
1147
pSrcNodeUuid :: Field
1148
pSrcNodeUuid =
1149
  withDoc "Source node UUID for import" $
1150
  optionalNEStringField "src_node_uuid"
1151

    
1152
pSrcPath :: Field
1153
pSrcPath =
1154
  withDoc "Source directory for import" $
1155
  optionalNEStringField "src_path"
1156

    
1157
pStartInstance :: Field
1158
pStartInstance =
1159
  withDoc "Whether to start instance after creation" $
1160
  defaultTrue "start"
1161

    
1162
-- FIXME: unify/simplify with pTags, once that migrates to NonEmpty String"
1163
pInstTags :: Field
1164
pInstTags =
1165
  withDoc "Instance tags" .
1166
  renameField "InstTags" .
1167
  defaultField [| [] |] $
1168
  simpleField "tags" [t| [NonEmptyString] |]
1169

    
1170
pMultiAllocInstances :: Field
1171
pMultiAllocInstances =
1172
  withDoc "List of instance create opcodes describing the instances to\
1173
          \ allocate" .
1174
  renameField "InstMultiAlloc" .
1175
  defaultField [| [] |] $
1176
  simpleField "instances"[t| [JSValue] |]
1177

    
1178
pOpportunisticLocking :: Field
1179
pOpportunisticLocking =
1180
  withDoc "Whether to employ opportunistic locking for nodes, meaning\
1181
          \ nodes already locked by another opcode won't be considered for\
1182
          \ instance allocation (only when an iallocator is used)" $
1183
  defaultFalse "opportunistic_locking"
1184

    
1185
pInstanceUuid :: Field
1186
pInstanceUuid =
1187
  withDoc "An instance UUID (for single-instance LUs)" .
1188
  optionalField $ simpleField "instance_uuid" [t| NonEmptyString |]
1189

    
1190
pTempOsParams :: Field
1191
pTempOsParams =
1192
  withDoc "Temporary OS parameters (currently only in reinstall, might be\
1193
          \ added to install as well)" .
1194
  renameField "TempOsParams" .
1195
  optionalField $ simpleField "osparams" [t| JSObject JSValue |]
1196

    
1197
pShutdownTimeout :: Field
1198
pShutdownTimeout =
1199
  withDoc "How long to wait for instance to shut down" .
1200
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1201
  simpleField "shutdown_timeout" [t| NonNegative Int |]
1202

    
1203
-- | Another name for the shutdown timeout, because we like to be
1204
-- inconsistent.
1205
pShutdownTimeout' :: Field
1206
pShutdownTimeout' =
1207
  withDoc "How long to wait for instance to shut down" .
1208
  renameField "InstShutdownTimeout" .
1209
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1210
  simpleField "timeout" [t| NonNegative Int |]
1211

    
1212
pIgnoreFailures :: Field
1213
pIgnoreFailures =
1214
  withDoc "Whether to ignore failures during removal" $
1215
  defaultFalse "ignore_failures"
1216

    
1217
pNewName :: Field
1218
pNewName =
1219
  withDoc "New group or instance name" $
1220
  simpleField "new_name" [t| NonEmptyString |]
1221
  
1222
pIgnoreOfflineNodes :: Field
1223
pIgnoreOfflineNodes =
1224
  withDoc "Whether to ignore offline nodes" $
1225
  defaultFalse "ignore_offline_nodes"
1226

    
1227
pTempHvParams :: Field
1228
pTempHvParams =
1229
  withDoc "Temporary hypervisor parameters, hypervisor-dependent" .
1230
  renameField "TempHvParams" .
1231
  defaultField [| toJSObject [] |] $
1232
  simpleField "hvparams" [t| JSObject JSValue |]
1233

    
1234
pTempBeParams :: Field
1235
pTempBeParams =
1236
  withDoc "Temporary backend parameters" .
1237
  renameField "TempBeParams" .
1238
  defaultField [| toJSObject [] |] $
1239
  simpleField "beparams" [t| JSObject JSValue |]
1240

    
1241
pNoRemember :: Field
1242
pNoRemember =
1243
  withDoc "Do not remember instance state changes" $
1244
  defaultFalse "no_remember"
1245

    
1246
pStartupPaused :: Field
1247
pStartupPaused =
1248
  withDoc "Pause instance at startup" $
1249
  defaultFalse "startup_paused"
1250

    
1251
pIgnoreSecondaries :: Field
1252
pIgnoreSecondaries =
1253
  withDoc "Whether to start the instance even if secondary disks are failing" $
1254
  defaultFalse "ignore_secondaries"
1255

    
1256
pRebootType :: Field
1257
pRebootType =
1258
  withDoc "How to reboot the instance" $
1259
  simpleField "reboot_type" [t| RebootType |]
1260

    
1261
pReplaceDisksMode :: Field
1262
pReplaceDisksMode =
1263
  withDoc "Replacement mode" .
1264
  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1265

    
1266
pReplaceDisksList :: Field
1267
pReplaceDisksList =
1268
  withDoc "List of disk indices" .
1269
  renameField "ReplaceDisksList" .
1270
  defaultField [| [] |] $
1271
  simpleField "disks" [t| [DiskIndex] |]
1272

    
1273
pMigrationCleanup :: Field
1274
pMigrationCleanup =
1275
  withDoc "Whether a previously failed migration should be cleaned up" .
1276
  renameField "MigrationCleanup" $ defaultFalse "cleanup"
1277

    
1278
pAllowFailover :: Field
1279
pAllowFailover =
1280
  withDoc "Whether we can fallback to failover if migration is not possible" $
1281
  defaultFalse "allow_failover"
1282

    
1283
pForceFailover :: Field
1284
pForceFailover =
1285
  withDoc "Disallow migration moves and always use failovers" $
1286
  defaultFalse "force_failover"
1287

    
1288
pMoveTargetNode :: Field
1289
pMoveTargetNode =
1290
  withDoc "Target node for instance move" .
1291
  renameField "MoveTargetNode" $
1292
  simpleField "target_node" [t| NonEmptyString |]
1293

    
1294
pMoveTargetNodeUuid :: Field
1295
pMoveTargetNodeUuid =
1296
  withDoc "Target node UUID for instance move" .
1297
  renameField "MoveTargetNodeUuid" . optionalField $
1298
  simpleField "target_node_uuid" [t| NonEmptyString |]
1299

    
1300
pIgnoreDiskSize :: Field
1301
pIgnoreDiskSize =
1302
  withDoc "Whether to ignore recorded disk size" $
1303
  defaultFalse "ignore_size"
1304
  
1305
pWaitForSyncFalse :: Field
1306
pWaitForSyncFalse =
1307
  withDoc "Whether to wait for the disk to synchronize (defaults to false)" $
1308
  defaultField [| False |] pWaitForSync
1309
  
1310
pRecreateDisksInfo :: Field
1311
pRecreateDisksInfo =
1312
  withDoc "Disk list for recreate disks" .
1313
  renameField "RecreateDisksInfo" .
1314
  defaultField [| RecreateDisksAll |] $
1315
  simpleField "disks" [t| RecreateDisksInfo |]
1316

    
1317
pStatic :: Field
1318
pStatic =
1319
  withDoc "Whether to only return configuration data without querying nodes" $
1320
  defaultFalse "static"
1321

    
1322
pInstParamsNicChanges :: Field
1323
pInstParamsNicChanges =
1324
  withDoc "List of NIC changes" .
1325
  renameField "InstNicChanges" .
1326
  defaultField [| SetParamsEmpty |] $
1327
  simpleField "nics" [t| SetParamsMods INicParams |]
1328

    
1329
pInstParamsDiskChanges :: Field
1330
pInstParamsDiskChanges =
1331
  withDoc "List of disk changes" .
1332
  renameField "InstDiskChanges" .
1333
  defaultField [| SetParamsEmpty |] $
1334
  simpleField "disks" [t| SetParamsMods IDiskParams |]
1335

    
1336
pRuntimeMem :: Field
1337
pRuntimeMem =
1338
  withDoc "New runtime memory" .
1339
  optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1340

    
1341
pOptDiskTemplate :: Field
1342
pOptDiskTemplate =
1343
  withDoc "Instance disk template" .
1344
  optionalField .
1345
  renameField "OptDiskTemplate" $
1346
  simpleField "disk_template" [t| DiskTemplate |]
1347

    
1348
pOsNameChange :: Field
1349
pOsNameChange =
1350
  withDoc "Change the instance's OS without reinstalling the instance" $
1351
  optionalNEStringField "os_name"
1352

    
1353
pDiskIndex :: Field
1354
pDiskIndex =
1355
  withDoc "Disk index for e.g. grow disk" .
1356
  renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
1357

    
1358
pDiskChgAmount :: Field
1359
pDiskChgAmount =
1360
  withDoc "Disk amount to add or grow to" .
1361
  renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
1362

    
1363
pDiskChgAbsolute :: Field
1364
pDiskChgAbsolute =
1365
  withDoc
1366
    "Whether the amount parameter is an absolute target or a relative one" .
1367
  renameField "DiskChkAbsolute" $ defaultFalse "absolute"
1368

    
1369
pTargetGroups :: Field
1370
pTargetGroups =
1371
  withDoc
1372
    "Destination group names or UUIDs (defaults to \"all but current group\")" .
1373
  optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
1374

    
1375
pNodeGroupAllocPolicy :: Field
1376
pNodeGroupAllocPolicy =
1377
  withDoc "Instance allocation policy" .
1378
  optionalField $
1379
  simpleField "alloc_policy" [t| AllocPolicy |]
1380

    
1381
pGroupNodeParams :: Field
1382
pGroupNodeParams =
1383
  withDoc "Default node parameters for group" .
1384
  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
1385

    
1386
pExportMode :: Field
1387
pExportMode =
1388
  withDoc "Export mode" .
1389
  renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1390

    
1391
-- FIXME: Rename target_node as it changes meaning for different
1392
-- export modes (e.g. "destination")
1393
pExportTargetNode :: Field
1394
pExportTargetNode =
1395
  withDoc "Target node (depends on export mode)" .
1396
  renameField "ExportTarget" $
1397
  simpleField "target_node" [t| ExportTarget |]
1398

    
1399
pExportTargetNodeUuid :: Field
1400
pExportTargetNodeUuid =
1401
  withDoc "Target node UUID (if local export)" .
1402
  renameField "ExportTargetNodeUuid" . optionalField $
1403
  simpleField "target_node_uuid" [t| NonEmptyString |]
1404

    
1405
pShutdownInstance :: Field
1406
pShutdownInstance =
1407
  withDoc "Whether to shutdown the instance before export" $
1408
  defaultTrue "shutdown"
1409

    
1410
pRemoveInstance :: Field
1411
pRemoveInstance =
1412
  withDoc "Whether to remove instance after export" $
1413
  defaultFalse "remove_instance"
1414

    
1415
pIgnoreRemoveFailures :: Field
1416
pIgnoreRemoveFailures =
1417
  withDoc "Whether to ignore failures while removing instances" $
1418
  defaultFalse "ignore_remove_failures"
1419

    
1420
pX509KeyName :: Field
1421
pX509KeyName =
1422
  withDoc "Name of X509 key (remote export only)" .
1423
  optionalField $ simpleField "x509_key_name" [t| [JSValue] |]
1424

    
1425
pX509DestCA :: Field
1426
pX509DestCA =
1427
  withDoc "Destination X509 CA (remote export only)" $
1428
  optionalNEStringField "destination_x509_ca"
1429

    
1430
pTagsObject :: Field
1431
pTagsObject =
1432
  withDoc "Tag kind" $
1433
  simpleField "kind" [t| TagKind |]
1434

    
1435
pTagsName :: Field
1436
pTagsName =
1437
  withDoc "Name of object" .
1438
  renameField "TagsGetName" .
1439
  optionalField $ simpleField "name" [t| String |]
1440

    
1441
pTagsList :: Field
1442
pTagsList =
1443
  withDoc "List of tag names" $
1444
  simpleField "tags" [t| [String] |]
1445

    
1446
-- FIXME: this should be compiled at load time?
1447
pTagSearchPattern :: Field
1448
pTagSearchPattern =
1449
  withDoc "Search pattern (regular expression)" .
1450
  renameField "TagSearchPattern" $
1451
  simpleField "pattern" [t| NonEmptyString |]
1452

    
1453
pDelayDuration :: Field
1454
pDelayDuration =
1455
  withDoc "Duration parameter for 'OpTestDelay'" .
1456
  renameField "DelayDuration" $
1457
  simpleField "duration" [t| Double |]
1458

    
1459
pDelayOnMaster :: Field
1460
pDelayOnMaster =
1461
  withDoc "on_master field for 'OpTestDelay'" .
1462
  renameField "DelayOnMaster" $
1463
  defaultTrue "on_master"
1464

    
1465
pDelayOnNodes :: Field
1466
pDelayOnNodes =
1467
  withDoc "on_nodes field for 'OpTestDelay'" .
1468
  renameField "DelayOnNodes" .
1469
  defaultField [| [] |] $
1470
  simpleField "on_nodes" [t| [NonEmptyString] |]
1471

    
1472
pDelayOnNodeUuids :: Field
1473
pDelayOnNodeUuids =
1474
  withDoc "on_node_uuids field for 'OpTestDelay'" .
1475
  renameField "DelayOnNodeUuids" . optionalField $
1476
  simpleField "on_node_uuids" [t| [NonEmptyString] |]
1477

    
1478
pDelayRepeat :: Field
1479
pDelayRepeat =
1480
  withDoc "Repeat parameter for OpTestDelay" .
1481
  renameField "DelayRepeat" .
1482
  defaultField [| forceNonNeg (0::Int) |] $
1483
  simpleField "repeat" [t| NonNegative Int |]
1484

    
1485
pDelayNoLocks :: Field
1486
pDelayNoLocks =
1487
  withDoc "Don't take locks during the delay" .
1488
  renameField "DelayNoLocks" $
1489
  defaultTrue "no_locks"
1490

    
1491
pIAllocatorDirection :: Field
1492
pIAllocatorDirection =
1493
  withDoc "IAllocator test direction" .
1494
  renameField "IAllocatorDirection" $
1495
  simpleField "direction" [t| IAllocatorTestDir |]
1496

    
1497
pIAllocatorMode :: Field
1498
pIAllocatorMode =
1499
  withDoc "IAllocator test mode" .
1500
  renameField "IAllocatorMode" $
1501
  simpleField "mode" [t| IAllocatorMode |]
1502

    
1503
pIAllocatorReqName :: Field
1504
pIAllocatorReqName =
1505
  withDoc "IAllocator target name (new instance, node to evac, etc.)" .
1506
  renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
1507

    
1508
pIAllocatorNics :: Field
1509
pIAllocatorNics =
1510
  withDoc "Custom OpTestIAllocator nics" .
1511
  renameField "IAllocatorNics" .
1512
  optionalField $ simpleField "nics" [t| [INicParams] |]
1513

    
1514
pIAllocatorDisks :: Field
1515
pIAllocatorDisks =
1516
  withDoc "Custom OpTestAllocator disks" .
1517
  renameField "IAllocatorDisks" .
1518
  optionalField $ simpleField "disks" [t| [JSValue] |]
1519

    
1520
pIAllocatorMemory :: Field
1521
pIAllocatorMemory =
1522
  withDoc "IAllocator memory field" .
1523
  renameField "IAllocatorMem" .
1524
  optionalField $
1525
  simpleField "memory" [t| NonNegative Int |]
1526

    
1527
pIAllocatorVCpus :: Field
1528
pIAllocatorVCpus =
1529
  withDoc "IAllocator vcpus field" .
1530
  renameField "IAllocatorVCpus" .
1531
  optionalField $
1532
  simpleField "vcpus" [t| NonNegative Int |]
1533

    
1534
pIAllocatorOs :: Field
1535
pIAllocatorOs =
1536
  withDoc "IAllocator os field" .
1537
  renameField "IAllocatorOs" $ optionalNEStringField "os"
1538

    
1539
pIAllocatorInstances :: Field
1540
pIAllocatorInstances =
1541
  withDoc "IAllocator instances field" .
1542
  renameField "IAllocatorInstances " .
1543
  optionalField $
1544
  simpleField "instances" [t| [NonEmptyString] |]
1545

    
1546
pIAllocatorEvacMode :: Field
1547
pIAllocatorEvacMode =
1548
  withDoc "IAllocator evac mode" .
1549
  renameField "IAllocatorEvacMode" .
1550
  optionalField $
1551
  simpleField "evac_mode" [t| EvacMode |]
1552

    
1553
pIAllocatorSpindleUse :: Field
1554
pIAllocatorSpindleUse =
1555
  withDoc "IAllocator spindle use" .
1556
  renameField "IAllocatorSpindleUse" .
1557
  defaultField [| forceNonNeg (1::Int) |] $
1558
  simpleField "spindle_use" [t| NonNegative Int |]
1559

    
1560
pIAllocatorCount :: Field
1561
pIAllocatorCount =
1562
  withDoc "IAllocator count field" .
1563
  renameField "IAllocatorCount" .
1564
  defaultField [| forceNonNeg (1::Int) |] $
1565
  simpleField "count" [t| NonNegative Int |]
1566

    
1567
pJQueueNotifyWaitLock :: Field
1568
pJQueueNotifyWaitLock =
1569
  withDoc "'OpTestJqueue' notify_waitlock" $
1570
  defaultFalse "notify_waitlock"
1571

    
1572
pJQueueNotifyExec :: Field
1573
pJQueueNotifyExec =
1574
  withDoc "'OpTestJQueue' notify_exec" $
1575
  defaultFalse "notify_exec"
1576

    
1577
pJQueueLogMessages :: Field
1578
pJQueueLogMessages =
1579
  withDoc "'OpTestJQueue' log_messages" .
1580
  defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
1581

    
1582
pJQueueFail :: Field
1583
pJQueueFail =
1584
  withDoc "'OpTestJQueue' fail attribute" .
1585
  renameField "JQueueFail" $ defaultFalse "fail"
1586

    
1587
pTestDummyResult :: Field
1588
pTestDummyResult =
1589
  withDoc "'OpTestDummy' result field" .
1590
  renameField "TestDummyResult" $ simpleField "result" [t| JSValue |]
1591

    
1592
pTestDummyMessages :: Field
1593
pTestDummyMessages =
1594
  withDoc "'OpTestDummy' messages field" .
1595
  renameField "TestDummyMessages" $
1596
  simpleField "messages" [t| JSValue |]
1597

    
1598
pTestDummyFail :: Field
1599
pTestDummyFail =
1600
  withDoc "'OpTestDummy' fail field" .
1601
  renameField "TestDummyFail" $ simpleField "fail" [t| JSValue |]
1602

    
1603
pTestDummySubmitJobs :: Field
1604
pTestDummySubmitJobs =
1605
  withDoc "'OpTestDummy' submit_jobs field" .
1606
  renameField "TestDummySubmitJobs" $
1607
  simpleField "submit_jobs" [t| JSValue |]
1608

    
1609
pNetworkName :: Field
1610
pNetworkName =
1611
  withDoc "Network name" $
1612
  simpleField "network_name" [t| NonEmptyString |]
1613

    
1614
pNetworkAddress4 :: Field
1615
pNetworkAddress4 =
1616
  withDoc "Network address (IPv4 subnet)" .
1617
  renameField "NetworkAddress4" $
1618
  simpleField "network" [t| IPv4Network |]
1619

    
1620
pNetworkGateway4 :: Field
1621
pNetworkGateway4 =
1622
  withDoc "Network gateway (IPv4 address)" .
1623
  renameField "NetworkGateway4" .
1624
  optionalField $ simpleField "gateway" [t| IPv4Address |]
1625

    
1626
pNetworkAddress6 :: Field
1627
pNetworkAddress6 =
1628
  withDoc "Network address (IPv6 subnet)" .
1629
  renameField "NetworkAddress6" .
1630
  optionalField $ simpleField "network6" [t| IPv6Network |]
1631

    
1632
pNetworkGateway6 :: Field
1633
pNetworkGateway6 =
1634
  withDoc "Network gateway (IPv6 address)" .
1635
  renameField "NetworkGateway6" .
1636
  optionalField $ simpleField "gateway6" [t| IPv6Address |]
1637

    
1638
pNetworkMacPrefix :: Field
1639
pNetworkMacPrefix =
1640
  withDoc "Network specific mac prefix (that overrides the cluster one)" .
1641
  renameField "NetMacPrefix" $
1642
  optionalNEStringField "mac_prefix"
1643

    
1644
pNetworkAddRsvdIps :: Field
1645
pNetworkAddRsvdIps =
1646
  withDoc "Which IP addresses to reserve" .
1647
  renameField "NetworkAddRsvdIps" .
1648
  optionalField $
1649
  simpleField "add_reserved_ips" [t| [IPv4Address] |]
1650

    
1651
pNetworkRemoveRsvdIps :: Field
1652
pNetworkRemoveRsvdIps =
1653
  withDoc "Which external IP addresses to release" .
1654
  renameField "NetworkRemoveRsvdIps" .
1655
  optionalField $
1656
  simpleField "remove_reserved_ips" [t| [IPv4Address] |]
1657

    
1658
pNetworkMode :: Field
1659
pNetworkMode =
1660
  withDoc "Network mode when connecting to a group" $
1661
  simpleField "network_mode" [t| NICMode |]
1662

    
1663
pNetworkLink :: Field
1664
pNetworkLink =
1665
  withDoc "Network link when connecting to a group" $
1666
  simpleField "network_link" [t| NonEmptyString |]