Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ 7295a6dc

History | View | Annotate | Download (45.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

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

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

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

    
32
-}
33

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

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

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

    
271
-- * Helper functions and types
272

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

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

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

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

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

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

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

    
306
-- ** Disks
307

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

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

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

    
324
-- ** I* param types
325

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

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

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

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

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

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

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

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

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

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

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

    
417
instance (JSON a) => JSON (SetParamsMods a) where
418
  showJSON SetParamsEmpty = showJSON ()
419
  showJSON (SetParamsDeprecated v) = showJSON v
420
  showJSON (SetParamsNew v) = showJSON v
421
  showJSON (SetParamsNewName v) = showJSON v
422
  readJSON = readSetParams
423

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

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

    
440
instance JSON ExportTarget where
441
  showJSON (ExportTargetLocal s)  = showJSON s
442
  showJSON (ExportTargetRemote l) = showJSON l
443
  readJSON = readExportTarget
444

    
445
-- * Common opcode parameters
446

    
447
pDryRun :: Field
448
pDryRun =
449
  withDoc "Run checks only, don't execute" .
450
  optionalField $ booleanField "dry_run"
451

    
452
pDebugLevel :: Field
453
pDebugLevel =
454
  withDoc "Debug level" .
455
  optionalField $ simpleField "debug_level" [t| NonNegative Int |]
456

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

    
464
pDependencies :: Field
465
pDependencies =
466
  withDoc "Job dependencies" .
467
  optionalNullSerField $ simpleField "depends" [t| [JobDependency] |]
468

    
469
pComment :: Field
470
pComment =
471
  withDoc "Comment field" .
472
  optionalNullSerField $ stringField "comment"
473

    
474
pReason :: Field
475
pReason =
476
  withDoc "Reason trail field" $
477
  simpleField C.opcodeReason [t| ReasonTrail |]
478

    
479
-- * Parameters
480

    
481
pDebugSimulateErrors :: Field
482
pDebugSimulateErrors =
483
  withDoc "Whether to simulate errors (useful for debugging)" $
484
  defaultFalse "debug_simulate_errors"
485

    
486
pErrorCodes :: Field
487
pErrorCodes =
488
  withDoc "Error codes" $
489
  defaultFalse "error_codes"
490

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

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

    
503
pVerbose :: Field
504
pVerbose =
505
  withDoc "Verbose mode" $
506
  defaultFalse "verbose"
507

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

    
514
pGroupName :: Field
515
pGroupName =
516
  withDoc "Group name" $
517
  simpleField "group_name" [t| NonEmptyString |]
518

    
519
-- | Whether to hotplug device.
520
pHotplug :: Field
521
pHotplug = defaultFalse "hotplug"
522

    
523
pInstances :: Field
524
pInstances =
525
  withDoc "List of instances" .
526
  defaultField [| [] |] $
527
  simpleField "instances" [t| [NonEmptyString] |]
528

    
529
pOutputFields :: Field
530
pOutputFields =
531
  withDoc "Selected output fields" $
532
  simpleField "output_fields" [t| [NonEmptyString] |]
533

    
534
pName :: Field
535
pName =
536
  withDoc "A generic name" $
537
  simpleField "name" [t| NonEmptyString |]
538

    
539
pForce :: Field
540
pForce =
541
  withDoc "Whether to force the operation" $
542
  defaultFalse "force"
543

    
544
pHvState :: Field
545
pHvState =
546
  withDoc "Set hypervisor states" .
547
  optionalField $ simpleField "hv_state" [t| JSObject JSValue |]
548

    
549
pDiskState :: Field
550
pDiskState =
551
  withDoc "Set disk states" .
552
  optionalField $ simpleField "disk_state" [t| JSObject JSValue |]
553

    
554
-- | Cluster-wide default directory for storing file-backed disks.
555
pClusterFileStorageDir :: Field
556
pClusterFileStorageDir =
557
  renameField "ClusterFileStorageDir" $
558
  optionalStringField "file_storage_dir"
559

    
560
-- | Cluster-wide default directory for storing shared-file-backed disks.
561
pClusterSharedFileStorageDir :: Field
562
pClusterSharedFileStorageDir =
563
  renameField "ClusterSharedFileStorageDir" $
564
  optionalStringField "shared_file_storage_dir"
565

    
566
-- | Volume group name.
567
pVgName :: Field
568
pVgName =
569
  withDoc "Volume group name" $
570
  optionalStringField "vg_name"
571

    
572
pEnabledHypervisors :: Field
573
pEnabledHypervisors =
574
  withDoc "List of enabled hypervisors" .
575
  optionalField $
576
  simpleField "enabled_hypervisors" [t| [Hypervisor] |]
577

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

    
585
pClusterBeParams :: Field
586
pClusterBeParams =
587
  withDoc "Cluster-wide backend parameter defaults" .
588
  renameField "ClusterBeParams" .
589
  optionalField $ simpleField "beparams" [t| JSObject JSValue |]
590

    
591
pOsHvp :: Field
592
pOsHvp =
593
  withDoc "Cluster-wide per-OS hypervisor parameter defaults" .
594
  optionalField $
595
  simpleField "os_hvp" [t| GenericContainer String (JSObject JSValue) |]
596

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

    
604
pDiskParams :: Field
605
pDiskParams =
606
  withDoc "Disk templates' parameter defaults" .
607
  optionalField $
608
  simpleField "diskparams"
609
              [t| GenericContainer DiskTemplate (JSObject JSValue) |]
610

    
611
pCandidatePoolSize :: Field
612
pCandidatePoolSize =
613
  withDoc "Master candidate pool size" .
