Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ 896cc964

History | View | Annotate | Download (45.3 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

    
3
{-| Implementation of opcodes parameters.
4

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

    
11
-}
12

    
13
{-
14

    
15
Copyright (C) 2012 Google Inc.
16

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

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

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

    
32
-}
33

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

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

    
263
import Ganeti.BasicTypes
264
import qualified Ganeti.Constants as C
265
import Ganeti.THH
266
import Ganeti.JSON
267
import Ganeti.Types
268
import qualified Ganeti.Query.Language as Qlang
269

    
270
-- * Helper functions and types
271

    
272
-- | Build a boolean field.
273
booleanField :: String -> Field
274
booleanField = flip simpleField [t| Bool |]
275

    
276
-- | Default a field to 'False'.
277
defaultFalse :: String -> Field
278
defaultFalse = defaultField [| False |] . booleanField
279

    
280
-- | Default a field to 'True'.
281
defaultTrue :: String -> Field
282
defaultTrue = defaultField [| True |] . booleanField
283

    
284
-- | An alias for a 'String' field.
285
stringField :: String -> Field
286
stringField = flip simpleField [t| String |]
287

    
288
-- | An alias for an optional string field.
289
optionalStringField :: String -> Field
290
optionalStringField = optionalField . stringField
291

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

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

    
305
-- ** Disks
306

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

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

    
319
instance JSON DiskIndex where
320
  readJSON v = readJSON v >>= mkDiskIndex
321
  showJSON = showJSON . unDiskIndex
322

    
323
-- ** I* param types
324

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

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

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

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

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

    
375
instance JSON RecreateDisksInfo where
376
  readJSON = readRecreateDisks
377
  showJSON  RecreateDisksAll            = showJSON ()
378
  showJSON (RecreateDisksIndices idx)   = showJSON idx
379
  showJSON (RecreateDisksParams params) = showJSON params
380

    
381
-- | Simple type for old-style ddm changes.
382
data DdmOldChanges = DdmOldIndex (NonNegative Int)
383
                   | DdmOldMod DdmSimple
384
                     deriving (Eq, Show)
385

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

    
395
instance JSON DdmOldChanges where
396
  showJSON (DdmOldIndex i) = showJSON i
397
  showJSON (DdmOldMod m)   = showJSON m
398
  readJSON = readDdmOldChanges
399

    
400
-- | Instance disk or nic modifications.
401
data SetParamsMods a
402
  = SetParamsEmpty
403
  | SetParamsDeprecated (NonEmpty (DdmOldChanges, a))
404
  | SetParamsNew (NonEmpty (DdmFull, Int, a))
405
    deriving (Eq, Show)
406

    
407
-- | Custom deserialiser for 'SetParamsMods'.
408
readSetParams :: (JSON a) => JSValue -> Text.JSON.Result (SetParamsMods a)
409
readSetParams (JSArray []) = return SetParamsEmpty
410
readSetParams v =
411
  case readJSON v::Text.JSON.Result [(DdmOldChanges, JSValue)] of
412
    Text.JSON.Ok _ -> liftM SetParamsDeprecated $ readJSON v
413
    _ -> liftM SetParamsNew $ readJSON v
414

    
415
instance (JSON a) => JSON (SetParamsMods a) where
416
  showJSON SetParamsEmpty = showJSON ()
417
  showJSON (SetParamsDeprecated v) = showJSON v
418
  showJSON (SetParamsNew v) = showJSON v
419
  readJSON = readSetParams
420

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

    
429
-- | Custom reader for 'ExportTarget'.
430
readExportTarget :: JSValue -> Text.JSON.Result ExportTarget
431
readExportTarget (JSString s) = liftM ExportTargetLocal $
432
                                mkNonEmpty (fromJSString s)
433
readExportTarget (JSArray arr) = return $ ExportTargetRemote arr
434
readExportTarget v = fail $ "Invalid value received for 'target_node': " ++
435
                     show (pp_value v)
436

    
437
instance JSON ExportTarget where
438
  showJSON (ExportTargetLocal s)  = showJSON s
439
  showJSON (ExportTargetRemote l) = showJSON l
440
  readJSON = readExportTarget
441

    
442
-- * Common opcode parameters
443

    
444
pDryRun :: Field
445
pDryRun =
446
  withDoc "Run checks only, don't execute" .
447
  optionalField $ booleanField "dry_run"
448

    
449
pDebugLevel :: Field
450
pDebugLevel =
451
  withDoc "Debug level" .
452
  optionalField $ simpleField "debug_level" [t| NonNegative Int |]
453

    
454
pOpPriority :: Field
455
pOpPriority =
456
  withDoc "Opcode priority. Note: python uses a separate constant,\
457
          \ we're using the actual value we know it's the default" .
458
  defaultField [| OpPrioNormal |] $
459
  simpleField "priority" [t| OpSubmitPriority |]
460

    
461
pDependencies :: Field
462
pDependencies =
463
  withDoc "Job dependencies" .
464
  optionalNullSerField $ simpleField "depends" [t| [JobDependency] |]
465

    
466
pComment :: Field
467
pComment =
468
  withDoc "Comment field" .
469
  optionalNullSerField $ stringField "comment"
470

    
471
pReason :: Field
472
pReason =
473
  withDoc "Reason trail field" $
474
  simpleField C.opcodeReason [t| ReasonTrail |]
475

    
476
-- * Parameters
477

    
478
pDebugSimulateErrors :: Field
479
pDebugSimulateErrors =
480
  withDoc "Whether to simulate errors (useful for debugging)" $
481
  defaultFalse "debug_simulate_errors"
482

    
483
pErrorCodes :: Field
484
pErrorCodes =
485
  withDoc "Error codes" $
486
  defaultFalse "error_codes"
487

    
488
pSkipChecks :: Field
489
pSkipChecks =
490
  withDoc "Which checks to skip" .
491
  defaultField [| emptyListSet |] $
492
  simpleField "skip_checks" [t| ListSet VerifyOptionalChecks |]
493

    
494
pIgnoreErrors :: Field
495
pIgnoreErrors =
496
  withDoc "List of error codes that should be treated as warnings" .
497
  defaultField [| emptyListSet |] $
498
  simpleField "ignore_errors" [t| ListSet CVErrorCode |]
499

    
500
pVerbose :: Field
501
pVerbose =
502
  withDoc "Verbose mode" $
503
  defaultFalse "verbose"
504

    
505
pOptGroupName :: Field
506
pOptGroupName =
507
  withDoc "Optional group name" .
508
  renameField "OptGroupName" .
509
  optionalField $ simpleField "group_name" [t| NonEmptyString |]
510

    
511
pGroupName :: Field
512
pGroupName =
513
  withDoc "Group name" $
514
  simpleField "group_name" [t| NonEmptyString |]
515

    
516
pInstances :: Field
517
pInstances =
518
  withDoc "List of instances" .
519
  defaultField [| [] |] $
520
  simpleField "instances" [t| [NonEmptyString] |]
521

    
522
pOutputFields :: Field
523
pOutputFields =
524
  withDoc "Selected output fields" $
525
  simpleField "output_fields" [t| [NonEmptyString] |]
526

    
527
pName :: Field
528
pName =
529
  withDoc "A generic name" $
530
  simpleField "name" [t| NonEmptyString |]
531

    
532
pForce :: Field
533
pForce =
534
  withDoc "Whether to force the operation" $
535
  defaultFalse "force"
536

    
537
pHvState :: Field
538
pHvState =
539
  withDoc "Set hypervisor states" .
540
  optionalField $ simpleField "hv_state" [t| JSObject JSValue |]
541

    
542
pDiskState :: Field
543
pDiskState =
544
  withDoc "Set disk states" .
545
  optionalField $ simpleField "disk_state" [t| JSObject JSValue |]
546

    
547
-- | Cluster-wide default directory for storing file-backed disks.
548
pClusterFileStorageDir :: Field
549
pClusterFileStorageDir =
550
  renameField "ClusterFileStorageDir" $
551
  optionalStringField "file_storage_dir"
552

    
553
-- | Cluster-wide default directory for storing shared-file-backed disks.
554
pClusterSharedFileStorageDir :: Field
555
pClusterSharedFileStorageDir =
556
  renameField "ClusterSharedFileStorageDir" $
557
  optionalStringField "shared_file_storage_dir"
558

    
559
-- | Volume group name.
560
pVgName :: Field
561
pVgName =
562
  withDoc "Volume group name" $
563
  optionalStringField "vg_name"
564

    
565
pEnabledHypervisors :: Field
566
pEnabledHypervisors =
567
  withDoc "List of enabled hypervisors" .
568
  optionalField $
569
  simpleField "enabled_hypervisors" [t| [Hypervisor] |]
570

    
571
pClusterHvParams :: Field
572
pClusterHvParams =
573
  withDoc "Cluster-wide hypervisor parameters, hypervisor-dependent" .
574
  renameField "ClusterHvParams" .
575
  optionalField $
576
  simpleField "hvparams" [t| GenericContainer String (JSObject JSValue) |]
577

    
578
pClusterBeParams :: Field
579
pClusterBeParams =
580
  withDoc "Cluster-wide backend parameter defaults" .
581
  renameField "ClusterBeParams" .
582
  optionalField $ simpleField "beparams" [t| JSObject JSValue |]
583

    
584
pOsHvp :: Field
585
pOsHvp =
586
  withDoc "Cluster-wide per-OS hypervisor parameter defaults" .
587
  optionalField $
588
  simpleField "os_hvp" [t| GenericContainer String (JSObject JSValue) |]
589

    
590
pClusterOsParams :: Field
591
pClusterOsParams =
592
  withDoc "Cluster-wide OS parameter defaults" .
593
  renameField "ClusterOsParams" .
594
  optionalField $
595
  simpleField "osparams" [t| GenericContainer String (JSObject JSValue) |]
596

    
597
pDiskParams :: Field
598
pDiskParams =
599
  withDoc "Disk templates' parameter defaults" .
600
  optionalField $
601
  simpleField "diskparams"
602
              [t| GenericContainer DiskTemplate (JSObject JSValue) |]
603

    
604
pCandidatePoolSize :: Field
605
pCandidatePoolSize =
606
  withDoc "Master candidate pool size" .
607
  optionalField $ simpleField "candidate_pool_size" [t| Positive Int |]
608

    
609
pUidPool :: Field
610
pUidPool =
611
  withDoc "Set UID pool, must be list of lists describing UID ranges\
612
          \ (two items, start and end inclusive)" .
613
  optionalField $ simpleField "uid_pool" [t| [(Int, Int)] |]
614

    
615
pAddUids :: Field
616
pAddUids =
617
  withDoc "Extend UID pool, must be list of lists describing UID\
618
          \ ranges (two items, start and end inclusive)" .
619
  optionalField $ simpleField "add_uids" [t| [(Int, Int)] |]
620

    
621
pRemoveUids :: Field
622
pRemoveUids =
623
  withDoc "Shrink UID pool, must be list of lists describing UID\
624
          \ ranges (two items, start and end inclusive) to be removed" .
625
  optionalField $ simpleField "remove_uids" [t| [(Int, Int)] |]
626

    
627
pMaintainNodeHealth :: Field
628
pMaintainNodeHealth =
629
  withDoc "Whether to automatically maintain node health" .
630
  optionalField $ booleanField "maintain_node_health"
631

    
632
-- | Whether to modify and keep in sync the @/etc/hosts@ files of nodes.
633
pModifyEtcHosts :: Field
634
pModifyEtcHosts = optionalField $ booleanField "modify_etc_hosts"
635

    
636
-- | Whether to wipe disks before allocating them to instances.
637
pPreallocWipeDisks :: Field
638
pPreallocWipeDisks =
639
  withDoc "Whether to wipe disks before allocating them to instances" .
640
  optionalField $ booleanField "prealloc_wipe_disks"
641

    
642
pNicParams :: Field
643
pNicParams =
644
  withDoc "Cluster-wide NIC parameter defaults" .
645
  optionalField $ simpleField "nicparams" [t| INicParams |]
646

    
647
pIpolicy :: Field
648
pIpolicy =
649
  withDoc "Ipolicy specs" .
650
  optionalField $ simpleField "ipolicy" [t| JSObject JSValue |]
651

    
652
pDrbdHelper :: Field
653
pDrbdHelper =
654
  withDoc "DRBD helper program" $
655
  optionalStringField "drbd_helper"
656

    
657
pDefaultIAllocator :: Field
658
pDefaultIAllocator =
659
  withDoc "Default iallocator for cluster" $
660
  optionalStringField "default_iallocator"
661

    
662
pMasterNetdev :: Field
663
pMasterNetdev =
664
  withDoc "Master network device" $
665
  optionalStringField "master_netdev"
666

    
667
pMasterNetmask :: Field
668
pMasterNetmask =
669
  withDoc "Netmask of the master IP" .
670
  optionalField $ simpleField "master_netmask" [t| NonNegative Int |]
671

    
672
pReservedLvs :: Field
673
pReservedLvs =
674
  withDoc "List of reserved LVs" .
675
  optionalField $ simpleField "reserved_lvs" [t| [NonEmptyString] |]
676

    
677
pHiddenOs :: Field
678
pHiddenOs =
679
  withDoc "Modify list of hidden operating systems: each modification\
680
          \ must have two items, the operation and the OS name; the operation\
681
          \ can be add or remove" .
682
  optionalField $ simpleField "hidden_os" [t| [(DdmSimple, NonEmptyString)] |]
683

    
684
pBlacklistedOs :: Field
685
pBlacklistedOs =
686
  withDoc "Modify list of blacklisted operating systems: each\
687
          \ modification must have two items, the operation and the OS name;\
688
          \ the operation can be add or remove" .
689
  optionalField $
690
  simpleField "blacklisted_os" [t| [(DdmSimple, NonEmptyString)] |]
691

    
692
pUseExternalMipScript :: Field
693
pUseExternalMipScript =
694
  withDoc "Whether to use an external master IP address setup script" .
695
  optionalField $ booleanField "use_external_mip_script"
696

    
697
pEnabledDiskTemplates :: Field
698
pEnabledDiskTemplates =
699
  withDoc "List of enabled disk templates" .
700
  optionalField $
701
  simpleField "enabled_disk_templates" [t| [DiskTemplate] |]
702

    
703
pQueryWhat :: Field
704
pQueryWhat =
705
  withDoc "Resource(s) to query for" $
706
  simpleField "what" [t| Qlang.QueryTypeOp |]
707

    
708
pUseLocking :: Field
709
pUseLocking =
710
  withDoc "Whether to use synchronization" $
711
  defaultFalse "use_locking"
712

    
713
pQueryFields :: Field
714
pQueryFields =
715
  withDoc "Requested fields" $
716
  simpleField "fields" [t| [NonEmptyString] |]
717

    
718
pQueryFilter :: Field
719
pQueryFilter =
720
  withDoc "Query filter" .
721
  optionalField $ simpleField "qfilter" [t| [JSValue] |]
722

    
723
pQueryFieldsFields :: Field
724
pQueryFieldsFields =
725
  withDoc "Requested fields; if not given, all are returned" .
726
  renameField "QueryFieldsFields" $
727
  optionalField pQueryFields
728

    
729
pNodeNames :: Field
730
pNodeNames =
731
  withDoc "List of node names to run the OOB command against" .
732
  defaultField [| [] |] $ simpleField "node_names" [t| [NonEmptyString] |]
733

    
734
pNodeUuids :: Field
735
pNodeUuids =
736
  withDoc "List of node UUIDs" .
737
  optionalField $ simpleField "node_uuids" [t| [NonEmptyString] |]
738

    
739
pOobCommand :: Field
740
pOobCommand =
741
  withDoc "OOB command to run" $
742
  simpleField "command" [t| OobCommand |]
743

    
744
pOobTimeout :: Field
745
pOobTimeout =
746
  withDoc "Timeout before the OOB helper will be terminated" .
747
  defaultField [| C.oobTimeout |] $
748
  simpleField "timeout" [t| Int |]
749

    
750
pIgnoreStatus :: Field
751
pIgnoreStatus =
752
  withDoc "Ignores the node offline status for power off" $
753
  defaultFalse "ignore_status"
754

    
755
pPowerDelay :: Field
756
pPowerDelay =
757
  -- FIXME: we can't use the proper type "NonNegative Double", since
758
  -- the default constant is a plain Double, not a non-negative one.
759
  -- And trying to fix the constant introduces a cyclic import.
760
  withDoc "Time in seconds to wait between powering on nodes" .
761
  defaultField [| C.oobPowerDelay |] $
762
  simpleField "power_delay" [t| Double |]
763

    
764
pRequiredNodes :: Field
765
pRequiredNodes =
766
  withDoc "Required list of node names" .
767
  renameField "ReqNodes " $ simpleField "nodes" [t| [NonEmptyString] |]
768

    
769
pRequiredNodeUuids :: Field
770
pRequiredNodeUuids =
771
  withDoc "Required list of node UUIDs" .
772
  renameField "ReqNodeUuids " . optionalField $
773
  simpleField "node_uuids" [t| [NonEmptyString] |]
774

    
775
pRestrictedCommand :: Field
776
pRestrictedCommand =
777
  withDoc "Restricted command name" .
778
  renameField "RestrictedCommand" $
779
  simpleField "command" [t| NonEmptyString |]
780

    
781
pNodeName :: Field
782
pNodeName =
783
  withDoc "A required node name (for single-node LUs)" $
784
  simpleField "node_name" [t| NonEmptyString |]
785

    
786
pNodeUuid :: Field
787
pNodeUuid =
788
  withDoc "A node UUID (for single-node LUs)" .
789
  optionalField $ simpleField "node_uuid" [t| NonEmptyString |]
790

    
791
pPrimaryIp :: Field
792
pPrimaryIp =
793
  withDoc "Primary IP address" .
794
  optionalField $
795
  simpleField "primary_ip" [t| NonEmptyString |]
796

    
797
pSecondaryIp :: Field
798
pSecondaryIp =
799
  withDoc "Secondary IP address" $
800
  optionalNEStringField "secondary_ip"
801

    
802
pReadd :: Field
803
pReadd =
804
  withDoc "Whether node is re-added to cluster" $
805
  defaultFalse "readd"
806

    
807
pNodeGroup :: Field
808
pNodeGroup =
809
  withDoc "Initial node group" $
810
  optionalNEStringField "group"
811

    
812
pMasterCapable :: Field
813
pMasterCapable =
814
  withDoc "Whether node can become master or master candidate" .
815
  optionalField $ booleanField "master_capable"
816

    
817
pVmCapable :: Field
818
pVmCapable =
819
  withDoc "Whether node can host instances" .
820
  optionalField $ booleanField "vm_capable"
821

    
822
pNdParams :: Field
823
pNdParams =
824
  withDoc "Node parameters" .
825
  renameField "genericNdParams" .
826
  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
827

    
828
pNames :: Field
829
pNames =
830
  withDoc "List of names" .
831
  defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
832

    
833
pNodes :: Field
834
pNodes =
835
  withDoc "List of nodes" .
836
  defaultField [| [] |] $ simpleField "nodes" [t| [NonEmptyString] |]
837

    
838
pStorageType :: Field
839
pStorageType =
840
  withDoc "Storage type" $ simpleField "storage_type" [t| StorageType |]
841

    
842
pStorageTypeOptional :: Field
843
pStorageTypeOptional =
844
  withDoc "Storage type" .
845
  renameField "StorageTypeOptional" .
846
  optionalField $ simpleField "storage_type" [t| StorageType |]
847

    
848
pStorageName :: Field
849
pStorageName =
850
  withDoc "Storage name" .
851
  renameField "StorageName" .
852
  optionalField $ simpleField "name" [t| NonEmptyString |]
853

    
854
pStorageChanges :: Field
855
pStorageChanges =
856
  withDoc "Requested storage changes" $
857
  simpleField "changes" [t| JSObject JSValue |]
858

    
859
pIgnoreConsistency :: Field
860
pIgnoreConsistency =
861
  withDoc "Whether to ignore disk consistency" $
862
  defaultFalse "ignore_consistency"
863

    
864
pMasterCandidate :: Field
865
pMasterCandidate =
866
  withDoc "Whether the node should become a master candidate" .
867
  optionalField $ booleanField "master_candidate"
868

    
869
pOffline :: Field
870
pOffline =
871
  withDoc "Whether to mark the node or instance offline" .
872
  optionalField $ booleanField "offline"
873

    
874
pDrained ::Field
875
pDrained =
876
  withDoc "Whether to mark the node as drained" .
877
  optionalField $ booleanField "drained"
878

    
879
pAutoPromote :: Field
880
pAutoPromote =
881
  withDoc "Whether node(s) should be promoted to master candidate if\
882
          \ necessary" $
883
  defaultFalse "auto_promote"
884

    
885
pPowered :: Field
886
pPowered =
887
  withDoc "Whether the node should be marked as powered" .
888
  optionalField $ booleanField "powered"
889

    
890
pMigrationMode :: Field
891
pMigrationMode =
892
  withDoc "Migration type (live/non-live)" .
893
  renameField "MigrationMode" .
894
  optionalField $
895
  simpleField "mode" [t| MigrationMode |]
896

    
897
pMigrationLive :: Field
898
pMigrationLive =
899
  withDoc "Obsolete \'live\' migration mode (do not use)" .
900
  renameField "OldLiveMode" . optionalField $ booleanField "live"
901

    
902
pMigrationTargetNode :: Field
903
pMigrationTargetNode =
904
  withDoc "Target node for instance migration/failover" $
905
  optionalNEStringField "target_node"
906

    
907
pMigrationTargetNodeUuid :: Field
908
pMigrationTargetNodeUuid =
909
  withDoc "Target node UUID for instance migration/failover" $
910
  optionalNEStringField "target_node_uuid"
911

    
912
pAllowRuntimeChgs :: Field
913
pAllowRuntimeChgs =
914
  withDoc "Whether to allow runtime changes while migrating" $
915
  defaultTrue "allow_runtime_changes"
916

    
917
pIgnoreIpolicy :: Field
918
pIgnoreIpolicy =
919
  withDoc "Whether to ignore ipolicy violations" $
920
  defaultFalse "ignore_ipolicy"
921

    
922
pIallocator :: Field
923
pIallocator =
924
  withDoc "Iallocator for deciding the target node for shared-storage\
925
          \ instances" $
926
  optionalNEStringField "iallocator"
927

    
928
pEarlyRelease :: Field
929
pEarlyRelease =
930
  withDoc "Whether to release locks as soon as possible" $
931
  defaultFalse "early_release"
932

    
933
pRemoteNode :: Field
934
pRemoteNode =
935
  withDoc "New secondary node" $
936
  optionalNEStringField "remote_node"
937

    
938
pRemoteNodeUuid :: Field
939
pRemoteNodeUuid =
940
  withDoc "New secondary node UUID" $
941
  optionalNEStringField "remote_node_uuid"
942

    
943
pEvacMode :: Field
944
pEvacMode =
945
  withDoc "Node evacuation mode" .
946
  renameField "EvacMode" $ simpleField "mode" [t| EvacMode |]
947

    
948
pInstanceName :: Field
949
pInstanceName =
950
  withDoc "A required instance name (for single-instance LUs)" $
951
  simpleField "instance_name" [t| String |]
952

    
953
pForceVariant :: Field
954
pForceVariant =
955
  withDoc "Whether to force an unknown OS variant" $
956
  defaultFalse "force_variant"
957

    
958
pWaitForSync :: Field
959
pWaitForSync =
960
  withDoc "Whether to wait for the disk to synchronize" $
961
  defaultTrue "wait_for_sync"
962

    
963
pNameCheck :: Field
964
pNameCheck =
965
  withDoc "Whether to check name" $
966
  defaultTrue "name_check"
967

    
968
pInstBeParams :: Field
969
pInstBeParams =
970
  withDoc "Backend parameters for instance" .
971
  renameField "InstBeParams" .
972
  defaultField [| toJSObject [] |] $
973
  simpleField "beparams" [t| JSObject JSValue |]
974

    
975
pInstDisks :: Field
976
pInstDisks =
977
  withDoc "List of instance disks" .
978
  renameField "instDisks" $ simpleField "disks" [t| [IDiskParams] |]
979

    
980
pDiskTemplate :: Field
981
pDiskTemplate =
982
  withDoc "Disk template" $
983
  simpleField "disk_template" [t| DiskTemplate |]
984

    
985
pFileDriver :: Field
986
pFileDriver =
987
  withDoc "Driver for file-backed disks" .
988
  optionalField $ simpleField "file_driver" [t| FileDriver |]
989

    
990
pFileStorageDir :: Field
991
pFileStorageDir =
992
  withDoc "Directory for storing file-backed disks" $
993
  optionalNEStringField "file_storage_dir"
994

    
995
pInstHvParams :: Field
996
pInstHvParams =
997
  withDoc "Hypervisor parameters for instance, hypervisor-dependent" .
998
  renameField "InstHvParams" .
999
  defaultField [| toJSObject [] |] $
1000
  simpleField "hvparams" [t| JSObject JSValue |]
1001

    
1002
pHypervisor :: Field
1003
pHypervisor =
1004
  withDoc "Selected hypervisor for an instance" .
1005
  optionalField $
1006
  simpleField "hypervisor" [t| Hypervisor |]
1007

    
1008
pResetDefaults :: Field
1009
pResetDefaults =
1010
  withDoc "Reset instance parameters to default if equal" $
1011
  defaultFalse "identify_defaults"
1012

    
1013
pIpCheck :: Field
1014
pIpCheck =
1015
  withDoc "Whether to ensure instance's IP address is inactive" $
1016
  defaultTrue "ip_check"
1017

    
1018
pIpConflictsCheck :: Field
1019
pIpConflictsCheck =
1020
  withDoc "Whether to check for conflicting IP addresses" $
1021
  defaultTrue "conflicts_check"
1022

    
1023
pInstCreateMode :: Field
1024
pInstCreateMode =
1025
  withDoc "Instance creation mode" .
1026
  renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
1027

    
1028
pInstNics :: Field
1029
pInstNics =
1030
  withDoc "List of NIC (network interface) definitions" $
1031
  simpleField "nics" [t| [INicParams] |]
1032

    
1033
pNoInstall :: Field
1034
pNoInstall =
1035
  withDoc "Do not install the OS (will disable automatic start)" .
1036
  optionalField $ booleanField "no_install"
1037

    
1038
pInstOs :: Field
1039
pInstOs =
1040
  withDoc "OS type for instance installation" $
1041
  optionalNEStringField "os_type"
1042

    
1043
pInstOsParams :: Field
1044
pInstOsParams =
1045
  withDoc "OS parameters for instance" .
1046
  renameField "InstOsParams" .
1047
  defaultField [| toJSObject [] |] $
1048
  simpleField "osparams" [t| JSObject JSValue |]
1049

    
1050
pPrimaryNode :: Field
1051
pPrimaryNode =
1052
  withDoc "Primary node for an instance" $
1053
  optionalNEStringField "pnode"
1054

    
1055
pPrimaryNodeUuid :: Field
1056
pPrimaryNodeUuid =
1057
  withDoc "Primary node UUID for an instance" $
1058
  optionalNEStringField "pnode_uuid"
1059

    
1060
pSecondaryNode :: Field
1061
pSecondaryNode =
1062
  withDoc "Secondary node for an instance" $
1063
  optionalNEStringField "snode"
1064

    
1065
pSecondaryNodeUuid :: Field
1066
pSecondaryNodeUuid =
1067
  withDoc "Secondary node UUID for an instance" $
1068
  optionalNEStringField "snode_uuid"
1069

    
1070
pSourceHandshake :: Field
1071
pSourceHandshake =
1072
  withDoc "Signed handshake from source (remote import only)" .
1073
  optionalField $ simpleField "source_handshake" [t| [JSValue] |]
1074

    
1075
pSourceInstance :: Field
1076
pSourceInstance =
1077
  withDoc "Source instance name (remote import only)" $
1078
  optionalNEStringField "source_instance_name"
1079

    
1080
-- FIXME: non-negative int, whereas the constant is a plain int.
1081
pSourceShutdownTimeout :: Field
1082
pSourceShutdownTimeout =
1083
  withDoc "How long source instance was given to shut down (remote import\
1084
          \ only)" .
