Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ 4f90370c

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

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

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

    
268
-- * Helper functions and types
269

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

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

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

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

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

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

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

    
303
-- ** Disks
304

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

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

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

    
321
-- ** I* param types
322

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
440
-- * Common opcode parameters
441

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

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

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

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

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

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

    
474
-- * Parameters
475

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
650
pDrbdHelper :: Field
651
pDrbdHelper =
652
  withDoc "DRBD helper program" $
653
  optionalStringField "drbd_helper"
654

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

    
660
pMasterNetdev :: Field
661
pMasterNetdev =
662
  withDoc "Master network device" $
663
  optionalStringField "master_netdev"
664

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
795
pSecondaryIp :: Field
796
pSecondaryIp =
797
  withDoc "Secondary IP address" $
798
  optionalNEStringField "secondary_ip"
799

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

    
805
pNodeGroup :: Field
806
pNodeGroup =
807
  withDoc "Initial node group" $
808
  optionalNEStringField "group"
809

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

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

    
820
pNdParams :: Field
821
pNdParams =
822
  withDoc "Node parameters" .
823
  renameField "genericNdParams" .
824
  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
825
  
826
pNames :: Field
827
pNames =
828
  withDoc "List of names" .
829
  defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
830

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
915
pIgnoreIpolicy :: Field
916
pIgnoreIpolicy =
917
  withDoc "Whether to ignore ipolicy violations" $
918
  defaultFalse "ignore_ipolicy"
919
  
920
pIallocator :: Field
921
pIallocator =
922
  withDoc "Iallocator for deciding the target node for shared-storage\
923
          \ instances" $
924
  optionalNEStringField "iallocator"
925

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

    
931
pRemoteNode :: Field
932
pRemoteNode =
933
  withDoc "New secondary node" $
934
  optionalNEStringField "remote_node"
935

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
1166
pNewName :: Field
1167
pNewName =
1168
  withDoc "New group or instance name" $
1169
  simpleField "new_name" [t| NonEmptyString |]
1170
  
1171
pIgnoreOfflineNodes :: Field
1172
pIgnoreOfflineNodes =
1173
  withDoc "Whether to ignore offline nodes" $
1174
  defaultFalse "ignore_offline_nodes"
1175

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

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

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

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

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

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

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

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

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

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

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

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

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

    
1261
pStatic :: Field
1262
pStatic =
1263
  withDoc "Whether to only return configuration data without querying nodes" $
1264
  defaultFalse "static"
1265

    
1266
pInstParamsNicChanges :: Field
1267
pInstParamsNicChanges =
1268
  withDoc "List of NIC changes" .
1269
  renameField "InstNicChanges" .
1270
  defaultField [| SetParamsEmpty |] $
1271
  simpleField "nics" [t| SetParamsMods INicParams |]
1272

    
1273
pInstParamsDiskChanges :: Field
1274
pInstParamsDiskChanges =
1275
  withDoc "List of disk changes" .
1276
  renameField "InstDiskChanges" .
1277
  defaultField [| SetParamsEmpty |] $
1278
  simpleField "disks" [t| SetParamsMods IDiskParams |]
1279

    
1280
pRuntimeMem :: Field
1281
pRuntimeMem =
1282
  withDoc "New runtime memory" .
1283
  optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1284

    
1285
pOptDiskTemplate :: Field
1286
pOptDiskTemplate =
1287
  withDoc "Instance disk template" .
1288
  optionalField .
1289
  renameField "OptDiskTemplate" $
1290
  simpleField "disk_template" [t| DiskTemplate |]
1291

    
1292
pOsNameChange :: Field
1293
pOsNameChange =
1294
  withDoc "Change the instance's OS without reinstalling the instance" $
1295
  optionalNEStringField "os_name"
1296

    
1297
pDiskIndex :: Field
1298
pDiskIndex =
1299
  withDoc "Disk index for e.g. grow disk" .
1300
  renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
1301

    
1302
pDiskChgAmount :: Field
1303
pDiskChgAmount =
1304
  withDoc "Disk amount to add or grow to" .
1305
  renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
1306

    
1307
pDiskChgAbsolute :: Field
1308
pDiskChgAbsolute =
1309
  withDoc