614
  optionalField $ simpleField "candidate_pool_size" [t| Positive Int |]
615

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

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

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

    
634
pMaintainNodeHealth :: Field
635
pMaintainNodeHealth =
636
  withDoc "Whether to automatically maintain node health" .
637
  optionalField $ booleanField "maintain_node_health"
638

    
639
-- | Whether to modify and keep in sync the @/etc/hosts@ files of nodes.
640
pModifyEtcHosts :: Field
641
pModifyEtcHosts = optionalField $ booleanField "modify_etc_hosts"
642

    
643
-- | Whether to wipe disks before allocating them to instances.
644
pPreallocWipeDisks :: Field
645
pPreallocWipeDisks =
646
  withDoc "Whether to wipe disks before allocating them to instances" .
647
  optionalField $ booleanField "prealloc_wipe_disks"
648

    
649
pNicParams :: Field
650
pNicParams =
651
  withDoc "Cluster-wide NIC parameter defaults" .
652
  optionalField $ simpleField "nicparams" [t| INicParams |]
653

    
654
pIpolicy :: Field
655
pIpolicy =
656
  withDoc "Ipolicy specs" .
657
  optionalField $ simpleField "ipolicy" [t| JSObject JSValue |]
658

    
659
pDrbdHelper :: Field
660
pDrbdHelper =
661
  withDoc "DRBD helper program" $
662
  optionalStringField "drbd_helper"
663

    
664
pDefaultIAllocator :: Field
665
pDefaultIAllocator =
666
  withDoc "Default iallocator for cluster" $
667
  optionalStringField "default_iallocator"
668

    
669
pMasterNetdev :: Field
670
pMasterNetdev =
671
  withDoc "Master network device" $
672
  optionalStringField "master_netdev"
673

    
674
pMasterNetmask :: Field
675
pMasterNetmask =
676
  withDoc "Netmask of the master IP" .
677
  optionalField $ simpleField "master_netmask" [t| NonNegative Int |]
678

    
679
pReservedLvs :: Field
680
pReservedLvs =
681
  withDoc "List of reserved LVs" .
682
  optionalField $ simpleField "reserved_lvs" [t| [NonEmptyString] |]
683

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

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

    
699
pUseExternalMipScript :: Field
700
pUseExternalMipScript =
701
  withDoc "Whether to use an external master IP address setup script" .
702
  optionalField $ booleanField "use_external_mip_script"
703

    
704
pEnabledDiskTemplates :: Field
705
pEnabledDiskTemplates =
706
  withDoc "List of enabled disk templates" .
707
  optionalField $
708
  simpleField "enabled_disk_templates" [t| [DiskTemplate] |]
709

    
710
pQueryWhat :: Field
711
pQueryWhat =
712
  withDoc "Resource(s) to query for" $
713
  simpleField "what" [t| Qlang.QueryTypeOp |]
714

    
715
pUseLocking :: Field
716
pUseLocking =
717
  withDoc "Whether to use synchronization" $
718
  defaultFalse "use_locking"
719

    
720
pQueryFields :: Field
721
pQueryFields =
722
  withDoc "Requested fields" $
723
  simpleField "fields" [t| [NonEmptyString] |]
724

    
725
pQueryFilter :: Field
726
pQueryFilter =
727
  withDoc "Query filter" .
728
  optionalField $ simpleField "qfilter" [t| [JSValue] |]
729

    
730
pQueryFieldsFields :: Field
731
pQueryFieldsFields =
732
  withDoc "Requested fields; if not given, all are returned" .
733
  renameField "QueryFieldsFields" $
734
  optionalField pQueryFields
735

    
736
pNodeNames :: Field
737
pNodeNames =
738
  withDoc "List of node names to run the OOB command against" .
739
  defaultField [| [] |] $ simpleField "node_names" [t| [NonEmptyString] |]
740

    
741
pNodeUuids :: Field
742
pNodeUuids =
743
  withDoc "List of node UUIDs" .
744
  optionalField $ simpleField "node_uuids" [t| [NonEmptyString] |]
745

    
746
pOobCommand :: Field
747
pOobCommand =
748
  withDoc "OOB command to run" $
749
  simpleField "command" [t| OobCommand |]
750

    
751
pOobTimeout :: Field
752
pOobTimeout =
753
  withDoc "Timeout before the OOB helper will be terminated" .
754
  defaultField [| C.oobTimeout |] $
755
  simpleField "timeout" [t| Int |]
756

    
757
pIgnoreStatus :: Field
758
pIgnoreStatus =
759
  withDoc "Ignores the node offline status for power off" $
760
  defaultFalse "ignore_status"
761

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

    
771
pRequiredNodes :: Field
772
pRequiredNodes =
773
  withDoc "Required list of node names" .
774
  renameField "ReqNodes " $ simpleField "nodes" [t| [NonEmptyString] |]
775

    
776
pRequiredNodeUuids :: Field
777
pRequiredNodeUuids =
778
  withDoc "Required list of node UUIDs" .
779
  renameField "ReqNodeUuids " . optionalField $
780
  simpleField "node_uuids" [t| [NonEmptyString] |]
781

    
782
pRestrictedCommand :: Field
783
pRestrictedCommand =
784
  withDoc "Restricted command name" .
785
  renameField "RestrictedCommand" $
786
  simpleField "command" [t| NonEmptyString |]
787

    
788
pNodeName :: Field
789
pNodeName =
790
  withDoc "A required node name (for single-node LUs)" $
791
  simpleField "node_name" [t| NonEmptyString |]