1085
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1086
  simpleField "source_shutdown_timeout" [t| NonNegative Int |]
1087

    
1088
pSourceX509Ca :: Field
1089
pSourceX509Ca =
1090
  withDoc "Source X509 CA in PEM format (remote import only)" $
1091
  optionalNEStringField "source_x509_ca"
1092

    
1093
pSrcNode :: Field
1094
pSrcNode =
1095
  withDoc "Source node for import" $
1096
  optionalNEStringField "src_node"
1097

    
1098
pSrcNodeUuid :: Field
1099
pSrcNodeUuid =
1100
  withDoc "Source node UUID for import" $
1101
  optionalNEStringField "src_node_uuid"
1102

    
1103
pSrcPath :: Field
1104
pSrcPath =
1105
  withDoc "Source directory for import" $
1106
  optionalNEStringField "src_path"
1107

    
1108
pStartInstance :: Field
1109
pStartInstance =
1110
  withDoc "Whether to start instance after creation" $
1111
  defaultTrue "start"
1112

    
1113
-- FIXME: unify/simplify with pTags, once that migrates to NonEmpty String"
1114
pInstTags :: Field
1115
pInstTags =
1116
  withDoc "Instance tags" .
1117
  renameField "InstTags" .
1118
  defaultField [| [] |] $