1310
    "Whether the amount parameter is an absolute target or a relative one" .
1311
  renameField "DiskChkAbsolute" $ defaultFalse "absolute"
1312

    
1313
pTargetGroups :: Field
1314
pTargetGroups =
1315
  withDoc
1316
    "Destination group names or UUIDs (defaults to \"all but current group\")" .
1317
  optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
1318

    
1319
pNodeGroupAllocPolicy :: Field
1320
pNodeGroupAllocPolicy =
1321
  withDoc "Instance allocation policy" .
1322
  optionalField $
1323
  simpleField "alloc_policy" [t| AllocPolicy |]
1324

    
1325
pGroupNodeParams :: Field
1326
pGroupNodeParams =
1327
  withDoc "Default node parameters for group" .
1328
  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
1329

    
1330
pExportMode :: Field
1331
pExportMode =
1332
  withDoc "Export mode" .
1333
  renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1334

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

    
1343
pExportTargetNodeUuid :: Field
1344
pExportTargetNodeUuid =
1345
  withDoc "Target node UUID (if local export)" .
1346
  renameField "ExportTargetNodeUuid" . optionalField $
1347
  simpleField "target_node_uuid" [t| NonEmptyString |]
1348

    
1349
pShutdownInstance :: Field
1350
pShutdownInstance =
1351
  withDoc "Whether to shutdown the instance before export" $
1352
  defaultTrue "shutdown"
1353

    
1354
pRemoveInstance :: Field
1355
pRemoveInstance =
1356
  withDoc "Whether to remove instance after export" $
1357
  defaultFalse "remove_instance"
1358

    
1359
pIgnoreRemoveFailures :: Field
1360
pIgnoreRemoveFailures =
1361
  withDoc "Whether to ignore failures while removing instances" $
1362
  defaultFalse "ignore_remove_failures"
1363

    
1364
pX509KeyName :: Field
1365
pX509KeyName =
1366
  withDoc "Name of X509 key (remote export only)" .
1367
  optionalField $ simpleField "x509_key_name" [t| [JSValue] |]
1368

    
1369
pX509DestCA :: Field
1370
pX509DestCA =
1371
  withDoc "Destination X509 CA (remote export only)" $
1372
  optionalNEStringField "destination_x509_ca"
1373

    
1374
pTagsObject :: Field
1375
pTagsObject =
1376
  withDoc "Tag kind" $
1377
  simpleField "kind" [t| TagKind |]
1378

    
1379
pTagsName :: Field
1380
pTagsName =
1381
  withDoc "Name of object" .
1382
  renameField "TagsGetName" .
1383
  optionalField $ simpleField "name" [t| String |]
1384

    
1385
pTagsList :: Field
1386
pTagsList =
1387
  withDoc "List of tag names" $
1388
  simpleField "tags" [t| [String] |]
1389

    
1390
-- FIXME: this should be compiled at load time?
1391
pTagSearchPattern :: Field
1392
pTagSearchPattern =
1393
  withDoc "Search pattern (regular expression)" .
1394
  renameField "TagSearchPattern" $
1395
  simpleField "pattern" [t| NonEmptyString |]
1396

    
1397
pDelayDuration :: Field
1398
pDelayDuration =
1399
  withDoc "Duration parameter for 'OpTestDelay'" .
1400
  renameField "DelayDuration" $
1401
  simpleField "duration" [t| Double |]
1402

    
1403
pDelayOnMaster :: Field
1404
pDelayOnMaster =
1405
  withDoc "on_master field for 'OpTestDelay'" .
1406
  renameField "DelayOnMaster" $
1407
  defaultTrue "on_master"
1408

    
1409
pDelayOnNodes :: Field
1410
pDelayOnNodes =
1411
  withDoc "on_nodes field for 'OpTestDelay'" .
1412
  renameField "DelayOnNodes" .
1413
  defaultField [| [] |] $
1414
  simpleField "on_nodes" [t| [NonEmptyString] |]
1415

    
1416
pDelayOnNodeUuids :: Field
1417
pDelayOnNodeUuids =
1418
  withDoc "on_node_uuids field for 'OpTestDelay'" .
