Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ 07e68848

History | View | Annotate | Download (45.1 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
  , pAllowRuntimeChgs
99
  , pInstDisks
100
  , pDiskTemplate
101
  , pOptDiskTemplate
102
  , pFileDriver
103
  , pFileStorageDir
104
  , pClusterFileStorageDir
105
  , pClusterSharedFileStorageDir
106
  , pVgName
107
  , pEnabledHypervisors
108
  , pHypervisor
109
  , pClusterHvParams
110
  , pInstHvParams
111
  , pClusterBeParams
112
  , pInstBeParams
113
  , pResetDefaults
114
  , pOsHvp
115
  , pClusterOsParams
116
  , pInstOsParams
117
  , pCandidatePoolSize
118
  , pUidPool
119
  , pAddUids
120
  , pRemoveUids
121
  , pMaintainNodeHealth
122
  , pModifyEtcHosts
123
  , pPreallocWipeDisks
124
  , pNicParams
125
  , pInstNics
126
  , pNdParams
127
  , pIpolicy
128
  , pDrbdHelper
129
  , pDefaultIAllocator
130
  , pMasterNetdev
131
  , pMasterNetmask
132
  , pReservedLvs
133
  , pHiddenOs
134
  , pBlacklistedOs
135
  , pUseExternalMipScript
136
  , pQueryFields
137
  , pQueryFilter
138
  , pQueryFieldsFields
139
  , pOobCommand
140
  , pOobTimeout
141
  , pIgnoreStatus
142
  , pPowerDelay
143
  , pPrimaryIp
144
  , pSecondaryIp
145
  , pReadd
146
  , pNodeGroup
147
  , pMasterCapable
148
  , pVmCapable
149
  , pNames
150
  , pNodes
151
  , pRequiredNodes
152
  , pRequiredNodeUuids
153
  , pStorageType
154
  , pStorageTypeOptional
155
  , pStorageChanges
156
  , pMasterCandidate
157
  , pOffline
158
  , pDrained
159
  , pAutoPromote
160
  , pPowered
161
  , pIallocator
162
  , pRemoteNode
163
  , pRemoteNodeUuid
164
  , pEvacMode
165
  , pInstCreateMode
166
  , pNoInstall
167
  , pInstOs
168
  , pPrimaryNode
169
  , pPrimaryNodeUuid
170
  , pSecondaryNode
171
  , pSecondaryNodeUuid
172
  , pSourceHandshake
173
  , pSourceInstance
174
  , pSourceShutdownTimeout
175
  , pSourceX509Ca
176
  , pSrcNode
177
  , pSrcNodeUuid
178
  , pSrcPath
179
  , pStartInstance
180
  , pInstTags
181
  , pMultiAllocInstances
182
  , pTempOsParams
183
  , pTempHvParams
184
  , pTempBeParams
185
  , pIgnoreFailures
186
  , pNewName
187
  , pIgnoreSecondaries
188
  , pRebootType
189
  , pIgnoreDiskSize
190
  , pRecreateDisksInfo
191
  , pStatic
192
  , pInstParamsNicChanges
193
  , pInstParamsDiskChanges
194
  , pRuntimeMem
195
  , pOsNameChange
196
  , pDiskIndex
197
  , pDiskChgAmount
198
  , pDiskChgAbsolute
199
  , pTargetGroups
200
  , pExportMode
201
  , pExportTargetNode
202
  , pExportTargetNodeUuid
203
  , pRemoveInstance
204
  , pIgnoreRemoveFailures
205
  , pX509KeyName
206
  , pX509DestCA
207
  , pTagSearchPattern
208
  , pRestrictedCommand
209
  , pReplaceDisksMode
210
  , pReplaceDisksList
211
  , pAllowFailover
212
  , pDelayDuration
213
  , pDelayOnMaster
214
  , pDelayOnNodes
215
  , pDelayOnNodeUuids
216
  , pDelayRepeat
217
  , pIAllocatorDirection
218
  , pIAllocatorMode
219
  , pIAllocatorReqName
220
  , pIAllocatorNics
221
  , pIAllocatorDisks
222
  , pIAllocatorMemory
223
  , pIAllocatorVCpus
224
  , pIAllocatorOs
225
  , pIAllocatorInstances
226
  , pIAllocatorEvacMode
227
  , pIAllocatorSpindleUse
228
  , pIAllocatorCount
229
  , pJQueueNotifyWaitLock
230
  , pJQueueNotifyExec
231
  , pJQueueLogMessages
232
  , pJQueueFail
233
  , pTestDummyResult
234
  , pTestDummyMessages
235
  , pTestDummyFail
236
  , pTestDummySubmitJobs
237
  , pNetworkName
238
  , pNetworkAddress4
239
  , pNetworkGateway4
240
  , pNetworkAddress6
241
  , pNetworkGateway6
242
  , pNetworkMacPrefix
243
  , pNetworkAddRsvdIps
244
  , pNetworkRemoveRsvdIps
245
  , pNetworkMode
246
  , pNetworkLink
247
  , pDryRun
248
  , pDebugLevel
249
  , pOpPriority
250
  , pDependencies
251
  , pComment
252
  , pReason
253
  , pEnabledDiskTemplates
254
  ) where