1119
  simpleField "tags" [t| [NonEmptyString] |]
1120

    
1121
pMultiAllocInstances :: Field
1122
pMultiAllocInstances =
1123
  withDoc "List of instance create opcodes describing the instances to\
1124
          \ allocate" .
1125
  renameField "InstMultiAlloc" .
1126
  defaultField [| [] |] $
1127
  simpleField "instances"[t| [JSValue] |]
1128

    
1129
pOpportunisticLocking :: Field
1130
pOpportunisticLocking =
1131
  withDoc "Whether to employ opportunistic locking for nodes, meaning\
1132
          \ nodes already locked by another opcode won't be considered for\
1133
          \ instance allocation (only when an iallocator is used)" $
1134
  defaultFalse "opportunistic_locking"
1135

    
1136
pInstanceUuid :: Field
1137
pInstanceUuid =
1138
  withDoc "An instance UUID (for single-instance LUs)" .
1139
  optionalField $ simpleField "instance_uuid" [t| NonEmptyString |]
1140

    
1141
pTempOsParams :: Field
1142
pTempOsParams =
1143
  withDoc "Temporary OS parameters (currently only in reinstall, might be\
1144
          \ added to install as well)" .
1145
  renameField "TempOsParams" .
1146
  optionalField $ simpleField "osparams" [t| JSObject JSValue |]