792

    
793
pNodeUuid :: Field
794
pNodeUuid =
795
  withDoc "A node UUID (for single-node LUs)" .
796
  optionalField $ simpleField "node_uuid" [t| NonEmptyString |]
797

    
798
pPrimaryIp :: Field
799
pPrimaryIp =
800
  withDoc "Primary IP address" .
801
  optionalField $
802
  simpleField "primary_ip" [t| NonEmptyString |]
803

    
804
pSecondaryIp :: Field
805
pSecondaryIp =
806
  withDoc "Secondary IP address" $
807
  optionalNEStringField "secondary_ip"
808

    
809
pReadd :: Field
810
pReadd =
811
  withDoc "Whether node is re-added to cluster" $
812
  defaultFalse "readd"
813

    
814
pNodeGroup :: Field
815
pNodeGroup =
816
  withDoc "Initial node group" $
817
  optionalNEStringField "group"
818

    
819
pMasterCapable :: Field
820
pMasterCapable =
821
  withDoc "Whether node can become master or master candidate" .
822
  optionalField $ booleanField "master_capable"
823

    
824
pVmCapable :: Field
825
pVmCapable =
826
  withDoc "Whether node can host instances" .
827
  optionalField $ booleanField "vm_capable"
828

    
829
pNdParams :: Field
830
pNdParams =
831
  withDoc "Node parameters" .
832
  renameField "genericNdParams" .
833
  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
834

    
835
pNames :: Field
836
pNames =
837
  withDoc "List of names" .
838
  defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
839

    
840
pNodes :: Field
841
pNodes =
842
  withDoc "List of nodes" .
843
  defaultField [| [] |] $ simpleField "nodes" [t| [NonEmptyString] |]
844

    
845
pStorageType :: Field
846
pStorageType =
847
  withDoc "Storage type" $ simpleField "storage_type" [t| StorageType |]
848

    
849
pStorageTypeOptional :: Field
850
pStorageTypeOptional =
851
  withDoc "Storage type" .
852
  renameField "StorageTypeOptional" .
853
  optionalField $ simpleField "storage_type" [t| StorageType |]
854

    
855
pStorageName :: Field
856
pStorageName =
857
  withDoc "Storage name" .
858
  renameField "StorageName" .
859
  optionalField $ simpleField "name" [t| NonEmptyString |]
860

    
861
pStorageChanges :: Field
862
pStorageChanges =
863
  withDoc "Requested storage changes" $
864
  simpleField "changes" [t| JSObject JSValue |]
865

    
866
pIgnoreConsistency :: Field
867
pIgnoreConsistency =
868
  withDoc "Whether to ignore disk consistency" $
869
  defaultFalse "ignore_consistency"
870

    
871
pMasterCandidate :: Field
872
pMasterCandidate =
873
  withDoc "Whether the node should become a master candidate" .
874
  optionalField $ booleanField "master_candidate"
875

    
876
pOffline :: Field
877
pOffline =
878
  withDoc "Whether to mark the node or instance offline" .
879
  optionalField $ booleanField "offline"
880

    
881
pDrained ::Field
882
pDrained =
883
  withDoc "Whether to mark the node as drained" .
884
  optionalField $ booleanField "drained"
885

    
886
pAutoPromote :: Field
887
pAutoPromote =
888
  withDoc "Whether node(s) should be promoted to master candidate if\
889
          \ necessary" $
890
  defaultFalse "auto_promote"
891

    
892
pPowered :: Field
893
pPowered =
894
  withDoc "Whether the node should be marked as powered" .
895
  optionalField $ booleanField "powered"
896

    
897
pMigrationMode :: Field
898
pMigrationMode =
899
  withDoc "Migration type (live/non-live)" .
900
  renameField "MigrationMode" .
901
  optionalField $
902
  simpleField "mode" [t| MigrationMode |]
903

    
904
pMigrationLive :: Field
905
pMigrationLive =
906
  withDoc "Obsolete \'live\' migration mode (do not use)" .
907
  renameField "OldLiveMode" . optionalField $ booleanField "live"
908

    
909
pMigrationTargetNode :: Field
910
pMigrationTargetNode =
911
  withDoc "Target node for instance migration/failover" $
912
  optionalNEStringField "target_node"
913

    
914
pMigrationTargetNodeUuid :: Field
915
pMigrationTargetNodeUuid =
916
  withDoc "Target node UUID for instance migration/failover" $
917
  optionalNEStringField "target_node_uuid"
918

    
919
pAllowRuntimeChgs :: Field
920
pAllowRuntimeChgs =
921
  withDoc "Whether to allow runtime changes while migrating" $
922
  defaultTrue "allow_runtime_changes"
923

    
924
pIgnoreIpolicy :: Field
925
pIgnoreIpolicy =
926
  withDoc "Whether to ignore ipolicy violations" $
927
  defaultFalse "ignore_ipolicy"
928

    
929
pIallocator :: Field
930
pIallocator =
931
  withDoc "Iallocator for deciding the target node for shared-storage\
932
          \ instances" $
933
  optionalNEStringField "iallocator"
934

    
935
pEarlyRelease :: Field
936
pEarlyRelease =
937
  withDoc "Whether to release locks as soon as possible" $
938
  defaultFalse "early_release"
939

    
940
pRemoteNode :: Field
941
pRemoteNode =
942
  withDoc "New secondary node" $
943
  optionalNEStringField "remote_node"
944

    
945
pRemoteNodeUuid :: Field
946
pRemoteNodeUuid =
947
  withDoc "New secondary node UUID" $
948
  optionalNEStringField "remote_node_uuid"