255

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

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

    
269
-- * Helper functions and types
270

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

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

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

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

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

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

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

    
304
-- ** Disks
305

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

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

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

    
322
-- ** I* param types
323

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
441
-- * Common opcode parameters
442

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

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

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

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

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

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

    
475
-- * Parameters
476

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

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

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

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

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

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

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

    
515
-- | Whether to hotplug device.
516
pHotplug :: Field
517
pHotplug = defaultFalse "hotplug"
518

    
519
pInstances :: Field
520
pInstances =
521
  withDoc "List of instances" .
522
  defaultField [| [] |] $
523
  simpleField "instances" [t| [NonEmptyString] |]
524

    
525
pOutputFields :: Field
526
pOutputFields =
527
  withDoc "Selected output fields" $
528
  simpleField "output_fields" [t| [NonEmptyString] |]
529

    
530
pName :: Field
531
pName =
532
  withDoc "A generic name" $
533
  simpleField "name" [t| NonEmptyString |]
534

    
535
pForce :: Field
536
pForce =
537
  withDoc "Whether to force the operation" $
538
  defaultFalse "force"
539

    
540
pHvState :: Field
541
pHvState =
542
  withDoc "Set hypervisor states" .
543
  optionalField $ simpleField "hv_state" [t| JSObject JSValue |]
544

    
545
pDiskState :: Field
546
pDiskState =
547
  withDoc "Set disk states" .
548
  optionalField $ simpleField "disk_state" [t| JSObject JSValue |]
549

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

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

    
562
-- | Volume group name.
563
pVgName :: Field
564
pVgName =
565
  withDoc "Volume group name" $
566
  optionalStringField "vg_name"
567

    
568
pEnabledHypervisors :: Field
569
pEnabledHypervisors =
570
  withDoc "List of enabled hypervisors" .
571
  optionalField $
572
  simpleField "enabled_hypervisors" [t| [Hypervisor] |]
573

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

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

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

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

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

    
607
pCandidatePoolSize :: Field
608
pCandidatePoolSize =
609
  withDoc "Master candidate pool size" .
610
  optionalField $ simpleField "candidate_pool_size" [t| Positive Int |]
611

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

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

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

    
630
pMaintainNodeHealth :: Field
631
pMaintainNodeHealth =
632
  withDoc "Whether to automatically maintain node health" .
633
  optionalField $ booleanField "maintain_node_health"
634

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

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

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

    
650
pIpolicy :: Field
651
pIpolicy =
652
  withDoc "Ipolicy specs" .
653
  optionalField $ simpleField "ipolicy" [t| JSObject JSValue |]
654

    
655
pDrbdHelper :: Field
656
pDrbdHelper =
657
  withDoc "DRBD helper program" $
658
  optionalStringField "drbd_helper"
659

    
660
pDefaultIAllocator :: Field
661
pDefaultIAllocator =
662
  withDoc "Default iallocator for cluster" $
663
  optionalStringField "default_iallocator"
664

    
665
pMasterNetdev :: Field
666
pMasterNetdev =
667
  withDoc "Master network device" $
668
  optionalStringField "master_netdev"
669

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

    
675
pReservedLvs :: Field
676
pReservedLvs =
677
  withDoc "List of reserved LVs" .
678
  optionalField $ simpleField "reserved_lvs" [t| [NonEmptyString] |]
679

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

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

    
695
pUseExternalMipScript :: Field
696
pUseExternalMipScript =
697
  withDoc "Whether to use an external master IP address setup script" .
698
  optionalField $ booleanField "use_external_mip_script"
699

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

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

    
711
pUseLocking :: Field
712
pUseLocking =
713
  withDoc "Whether to use synchronization" $
714
  defaultFalse "use_locking"
715

    
716
pQueryFields :: Field
717
pQueryFields =
718
  withDoc "Requested fields" $