1147

    
1148
pShutdownTimeout :: Field
1149
pShutdownTimeout =
1150
  withDoc "How long to wait for instance to shut down" .
1151
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1152
  simpleField "shutdown_timeout" [t| NonNegative Int |]
1153

    
1154
-- | Another name for the shutdown timeout, because we like to be
1155
-- inconsistent.
1156
pShutdownTimeout' :: Field
1157
pShutdownTimeout' =
1158
  withDoc "How long to wait for instance to shut down" .
1159
  renameField "InstShutdownTimeout" .
1160
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1161
  simpleField "timeout" [t| NonNegative Int |]
1162

    
1163
pIgnoreFailures :: Field
1164
pIgnoreFailures =
1165
  withDoc "Whether to ignore failures during removal" $
1166
  defaultFalse "ignore_failures"
1167

    
1168
pNewName :: Field
1169
pNewName =
1170
  withDoc "New group or instance name" $
1171
  simpleField "new_name" [t| NonEmptyString |]
1172

    
1173
pIgnoreOfflineNodes :: Field
1174
pIgnoreOfflineNodes =
1175
  withDoc "Whether to ignore offline nodes" $
1176
  defaultFalse "ignore_offline_nodes"
1177

    
1178
pTempHvParams :: Field
1179
pTempHvParams =
1180
  withDoc "Temporary hypervisor parameters, hypervisor-dependent" .