949

    
950
pEvacMode :: Field
951
pEvacMode =
952
  withDoc "Node evacuation mode" .
953
  renameField "EvacMode" $ simpleField "mode" [t| EvacMode |]
954

    
955
pInstanceName :: Field
956
pInstanceName =
957
  withDoc "A required instance name (for single-instance LUs)" $
958
  simpleField "instance_name" [t| String |]
959

    
960
pForceVariant :: Field
961
pForceVariant =
962
  withDoc "Whether to force an unknown OS variant" $
963
  defaultFalse "force_variant"
964

    
965
pWaitForSync :: Field
966
pWaitForSync =
967
  withDoc "Whether to wait for the disk to synchronize" $
968
  defaultTrue "wait_for_sync"
969

    
970
pNameCheck :: Field
971
pNameCheck =
972
  withDoc "Whether to check name" $
973
  defaultTrue "name_check"
974

    
975
pInstBeParams :: Field
976
pInstBeParams =
977
  withDoc "Backend parameters for instance" .
978
  renameField "InstBeParams" .
979
  defaultField [| toJSObject [] |] $
980
  simpleField "beparams" [t| JSObject JSValue |]
981

    
982
pInstDisks :: Field
983
pInstDisks =
984
  withDoc "List of instance disks" .
985
  renameField "instDisks" $ simpleField "disks" [t| [IDiskParams] |]
986

    
987
pDiskTemplate :: Field
988
pDiskTemplate =
989
  withDoc "Disk template" $
990
  simpleField "disk_template" [t| DiskTemplate |]
991

    
992
pFileDriver :: Field
993
pFileDriver =
994
  withDoc "Driver for file-backed disks" .
995
  optionalField $ simpleField "file_driver" [t| FileDriver |]
996

    
997
pFileStorageDir :: Field
998
pFileStorageDir =
999
  withDoc "Directory for storing file-backed disks" $
1000
  optionalNEStringField "file_storage_dir"
1001

    
1002
pInstHvParams :: Field
1003
pInstHvParams =
1004
  withDoc "Hypervisor parameters for instance, hypervisor-dependent" .
1005
  renameField "InstHvParams" .
1006
  defaultField [| toJSObject [] |] $
1007
  simpleField "hvparams" [t| JSObject JSValue |]
1008

    
1009
pHypervisor :: Field
1010
pHypervisor =
1011
  withDoc "Selected hypervisor for an instance" .
1012
  optionalField $
1013
  simpleField "hypervisor" [t| Hypervisor |]
1014

    
1015
pResetDefaults :: Field
1016
pResetDefaults =
1017
  withDoc "Reset instance parameters to default if equal" $
1018
  defaultFalse "identify_defaults"
1019

    
1020
pIpCheck :: Field
1021
pIpCheck =
1022
  withDoc "Whether to ensure instance's IP address is inactive" $
1023
  defaultTrue "ip_check"
1024

    
1025
pIpConflictsCheck :: Field
1026
pIpConflictsCheck =
1027
  withDoc "Whether to check for conflicting IP addresses" $
1028
  defaultTrue "conflicts_check"
1029

    
1030
pInstCreateMode :: Field
1031
pInstCreateMode =
1032
  withDoc "Instance creation mode" .
1033
  renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
1034

    
1035
pInstNics :: Field
1036
pInstNics =
1037
  withDoc "List of NIC (network interface) definitions" $
1038
  simpleField "nics" [t| [INicParams] |]
1039

    
1040
pNoInstall :: Field
1041
pNoInstall =
1042
  withDoc "Do not install the OS (will disable automatic start)" .
1043
  optionalField $ booleanField "no_install"
1044

    
1045
pInstOs :: Field
1046
pInstOs =
1047
  withDoc "OS type for instance installation" $
1048
  optionalNEStringField "os_type"
1049

    
1050
pInstOsParams :: Field
1051
pInstOsParams =
1052
  withDoc "OS parameters for instance" .
1053
  renameField "InstOsParams" .
1054
  defaultField [| toJSObject [] |] $
1055
  simpleField "osparams" [t| JSObject JSValue |]
1056

    
1057
pPrimaryNode :: Field
1058
pPrimaryNode =
1059
  withDoc "Primary node for an instance" $
1060
  optionalNEStringField "pnode"
1061

    
1062
pPrimaryNodeUuid :: Field
1063
pPrimaryNodeUuid =
1064
  withDoc "Primary node UUID for an instance" $
1065
  optionalNEStringField "pnode_uuid"
1066

    
1067
pSecondaryNode :: Field
1068
pSecondaryNode =
1069
  withDoc "Secondary node for an instance" $
1070
  optionalNEStringField "snode"
1071

    
1072
pSecondaryNodeUuid :: Field
1073
pSecondaryNodeUuid =
1074
  withDoc "Secondary node UUID for an instance" $
1075
  optionalNEStringField "snode_uuid"
1076

    
1077
pSourceHandshake :: Field
1078
pSourceHandshake =
1079
  withDoc "Signed handshake from source (remote import only)" .
1080
  optionalField $ simpleField "source_handshake" [t| [JSValue] |]
1081

    
1082
pSourceInstance :: Field
1083
pSourceInstance =
1084
  withDoc "Source instance name (remote import only)" $
1085
  optionalNEStringField "source_instance_name"
1086

    
1087
-- FIXME: non-negative int, whereas the constant is a plain int.
1088
pSourceShutdownTimeout :: Field
1089
pSourceShutdownTimeout =
1090
  withDoc "How long source instance was given to shut down (remote import\
1091
          \ only)" .