719
  simpleField "fields" [t| [NonEmptyString] |]
720

    
721
pQueryFilter :: Field
722
pQueryFilter =
723
  withDoc "Query filter" .
724
  optionalField $ simpleField "qfilter" [t| [JSValue] |]
725

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

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

    
737
pNodeUuids :: Field
738
pNodeUuids =
739
  withDoc "List of node UUIDs" .
740
  optionalField $ simpleField "node_uuids" [t| [NonEmptyString] |]
741

    
742
pOobCommand :: Field
743
pOobCommand =
744
  withDoc "OOB command to run" $
745
  simpleField "command" [t| OobCommand |]
746

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

    
753
pIgnoreStatus :: Field
754
pIgnoreStatus =
755
  withDoc "Ignores the node offline status for power off" $
756
  defaultFalse "ignore_status"
757

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

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

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

    
778
pRestrictedCommand :: Field
779
pRestrictedCommand =
780
  withDoc "Restricted command name" .
781
  renameField "RestrictedCommand" $
782
  simpleField "command" [t| NonEmptyString |]
783

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

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

    
794
pPrimaryIp :: Field
795
pPrimaryIp =
796
  withDoc "Primary IP address" .
797
  optionalField $
798
  simpleField "primary_ip" [t| NonEmptyString |]
799

    
800
pSecondaryIp :: Field
801
pSecondaryIp =
802
  withDoc "Secondary IP address" $
803
  optionalNEStringField "secondary_ip"
804

    
805
pReadd :: Field
806
pReadd =
807
  withDoc "Whether node is re-added to cluster" $
808
  defaultFalse "readd"
809

    
810
pNodeGroup :: Field
811
pNodeGroup =
812
  withDoc "Initial node group" $
813
  optionalNEStringField "group"
814

    
815
pMasterCapable :: Field
816
pMasterCapable =
817
  withDoc "Whether node can become master or master candidate" .
818
  optionalField $ booleanField "master_capable"
819

    
820
pVmCapable :: Field
821
pVmCapable =
822
  withDoc "Whether node can host instances" .
823
  optionalField $ booleanField "vm_capable"
824

    
825
pNdParams :: Field
826
pNdParams =
827
  withDoc "Node parameters" .
828
  renameField "genericNdParams" .
829
  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
830
  
831
pNames :: Field
832
pNames =
833
  withDoc "List of names" .
834
  defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
835

    
836
pNodes :: Field
837
pNodes =
838
  withDoc "List of nodes" .
839
  defaultField [| [] |] $ simpleField "nodes" [t| [NonEmptyString] |]
840

    
841
pStorageType :: Field
842
pStorageType =
843
  withDoc "Storage type" $ simpleField "storage_type" [t| StorageType |]
844

    
845
pStorageTypeOptional :: Field
846
pStorageTypeOptional =
847
  withDoc "Storage type" .
848
  renameField "StorageTypeOptional" .
849
  optionalField $ simpleField "storage_type" [t| StorageType |]
850

    
851
pStorageName :: Field
852
pStorageName =
853
  withDoc "Storage name" .
854
  renameField "StorageName" .
855
  optionalField $ simpleField "name" [t| NonEmptyString |]
856

    
857
pStorageChanges :: Field
858
pStorageChanges =
859
  withDoc "Requested storage changes" $
860
  simpleField "changes" [t| JSObject JSValue |]
861

    
862
pIgnoreConsistency :: Field
863
pIgnoreConsistency =
864
  withDoc "Whether to ignore disk consistency" $
865
  defaultFalse "ignore_consistency"
866

    
867
pMasterCandidate :: Field
868
pMasterCandidate =
869
  withDoc "Whether the node should become a master candidate" .
870
  optionalField $ booleanField "master_candidate"
871

    
872
pOffline :: Field
873
pOffline =
874
  withDoc "Whether to mark the node or instance offline" .
875
  optionalField $ booleanField "offline"
876

    
877
pDrained ::Field
878
pDrained =
879
  withDoc "Whether to mark the node as drained" .
880
  optionalField $ booleanField "drained"
881

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

    
888
pPowered :: Field
889
pPowered =
890
  withDoc "Whether the node should be marked as powered" .
891
  optionalField $ booleanField "powered"
892

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

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

    
905
pMigrationTargetNode :: Field
906
pMigrationTargetNode =
907
  withDoc "Target node for instance migration/failover" $
908
  optionalNEStringField "target_node"