1181
  renameField "TempHvParams" .
1182
  defaultField [| toJSObject [] |] $
1183
  simpleField "hvparams" [t| JSObject JSValue |]
1184

    
1185
pTempBeParams :: Field
1186
pTempBeParams =
1187
  withDoc "Temporary backend parameters" .
1188
  renameField "TempBeParams" .
1189
  defaultField [| toJSObject [] |] $
1190
  simpleField "beparams" [t| JSObject JSValue |]
1191

    
1192
pNoRemember :: Field
1193
pNoRemember =
1194
  withDoc "Do not remember instance state changes" $
1195
  defaultFalse "no_remember"
1196

    
1197
pStartupPaused :: Field
1198
pStartupPaused =
1199
  withDoc "Pause instance at startup" $
1200
  defaultFalse "startup_paused"
1201

    
1202
pIgnoreSecondaries :: Field
1203
pIgnoreSecondaries =
1204
  withDoc "Whether to start the instance even if secondary disks are failing" $
1205
  defaultFalse "ignore_secondaries"
1206

    
1207
pRebootType :: Field
1208
pRebootType =
1209
  withDoc "How to reboot the instance" $
1210
  simpleField "reboot_type" [t| RebootType |]
1211

    
1212
pReplaceDisksMode :: Field
1213
pReplaceDisksMode =
1214
  withDoc "Replacement mode" .