1419
  renameField "DelayOnNodeUuids" . optionalField $
1420
  simpleField "on_node_uuids" [t| [NonEmptyString] |]
1421

    
1422
pDelayRepeat :: Field
1423
pDelayRepeat =
1424
  withDoc "Repeat parameter for OpTestDelay" .
1425
  renameField "DelayRepeat" .
1426
  defaultField [| forceNonNeg (0::Int) |] $
1427
  simpleField "repeat" [t| NonNegative Int |]
1428

    
1429
pIAllocatorDirection :: Field
1430
pIAllocatorDirection =
1431
  withDoc "IAllocator test direction" .
1432
  renameField "IAllocatorDirection" $
1433
  simpleField "direction" [t| IAllocatorTestDir |]
1434

    
1435
pIAllocatorMode :: Field
1436
pIAllocatorMode =
1437
  withDoc "IAllocator test mode" .
1438
  renameField "IAllocatorMode" $
1439
  simpleField "mode" [t| IAllocatorMode |]
1440

    
1441
pIAllocatorReqName :: Field
1442
pIAllocatorReqName =
1443
  withDoc "IAllocator target name (new instance, node to evac, etc.)" .
1444
  renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
1445

    
1446
pIAllocatorNics :: Field
1447
pIAllocatorNics =
1448
  withDoc "Custom OpTestIAllocator nics" .
1449
  renameField "IAllocatorNics" .
1450
  optionalField $ simpleField "nics" [t| [INicParams] |]
1451

    
1452
pIAllocatorDisks :: Field
1453
pIAllocatorDisks =
1454
  withDoc "Custom OpTestAllocator disks" .
1455
  renameField "IAllocatorDisks" .
1456
  optionalField $ simpleField "disks" [t| [JSValue] |]
1457

    
1458
pIAllocatorMemory :: Field
1459
pIAllocatorMemory =
1460
  withDoc "IAllocator memory field" .
1461
  renameField "IAllocatorMem" .
1462
  optionalField $
1463
  simpleField "memory" [t| NonNegative Int |]
1464

    
1465
pIAllocatorVCpus :: Field
1466
pIAllocatorVCpus =
1467
  withDoc "IAllocator vcpus field" .
1468
  renameField "IAllocatorVCpus" .
1469
  optionalField $
1470
  simpleField "vcpus" [t| NonNegative Int |]
1471

    
1472
pIAllocatorOs :: Field
1473
pIAllocatorOs =
1474
  withDoc "IAllocator os field" .
1475
  renameField "IAllocatorOs" $ optionalNEStringField "os"
1476

    
1477
pIAllocatorInstances :: Field
1478
pIAllocatorInstances =
1479
  withDoc "IAllocator instances field" .
1480
  renameField "IAllocatorInstances " .
1481
  optionalField $
1482
  simpleField "instances" [t| [NonEmptyString] |]
1483

    
1484
pIAllocatorEvacMode :: Field
1485
pIAllocatorEvacMode =
1486
  withDoc "IAllocator evac mode" .
1487
  renameField "IAllocatorEvacMode" .
1488
  optionalField $
1489
  simpleField "evac_mode" [t| EvacMode |]
1490

    
1491
pIAllocatorSpindleUse :: Field
1492
pIAllocatorSpindleUse =
1493
  withDoc "IAllocator spindle use" .
1494
  renameField "IAllocatorSpindleUse" .
1495
  defaultField [| forceNonNeg (1::Int) |] $
1496
  simpleField "spindle_use" [t| NonNegative Int |]
1497

    
1498
pIAllocatorCount :: Field
1499
pIAllocatorCount =
1500
  withDoc "IAllocator count field" .
1501
  renameField "IAllocatorCount" .
1502
  defaultField [| forceNonNeg (1::Int) |] $
1503
  simpleField "count" [t| NonNegative Int |]
1504

    
1505
pJQueueNotifyWaitLock :: Field
1506
pJQueueNotifyWaitLock =
1507
  withDoc "'OpTestJqueue' notify_waitlock" $
1508
  defaultFalse "notify_waitlock"
1509

    
1510
pJQueueNotifyExec :: Field
1511
pJQueueNotifyExec =
1512
  withDoc "'OpTestJQueue' notify_exec" $