909

    
910
pMigrationTargetNodeUuid :: Field
911
pMigrationTargetNodeUuid =
912
  withDoc "Target node UUID for instance migration/failover" $
913
  optionalNEStringField "target_node_uuid"
914

    
915
pAllowRuntimeChgs :: Field
916
pAllowRuntimeChgs =
917
  withDoc "Whether to allow runtime changes while migrating" $
918
  defaultTrue "allow_runtime_changes"
919

    
920
pIgnoreIpolicy :: Field
921
pIgnoreIpolicy =
922
  withDoc "Whether to ignore ipolicy violations" $
923
  defaultFalse "ignore_ipolicy"
924
  
925
pIallocator :: Field
926
pIallocator =
927
  withDoc "Iallocator for deciding the target node for shared-storage\
928
          \ instances" $
929
  optionalNEStringField "iallocator"
930

    
931
pEarlyRelease :: Field
932
pEarlyRelease =
933
  withDoc "Whether to release locks as soon as possible" $
934
  defaultFalse "early_release"
935

    
936
pRemoteNode :: Field
937
pRemoteNode =
938
  withDoc "New secondary node" $
939
  optionalNEStringField "remote_node"
940

    
941
pRemoteNodeUuid :: Field
942
pRemoteNodeUuid =
943
  withDoc "New secondary node UUID" $
944
  optionalNEStringField "remote_node_uuid"
945

    
946
pEvacMode :: Field
947
pEvacMode =
948
  withDoc "Node evacuation mode" .
949
  renameField "EvacMode" $ simpleField "mode" [t| EvacMode |]
950

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

    
956
pForceVariant :: Field
957
pForceVariant =
958
  withDoc "Whether to force an unknown OS variant" $
959
  defaultFalse "force_variant"
960

    
961
pWaitForSync :: Field
962
pWaitForSync =
963
  withDoc "Whether to wait for the disk to synchronize" $
964
  defaultTrue "wait_for_sync"
965

    
966
pNameCheck :: Field
967
pNameCheck =
968
  withDoc "Whether to check name" $
969
  defaultTrue "name_check"
970

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

    
978
pInstDisks :: Field
979
pInstDisks =
980
  withDoc "List of instance disks" .
981
  renameField "instDisks" $ simpleField "disks" [t| [IDiskParams] |]
982

    
983
pDiskTemplate :: Field
984
pDiskTemplate =
985
  withDoc "Disk template" $
986
  simpleField "disk_template" [t| DiskTemplate |]
987

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

    
993
pFileStorageDir :: Field
994
pFileStorageDir =
995
  withDoc "Directory for storing file-backed disks" $
996
  optionalNEStringField "file_storage_dir"
997

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

    
1005
pHypervisor :: Field
1006
pHypervisor =
1007
  withDoc "Selected hypervisor for an instance" .
1008
  optionalField $
1009
  simpleField "hypervisor" [t| Hypervisor |]
1010

    
1011
pResetDefaults :: Field
1012
pResetDefaults =
1013
  withDoc "Reset instance parameters to default if equal" $
1014
  defaultFalse "identify_defaults"
1015

    
1016
pIpCheck :: Field
1017
pIpCheck =
1018
  withDoc "Whether to ensure instance's IP address is inactive" $
1019
  defaultTrue "ip_check"
1020

    
1021
pIpConflictsCheck :: Field
1022
pIpConflictsCheck =
1023
  withDoc "Whether to check for conflicting IP addresses" $
1024
  defaultTrue "conflicts_check"
1025

    
1026
pInstCreateMode :: Field
1027
pInstCreateMode =
1028
  withDoc "Instance creation mode" .
1029
  renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
1030

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

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

    
1041
pInstOs :: Field
1042
pInstOs =
1043
  withDoc "OS type for instance installation" $
1044
  optionalNEStringField "os_type"
1045

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

    
1053
pPrimaryNode :: Field
1054
pPrimaryNode =
1055
  withDoc "Primary node for an instance" $
1056
  optionalNEStringField "pnode"
1057

    
1058
pPrimaryNodeUuid :: Field
1059
pPrimaryNodeUuid =
1060
  withDoc "Primary node UUID for an instance" $
1061
  optionalNEStringField "pnode_uuid"
1062

    
1063
pSecondaryNode :: Field
1064
pSecondaryNode =
1065
  withDoc "Secondary node for an instance" $
1066
  optionalNEStringField "snode"
1067

    
1068
pSecondaryNodeUuid :: Field
1069
pSecondaryNodeUuid =
1070
  withDoc "Secondary node UUID for an instance" $