1092
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1093
  simpleField "source_shutdown_timeout" [t| NonNegative Int |]
1094

    
1095
pSourceX509Ca :: Field
1096
pSourceX509Ca =
1097
  withDoc "Source X509 CA in PEM format (remote import only)" $
1098
  optionalNEStringField "source_x509_ca"
1099

    
1100
pSrcNode :: Field
1101
pSrcNode =
1102
  withDoc "Source node for import" $
1103
  optionalNEStringField "src_node"
1104

    
1105
pSrcNodeUuid :: Field
1106
pSrcNodeUuid =
1107
  withDoc "Source node UUID for import" $
1108
  optionalNEStringField "src_node_uuid"
1109

    
1110
pSrcPath :: Field
1111
pSrcPath =
1112
  withDoc "Source directory for import" $
1113
  optionalNEStringField "src_path"
1114

    
1115
pStartInstance :: Field
1116
pStartInstance =
1117
  withDoc "Whether to start instance after creation" $
1118
  defaultTrue "start"
1119

    
1120
-- FIXME: unify/simplify with pTags, once that migrates to NonEmpty String"
1121
pInstTags :: Field
1122
pInstTags =
1123
  withDoc "Instance tags" .
1124
  renameField "InstTags" .
1125
  defaultField [| [] |] $
1126
  simpleField "tags" [t| [NonEmptyString] |]
1127

    
1128
pMultiAllocInstances :: Field
1129
pMultiAllocInstances =
1130
  withDoc "List of instance create opcodes describing the instances to\
1131
          \ allocate" .
1132
  renameField "InstMultiAlloc" .
1133
  defaultField [| [] |] $
1134
  simpleField "instances"[t| [JSValue] |]
1135

    
1136
pOpportunisticLocking :: Field
1137
pOpportunisticLocking =
1138
  withDoc "Whether to employ opportunistic locking for nodes, meaning\
1139
          \ nodes already locked by another opcode won't be considered for\
1140
          \ instance allocation (only when an iallocator is used)" $
1141
  defaultFalse "opportunistic_locking"
1142

    
1143
pInstanceUuid :: Field
1144
pInstanceUuid =
1145
  withDoc "An instance UUID (for single-instance LUs)" .
1146
  optionalField $ simpleField "instance_uuid" [t| NonEmptyString |]
1147

    
1148
pTempOsParams :: Field
1149
pTempOsParams =
1150
  withDoc "Temporary OS parameters (currently only in reinstall, might be\
1151
          \ added to install as well)" .
1152
  renameField "TempOsParams" .
1153
  optionalField $ simpleField "osparams" [t| JSObject JSValue |]
1154

    
1155
pShutdownTimeout :: Field
1156
pShutdownTimeout =
1157
  withDoc "How long to wait for instance to shut down" .
1158
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1159
  simpleField "shutdown_timeout" [t| NonNegative Int |]
1160

    
1161
-- | Another name for the shutdown timeout, because we like to be
1162
-- inconsistent.
1163
pShutdownTimeout' :: Field
1164
pShutdownTimeout' =
1165
  withDoc "How long to wait for instance to shut down" .
1166
  renameField "InstShutdownTimeout" .
1167
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1168
  simpleField "timeout" [t| NonNegative Int |]
1169

    
1170
pIgnoreFailures :: Field
1171
pIgnoreFailures =
1172
  withDoc "Whether to ignore failures during removal" $
1173
  defaultFalse "ignore_failures"
1174

    
1175
pNewName :: Field
1176
pNewName =
1177
  withDoc "New group or instance name" $
1178
  simpleField "new_name" [t| NonEmptyString |]
1179

    
1180
pIgnoreOfflineNodes :: Field
1181
pIgnoreOfflineNodes =
1182
  withDoc "Whether to ignore offline nodes" $
1183
  defaultFalse "ignore_offline_nodes"
1184

    
1185
pTempHvParams :: Field
1186
pTempHvParams =
1187
  withDoc "Temporary hypervisor parameters, hypervisor-dependent" .
1188
  renameField "TempHvParams" .
1189
  defaultField [| toJSObject [] |] $
1190
  simpleField "hvparams" [t| JSObject JSValue |]
1191

    
1192
pTempBeParams :: Field
1193
pTempBeParams =
1194
  withDoc "Temporary backend parameters" .
1195
  renameField "TempBeParams" .
1196
  defaultField [| toJSObject [] |] $
1197
  simpleField "beparams" [t| JSObject JSValue |]
1198

    
1199
pNoRemember :: Field
1200
pNoRemember =
1201
  withDoc "Do not remember instance state changes" $
1202
  defaultFalse "no_remember"
1203

    
1204
pStartupPaused :: Field
1205
pStartupPaused =
1206
  withDoc "Pause instance at startup" $
1207
  defaultFalse "startup_paused"
1208

    
1209
pIgnoreSecondaries :: Field
1210
pIgnoreSecondaries =
1211
  withDoc "Whether to start the instance even if secondary disks are failing" $
1212
  defaultFalse "ignore_secondaries"
1213

    
1214
pRebootType :: Field
1215
pRebootType =
1216
  withDoc "How to reboot the instance" $
1217
  simpleField "reboot_type" [t| RebootType |]
1218

    
1219
pReplaceDisksMode :: Field
1220
pReplaceDisksMode =
1221
  withDoc "Replacement mode" .
1222
  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1223

    
1224
pReplaceDisksList :: Field
1225
pReplaceDisksList =
1226
  withDoc "List of disk indices" .
1227
  renameField "ReplaceDisksList" .
1228
  defaultField [| [] |] $
