Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ 1ecc03c1

History | View | Annotate | Download (46.5 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

    
3
{-| Implementation of opcodes parameters.
4

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

    
11
-}
12

    
13
{-
14

    
15
Copyright (C) 2012 Google Inc.
16
All rights reserved.
17

    
18
Redistribution and use in source and binary forms, with or without
19
modification, are permitted provided that the following conditions are
20
met:
21

    
22
1. Redistributions of source code must retain the above copyright notice,
23
this list of conditions and the following disclaimer.
24

    
25
2. Redistributions in binary form must reproduce the above copyright
26
notice, this list of conditions and the following disclaimer in the
27
documentation and/or other materials provided with the distribution.
28

    
29
THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS
30
IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
31
TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
32
PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR
33
CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL,
34
EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO,
35
PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR
36
PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF
37
LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING
38
NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS
39
SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
40

    
41
-}
42

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

    
270
import Control.Monad (liftM)
271
import Text.JSON (JSON, JSValue(..), JSObject (..), readJSON, showJSON,
272
                  fromJSString, toJSObject)
273
import qualified Text.JSON
274
import Text.JSON.Pretty (pp_value)
275

    
276
import Ganeti.BasicTypes
277
import qualified Ganeti.Constants as C
278
import Ganeti.THH
279
import Ganeti.JSON
280
import Ganeti.Types
281
import qualified Ganeti.Query.Language as Qlang
282

    
283
-- * Helper functions and types
284

    
285
-- | Build a boolean field.
286
booleanField :: String -> Field
287
booleanField = flip simpleField [t| Bool |]
288

    
289
-- | Default a field to 'False'.
290
defaultFalse :: String -> Field
291
defaultFalse = defaultField [| False |] . booleanField
292

    
293
-- | Default a field to 'True'.
294
defaultTrue :: String -> Field
295
defaultTrue = defaultField [| True |] . booleanField
296

    
297
-- | An alias for a 'String' field.
298
stringField :: String -> Field
299
stringField = flip simpleField [t| String |]
300

    
301
-- | An alias for an optional string field.
302
optionalStringField :: String -> Field
303
optionalStringField = optionalField . stringField
304

    
305
-- | An alias for an optional non-empty string field.
306
optionalNEStringField :: String -> Field
307
optionalNEStringField = optionalField . flip simpleField [t| NonEmptyString |]
308

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

    
318
-- ** Disks
319

    
320
-- | Disk index type (embedding constraints on the index value via a
321
-- smart constructor).
322
newtype DiskIndex = DiskIndex { unDiskIndex :: Int }
323
  deriving (Show, Eq, Ord)
324

    
325
-- | Smart constructor for 'DiskIndex'.
326
mkDiskIndex :: (Monad m) => Int -> m DiskIndex
327
mkDiskIndex i | i >= 0 && i < C.maxDisks = return (DiskIndex i)
328
              | otherwise = fail $ "Invalid value for disk index '" ++
329
                            show i ++ "', required between 0 and " ++
330
                            show C.maxDisks
331

    
332
instance JSON DiskIndex where
333
  readJSON v = readJSON v >>= mkDiskIndex
334
  showJSON = showJSON . unDiskIndex
335

    
336
-- ** I* param types
337

    
338
-- | Type holding disk access modes.
339
$(declareSADT "DiskAccess"
340
  [ ("DiskReadOnly",  'C.diskRdonly)
341
  , ("DiskReadWrite", 'C.diskRdwr)
342
  ])
343
$(makeJSONInstance ''DiskAccess)
344

    
345
-- | NIC modification definition.
346
$(buildObject "INicParams" "inic"
347
  [ optionalField $ simpleField C.inicMac    [t| NonEmptyString |]
348
  , optionalField $ simpleField C.inicIp     [t| String         |]
349
  , optionalField $ simpleField C.inicMode   [t| NonEmptyString |]
350
  , optionalField $ simpleField C.inicLink   [t| NonEmptyString |]
351
  , optionalField $ simpleField C.inicName   [t| NonEmptyString |]
352
  , optionalField $ simpleField C.inicVlan   [t| NonEmptyString |]
353
  , optionalField $ simpleField C.inicBridge [t| NonEmptyString |]
354
  ])
355

    
356
-- | Disk modification definition. FIXME: disksize should be VTYPE_UNIT.
357
$(buildObject "IDiskParams" "idisk"
358
  [ optionalField $ simpleField C.idiskSize   [t| Int            |]
359
  , optionalField $ simpleField C.idiskMode   [t| DiskAccess     |]
360
  , optionalField $ simpleField C.idiskAdopt  [t| NonEmptyString |]
361
  , optionalField $ simpleField C.idiskVg     [t| NonEmptyString |]
362
  , optionalField $ simpleField C.idiskMetavg [t| NonEmptyString |]
363
  , optionalField $ simpleField C.idiskName   [t| NonEmptyString |]
364
  , optionalField $ simpleField C.idiskProvider [t| NonEmptyString |]
365
  , optionalField $ simpleField C.idiskAccess   [t| NonEmptyString |]
366
  , andRestArguments "opaque"
367
  ])
368

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

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

    
391
instance JSON RecreateDisksInfo where
392
  readJSON = readRecreateDisks
393
  showJSON  RecreateDisksAll            = showJSON ()
394
  showJSON (RecreateDisksIndices idx)   = showJSON idx
395
  showJSON (RecreateDisksParams params) = showJSON params
396

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

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

    
411
instance JSON DdmOldChanges where
412
  showJSON (DdmOldIndex i) = showJSON i
413
  showJSON (DdmOldMod m)   = showJSON m
414
  readJSON = readDdmOldChanges
415

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

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

    
431
instance (JSON a) => JSON (SetParamsMods a) where
432
  showJSON SetParamsEmpty = showJSON ()
433
  showJSON (SetParamsDeprecated v) = showJSON v
434
  showJSON (SetParamsNew v) = showJSON v
435
  readJSON = readSetParams
436

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

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

    
453
instance JSON ExportTarget where
454
  showJSON (ExportTargetLocal s)  = showJSON s
455
  showJSON (ExportTargetRemote l) = showJSON l
456
  readJSON = readExportTarget
457

    
458
-- * Common opcode parameters
459

    
460
pDryRun :: Field
461
pDryRun =
462
  withDoc "Run checks only, don't execute" .
463
  optionalField $ booleanField "dry_run"
464

    
465
pDebugLevel :: Field
466
pDebugLevel =
467
  withDoc "Debug level" .
468
  optionalField $ simpleField "debug_level" [t| NonNegative Int |]
469

    
470
pOpPriority :: Field
471
pOpPriority =
472
  withDoc "Opcode priority. Note: python uses a separate constant,\
473
          \ we're using the actual value we know it's the default" .
474
  defaultField [| OpPrioNormal |] $
475
  simpleField "priority" [t| OpSubmitPriority |]
476

    
477
pDependencies :: Field
478
pDependencies =
479
  withDoc "Job dependencies" .
480
  optionalNullSerField $ simpleField "depends" [t| [JobDependency] |]
481

    
482
pComment :: Field
483
pComment =
484
  withDoc "Comment field" .
485
  optionalNullSerField $ stringField "comment"
486

    
487
pReason :: Field
488
pReason =
489
  withDoc "Reason trail field" $
490
  simpleField C.opcodeReason [t| ReasonTrail |]
491

    
492
pSequential :: Field
493
pSequential =
494
  withDoc "Sequential job execution" $
495
  defaultFalse C.opcodeSequential
496

    
497
-- * Parameters
498

    
499
pDebugSimulateErrors :: Field
500
pDebugSimulateErrors =
501
  withDoc "Whether to simulate errors (useful for debugging)" $
502
  defaultFalse "debug_simulate_errors"
503

    
504
pErrorCodes :: Field
505
pErrorCodes = 
506
  withDoc "Error codes" $
507
  defaultFalse "error_codes"
508

    
509
pSkipChecks :: Field
510
pSkipChecks = 
511
  withDoc "Which checks to skip" .
512
  defaultField [| emptyListSet |] $
513
  simpleField "skip_checks" [t| ListSet VerifyOptionalChecks |]
514

    
515
pIgnoreErrors :: Field
516
pIgnoreErrors =
517
  withDoc "List of error codes that should be treated as warnings" .
518
  defaultField [| emptyListSet |] $
519
  simpleField "ignore_errors" [t| ListSet CVErrorCode |]
520

    
521
pVerbose :: Field
522
pVerbose =
523
  withDoc "Verbose mode" $
524
  defaultFalse "verbose"
525

    
526
pOptGroupName :: Field
527
pOptGroupName =
528
  withDoc "Optional group name" .
529
  renameField "OptGroupName" .
530
  optionalField $ simpleField "group_name" [t| NonEmptyString |]
531

    
532
pGroupName :: Field
533
pGroupName =
534
  withDoc "Group name" $
535
  simpleField "group_name" [t| NonEmptyString |]
536

    
537
-- | Whether to hotplug device.
538
pHotplug :: Field
539
pHotplug = defaultFalse "hotplug"
540

    
541
pHotplugIfPossible :: Field
542
pHotplugIfPossible = defaultFalse "hotplug_if_possible"
543

    
544
pInstances :: Field
545
pInstances =
546
  withDoc "List of instances" .
547
  defaultField [| [] |] $
548
  simpleField "instances" [t| [NonEmptyString] |]
549

    
550
pOutputFields :: Field
551
pOutputFields =
552
  withDoc "Selected output fields" $
553
  simpleField "output_fields" [t| [NonEmptyString] |]
554

    
555
pName :: Field
556
pName =
557
  withDoc "A generic name" $
558
  simpleField "name" [t| NonEmptyString |]
559

    
560
pForce :: Field
561
pForce =
562
  withDoc "Whether to force the operation" $
563
  defaultFalse "force"
564

    
565
pHvState :: Field
566
pHvState =
567
  withDoc "Set hypervisor states" .
568
  optionalField $ simpleField "hv_state" [t| JSObject JSValue |]
569

    
570
pDiskState :: Field
571
pDiskState =
572
  withDoc "Set disk states" .
573
  optionalField $ simpleField "disk_state" [t| JSObject JSValue |]
574

    
575
-- | Cluster-wide default directory for storing file-backed disks.
576
pClusterFileStorageDir :: Field
577
pClusterFileStorageDir =
578
  renameField "ClusterFileStorageDir" $
579
  optionalStringField "file_storage_dir"
580

    
581
-- | Cluster-wide default directory for storing shared-file-backed disks.
582
pClusterSharedFileStorageDir :: Field
583
pClusterSharedFileStorageDir =
584
  renameField "ClusterSharedFileStorageDir" $
585
  optionalStringField "shared_file_storage_dir"
586

    
587
-- | Volume group name.
588
pVgName :: Field
589
pVgName =
590
  withDoc "Volume group name" $
591
  optionalStringField "vg_name"
592

    
593
pEnabledHypervisors :: Field
594
pEnabledHypervisors =
595
  withDoc "List of enabled hypervisors" .
596
  optionalField $
597
  simpleField "enabled_hypervisors" [t| [Hypervisor] |]
598

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

    
606
pClusterBeParams :: Field
607
pClusterBeParams =
608
  withDoc "Cluster-wide backend parameter defaults" .
609
  renameField "ClusterBeParams" .
610
  optionalField $ simpleField "beparams" [t| JSObject JSValue |]
611

    
612
pOsHvp :: Field
613
pOsHvp =
614
  withDoc "Cluster-wide per-OS hypervisor parameter defaults" .
615
  optionalField $
616
  simpleField "os_hvp" [t| GenericContainer String (JSObject JSValue) |]
617

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

    
625
pGroupDiskParams :: Field
626
pGroupDiskParams =
627
  withDoc "Disk templates' parameter defaults" .
628
  optionalField $
629
  simpleField "diskparams"
630
              [t| GenericContainer DiskTemplate (JSObject JSValue) |]
631

    
632
pCandidatePoolSize :: Field
633
pCandidatePoolSize =
634
  withDoc "Master candidate pool size" .
635
  optionalField $ simpleField "candidate_pool_size" [t| Positive Int |]
636

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

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

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

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

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

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

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

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

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

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

    
690
pMasterNetdev :: Field
691
pMasterNetdev =
692
  withDoc "Master network device" $
693
  optionalStringField "master_netdev"
694

    
695
pMasterNetmask :: Field
696
pMasterNetmask =
697
  withDoc "Netmask of the master IP" .
698
  optionalField $ simpleField "master_netmask" [t| NonNegative Int |]
699

    
700
pReservedLvs :: Field
701
pReservedLvs =
702
  withDoc "List of reserved LVs" .
703
  optionalField $ simpleField "reserved_lvs" [t| [NonEmptyString] |]
704

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

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

    
720
pUseExternalMipScript :: Field
721
pUseExternalMipScript =
722
  withDoc "Whether to use an external master IP address setup script" .
723
  optionalField $ booleanField "use_external_mip_script"
724

    
725
pEnabledDiskTemplates :: Field
726
pEnabledDiskTemplates =
727
  withDoc "List of enabled disk templates" .
728
  optionalField $
729
  simpleField "enabled_disk_templates" [t| [DiskTemplate] |]
730

    
731
pQueryWhat :: Field
732
pQueryWhat =
733
  withDoc "Resource(s) to query for" $
734
  simpleField "what" [t| Qlang.QueryTypeOp |]
735

    
736
pUseLocking :: Field
737
pUseLocking =
738
  withDoc "Whether to use synchronization" $
739
  defaultFalse "use_locking"
740

    
741
pQueryFields :: Field
742
pQueryFields =
743
  withDoc "Requested fields" $
744
  simpleField "fields" [t| [NonEmptyString] |]
745

    
746
pQueryFilter :: Field
747
pQueryFilter =
748
  withDoc "Query filter" .
749
  optionalField $ simpleField "qfilter" [t| [JSValue] |]
750

    
751
pQueryFieldsFields :: Field
752
pQueryFieldsFields =
753
  withDoc "Requested fields; if not given, all are returned" .
754
  renameField "QueryFieldsFields" $
755
  optionalField pQueryFields
756

    
757
pNodeNames :: Field
758
pNodeNames =
759
  withDoc "List of node names to run the OOB command against" .
760
  defaultField [| [] |] $ simpleField "node_names" [t| [NonEmptyString] |]
761

    
762
pNodeUuids :: Field
763
pNodeUuids =
764
  withDoc "List of node UUIDs" .
765
  optionalField $ simpleField "node_uuids" [t| [NonEmptyString] |]
766

    
767
pOobCommand :: Field
768
pOobCommand =
769
  withDoc "OOB command to run" $
770
  simpleField "command" [t| OobCommand |]
771

    
772
pOobTimeout :: Field
773
pOobTimeout =
774
  withDoc "Timeout before the OOB helper will be terminated" .
775
  defaultField [| C.oobTimeout |] $
776
  simpleField "timeout" [t| Int |]
777

    
778
pIgnoreStatus :: Field
779
pIgnoreStatus =
780
  withDoc "Ignores the node offline status for power off" $
781
  defaultFalse "ignore_status"
782

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

    
792
pRequiredNodes :: Field
793
pRequiredNodes =
794
  withDoc "Required list of node names" .
795
  renameField "ReqNodes " $ simpleField "nodes" [t| [NonEmptyString] |]
796

    
797
pRequiredNodeUuids :: Field
798
pRequiredNodeUuids =
799
  withDoc "Required list of node UUIDs" .
800
  renameField "ReqNodeUuids " . optionalField $
801
  simpleField "node_uuids" [t| [NonEmptyString] |]
802

    
803
pRestrictedCommand :: Field
804
pRestrictedCommand =
805
  withDoc "Restricted command name" .
806
  renameField "RestrictedCommand" $
807
  simpleField "command" [t| NonEmptyString |]
808

    
809
pNodeName :: Field
810
pNodeName =
811
  withDoc "A required node name (for single-node LUs)" $
812
  simpleField "node_name" [t| NonEmptyString |]
813

    
814
pNodeUuid :: Field
815
pNodeUuid =
816
  withDoc "A node UUID (for single-node LUs)" .
817
  optionalField $ simpleField "node_uuid" [t| NonEmptyString |]
818

    
819
pPrimaryIp :: Field
820
pPrimaryIp =
821
  withDoc "Primary IP address" .
822
  optionalField $
823
  simpleField "primary_ip" [t| NonEmptyString |]
824

    
825
pSecondaryIp :: Field
826
pSecondaryIp =
827
  withDoc "Secondary IP address" $
828
  optionalNEStringField "secondary_ip"
829

    
830
pReadd :: Field
831
pReadd =
832
  withDoc "Whether node is re-added to cluster" $
833
  defaultFalse "readd"
834

    
835
pNodeGroup :: Field
836
pNodeGroup =
837
  withDoc "Initial node group" $
838
  optionalNEStringField "group"
839

    
840
pMasterCapable :: Field
841
pMasterCapable =
842
  withDoc "Whether node can become master or master candidate" .
843
  optionalField $ booleanField "master_capable"
844

    
845
pVmCapable :: Field
846
pVmCapable =
847
  withDoc "Whether node can host instances" .
848
  optionalField $ booleanField "vm_capable"
849

    
850
pNdParams :: Field
851
pNdParams =
852
  withDoc "Node parameters" .
853
  renameField "genericNdParams" .
854
  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
855
  
856
pNames :: Field
857
pNames =
858
  withDoc "List of names" .
859
  defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
860

    
861
pNodes :: Field
862
pNodes =
863
  withDoc "List of nodes" .
864
  defaultField [| [] |] $ simpleField "nodes" [t| [NonEmptyString] |]
865

    
866
pStorageType :: Field
867
pStorageType =
868
  withDoc "Storage type" $ simpleField "storage_type" [t| StorageType |]
869

    
870
pStorageTypeOptional :: Field
871
pStorageTypeOptional =
872
  withDoc "Storage type" .
873
  renameField "StorageTypeOptional" .
874
  optionalField $ simpleField "storage_type" [t| StorageType |]
875

    
876
pStorageName :: Field
877
pStorageName =
878
  withDoc "Storage name" .
879
  renameField "StorageName" .
880
  optionalField $ simpleField "name" [t| NonEmptyString |]
881

    
882
pStorageChanges :: Field
883
pStorageChanges =
884
  withDoc "Requested storage changes" $
885
  simpleField "changes" [t| JSObject JSValue |]
886

    
887
pIgnoreConsistency :: Field
888
pIgnoreConsistency =
889
  withDoc "Whether to ignore disk consistency" $
890
  defaultFalse "ignore_consistency"
891

    
892
pMasterCandidate :: Field
893
pMasterCandidate =
894
  withDoc "Whether the node should become a master candidate" .
895
  optionalField $ booleanField "master_candidate"
896

    
897
pOffline :: Field
898
pOffline =
899
  withDoc "Whether to mark the node or instance offline" .
900
  optionalField $ booleanField "offline"
901

    
902
pDrained ::Field
903
pDrained =
904
  withDoc "Whether to mark the node as drained" .
905
  optionalField $ booleanField "drained"
906

    
907
pAutoPromote :: Field
908
pAutoPromote =
909
  withDoc "Whether node(s) should be promoted to master candidate if\
910
          \ necessary" $
911
  defaultFalse "auto_promote"
912

    
913
pPowered :: Field
914
pPowered =
915
  withDoc "Whether the node should be marked as powered" .
916
  optionalField $ booleanField "powered"
917

    
918
pMigrationMode :: Field
919
pMigrationMode =
920
  withDoc "Migration type (live/non-live)" .
921
  renameField "MigrationMode" .
922
  optionalField $
923
  simpleField "mode" [t| MigrationMode |]
924

    
925
pMigrationLive :: Field
926
pMigrationLive =
927
  withDoc "Obsolete \'live\' migration mode (do not use)" .
928
  renameField "OldLiveMode" . optionalField $ booleanField "live"
929

    
930
pMigrationTargetNode :: Field
931
pMigrationTargetNode =
932
  withDoc "Target node for instance migration/failover" $
933
  optionalNEStringField "target_node"
934

    
935
pMigrationTargetNodeUuid :: Field
936
pMigrationTargetNodeUuid =
937
  withDoc "Target node UUID for instance migration/failover" $
938
  optionalNEStringField "target_node_uuid"
939

    
940
pAllowRuntimeChgs :: Field
941
pAllowRuntimeChgs =
942
  withDoc "Whether to allow runtime changes while migrating" $
943
  defaultTrue "allow_runtime_changes"
944

    
945
pIgnoreIpolicy :: Field
946
pIgnoreIpolicy =
947
  withDoc "Whether to ignore ipolicy violations" $
948
  defaultFalse "ignore_ipolicy"
949
  
950
pIallocator :: Field
951
pIallocator =
952
  withDoc "Iallocator for deciding the target node for shared-storage\
953
          \ instances" $
954
  optionalNEStringField "iallocator"
955

    
956
pEarlyRelease :: Field
957
pEarlyRelease =
958
  withDoc "Whether to release locks as soon as possible" $
959
  defaultFalse "early_release"
960

    
961
pRemoteNode :: Field
962
pRemoteNode =
963
  withDoc "New secondary node" $
964
  optionalNEStringField "remote_node"
965

    
966
pRemoteNodeUuid :: Field
967
pRemoteNodeUuid =
968
  withDoc "New secondary node UUID" $
969
  optionalNEStringField "remote_node_uuid"
970

    
971
pEvacMode :: Field
972
pEvacMode =
973
  withDoc "Node evacuation mode" .
974
  renameField "EvacMode" $ simpleField "mode" [t| EvacMode |]
975

    
976
pInstanceName :: Field
977
pInstanceName =
978
  withDoc "A required instance name (for single-instance LUs)" $
979
  simpleField "instance_name" [t| String |]
980

    
981
pForceVariant :: Field
982
pForceVariant =
983
  withDoc "Whether to force an unknown OS variant" $
984
  defaultFalse "force_variant"
985

    
986
pWaitForSync :: Field
987
pWaitForSync =
988
  withDoc "Whether to wait for the disk to synchronize" $
989
  defaultTrue "wait_for_sync"
990

    
991
pNameCheck :: Field
992
pNameCheck =
993
  withDoc "Whether to check name" $
994
  defaultTrue "name_check"
995

    
996
pInstBeParams :: Field
997
pInstBeParams =
998
  withDoc "Backend parameters for instance" .
999
  renameField "InstBeParams" .
1000
  defaultField [| toJSObject [] |] $
1001
  simpleField "beparams" [t| JSObject JSValue |]
1002

    
1003
pInstDisks :: Field
1004
pInstDisks =
1005
  withDoc "List of instance disks" .
1006
  renameField "instDisks" $ simpleField "disks" [t| [IDiskParams] |]
1007

    
1008
pDiskTemplate :: Field
1009
pDiskTemplate =
1010
  withDoc "Disk template" $
1011
  simpleField "disk_template" [t| DiskTemplate |]
1012

    
1013
pFileDriver :: Field
1014
pFileDriver =
1015
  withDoc "Driver for file-backed disks" .
1016
  optionalField $ simpleField "file_driver" [t| FileDriver |]
1017

    
1018
pFileStorageDir :: Field
1019
pFileStorageDir =
1020
  withDoc "Directory for storing file-backed disks" $
1021
  optionalNEStringField "file_storage_dir"
1022

    
1023
pInstHvParams :: Field
1024
pInstHvParams =
1025
  withDoc "Hypervisor parameters for instance, hypervisor-dependent" .
1026
  renameField "InstHvParams" .
1027
  defaultField [| toJSObject [] |] $
1028
  simpleField "hvparams" [t| JSObject JSValue |]
1029

    
1030
pHypervisor :: Field
1031
pHypervisor =
1032
  withDoc "Selected hypervisor for an instance" .
1033
  optionalField $
1034
  simpleField "hypervisor" [t| Hypervisor |]
1035

    
1036
pResetDefaults :: Field
1037
pResetDefaults =
1038
  withDoc "Reset instance parameters to default if equal" $
1039
  defaultFalse "identify_defaults"
1040

    
1041
pIpCheck :: Field
1042
pIpCheck =
1043
  withDoc "Whether to ensure instance's IP address is inactive" $
1044
  defaultTrue "ip_check"
1045

    
1046
pIpConflictsCheck :: Field
1047
pIpConflictsCheck =
1048
  withDoc "Whether to check for conflicting IP addresses" $
1049
  defaultTrue "conflicts_check"
1050

    
1051
pInstCreateMode :: Field
1052
pInstCreateMode =
1053
  withDoc "Instance creation mode" .
1054
  renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
1055

    
1056
pInstNics :: Field
1057
pInstNics =
1058
  withDoc "List of NIC (network interface) definitions" $
1059
  simpleField "nics" [t| [INicParams] |]
1060

    
1061
pNoInstall :: Field
1062
pNoInstall =
1063
  withDoc "Do not install the OS (will disable automatic start)" .
1064
  optionalField $ booleanField "no_install"
1065

    
1066
pInstOs :: Field
1067
pInstOs =
1068
  withDoc "OS type for instance installation" $
1069
  optionalNEStringField "os_type"
1070

    
1071
pInstOsParams :: Field
1072
pInstOsParams =
1073
  withDoc "OS parameters for instance" .
1074
  renameField "InstOsParams" .
1075
  defaultField [| toJSObject [] |] $
1076
  simpleField "osparams" [t| JSObject JSValue |]
1077

    
1078
pPrimaryNode :: Field
1079
pPrimaryNode =
1080
  withDoc "Primary node for an instance" $
1081
  optionalNEStringField "pnode"
1082

    
1083
pPrimaryNodeUuid :: Field
1084
pPrimaryNodeUuid =
1085
  withDoc "Primary node UUID for an instance" $
1086
  optionalNEStringField "pnode_uuid"
1087

    
1088
pSecondaryNode :: Field
1089
pSecondaryNode =
1090
  withDoc "Secondary node for an instance" $
1091
  optionalNEStringField "snode"
1092

    
1093
pSecondaryNodeUuid :: Field
1094
pSecondaryNodeUuid =
1095
  withDoc "Secondary node UUID for an instance" $
1096
  optionalNEStringField "snode_uuid"
1097

    
1098
pSourceHandshake :: Field
1099
pSourceHandshake =
1100
  withDoc "Signed handshake from source (remote import only)" .
1101
  optionalField $ simpleField "source_handshake" [t| [JSValue] |]
1102

    
1103
pSourceInstance :: Field
1104
pSourceInstance =
1105
  withDoc "Source instance name (remote import only)" $
1106
  optionalNEStringField "source_instance_name"
1107

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

    
1116
pSourceX509Ca :: Field
1117
pSourceX509Ca =
1118
  withDoc "Source X509 CA in PEM format (remote import only)" $
1119
  optionalNEStringField "source_x509_ca"
1120

    
1121
pSrcNode :: Field
1122
pSrcNode =
1123
  withDoc "Source node for import" $
1124
  optionalNEStringField "src_node"
1125

    
1126
pSrcNodeUuid :: Field
1127
pSrcNodeUuid =
1128
  withDoc "Source node UUID for import" $
1129
  optionalNEStringField "src_node_uuid"
1130

    
1131
pSrcPath :: Field
1132
pSrcPath =
1133
  withDoc "Source directory for import" $
1134
  optionalNEStringField "src_path"
1135

    
1136
pStartInstance :: Field
1137
pStartInstance =
1138
  withDoc "Whether to start instance after creation" $
1139
  defaultTrue "start"
1140

    
1141
-- FIXME: unify/simplify with pTags, once that migrates to NonEmpty String"
1142
pInstTags :: Field
1143
pInstTags =
1144
  withDoc "Instance tags" .
1145
  renameField "InstTags" .
1146
  defaultField [| [] |] $
1147
  simpleField "tags" [t| [NonEmptyString] |]
1148

    
1149
pMultiAllocInstances :: Field
1150
pMultiAllocInstances =
1151
  withDoc "List of instance create opcodes describing the instances to\
1152
          \ allocate" .
1153
  renameField "InstMultiAlloc" .
1154
  defaultField [| [] |] $
1155
  simpleField "instances"[t| [JSValue] |]
1156

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

    
1164
pInstanceUuid :: Field
1165
pInstanceUuid =
1166
  withDoc "An instance UUID (for single-instance LUs)" .
1167
  optionalField $ simpleField "instance_uuid" [t| NonEmptyString |]
1168

    
1169
pTempOsParams :: Field
1170
pTempOsParams =
1171
  withDoc "Temporary OS parameters (currently only in reinstall, might be\
1172
          \ added to install as well)" .
1173
  renameField "TempOsParams" .
1174
  optionalField $ simpleField "osparams" [t| JSObject JSValue |]
1175

    
1176
pShutdownTimeout :: Field
1177
pShutdownTimeout =
1178
  withDoc "How long to wait for instance to shut down" .
1179
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1180
  simpleField "shutdown_timeout" [t| NonNegative Int |]
1181

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

    
1191
pIgnoreFailures :: Field
1192
pIgnoreFailures =
1193
  withDoc "Whether to ignore failures during removal" $
1194
  defaultFalse "ignore_failures"
1195

    
1196
pNewName :: Field
1197
pNewName =
1198
  withDoc "New group or instance name" $
1199
  simpleField "new_name" [t| NonEmptyString |]
1200
  
1201
pIgnoreOfflineNodes :: Field
1202
pIgnoreOfflineNodes =
1203
  withDoc "Whether to ignore offline nodes" $
1204
  defaultFalse "ignore_offline_nodes"
1205

    
1206
pTempHvParams :: Field
1207
pTempHvParams =
1208
  withDoc "Temporary hypervisor parameters, hypervisor-dependent" .
1209
  renameField "TempHvParams" .
1210
  defaultField [| toJSObject [] |] $
1211
  simpleField "hvparams" [t| JSObject JSValue |]
1212

    
1213
pTempBeParams :: Field
1214
pTempBeParams =
1215
  withDoc "Temporary backend parameters" .
1216
  renameField "TempBeParams" .
1217
  defaultField [| toJSObject [] |] $
1218
  simpleField "beparams" [t| JSObject JSValue |]
1219

    
1220
pNoRemember :: Field
1221
pNoRemember =
1222
  withDoc "Do not remember instance state changes" $
1223
  defaultFalse "no_remember"
1224

    
1225
pStartupPaused :: Field
1226
pStartupPaused =
1227
  withDoc "Pause instance at startup" $
1228
  defaultFalse "startup_paused"
1229

    
1230
pIgnoreSecondaries :: Field
1231
pIgnoreSecondaries =
1232
  withDoc "Whether to start the instance even if secondary disks are failing" $
1233
  defaultFalse "ignore_secondaries"
1234

    
1235
pRebootType :: Field
1236
pRebootType =
1237
  withDoc "How to reboot the instance" $
1238
  simpleField "reboot_type" [t| RebootType |]
1239

    
1240
pReplaceDisksMode :: Field
1241
pReplaceDisksMode =
1242
  withDoc "Replacement mode" .
1243
  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1244

    
1245
pReplaceDisksList :: Field
1246
pReplaceDisksList =
1247
  withDoc "List of disk indices" .
1248
  renameField "ReplaceDisksList" .
1249
  defaultField [| [] |] $
1250
  simpleField "disks" [t| [DiskIndex] |]
1251

    
1252
pMigrationCleanup :: Field
1253
pMigrationCleanup =
1254
  withDoc "Whether a previously failed migration should be cleaned up" .
1255
  renameField "MigrationCleanup" $ defaultFalse "cleanup"
1256

    
1257
pAllowFailover :: Field
1258
pAllowFailover =
1259
  withDoc "Whether we can fallback to failover if migration is not possible" $
1260
  defaultFalse "allow_failover"
1261

    
1262
pForceFailover :: Field
1263
pForceFailover =
1264
  withDoc "Disallow migration moves and always use failovers" $
1265
  defaultFalse "force_failover"
1266

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
1464
pDelayNoLocks :: Field
1465
pDelayNoLocks =
1466
  withDoc "Don't take locks during the delay" .
1467
  renameField "DelayNoLocks" $
1468
  defaultTrue "no_locks"
1469

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
1647
pNetworkVlan :: Field
1648
pNetworkVlan =
1649
  withDoc "Network vlan when connecting to a group" .
1650
  defaultField [| "" |] $ stringField "network_vlan"