1071
  optionalNEStringField "snode_uuid"
1072

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

    
1078
pSourceInstance :: Field
1079
pSourceInstance =
1080
  withDoc "Source instance name (remote import only)" $
1081
  optionalNEStringField "source_instance_name"
1082

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

    
1091
pSourceX509Ca :: Field
1092
pSourceX509Ca =
1093
  withDoc "Source X509 CA in PEM format (remote import only)" $
1094
  optionalNEStringField "source_x509_ca"
1095

    
1096
pSrcNode :: Field
1097
pSrcNode =
1098
  withDoc "Source node for import" $
1099
  optionalNEStringField "src_node"
1100

    
1101
pSrcNodeUuid :: Field
1102
pSrcNodeUuid =
1103
  withDoc "Source node UUID for import" $
1104
  optionalNEStringField "src_node_uuid"
1105

    
1106
pSrcPath :: Field
1107
pSrcPath =
1108
  withDoc "Source directory for import" $
1109
  optionalNEStringField "src_path"
1110

    
1111
pStartInstance :: Field
1112
pStartInstance =
1113
  withDoc "Whether to start instance after creation" $
1114
  defaultTrue "start"
1115

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

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

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

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

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

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

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

    
1166
pIgnoreFailures :: Field
1167
pIgnoreFailures =
1168
  withDoc "Whether to ignore failures during removal" $
1169
  defaultFalse "ignore_failures"
1170

    
1171
pNewName :: Field
1172
pNewName =
1173
  withDoc "New group or instance name" $
1174
  simpleField "new_name" [t| NonEmptyString |]
1175
  
1176
pIgnoreOfflineNodes :: Field
1177
pIgnoreOfflineNodes =
1178
  withDoc "Whether to ignore offline nodes" $
1179
  defaultFalse "ignore_offline_nodes"
1180

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

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

    
1195
pNoRemember :: Field
1196
pNoRemember =
1197
  withDoc "Do not remember instance state changes" $
1198
  defaultFalse "no_remember"
1199

    
1200
pStartupPaused :: Field
1201
pStartupPaused =
1202
  withDoc "Pause instance at startup" $
1203
  defaultFalse "startup_paused"
1204

    
1205
pIgnoreSecondaries :: Field
1206
pIgnoreSecondaries =
1207
  withDoc "Whether to start the instance even if secondary disks are failing" $
1208
  defaultFalse "ignore_secondaries"
1209

    
1210
pRebootType :: Field
1211
pRebootType =
1212
  withDoc "How to reboot the instance" $
1213
  simpleField "reboot_type" [t| RebootType |]
1214

    
1215
pReplaceDisksMode :: Field
1216
pReplaceDisksMode =
1217
  withDoc "Replacement mode" .
1218
  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1219

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

    
1227
pMigrationCleanup :: Field
1228
pMigrationCleanup =
1229
  withDoc "Whether a previously failed migration should be cleaned up" .
1230
  renameField "MigrationCleanup" $ defaultFalse "cleanup"
1231

    
1232
pAllowFailover :: Field
1233
pAllowFailover =
1234
  withDoc "Whether we can fallback to failover if migration is not possible" $
1235
  defaultFalse "allow_failover"
1236

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

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

    
1249
pIgnoreDiskSize :: Field
1250
pIgnoreDiskSize =
1251
  withDoc "Whether to ignore recorded disk size" $
1252
  defaultFalse "ignore_size"
1253
  
1254
pWaitForSyncFalse :: Field
1255
pWaitForSyncFalse =
1256
  withDoc "Whether to wait for the disk to synchronize (defaults to false)" $
1257
  defaultField [| False |] pWaitForSync
1258
  
1259
pRecreateDisksInfo :: Field
1260
pRecreateDisksInfo =
1261
  withDoc "Disk list for recreate disks" .
1262
  renameField "RecreateDisksInfo" .
1263
  defaultField [| RecreateDisksAll |] $
1264
  simpleField "disks" [t| RecreateDisksInfo |]
1265

    
1266
pStatic :: Field
1267
pStatic =
1268
  withDoc "Whether to only return configuration data without querying nodes" $
1269
  defaultFalse "static"
1270

    
1271
pInstParamsNicChanges :: Field
1272
pInstParamsNicChanges =
1273
  withDoc "List of NIC changes" .
1274
  renameField "InstNicChanges" .
1275
  defaultField [| SetParamsEmpty |] $
1276
  simpleField "nics" [t| SetParamsMods INicParams |]