1229
  simpleField "disks" [t| [DiskIndex] |]
1230

    
1231
pMigrationCleanup :: Field
1232
pMigrationCleanup =
1233
  withDoc "Whether a previously failed migration should be cleaned up" .
1234
  renameField "MigrationCleanup" $ defaultFalse "cleanup"
1235

    
1236
pAllowFailover :: Field
1237
pAllowFailover =
1238
  withDoc "Whether we can fallback to failover if migration is not possible" $
1239
  defaultFalse "allow_failover"
1240

    
1241
pMoveTargetNode :: Field
1242
pMoveTargetNode =
1243
  withDoc "Target node for instance move" .
1244
  renameField "MoveTargetNode" $
1245
  simpleField "target_node" [t| NonEmptyString |]
1246

    
1247
pMoveTargetNodeUuid :: Field
1248
pMoveTargetNodeUuid =
1249
  withDoc "Target node UUID for instance move" .
1250
  renameField "MoveTargetNodeUuid" . optionalField $
1251
  simpleField "target_node_uuid" [t| NonEmptyString |]
1252

    
1253
pMoveCompress :: Field
1254
pMoveCompress =
1255
  withDoc "Compression mode to use during instance moves" .
1256
  defaultField [| None |] $
1257
  simpleField "compress" [t| ImportExportCompression |]
1258

    
1259
pBackupCompress :: Field
1260
pBackupCompress =
1261
  withDoc "Compression mode to use for moves during backups/imports" .
1262
  defaultField [| None |] $
1263
  simpleField "compress" [t| ImportExportCompression |]
1264

    
1265
pIgnoreDiskSize :: Field
1266
pIgnoreDiskSize =
1267
  withDoc "Whether to ignore recorded disk size" $
1268
  defaultFalse "ignore_size"
1269

    
1270
pWaitForSyncFalse :: Field
1271
pWaitForSyncFalse =
1272
  withDoc "Whether to wait for the disk to synchronize (defaults to false)" $
1273
  defaultField [| False |] pWaitForSync
1274

    
1275
pRecreateDisksInfo :: Field
1276
pRecreateDisksInfo =
1277
  withDoc "Disk list for recreate disks" .
1278
  renameField "RecreateDisksInfo" .
1279
  defaultField [| RecreateDisksAll |] $
1280
  simpleField "disks" [t| RecreateDisksInfo |]
1281

    
1282
pStatic :: Field
1283
pStatic =
1284
  withDoc "Whether to only return configuration data without querying nodes" $
1285
  defaultFalse "static"
1286

    
1287
pInstParamsNicChanges :: Field
1288
pInstParamsNicChanges =
1289
  withDoc "List of NIC changes" .
1290
  renameField "InstNicChanges" .
1291
  defaultField [| SetParamsEmpty |] $
1292
  simpleField "nics" [t| SetParamsMods INicParams |]
1293

    
1294
pInstParamsDiskChanges :: Field
1295
pInstParamsDiskChanges =
1296
  withDoc "List of disk changes" .
1297
  renameField "InstDiskChanges" .
1298
  defaultField [| SetParamsEmpty |] $
1299
  simpleField "disks" [t| SetParamsMods IDiskParams |]
1300

    
1301
pRuntimeMem :: Field
1302
pRuntimeMem =
1303
  withDoc "New runtime memory" .
1304
  optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1305

    
1306
pOptDiskTemplate :: Field
1307
pOptDiskTemplate =
1308
  withDoc "Instance disk template" .
1309
  optionalField .
1310
  renameField "OptDiskTemplate" $
1311
  simpleField "disk_template" [t| DiskTemplate |]
1312

    
1313
pOsNameChange :: Field
1314
pOsNameChange =
1315
  withDoc "Change the instance's OS without reinstalling the instance" $
1316
  optionalNEStringField "os_name"
1317

    
1318
pDiskIndex :: Field
1319
pDiskIndex =
1320
  withDoc "Disk index for e.g. grow disk" .
1321
  renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
1322

    
1323
pDiskChgAmount :: Field
1324
pDiskChgAmount =
1325
  withDoc "Disk amount to add or grow to" .
1326
  renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
1327

    
1328
pDiskChgAbsolute :: Field
1329
pDiskChgAbsolute =
1330
  withDoc
1331
    "Whether the amount parameter is an absolute target or a relative one" .
1332
  renameField "DiskChkAbsolute" $ defaultFalse "absolute"
1333

    
1334
pTargetGroups :: Field
1335
pTargetGroups =
1336
  withDoc
1337
    "Destination group names or UUIDs (defaults to \"all but current group\")" .
1338
  optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
1339

    
1340
pNodeGroupAllocPolicy :: Field
1341
pNodeGroupAllocPolicy =
1342
  withDoc "Instance allocation policy" .
1343
  optionalField $
1344
  simpleField "alloc_policy" [t| AllocPolicy |]
1345

    
1346
pGroupNodeParams :: Field
1347
pGroupNodeParams =
1348
  withDoc "Default node parameters for group" .
1349
  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
1350

    
1351
pExportMode :: Field
1352
pExportMode =
1353
  withDoc "Export mode" .
1354
  renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1355

    
1356
-- FIXME: Rename target_node as it changes meaning for different
1357
-- export modes (e.g. "destination")
1358
pExportTargetNode :: Field
1359
pExportTargetNode =
1360
  withDoc "Target node (depends on export mode)" .
1361
  renameField "ExportTarget" $
1362
  simpleField "target_node" [t| ExportTarget |]
1363

    
1364
pExportTargetNodeUuid :: Field
1365
pExportTargetNodeUuid =
1366
  withDoc "Target node UUID (if local export)" .
