Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ 96ed3a3e

History | View | Annotate | Download (45.2 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
  , pStartupPaused
87
  , pVerbose
88
  , pDebugSimulateErrors
89
  , pErrorCodes
90
  , pSkipChecks
91
  , pIgnoreErrors
92
  , pOptGroupName
93
  , pDiskParams
94
  , pHvState
95
  , pDiskState
96
  , pIgnoreIpolicy
97
  , pHotplug
98
  , pHotplugIfPossible
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
-- | Whether to hotplug device.
517
pHotplug :: Field
518
pHotplug = defaultFalse "hotplug"
519

    
520
pHotplugIfPossible :: Field
521
pHotplugIfPossible = defaultFalse "hotplug_if_possible"
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
pIgnoreDiskSize :: Field
1254
pIgnoreDiskSize =
1255
  withDoc "Whether to ignore recorded disk size" $
1256
  defaultFalse "ignore_size"
1257
  
1258
pWaitForSyncFalse :: Field
1259
pWaitForSyncFalse =
1260
  withDoc "Whether to wait for the disk to synchronize (defaults to false)" $
1261
  defaultField [| False |] pWaitForSync
1262
  
1263
pRecreateDisksInfo :: Field
1264
pRecreateDisksInfo =
1265
  withDoc "Disk list for recreate disks" .
1266
  renameField "RecreateDisksInfo" .
1267
  defaultField [| RecreateDisksAll |] $
1268
  simpleField "disks" [t| RecreateDisksInfo |]
1269

    
1270
pStatic :: Field
1271
pStatic =
1272
  withDoc "Whether to only return configuration data without querying nodes" $
1273
  defaultFalse "static"
1274

    
1275
pInstParamsNicChanges :: Field
1276
pInstParamsNicChanges =
1277
  withDoc "List of NIC changes" .
1278
  renameField "InstNicChanges" .
1279
  defaultField [| SetParamsEmpty |] $
1280
  simpleField "nics" [t| SetParamsMods INicParams |]
1281

    
1282
pInstParamsDiskChanges :: Field
1283
pInstParamsDiskChanges =
1284
  withDoc "List of disk changes" .
1285
  renameField "InstDiskChanges" .
1286
  defaultField [| SetParamsEmpty |] $
1287
  simpleField "disks" [t| SetParamsMods IDiskParams |]
1288

    
1289
pRuntimeMem :: Field
1290
pRuntimeMem =
1291
  withDoc "New runtime memory" .
1292
  optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1293

    
1294
pOptDiskTemplate :: Field
1295
pOptDiskTemplate =
1296
  withDoc "Instance disk template" .
1297
  optionalField .
1298
  renameField "OptDiskTemplate" $
1299
  simpleField "disk_template" [t| DiskTemplate |]
1300

    
1301
pOsNameChange :: Field
1302
pOsNameChange =
1303
  withDoc "Change the instance's OS without reinstalling the instance" $
1304
  optionalNEStringField "os_name"
1305

    
1306
pDiskIndex :: Field
1307
pDiskIndex =
1308
  withDoc "Disk index for e.g. grow disk" .
1309
  renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
1310

    
1311
pDiskChgAmount :: Field
1312
pDiskChgAmount =
1313
  withDoc "Disk amount to add or grow to" .
1314
  renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
1315

    
1316
pDiskChgAbsolute :: Field
1317
pDiskChgAbsolute =
1318
  withDoc
1319
    "Whether the amount parameter is an absolute target or a relative one" .
1320
  renameField "DiskChkAbsolute" $ defaultFalse "absolute"
1321

    
1322
pTargetGroups :: Field
1323
pTargetGroups =
1324
  withDoc
1325
    "Destination group names or UUIDs (defaults to \"all but current group\")" .
1326
  optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
1327

    
1328
pNodeGroupAllocPolicy :: Field
1329
pNodeGroupAllocPolicy =
1330
  withDoc "Instance allocation policy" .
1331
  optionalField $
1332
  simpleField "alloc_policy" [t| AllocPolicy |]
1333

    
1334
pGroupNodeParams :: Field
1335
pGroupNodeParams =
1336
  withDoc "Default node parameters for group" .
1337
  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
1338

    
1339
pExportMode :: Field
1340
pExportMode =
1341
  withDoc "Export mode" .
1342
  renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1343

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

    
1352
pExportTargetNodeUuid :: Field
1353
pExportTargetNodeUuid =
1354
  withDoc "Target node UUID (if local export)" .
1355
  renameField "ExportTargetNodeUuid" . optionalField $
1356
  simpleField "target_node_uuid" [t| NonEmptyString |]
1357

    
1358
pShutdownInstance :: Field
1359
pShutdownInstance =
1360
  withDoc "Whether to shutdown the instance before export" $
1361
  defaultTrue "shutdown"
1362

    
1363
pRemoveInstance :: Field
1364
pRemoveInstance =
1365
  withDoc "Whether to remove instance after export" $
1366
  defaultFalse "remove_instance"
1367

    
1368
pIgnoreRemoveFailures :: Field
1369
pIgnoreRemoveFailures =
1370
  withDoc "Whether to ignore failures while removing instances" $
1371
  defaultFalse "ignore_remove_failures"
1372

    
1373
pX509KeyName :: Field
1374
pX509KeyName =
1375
  withDoc "Name of X509 key (remote export only)" .
1376
  optionalField $ simpleField "x509_key_name" [t| [JSValue] |]
1377

    
1378
pX509DestCA :: Field
1379
pX509DestCA =
1380
  withDoc "Destination X509 CA (remote export only)" $
1381
  optionalNEStringField "destination_x509_ca"
1382

    
1383
pTagsObject :: Field
1384
pTagsObject =
1385
  withDoc "Tag kind" $
1386
  simpleField "kind" [t| TagKind |]
1387

    
1388
pTagsName :: Field
1389
pTagsName =
1390
  withDoc "Name of object" .
1391
  renameField "TagsGetName" .
1392
  optionalField $ simpleField "name" [t| String |]
1393

    
1394
pTagsList :: Field
1395
pTagsList =
1396
  withDoc "List of tag names" $
1397
  simpleField "tags" [t| [String] |]
1398

    
1399
-- FIXME: this should be compiled at load time?
1400
pTagSearchPattern :: Field
1401
pTagSearchPattern =
1402
  withDoc "Search pattern (regular expression)" .
1403
  renameField "TagSearchPattern" $
1404
  simpleField "pattern" [t| NonEmptyString |]
1405

    
1406
pDelayDuration :: Field
1407
pDelayDuration =
1408
  withDoc "Duration parameter for 'OpTestDelay'" .
1409
  renameField "DelayDuration" $
1410
  simpleField "duration" [t| Double |]
1411

    
1412
pDelayOnMaster :: Field
1413
pDelayOnMaster =
1414
  withDoc "on_master field for 'OpTestDelay'" .
1415
  renameField "DelayOnMaster" $
1416
  defaultTrue "on_master"
1417

    
1418
pDelayOnNodes :: Field
1419
pDelayOnNodes =
1420
  withDoc "on_nodes field for 'OpTestDelay'" .
1421
  renameField "DelayOnNodes" .
1422
  defaultField [| [] |] $
1423
  simpleField "on_nodes" [t| [NonEmptyString] |]
1424

    
1425
pDelayOnNodeUuids :: Field
1426
pDelayOnNodeUuids =
1427
  withDoc "on_node_uuids field for 'OpTestDelay'" .
1428
  renameField "DelayOnNodeUuids" . optionalField $
1429
  simpleField "on_node_uuids" [t| [NonEmptyString] |]
1430

    
1431
pDelayRepeat :: Field
1432
pDelayRepeat =
1433
  withDoc "Repeat parameter for OpTestDelay" .
1434
  renameField "DelayRepeat" .
1435
  defaultField [| forceNonNeg (0::Int) |] $
1436
  simpleField "repeat" [t| NonNegative Int |]
1437

    
1438
pIAllocatorDirection :: Field
1439
pIAllocatorDirection =
1440
  withDoc "IAllocator test direction" .
1441
  renameField "IAllocatorDirection" $
1442
  simpleField "direction" [t| IAllocatorTestDir |]
1443

    
1444
pIAllocatorMode :: Field
1445
pIAllocatorMode =
1446
  withDoc "IAllocator test mode" .
1447
  renameField "IAllocatorMode" $
1448
  simpleField "mode" [t| IAllocatorMode |]
1449

    
1450
pIAllocatorReqName :: Field
1451
pIAllocatorReqName =
1452
  withDoc "IAllocator target name (new instance, node to evac, etc.)" .
1453
  renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
1454

    
1455
pIAllocatorNics :: Field
1456
pIAllocatorNics =
1457
  withDoc "Custom OpTestIAllocator nics" .
1458
  renameField "IAllocatorNics" .
1459
  optionalField $ simpleField "nics" [t| [INicParams] |]
1460

    
1461
pIAllocatorDisks :: Field
1462
pIAllocatorDisks =
1463
  withDoc "Custom OpTestAllocator disks" .
1464
  renameField "IAllocatorDisks" .
1465
  optionalField $ simpleField "disks" [t| [JSValue] |]
1466

    
1467
pIAllocatorMemory :: Field
1468
pIAllocatorMemory =
1469
  withDoc "IAllocator memory field" .
1470
  renameField "IAllocatorMem" .
1471
  optionalField $
1472
  simpleField "memory" [t| NonNegative Int |]
1473

    
1474
pIAllocatorVCpus :: Field
1475
pIAllocatorVCpus =
1476
  withDoc "IAllocator vcpus field" .
1477
  renameField "IAllocatorVCpus" .
1478
  optionalField $
1479
  simpleField "vcpus" [t| NonNegative Int |]
1480

    
1481
pIAllocatorOs :: Field
1482
pIAllocatorOs =
1483
  withDoc "IAllocator os field" .
1484
  renameField "IAllocatorOs" $ optionalNEStringField "os"
1485

    
1486
pIAllocatorInstances :: Field
1487
pIAllocatorInstances =
1488
  withDoc "IAllocator instances field" .
1489
  renameField "IAllocatorInstances " .
1490
  optionalField $
1491
  simpleField "instances" [t| [NonEmptyString] |]
1492

    
1493
pIAllocatorEvacMode :: Field
1494
pIAllocatorEvacMode =
1495
  withDoc "IAllocator evac mode" .
1496
  renameField "IAllocatorEvacMode" .
1497
  optionalField $
1498
  simpleField "evac_mode" [t| EvacMode |]
1499

    
1500
pIAllocatorSpindleUse :: Field
1501
pIAllocatorSpindleUse =
1502
  withDoc "IAllocator spindle use" .
1503
  renameField "IAllocatorSpindleUse" .
1504
  defaultField [| forceNonNeg (1::Int) |] $
1505
  simpleField "spindle_use" [t| NonNegative Int |]
1506

    
1507
pIAllocatorCount :: Field
1508
pIAllocatorCount =
1509
  withDoc "IAllocator count field" .
1510
  renameField "IAllocatorCount" .
1511
  defaultField [| forceNonNeg (1::Int) |] $
1512
  simpleField "count" [t| NonNegative Int |]
1513

    
1514
pJQueueNotifyWaitLock :: Field
1515
pJQueueNotifyWaitLock =
1516
  withDoc "'OpTestJqueue' notify_waitlock" $
1517
  defaultFalse "notify_waitlock"
1518

    
1519
pJQueueNotifyExec :: Field
1520
pJQueueNotifyExec =
1521
  withDoc "'OpTestJQueue' notify_exec" $
1522
  defaultFalse "notify_exec"
1523

    
1524
pJQueueLogMessages :: Field
1525
pJQueueLogMessages =
1526
  withDoc "'OpTestJQueue' log_messages" .
1527
  defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
1528

    
1529
pJQueueFail :: Field
1530
pJQueueFail =
1531
  withDoc "'OpTestJQueue' fail attribute" .
1532
  renameField "JQueueFail" $ defaultFalse "fail"
1533

    
1534
pTestDummyResult :: Field
1535
pTestDummyResult =
1536
  withDoc "'OpTestDummy' result field" .
1537
  renameField "TestDummyResult" $ simpleField "result" [t| JSValue |]
1538

    
1539
pTestDummyMessages :: Field
1540
pTestDummyMessages =
1541
  withDoc "'OpTestDummy' messages field" .
1542
  renameField "TestDummyMessages" $
1543
  simpleField "messages" [t| JSValue |]
1544

    
1545
pTestDummyFail :: Field
1546
pTestDummyFail =
1547
  withDoc "'OpTestDummy' fail field" .
1548
  renameField "TestDummyFail" $ simpleField "fail" [t| JSValue |]
1549

    
1550
pTestDummySubmitJobs :: Field
1551
pTestDummySubmitJobs =
1552
  withDoc "'OpTestDummy' submit_jobs field" .
1553
  renameField "TestDummySubmitJobs" $
1554
  simpleField "submit_jobs" [t| JSValue |]
1555

    
1556
pNetworkName :: Field
1557
pNetworkName =
1558
  withDoc "Network name" $
1559
  simpleField "network_name" [t| NonEmptyString |]
1560

    
1561
pNetworkAddress4 :: Field
1562
pNetworkAddress4 =
1563
  withDoc "Network address (IPv4 subnet)" .
1564
  renameField "NetworkAddress4" $
1565
  simpleField "network" [t| IPv4Network |]
1566

    
1567
pNetworkGateway4 :: Field
1568
pNetworkGateway4 =
1569
  withDoc "Network gateway (IPv4 address)" .
1570
  renameField "NetworkGateway4" .
1571
  optionalField $ simpleField "gateway" [t| IPv4Address |]
1572

    
1573
pNetworkAddress6 :: Field
1574
pNetworkAddress6 =
1575
  withDoc "Network address (IPv6 subnet)" .
1576
  renameField "NetworkAddress6" .
1577
  optionalField $ simpleField "network6" [t| IPv6Network |]
1578

    
1579
pNetworkGateway6 :: Field
1580
pNetworkGateway6 =
1581
  withDoc "Network gateway (IPv6 address)" .
1582
  renameField "NetworkGateway6" .
1583
  optionalField $ simpleField "gateway6" [t| IPv6Address |]
1584

    
1585
pNetworkMacPrefix :: Field
1586
pNetworkMacPrefix =
1587
  withDoc "Network specific mac prefix (that overrides the cluster one)" .
1588
  renameField "NetMacPrefix" $
1589
  optionalNEStringField "mac_prefix"
1590

    
1591
pNetworkAddRsvdIps :: Field
1592
pNetworkAddRsvdIps =
1593
  withDoc "Which IP addresses to reserve" .
1594
  renameField "NetworkAddRsvdIps" .
1595
  optionalField $
1596
  simpleField "add_reserved_ips" [t| [IPv4Address] |]
1597

    
1598
pNetworkRemoveRsvdIps :: Field
1599
pNetworkRemoveRsvdIps =
1600
  withDoc "Which external IP addresses to release" .
1601
  renameField "NetworkRemoveRsvdIps" .
1602
  optionalField $
1603
  simpleField "remove_reserved_ips" [t| [IPv4Address] |]
1604

    
1605
pNetworkMode :: Field
1606
pNetworkMode =
1607
  withDoc "Network mode when connecting to a group" $
1608
  simpleField "network_mode" [t| NICMode |]
1609

    
1610
pNetworkLink :: Field
1611
pNetworkLink =
1612
  withDoc "Network link when connecting to a group" $
1613
  simpleField "network_link" [t| NonEmptyString |]