1277

    
1278
pInstParamsDiskChanges :: Field
1279
pInstParamsDiskChanges =
1280
  withDoc "List of disk changes" .
1281
  renameField "InstDiskChanges" .
1282
  defaultField [| SetParamsEmpty |] $
1283
  simpleField "disks" [t| SetParamsMods IDiskParams |]
1284

    
1285
pRuntimeMem :: Field
1286
pRuntimeMem =
1287
  withDoc "New runtime memory" .
1288
  optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1289

    
1290
pOptDiskTemplate :: Field
1291
pOptDiskTemplate =
1292
  withDoc "Instance disk template" .
1293
  optionalField .
1294
  renameField "OptDiskTemplate" $
1295
  simpleField "disk_template" [t| DiskTemplate |]
1296

    
1297
pOsNameChange :: Field
1298
pOsNameChange =
1299
  withDoc "Change the instance's OS without reinstalling the instance" $
1300
  optionalNEStringField "os_name"
1301

    
1302
pDiskIndex :: Field
1303
pDiskIndex =
1304
  withDoc "Disk index for e.g. grow disk" .
1305
  renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
1306

    
1307
pDiskChgAmount :: Field
1308
pDiskChgAmount =
1309
  withDoc "Disk amount to add or grow to" .
1310
  renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
1311

    
1312
pDiskChgAbsolute :: Field
1313
pDiskChgAbsolute =
1314
  withDoc
1315
    "Whether the amount parameter is an absolute target or a relative one" .
1316
  renameField "DiskChkAbsolute" $ defaultFalse "absolute"
1317

    
1318
pTargetGroups :: Field
1319
pTargetGroups =
1320
  withDoc
1321
    "Destination group names or UUIDs (defaults to \"all but current group\")" .
1322
  optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
1323

    
1324
pNodeGroupAllocPolicy :: Field
1325
pNodeGroupAllocPolicy =
1326
  withDoc "Instance allocation policy" .
1327
  optionalField $
1328
  simpleField "alloc_policy" [t| AllocPolicy |]
1329

    
1330
pGroupNodeParams :: Field
1331
pGroupNodeParams =
1332
  withDoc "Default node parameters for group" .
1333
  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
1334

    
1335
pExportMode :: Field
1336
pExportMode =
1337
  withDoc "Export mode" .
1338
  renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1339

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

    
1348
pExportTargetNodeUuid :: Field
1349
pExportTargetNodeUuid =
1350
  withDoc "Target node UUID (if local export)" .
1351
  renameField "ExportTargetNodeUuid" . optionalField $
1352
  simpleField "target_node_uuid" [t| NonEmptyString |]
1353

    
1354
pShutdownInstance :: Field
1355
pShutdownInstance =
1356
  withDoc "Whether to shutdown the instance before export" $
1357
  defaultTrue "shutdown"
1358

    
1359
pRemoveInstance :: Field
1360
pRemoveInstance =
1361
  withDoc "Whether to remove instance after export" $
1362
  defaultFalse "remove_instance"
1363

    
1364
pIgnoreRemoveFailures :: Field
1365
pIgnoreRemoveFailures =
1366
  withDoc "Whether to ignore failures while removing instances" $
1367
  defaultFalse "ignore_remove_failures"
1368

    
1369
pX509KeyName :: Field
1370
pX509KeyName =
1371
  withDoc "Name of X509 key (remote export only)" .
1372
  optionalField $ simpleField "x509_key_name" [t| [JSValue] |]
1373

    
1374
pX509DestCA :: Field
1375
pX509DestCA =
1376
  withDoc "Destination X509 CA (remote export only)" $
1377
  optionalNEStringField "destination_x509_ca"
1378

    
1379
pTagsObject :: Field
1380
pTagsObject =
1381
  withDoc "Tag kind" $
1382
  simpleField "kind" [t| TagKind |]
1383

    
1384
pTagsName :: Field
1385
pTagsName =
1386
  withDoc "Name of object" .
1387
  renameField "TagsGetName" .
1388
  optionalField $ simpleField "name" [t| String |]
1389

    
1390
pTagsList :: Field
1391
pTagsList =
1392
  withDoc "List of tag names" $
1393
  simpleField "tags" [t| [String] |]
1394

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

    
1402
pDelayDuration :: Field
1403
pDelayDuration =
1404
  withDoc "Duration parameter for 'OpTestDelay'" .
1405
  renameField "DelayDuration" $
1406
  simpleField "duration" [t| Double |]