1215
  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1216

    
1217
pReplaceDisksList :: Field
1218
pReplaceDisksList =
1219
  withDoc "List of disk indices" .
1220
  renameField "ReplaceDisksList" .
1221
  defaultField [| [] |] $
1222
  simpleField "disks" [t| [DiskIndex] |]
1223

    
1224
pMigrationCleanup :: Field
1225
pMigrationCleanup =
1226
  withDoc "Whether a previously failed migration should be cleaned up" .
1227
  renameField "MigrationCleanup" $ defaultFalse "cleanup"
1228

    
1229
pAllowFailover :: Field
1230
pAllowFailover =
1231
  withDoc "Whether we can fallback to failover if migration is not possible" $
1232
  defaultFalse "allow_failover"
1233

    
1234
pMoveTargetNode :: Field
1235
pMoveTargetNode =
1236
  withDoc "Target node for instance move" .
1237
  renameField "MoveTargetNode" $
1238
  simpleField "target_node" [t| NonEmptyString |]
1239

    
1240
pMoveTargetNodeUuid :: Field
1241
pMoveTargetNodeUuid =
1242
  withDoc "Target node UUID for instance move" .
1243
  renameField "MoveTargetNodeUuid" . optionalField $
1244
  simpleField "target_node_uuid" [t| NonEmptyString |]
1245

    
1246
pMoveCompress :: Field
1247
pMoveCompress =
1248
  withDoc "Compression mode to use during instance moves" .
1249
  defaultField [| None |] $
1250
  simpleField "compress" [t| ImportExportCompression |]
1251

    
1252
pBackupCompress :: Field
1253
pBackupCompress =
1254
  withDoc "Compression mode to use for moves during backups" .
1255
  defaultField [| None |] $
1256
  simpleField "compress" [t| ImportExportCompression |]
1257

    
1258
pIgnoreDiskSize :: Field
1259
pIgnoreDiskSize =
1260
  withDoc "Whether to ignore recorded disk size" $
1261
  defaultFalse "ignore_size"
1262

    
1263
pWaitForSyncFalse :: Field
1264
pWaitForSyncFalse =
1265
  withDoc "Whether to wait for the disk to synchronize (defaults to false)" $
1266
  defaultField [| False |] pWaitForSync
1267

    
1268
pRecreateDisksInfo :: Field
1269
pRecreateDisksInfo =
1270
  withDoc "Disk list for recreate disks" .
1271
  renameField "RecreateDisksInfo" .
1272
  defaultField [| RecreateDisksAll |] $
1273
  simpleField "disks" [t| RecreateDisksInfo |]
1274

    
1275
pStatic :: Field
1276
pStatic =
1277
  withDoc "Whether to only return configuration data without querying nodes" $
1278
  defaultFalse "static"
1279

    
1280
pInstParamsNicChanges :: Field
1281
pInstParamsNicChanges =
1282
  withDoc "List of NIC changes" .
1283
  renameField "InstNicChanges" .
1284
  defaultField [| SetParamsEmpty |] $
1285
  simpleField "nics" [t| SetParamsMods INicParams |]
1286

    
1287
pInstParamsDiskChanges :: Field
1288
pInstParamsDiskChanges =
1289
  withDoc "List of disk changes" .
1290
  renameField "InstDiskChanges" .
1291
  defaultField [| SetParamsEmpty |] $
1292
  simpleField "disks" [t| SetParamsMods IDiskParams |]
1293

    
1294
pRuntimeMem :: Field
1295
pRuntimeMem =
1296
  withDoc "New runtime memory" .
1297
  optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1298

    
1299
pOptDiskTemplate :: Field
1300
pOptDiskTemplate =
1301
  withDoc "Instance disk template" .
1302
  optionalField .
1303
  renameField "OptDiskTemplate" $
1304
  simpleField "disk_template" [t| DiskTemplate |]
1305

    
1306
pOsNameChange :: Field
1307
pOsNameChange =
1308
  withDoc "Change the instance's OS without reinstalling the instance" $
1309
  optionalNEStringField "os_name"
1310

    
1311
pDiskIndex :: Field
1312
pDiskIndex =
1313
  withDoc "Disk index for e.g. grow disk" .
1314
  renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
1315

    
1316
pDiskChgAmount :: Field
1317
pDiskChgAmount =
1318
  withDoc "Disk amount to add or grow to" .
1319
  renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