1367
  renameField "ExportTargetNodeUuid" . optionalField $
1368
  simpleField "target_node_uuid" [t| NonEmptyString |]
1369

    
1370
pShutdownInstance :: Field
1371
pShutdownInstance =
1372
  withDoc "Whether to shutdown the instance before export" $
1373
  defaultTrue "shutdown"
1374

    
1375
pRemoveInstance :: Field
1376
pRemoveInstance =
1377
  withDoc "Whether to remove instance after export" $
1378
  defaultFalse "remove_instance"
1379

    
1380
pIgnoreRemoveFailures :: Field
1381
pIgnoreRemoveFailures =
1382
  withDoc "Whether to ignore failures while removing instances" $
1383
  defaultFalse "ignore_remove_failures"
1384

    
1385
pX509KeyName :: Field
1386
pX509KeyName =
1387
  withDoc "Name of X509 key (remote export only)" .
1388
  optionalField $ simpleField "x509_key_name" [t| [JSValue] |]
1389

    
1390
pX509DestCA :: Field
1391
pX509DestCA =
1392
  withDoc "Destination X509 CA (remote export only)" $
1393
  optionalNEStringField "destination_x509_ca"
1394

    
1395
pTagsObject :: Field
1396
pTagsObject =
1397
  withDoc "Tag kind" $
1398
  simpleField "kind" [t| TagKind |]
1399

    
1400
pTagsName :: Field
1401
pTagsName =
1402
  withDoc "Name of object" .
1403
  renameField "TagsGetName" .
1404
  optionalField $ simpleField "name" [t| String |]
1405

    
1406
pTagsList :: Field
1407
pTagsList =
1408
  withDoc "List of tag names" $
1409
  simpleField "tags" [t| [String] |]
1410

    
1411
-- FIXME: this should be compiled at load time?
1412
pTagSearchPattern :: Field
1413
pTagSearchPattern =
1414
  withDoc "Search pattern (regular expression)" .
1415
  renameField "TagSearchPattern" $
1416
  simpleField "pattern" [t| NonEmptyString |]
1417

    
1418
pDelayDuration :: Field
1419
pDelayDuration =
1420
  withDoc "Duration parameter for 'OpTestDelay'" .
1421
  renameField "DelayDuration" $
1422
  simpleField "duration" [t| Double |]
1423

    
1424
pDelayOnMaster :: Field
1425
pDelayOnMaster =
1426
  withDoc "on_master field for 'OpTestDelay'" .
1427
  renameField "DelayOnMaster" $
1428
  defaultTrue "on_master"
1429

    
1430
pDelayOnNodes :: Field
1431
pDelayOnNodes =
1432
  withDoc "on_nodes field for 'OpTestDelay'" .
1433
  renameField "DelayOnNodes" .
1434
  defaultField [| [] |] $
1435
  simpleField "on_nodes" [t| [NonEmptyString] |]
1436

    
1437
pDelayOnNodeUuids :: Field
1438
pDelayOnNodeUuids =
1439
  withDoc "on_node_uuids field for 'OpTestDelay'" .
1440
  renameField "DelayOnNodeUuids" . optionalField $
1441
  simpleField "on_node_uuids" [t| [NonEmptyString] |]
1442

    
1443
pDelayRepeat :: Field
1444
pDelayRepeat =
1445
  withDoc "Repeat parameter for OpTestDelay" .
1446
  renameField "DelayRepeat" .
1447
  defaultField [| forceNonNeg (0::Int) |] $
1448
  simpleField "repeat" [t| NonNegative Int |]
1449

    
1450
pIAllocatorDirection :: Field
1451
pIAllocatorDirection =
1452
  withDoc "IAllocator test direction" .
1453
  renameField "IAllocatorDirection" $
1454
  simpleField "direction" [t| IAllocatorTestDir |]
1455

    
1456
pIAllocatorMode :: Field
1457
pIAllocatorMode =
1458
  withDoc "IAllocator test mode" .
1459
  renameField "IAllocatorMode" $
1460
  simpleField "mode" [t| IAllocatorMode |]
1461

    
1462
pIAllocatorReqName :: Field
1463
pIAllocatorReqName =
1464
  withDoc "IAllocator target name (new instance, node to evac, etc.)" .
1465
  renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
1466

    
1467
pIAllocatorNics :: Field
1468
pIAllocatorNics =
1469
  withDoc "Custom OpTestIAllocator nics" .
1470
  renameField "IAllocatorNics" .
1471
  optionalField $ simpleField "nics" [t| [INicParams] |]
1472

    
1473
pIAllocatorDisks :: Field
1474
pIAllocatorDisks =
1475
  withDoc "Custom OpTestAllocator disks" .
1476
  renameField "IAllocatorDisks" .
1477
  optionalField $ simpleField "disks" [t| [JSValue] |]
1478

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

    
1486
pIAllocatorVCpus :: Field
1487
pIAllocatorVCpus =
1488
  withDoc "IAllocator vcpus field" .
1489
  renameField "IAllocatorVCpus" .
1490
  optionalField $
1491
  simpleField "vcpus" [t| NonNegative Int |]
1492

    
1493
pIAllocatorOs :: Field
1494
pIAllocatorOs =
1495
  withDoc "IAllocator os field" .
1496
  renameField "IAllocatorOs" $ optionalNEStringField "os"
1497

    
1498
pIAllocatorInstances :: Field
1499
pIAllocatorInstances =
1500
  withDoc "IAllocator instances field" .
1501
  renameField "IAllocatorInstances " .