1407

    
1408
pDelayOnMaster :: Field
1409
pDelayOnMaster =
1410
  withDoc "on_master field for 'OpTestDelay'" .
1411
  renameField "DelayOnMaster" $
1412
  defaultTrue "on_master"
1413

    
1414
pDelayOnNodes :: Field
1415
pDelayOnNodes =
1416
  withDoc "on_nodes field for 'OpTestDelay'" .
1417
  renameField "DelayOnNodes" .
1418
  defaultField [| [] |] $
1419
  simpleField "on_nodes" [t| [NonEmptyString] |]
1420

    
1421
pDelayOnNodeUuids :: Field
1422
pDelayOnNodeUuids =
1423
  withDoc "on_node_uuids field for 'OpTestDelay'" .
1424
  renameField "DelayOnNodeUuids" . optionalField $
1425
  simpleField "on_node_uuids" [t| [NonEmptyString] |]
1426

    
1427
pDelayRepeat :: Field
1428
pDelayRepeat =
1429
  withDoc "Repeat parameter for OpTestDelay" .
1430
  renameField "DelayRepeat" .
1431
  defaultField [| forceNonNeg (0::Int) |] $
1432
  simpleField "repeat" [t| NonNegative Int |]
1433

    
1434
pIAllocatorDirection :: Field
1435
pIAllocatorDirection =
1436
  withDoc "IAllocator test direction" .
1437
  renameField "IAllocatorDirection" $
1438
  simpleField "direction" [t| IAllocatorTestDir |]
1439

    
1440
pIAllocatorMode :: Field
1441
pIAllocatorMode =
1442
  withDoc "IAllocator test mode" .
1443
  renameField "IAllocatorMode" $
1444
  simpleField "mode" [t| IAllocatorMode |]
1445

    
1446
pIAllocatorReqName :: Field
1447
pIAllocatorReqName =
1448
  withDoc "IAllocator target name (new instance, node to evac, etc.)" .
1449
  renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
1450

    
1451
pIAllocatorNics :: Field
1452
pIAllocatorNics =
1453
  withDoc "Custom OpTestIAllocator nics" .
1454
  renameField "IAllocatorNics" .
1455
  optionalField $ simpleField "nics" [t| [INicParams] |]
1456

    
1457
pIAllocatorDisks :: Field
1458
pIAllocatorDisks =
1459
  withDoc "Custom OpTestAllocator disks" .
1460
  renameField "IAllocatorDisks" .
1461
  optionalField $ simpleField "disks" [t| [JSValue] |]
1462

    
1463
pIAllocatorMemory :: Field
1464
pIAllocatorMemory =
1465
  withDoc "IAllocator memory field" .
1466
  renameField "IAllocatorMem" .
1467
  optionalField $
1468
  simpleField "memory" [t| NonNegative Int |]
1469

    
1470
pIAllocatorVCpus :: Field
1471
pIAllocatorVCpus =
1472
  withDoc "IAllocator vcpus field" .
1473
  renameField "IAllocatorVCpus" .
1474
  optionalField $
1475
  simpleField "vcpus" [t| NonNegative Int |]
1476

    
1477
pIAllocatorOs :: Field
1478
pIAllocatorOs =
1479
  withDoc "IAllocator os field" .
1480
  renameField "IAllocatorOs" $ optionalNEStringField "os"
1481

    
1482
pIAllocatorInstances :: Field
1483
pIAllocatorInstances =
1484
  withDoc "IAllocator instances field" .
1485
  renameField "IAllocatorInstances " .
1486
  optionalField $
1487
  simpleField "instances" [t| [NonEmptyString] |]
1488

    
1489
pIAllocatorEvacMode :: Field
1490
pIAllocatorEvacMode =
1491
  withDoc "IAllocator evac mode" .
1492
  renameField "IAllocatorEvacMode" .
1493
  optionalField $
1494
  simpleField "evac_mode" [t| EvacMode |]
1495

    
1496
pIAllocatorSpindleUse :: Field
1497
pIAllocatorSpindleUse =
1498
  withDoc "IAllocator spindle use" .
1499
  renameField "IAllocatorSpindleUse" .
1500
  defaultField [| forceNonNeg (1::Int) |] $
1501
  simpleField "spindle_use" [t| NonNegative Int |]
1502

    
1503
pIAllocatorCount :: Field
1504
pIAllocatorCount =
1505
  withDoc "IAllocator count field" .
1506
  renameField "IAllocatorCount" .
1507
  defaultField [| forceNonNeg (1::Int) |] $
1508
  simpleField "count" [t| NonNegative Int |]