1513
  defaultFalse "notify_exec"
1514

    
1515
pJQueueLogMessages :: Field
1516
pJQueueLogMessages =
1517
  withDoc "'OpTestJQueue' log_messages" .
1518
  defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
1519

    
1520
pJQueueFail :: Field
1521
pJQueueFail =
1522
  withDoc "'OpTestJQueue' fail attribute" .
1523
  renameField "JQueueFail" $ defaultFalse "fail"
1524

    
1525
pTestDummyResult :: Field
1526
pTestDummyResult =
1527
  withDoc "'OpTestDummy' result field" .
1528
  renameField "TestDummyResult" $ simpleField "result" [t| JSValue |]
1529

    
1530
pTestDummyMessages :: Field
1531
pTestDummyMessages =
1532
  withDoc "'OpTestDummy' messages field" .
1533
  renameField "TestDummyMessages" $
1534
  simpleField "messages" [t| JSValue |]
1535

    
1536
pTestDummyFail :: Field
1537
pTestDummyFail =
1538
  withDoc "'OpTestDummy' fail field" .
1539
  renameField "TestDummyFail" $ simpleField "fail" [t| JSValue |]
1540

    
1541
pTestDummySubmitJobs :: Field
1542
pTestDummySubmitJobs =
1543
  withDoc "'OpTestDummy' submit_jobs field" .
1544
  renameField "TestDummySubmitJobs" $
1545
  simpleField "submit_jobs" [t| JSValue |]
1546

    
1547
pNetworkName :: Field
1548
pNetworkName =
1549
  withDoc "Network name" $
1550
  simpleField "network_name" [t| NonEmptyString |]
1551

    
1552
pNetworkAddress4 :: Field
1553
pNetworkAddress4 =
1554
  withDoc "Network address (IPv4 subnet)" .
1555
  renameField "NetworkAddress4" $
1556
  simpleField "network" [t| IPv4Network |]
1557

    
1558
pNetworkGateway4 :: Field
1559
pNetworkGateway4 =
1560
  withDoc "Network gateway (IPv4 address)" .
1561
  renameField "NetworkGateway4" .
1562
  optionalField $ simpleField "gateway" [t| IPv4Address |]
1563

    
1564
pNetworkAddress6 :: Field
1565
pNetworkAddress6 =
1566
  withDoc "Network address (IPv6 subnet)" .
1567
  renameField "NetworkAddress6" .
1568
  optionalField $ simpleField "network6" [t| IPv6Network |]
1569

    
1570
pNetworkGateway6 :: Field
1571
pNetworkGateway6 =
1572
  withDoc "Network gateway (IPv6 address)" .
1573
  renameField "NetworkGateway6" .
1574
  optionalField $ simpleField "gateway6" [t| IPv6Address |]
1575

    
1576
pNetworkMacPrefix :: Field
1577
pNetworkMacPrefix =
1578
  withDoc "Network specific mac prefix (that overrides the cluster one)" .
1579
  renameField "NetMacPrefix" $
1580
  optionalNEStringField "mac_prefix"
1581

    
1582
pNetworkAddRsvdIps :: Field
1583
pNetworkAddRsvdIps =
1584
  withDoc "Which IP addresses to reserve" .
1585
  renameField "NetworkAddRsvdIps" .
1586
  optionalField $
1587
  simpleField "add_reserved_ips" [t| [IPv4Address] |]
1588

    
1589
pNetworkRemoveRsvdIps :: Field
1590
pNetworkRemoveRsvdIps =
1591
  withDoc "Which external IP addresses to release" .
1592
  renameField "NetworkRemoveRsvdIps" .
1593
  optionalField $
1594
  simpleField "remove_reserved_ips" [t| [IPv4Address] |]
1595

    
1596
pNetworkMode :: Field
1597
pNetworkMode =
1598
  withDoc "Network mode when connecting to a group" $
1599
  simpleField "network_mode" [t| NICMode |]
1600

    
1601
pNetworkLink :: Field
1602
pNetworkLink =
1603
  withDoc "Network link when connecting to a group" $
1604
  simpleField "network_link" [t| NonEmptyString |]