1320

    
1321
pDiskChgAbsolute :: Field
1322
pDiskChgAbsolute =
1323
  withDoc
1324
    "Whether the amount parameter is an absolute target or a relative one" .
1325
  renameField "DiskChkAbsolute" $ defaultFalse "absolute"
1326

    
1327
pTargetGroups :: Field
1328
pTargetGroups =
1329
  withDoc
1330
    "Destination group names or UUIDs (defaults to \"all but current group\")" .
1331
  optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
1332

    
1333
pNodeGroupAllocPolicy :: Field
1334
pNodeGroupAllocPolicy =
1335
  withDoc "Instance allocation policy" .
1336
  optionalField $
1337
  simpleField "alloc_policy" [t| AllocPolicy |]
1338

    
1339
pGroupNodeParams :: Field
1340
pGroupNodeParams =
1341
  withDoc "Default node parameters for group" .
1342
  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
1343

    
1344
pExportMode :: Field
1345
pExportMode =
1346
  withDoc "Export mode" .
1347
  renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1348

    
1349
-- FIXME: Rename target_node as it changes meaning for different
1350
-- export modes (e.g. "destination")
1351
pExportTargetNode :: Field
1352
pExportTargetNode =
1353
  withDoc "Target node (depends on export mode)" .
1354
  renameField "ExportTarget" $
1355
  simpleField "target_node" [t| ExportTarget |]
1356

    
1357
pExportTargetNodeUuid :: Field
1358
pExportTargetNodeUuid =
1359
  withDoc "Target node UUID (if local export)" .
1360
  renameField "ExportTargetNodeUuid" . optionalField $
1361
  simpleField "target_node_uuid" [t| NonEmptyString |]
1362

    
1363
pShutdownInstance :: Field
1364
pShutdownInstance =
1365
  withDoc "Whether to shutdown the instance before export" $
1366
  defaultTrue "shutdown"
1367

    
1368
pRemoveInstance :: Field
1369
pRemoveInstance =
1370
  withDoc "Whether to remove instance after export" $
1371
  defaultFalse "remove_instance"
1372

    
1373
pIgnoreRemoveFailures :: Field
1374
pIgnoreRemoveFailures =
1375
  withDoc "Whether to ignore failures while removing instances" $
1376
  defaultFalse "ignore_remove_failures"
1377

    
1378
pX509KeyName :: Field
1379
pX509KeyName =
1380
  withDoc "Name of X509 key (remote export only)" .
1381
  optionalField $ simpleField "x509_key_name" [t| [JSValue] |]
1382

    
1383
pX509DestCA :: Field
1384
pX509DestCA =
1385
  withDoc "Destination X509 CA (remote export only)" $
1386
  optionalNEStringField "destination_x509_ca"
1387

    
1388
pTagsObject :: Field
1389
pTagsObject =
1390
  withDoc "Tag kind" $
1391
  simpleField "kind" [t| TagKind |]
1392

    
1393
pTagsName :: Field
1394
pTagsName =
1395
  withDoc "Name of object" .
1396
  renameField "TagsGetName" .
1397
  optionalField $ simpleField "name" [t| String |]
1398

    
1399
pTagsList :: Field
1400
pTagsList =
1401
  withDoc "List of tag names" $
1402
  simpleField "tags" [t| [String] |]
1403

    
1404
-- FIXME: this should be compiled at load time?
1405
pTagSearchPattern :: Field
1406
pTagSearchPattern =
1407
  withDoc "Search pattern (regular expression)" .
1408
  renameField "TagSearchPattern" $
1409
  simpleField "pattern" [t| NonEmptyString |]
1410

    
1411
pDelayDuration :: Field
1412
pDelayDuration =
1413
  withDoc "Duration parameter for 'OpTestDelay'" .
1414
  renameField "DelayDuration" $
1415
  simpleField "duration" [t| Double |]
1416

    
1417
pDelayOnMaster :: Field
1418
pDelayOnMaster =
1419
  withDoc "on_master field for 'OpTestDelay'" .
1420
  renameField "DelayOnMaster" $
1421
  defaultTrue "on_master"
1422

    
1423
pDelayOnNodes :: Field
1424
pDelayOnNodes =
1425
  withDoc "on_nodes field for 'OpTestDelay'" .
1426
  renameField "DelayOnNodes" .
1427
  defaultField [| [] |] $
1428
  simpleField "on_nodes" [t| [NonEmptyString] |]
1429

    
1430
pDelayOnNodeUuids :: Field
1431
pDelayOnNodeUuids =
1432
  withDoc "on_node_uuids field for 'OpTestDelay'" .
1433
  renameField "DelayOnNodeUuids" . optionalField $
1434
  simpleField "on_node_uuids" [t| [NonEmptyString] |]
1435

    
1436
pDelayRepeat :: Field
1437
pDelayRepeat =
1438
  withDoc "Repeat parameter for OpTestDelay" .
1439
  renameField "DelayRepeat" .
1440
  defaultField [| forceNonNeg (0::Int) |] $
1441
  simpleField "repeat" [t| NonNegative Int |]
1442

    
1443
pIAllocatorDirection :: Field
1444
pIAllocatorDirection =
1445
  withDoc "IAllocator test direction" .
1446
  renameField "IAllocatorDirection" $
1447
  simpleField "direction" [t| IAllocatorTestDir |]
1448

    
1449
pIAllocatorMode :: Field
1450
pIAllocatorMode =
1451
  withDoc "IAllocator test mode" .
1452
  renameField "IAllocatorMode" $
1453
  simpleField "mode" [t| IAllocatorMode |]
1454

    
1455
pIAllocatorReqName :: Field
1456
pIAllocatorReqName =
1457
  withDoc "IAllocator target name (new instance, node to evac, etc.)" .
1458
  renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
1459

    
1460
pIAllocatorNics :: Field
1461
pIAllocatorNics =
1462
  withDoc "Custom OpTestIAllocator nics" .
1463
  renameField "IAllocatorNics" .
1464
  optionalField $ simpleField "nics" [t| [INicParams] |]
1465

    
1466
pIAllocatorDisks :: Field
1467
pIAllocatorDisks =
1468
  withDoc "Custom OpTestAllocator disks" .
1469
  renameField "IAllocatorDisks" .
1470
  optionalField $ simpleField "disks" [t| [JSValue] |]
1471

    
1472
pIAllocatorMemory :: Field
1473
pIAllocatorMemory =
1474
  withDoc "IAllocator memory field" .