1509

    
1510
pJQueueNotifyWaitLock :: Field
1511
pJQueueNotifyWaitLock =
1512
  withDoc "'OpTestJqueue' notify_waitlock" $
1513
  defaultFalse "notify_waitlock"
1514

    
1515
pJQueueNotifyExec :: Field
1516
pJQueueNotifyExec =
1517
  withDoc "'OpTestJQueue' notify_exec" $
1518
  defaultFalse "notify_exec"
1519

    
1520
pJQueueLogMessages :: Field
1521
pJQueueLogMessages =
1522
  withDoc "'OpTestJQueue' log_messages" .
1523
  defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
1524

    
1525
pJQueueFail :: Field
1526
pJQueueFail =
1527
  withDoc "'OpTestJQueue' fail attribute" .
1528
  renameField "JQueueFail" $ defaultFalse "fail"
1529

    
1530
pTestDummyResult :: Field
1531
pTestDummyResult =
1532
  withDoc "'OpTestDummy' result field" .
1533
  renameField "TestDummyResult" $ simpleField "result" [t| JSValue |]
1534

    
1535
pTestDummyMessages :: Field
1536
pTestDummyMessages =
1537
  withDoc "'OpTestDummy' messages field" .
1538
  renameField "TestDummyMessages" $
1539
  simpleField "messages" [t| JSValue |]
1540

    
1541
pTestDummyFail :: Field
1542
pTestDummyFail =
1543
  withDoc "'OpTestDummy' fail field" .
1544
  renameField "TestDummyFail" $ simpleField "fail" [t| JSValue |]
1545

    
1546
pTestDummySubmitJobs :: Field
1547
pTestDummySubmitJobs =
1548
  withDoc "'OpTestDummy' submit_jobs field" .
1549
  renameField "TestDummySubmitJobs" $
1550
  simpleField "submit_jobs" [t| JSValue |]
1551

    
1552
pNetworkName :: Field
1553
pNetworkName =
1554
  withDoc "Network name" $
1555
  simpleField "network_name" [t| NonEmptyString |]
1556

    
1557
pNetworkAddress4 :: Field
1558
pNetworkAddress4 =
1559
  withDoc "Network address (IPv4 subnet)" .
1560
  renameField "NetworkAddress4" $
1561
  simpleField "network" [t| IPv4Network |]
1562

    
1563
pNetworkGateway4 :: Field
1564
pNetworkGateway4 =
1565
  withDoc "Network gateway (IPv4 address)" .
1566
  renameField "NetworkGateway4" .
1567
  optionalField $ simpleField "gateway" [t| IPv4Address |]
1568

    
1569
pNetworkAddress6 :: Field
1570
pNetworkAddress6 =
1571
  withDoc "Network address (IPv6 subnet)" .
1572
  renameField "NetworkAddress6" .
1573
  optionalField $ simpleField "network6" [t| IPv6Network |]
1574

    
1575
pNetworkGateway6 :: Field
1576
pNetworkGateway6 =
1577
  withDoc "Network gateway (IPv6 address)" .
1578
  renameField "NetworkGateway6" .
1579
  optionalField $ simpleField "gateway6" [t| IPv6Address |]
1580

    
1581
pNetworkMacPrefix :: Field
1582
pNetworkMacPrefix =
1583
  withDoc "Network specific mac prefix (that overrides the cluster one)" .
1584
  renameField "NetMacPrefix" $
1585
  optionalNEStringField "mac_prefix"
1586

    
1587
pNetworkAddRsvdIps :: Field
1588
pNetworkAddRsvdIps =
1589
  withDoc "Which IP addresses to reserve" .
1590
  renameField "NetworkAddRsvdIps" .
1591
  optionalField $
1592
  simpleField "add_reserved_ips" [t| [IPv4Address] |]
1593

    
1594
pNetworkRemoveRsvdIps :: Field
1595
pNetworkRemoveRsvdIps =
1596
  withDoc "Which external IP addresses to release" .
1597
  renameField "NetworkRemoveRsvdIps" .
1598
  optionalField $
1599
  simpleField "remove_reserved_ips" [t| [IPv4Address] |]
1600

    
1601
pNetworkMode :: Field
1602
pNetworkMode =
1603
  withDoc "Network mode when connecting to a group" $
1604
  simpleField "network_mode" [t| NICMode |]
1605

    
1606
pNetworkLink :: Field
1607
pNetworkLink =
1608
  withDoc "Network link when connecting to a group" $
1609
  simpleField "network_link" [t| NonEmptyString |]