1502
  optionalField $
1503
  simpleField "instances" [t| [NonEmptyString] |]
1504

    
1505
pIAllocatorEvacMode :: Field
1506
pIAllocatorEvacMode =
1507
  withDoc "IAllocator evac mode" .
1508
  renameField "IAllocatorEvacMode" .
1509
  optionalField $
1510
  simpleField "evac_mode" [t| EvacMode |]
1511

    
1512
pIAllocatorSpindleUse :: Field
1513
pIAllocatorSpindleUse =
1514
  withDoc "IAllocator spindle use" .
1515
  renameField "IAllocatorSpindleUse" .
1516
  defaultField [| forceNonNeg (1::Int) |] $
1517
  simpleField "spindle_use" [t| NonNegative Int |]
1518

    
1519
pIAllocatorCount :: Field
1520
pIAllocatorCount =
1521
  withDoc "IAllocator count field" .
1522
  renameField "IAllocatorCount" .
1523
  defaultField [| forceNonNeg (1::Int) |] $
1524
  simpleField "count" [t| NonNegative Int |]
1525

    
1526
pJQueueNotifyWaitLock :: Field
1527
pJQueueNotifyWaitLock =
1528
  withDoc "'OpTestJqueue' notify_waitlock" $
1529
  defaultFalse "notify_waitlock"
1530

    
1531
pJQueueNotifyExec :: Field
1532
pJQueueNotifyExec =
1533
  withDoc "'OpTestJQueue' notify_exec" $
1534
  defaultFalse "notify_exec"
1535

    
1536
pJQueueLogMessages :: Field
1537
pJQueueLogMessages =
1538
  withDoc "'OpTestJQueue' log_messages" .
1539
  defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
1540

    
1541
pJQueueFail :: Field
1542
pJQueueFail =
1543
  withDoc "'OpTestJQueue' fail attribute" .
1544
  renameField "JQueueFail" $ defaultFalse "fail"
1545

    
1546
pTestDummyResult :: Field
1547
pTestDummyResult =
1548
  withDoc "'OpTestDummy' result field" .
1549
  renameField "TestDummyResult" $ simpleField "result" [t| JSValue |]
1550

    
1551
pTestDummyMessages :: Field
1552
pTestDummyMessages =
1553
  withDoc "'OpTestDummy' messages field" .
1554
  renameField "TestDummyMessages" $
1555
  simpleField "messages" [t| JSValue |]
1556

    
1557
pTestDummyFail :: Field
1558
pTestDummyFail =
1559
  withDoc "'OpTestDummy' fail field" .
1560
  renameField "TestDummyFail" $ simpleField "fail" [t| JSValue |]
1561

    
1562
pTestDummySubmitJobs :: Field
1563
pTestDummySubmitJobs =
1564
  withDoc "'OpTestDummy' submit_jobs field" .
1565
  renameField "TestDummySubmitJobs" $
1566
  simpleField "submit_jobs" [t| JSValue |]
1567

    
1568
pNetworkName :: Field
1569
pNetworkName =
1570
  withDoc "Network name" $
1571
  simpleField "network_name" [t| NonEmptyString |]
1572

    
1573
pNetworkAddress4 :: Field
1574
pNetworkAddress4 =
1575
  withDoc "Network address (IPv4 subnet)" .
1576
  renameField "NetworkAddress4" $
1577
  simpleField "network" [t| IPv4Network |]
1578

    
1579
pNetworkGateway4 :: Field
1580
pNetworkGateway4 =
1581
  withDoc "Network gateway (IPv4 address)" .
1582
  renameField "NetworkGateway4" .
1583
  optionalField $ simpleField "gateway" [t| IPv4Address |]
1584

    
1585
pNetworkAddress6 :: Field
1586
pNetworkAddress6 =
1587
  withDoc "Network address (IPv6 subnet)" .
1588
  renameField "NetworkAddress6" .
1589
  optionalField $ simpleField "network6" [t| IPv6Network |]
1590

    
1591
pNetworkGateway6 :: Field
1592
pNetworkGateway6 =
1593
  withDoc "Network gateway (IPv6 address)" .
1594
  renameField "NetworkGateway6" .
1595
  optionalField $ simpleField "gateway6" [t| IPv6Address |]
1596

    
1597
pNetworkMacPrefix :: Field
1598
pNetworkMacPrefix =
1599
  withDoc "Network specific mac prefix (that overrides the cluster one)" .
1600
  renameField "NetMacPrefix" $
1601
  optionalNEStringField "mac_prefix"
1602

    
1603
pNetworkAddRsvdIps :: Field
1604
pNetworkAddRsvdIps =
1605
  withDoc "Which IP addresses to reserve" .
1606
  renameField "NetworkAddRsvdIps" .
1607
  optionalField $
1608
  simpleField "add_reserved_ips" [t| [IPv4Address] |]
1609

    
1610
pNetworkRemoveRsvdIps :: Field
1611
pNetworkRemoveRsvdIps =
1612
  withDoc "Which external IP addresses to release" .
1613
  renameField "NetworkRemoveRsvdIps" .
1614
  optionalField $
1615
  simpleField "remove_reserved_ips" [t| [IPv4Address] |]
1616

    
1617
pNetworkMode :: Field
1618
pNetworkMode =
1619
  withDoc "Network mode when connecting to a group" $
1620
  simpleField "network_mode" [t| NICMode |]
1621

    
1622
pNetworkLink :: Field
1623
pNetworkLink =
1624
  withDoc "Network link when connecting to a group" $
1625
  simpleField "network_link" [t| NonEmptyString |]