1475
  renameField "IAllocatorMem" .
1476
  optionalField $
1477
  simpleField "memory" [t| NonNegative Int |]
1478

    
1479
pIAllocatorVCpus :: Field
1480
pIAllocatorVCpus =
1481
  withDoc "IAllocator vcpus field" .
1482
  renameField "IAllocatorVCpus" .
1483
  optionalField $
1484
  simpleField "vcpus" [t| NonNegative Int |]
1485

    
1486
pIAllocatorOs :: Field
1487
pIAllocatorOs =
1488
  withDoc "IAllocator os field" .
1489
  renameField "IAllocatorOs" $ optionalNEStringField "os"
1490

    
1491
pIAllocatorInstances :: Field
1492
pIAllocatorInstances =
1493
  withDoc "IAllocator instances field" .
1494
  renameField "IAllocatorInstances " .
1495
  optionalField $
1496
  simpleField "instances" [t| [NonEmptyString] |]
1497

    
1498
pIAllocatorEvacMode :: Field
1499
pIAllocatorEvacMode =
1500
  withDoc "IAllocator evac mode" .
1501
  renameField "IAllocatorEvacMode" .
1502
  optionalField $
1503
  simpleField "evac_mode" [t| EvacMode |]
1504

    
1505
pIAllocatorSpindleUse :: Field
1506
pIAllocatorSpindleUse =
1507
  withDoc "IAllocator spindle use" .
1508
  renameField "IAllocatorSpindleUse" .
1509
  defaultField [| forceNonNeg (1::Int) |] $
1510
  simpleField "spindle_use" [t| NonNegative Int |]
1511

    
1512
pIAllocatorCount :: Field
1513
pIAllocatorCount =
1514
  withDoc "IAllocator count field" .
1515
  renameField "IAllocatorCount" .
1516
  defaultField [| forceNonNeg (1::Int) |] $
1517
  simpleField "count" [t| NonNegative Int |]
1518

    
1519
pJQueueNotifyWaitLock :: Field
1520
pJQueueNotifyWaitLock =
1521
  withDoc "'OpTestJqueue' notify_waitlock" $
1522
  defaultFalse "notify_waitlock"
1523

    
1524
pJQueueNotifyExec :: Field
1525
pJQueueNotifyExec =
1526
  withDoc "'OpTestJQueue' notify_exec" $
1527
  defaultFalse "notify_exec"
1528

    
1529
pJQueueLogMessages :: Field
1530
pJQueueLogMessages =
1531
  withDoc "'OpTestJQueue' log_messages" .
1532
  defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
1533

    
1534
pJQueueFail :: Field
1535
pJQueueFail =
1536
  withDoc "'OpTestJQueue' fail attribute" .
1537
  renameField "JQueueFail" $ defaultFalse "fail"
1538

    
1539
pTestDummyResult :: Field
1540
pTestDummyResult =
1541
  withDoc "'OpTestDummy' result field" .
1542
  renameField "TestDummyResult" $ simpleField "result" [t| JSValue |]
1543

    
1544
pTestDummyMessages :: Field
1545
pTestDummyMessages =
1546
  withDoc "'OpTestDummy' messages field" .
1547
  renameField "TestDummyMessages" $
1548
  simpleField "messages" [t| JSValue |]
1549

    
1550
pTestDummyFail :: Field
1551
pTestDummyFail =
1552
  withDoc "'OpTestDummy' fail field" .
1553
  renameField "TestDummyFail" $ simpleField "fail" [t| JSValue |]
1554

    
1555
pTestDummySubmitJobs :: Field
1556
pTestDummySubmitJobs =
1557
  withDoc "'OpTestDummy' submit_jobs field" .
1558
  renameField "TestDummySubmitJobs" $
1559
  simpleField "submit_jobs" [t| JSValue |]
1560

    
1561
pNetworkName :: Field
1562
pNetworkName =
1563
  withDoc "Network name" $
1564
  simpleField "network_name" [t| NonEmptyString |]
1565

    
1566
pNetworkAddress4 :: Field
1567
pNetworkAddress4 =
1568
  withDoc "Network address (IPv4 subnet)" .
1569
  renameField "NetworkAddress4" $
1570
  simpleField "network" [t| IPv4Network |]
1571

    
1572
pNetworkGateway4 :: Field
1573
pNetworkGateway4 =
1574
  withDoc "Network gateway (IPv4 address)" .
1575
  renameField "NetworkGateway4" .
1576
  optionalField $ simpleField "gateway" [t| IPv4Address |]
1577

    
1578
pNetworkAddress6 :: Field
1579
pNetworkAddress6 =
1580
  withDoc "Network address (IPv6 subnet)" .
1581
  renameField "NetworkAddress6" .
1582
  optionalField $ simpleField "network6" [t| IPv6Network |]
1583

    
1584
pNetworkGateway6 :: Field
1585
pNetworkGateway6 =
1586
  withDoc "Network gateway (IPv6 address)" .
1587
  renameField "NetworkGateway6" .
1588
  optionalField $ simpleField "gateway6" [t| IPv6Address |]
1589

    
1590
pNetworkMacPrefix :: Field
1591
pNetworkMacPrefix =
1592
  withDoc "Network specific mac prefix (that overrides the cluster one)" .
1593
  renameField "NetMacPrefix" $
1594
  optionalNEStringField "mac_prefix"
1595

    
1596
pNetworkAddRsvdIps :: Field
1597
pNetworkAddRsvdIps =
1598
  withDoc "Which IP addresses to reserve" .
1599
  renameField "NetworkAddRsvdIps" .
1600
  optionalField $
1601
  simpleField "add_reserved_ips" [t| [IPv4Address] |]
1602

    
1603
pNetworkRemoveRsvdIps :: Field
1604
pNetworkRemoveRsvdIps =
1605
  withDoc "Which external IP addresses to release" .
1606
  renameField "NetworkRemoveRsvdIps" .
1607
  optionalField $
1608
  simpleField "remove_reserved_ips" [t| [IPv4Address] |]
1609

    
1610
pNetworkMode :: Field
1611
pNetworkMode =
1612
  withDoc "Network mode when connecting to a group" $
1613
  simpleField "network_mode" [t| NICMode |]
1614

    
1615
pNetworkLink :: Field
1616
pNetworkLink =
1617
  withDoc "Network link when connecting to a group" $
1618
  simpleField "network_link" [t| NonEmptyString |]