Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ a5450d2a

History | View | Annotate | Download (44.6 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
  , pGlobalFileStorageDir
104
  , pGlobalSharedFileStorageDir
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
  , pStorageChanges
154
  , pMasterCandidate
155
  , pOffline
156
  , pDrained
157
  , pAutoPromote
158
  , pPowered
159
  , pIallocator
160
  , pRemoteNode
161
  , pRemoteNodeUuid
162
  , pEvacMode
163
  , pInstCreateMode
164
  , pNoInstall
165
  , pInstOs
166
  , pPrimaryNode
167
  , pPrimaryNodeUuid
168
  , pSecondaryNode
169
  , pSecondaryNodeUuid
170
  , pSourceHandshake
171
  , pSourceInstance
172
  , pSourceShutdownTimeout
173
  , pSourceX509Ca
174
  , pSrcNode
175
  , pSrcNodeUuid
176
  , pSrcPath
177
  , pStartInstance
178
  , pInstTags
179
  , pMultiAllocInstances
180
  , pTempOsParams
181
  , pTempHvParams
182
  , pTempBeParams
183
  , pIgnoreFailures
184
  , pNewName
185
  , pIgnoreSecondaries
186
  , pRebootType
187
  , pIgnoreDiskSize
188
  , pRecreateDisksInfo
189
  , pStatic
190
  , pInstParamsNicChanges
191
  , pInstParamsDiskChanges
192
  , pRuntimeMem
193
  , pOsNameChange
194
  , pDiskIndex
195
  , pDiskChgAmount
196
  , pDiskChgAbsolute
197
  , pTargetGroups
198
  , pExportMode
199
  , pExportTargetNode
200
  , pExportTargetNodeUuid
201
  , pRemoveInstance
202
  , pIgnoreRemoveFailures
203
  , pX509KeyName
204
  , pX509DestCA
205
  , pTagSearchPattern
206
  , pRestrictedCommand
207
  , pReplaceDisksMode
208
  , pReplaceDisksList
209
  , pAllowFailover
210
  , pDelayDuration
211
  , pDelayOnMaster
212
  , pDelayOnNodes
213
  , pDelayOnNodeUuids
214
  , pDelayRepeat
215
  , pIAllocatorDirection
216
  , pIAllocatorMode
217
  , pIAllocatorReqName
218
  , pIAllocatorNics
219
  , pIAllocatorDisks
220
  , pIAllocatorMemory
221
  , pIAllocatorVCpus
222
  , pIAllocatorOs
223
  , pIAllocatorInstances
224
  , pIAllocatorEvacMode
225
  , pIAllocatorSpindleUse
226
  , pIAllocatorCount
227
  , pJQueueNotifyWaitLock
228
  , pJQueueNotifyExec
229
  , pJQueueLogMessages
230
  , pJQueueFail
231
  , pTestDummyResult
232
  , pTestDummyMessages
233
  , pTestDummyFail
234
  , pTestDummySubmitJobs
235
  , pNetworkName
236
  , pNetworkAddress4
237
  , pNetworkGateway4
238
  , pNetworkAddress6
239
  , pNetworkGateway6
240
  , pNetworkMacPrefix
241
  , pNetworkAddRsvdIps
242
  , pNetworkRemoveRsvdIps
243
  , pNetworkMode
244
  , pNetworkLink
245
  , pDryRun
246
  , pDebugLevel
247
  , pOpPriority
248
  , pDependencies
249
  , pComment
250
  , pReason
251
  , pEnabledDiskTemplates
252
  ) where
253

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

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

    
267
-- * Helper functions and types
268

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

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

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

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

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

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

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

    
302
-- ** Disks
303

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

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

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

    
320
-- ** I* param types
321

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
439
-- * Common opcode parameters
440

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

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

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

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

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

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

    
473
-- * Parameters
474

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

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

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

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

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

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

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

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

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

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

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

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

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

    
544
-- | Global directory for storing file-backed disks.
545
pGlobalFileStorageDir :: Field
546
pGlobalFileStorageDir = optionalNEStringField "file_storage_dir"
547

    
548
-- | Global directory for storing shared-file-backed disks.
549
pGlobalSharedFileStorageDir :: Field
550
pGlobalSharedFileStorageDir = optionalNEStringField "shared_file_storage_dir"
551

    
552
-- | Volume group name.
553
pVgName :: Field
554
pVgName =
555
  withDoc "Volume group name" $
556
  optionalStringField "vg_name"
557

    
558
pEnabledHypervisors :: Field
559
pEnabledHypervisors =
560
  withDoc "List of enabled hypervisors" .
561
  optionalField $
562
  simpleField "enabled_hypervisors" [t| [Hypervisor] |]
563

    
564
pClusterHvParams :: Field
565
pClusterHvParams =
566
  withDoc "Cluster-wide hypervisor parameters, hypervisor-dependent" .
567
  renameField "ClusterHvParams" .
568
  optionalField $
569
  simpleField "hvparams" [t| GenericContainer String (JSObject JSValue) |]
570

    
571
pClusterBeParams :: Field
572
pClusterBeParams =
573
  withDoc "Cluster-wide backend parameter defaults" .
574
  renameField "ClusterBeParams" .
575
  optionalField $ simpleField "beparams" [t| JSObject JSValue |]
576

    
577
pOsHvp :: Field
578
pOsHvp =
579
  withDoc "Cluster-wide per-OS hypervisor parameter defaults" .
580
  optionalField $
581
  simpleField "os_hvp" [t| GenericContainer String (JSObject JSValue) |]
582

    
583
pClusterOsParams :: Field
584
pClusterOsParams =
585
  withDoc "Cluster-wide OS parameter defaults" .
586
  renameField "ClusterOsParams" .
587
  optionalField $
588
  simpleField "osparams" [t| GenericContainer String (JSObject JSValue) |]
589

    
590
pDiskParams :: Field
591
pDiskParams =
592
  withDoc "Disk templates' parameter defaults" .
593
  optionalField $
594
  simpleField "diskparams"
595
              [t| GenericContainer DiskTemplate (JSObject JSValue) |]
596

    
597
pCandidatePoolSize :: Field
598
pCandidatePoolSize =
599
  withDoc "Master candidate pool size" .
600
  optionalField $ simpleField "candidate_pool_size" [t| Positive Int |]
601

    
602
pUidPool :: Field
603
pUidPool =
604
  withDoc "Set UID pool, must be list of lists describing UID ranges\
605
          \ (two items, start and end inclusive)" .
606
  optionalField $ simpleField "uid_pool" [t| [(Int, Int)] |]
607

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

    
614
pRemoveUids :: Field
615
pRemoveUids =
616
  withDoc "Shrink UID pool, must be list of lists describing UID\
617
          \ ranges (two items, start and end inclusive) to be removed" .
618
  optionalField $ simpleField "remove_uids" [t| [(Int, Int)] |]
619

    
620
pMaintainNodeHealth :: Field
621
pMaintainNodeHealth =
622
  withDoc "Whether to automatically maintain node health" .
623
  optionalField $ booleanField "maintain_node_health"
624

    
625
-- | Whether to modify and keep in sync the @/etc/hosts@ files of nodes.
626
pModifyEtcHosts :: Field
627
pModifyEtcHosts = optionalField $ booleanField "modify_etc_hosts"
628

    
629
-- | Whether to wipe disks before allocating them to instances.
630
pPreallocWipeDisks :: Field
631
pPreallocWipeDisks =
632
  withDoc "Whether to wipe disks before allocating them to instances" .
633
  optionalField $ booleanField "prealloc_wipe_disks"
634

    
635
pNicParams :: Field
636
pNicParams =
637
  withDoc "Cluster-wide NIC parameter defaults" .
638
  optionalField $ simpleField "nicparams" [t| INicParams |]
639

    
640
pIpolicy :: Field
641
pIpolicy =
642
  withDoc "Ipolicy specs" .
643
  optionalField $ simpleField "ipolicy" [t| JSObject JSValue |]
644

    
645
pDrbdHelper :: Field
646
pDrbdHelper =
647
  withDoc "DRBD helper program" $
648
  optionalStringField "drbd_helper"
649

    
650
pDefaultIAllocator :: Field
651
pDefaultIAllocator =
652
  withDoc "Default iallocator for cluster" $
653
  optionalStringField "default_iallocator"
654

    
655
pMasterNetdev :: Field
656
pMasterNetdev =
657
  withDoc "Master network device" $
658
  optionalStringField "master_netdev"
659

    
660
pMasterNetmask :: Field
661
pMasterNetmask =
662
  withDoc "Netmask of the master IP" .
663
  optionalField $ simpleField "master_netmask" [t| NonNegative Int |]
664

    
665
pReservedLvs :: Field
666
pReservedLvs =
667
  withDoc "List of reserved LVs" .
668
  optionalField $ simpleField "reserved_lvs" [t| [NonEmptyString] |]
669

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

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

    
685
pUseExternalMipScript :: Field
686
pUseExternalMipScript =
687
  withDoc "Whether to use an external master IP address setup script" .
688
  optionalField $ booleanField "use_external_mip_script"
689

    
690
pEnabledDiskTemplates :: Field
691
pEnabledDiskTemplates =
692
  withDoc "List of enabled disk templates" .
693
  optionalField $
694
  simpleField "enabled_disk_templates" [t| [DiskTemplate] |]
695

    
696
pQueryWhat :: Field
697
pQueryWhat =
698
  withDoc "Resource(s) to query for" $
699
  simpleField "what" [t| Qlang.QueryTypeOp |]
700

    
701
pUseLocking :: Field
702
pUseLocking =
703
  withDoc "Whether to use synchronization" $
704
  defaultFalse "use_locking"
705

    
706
pQueryFields :: Field
707
pQueryFields =
708
  withDoc "Requested fields" $
709
  simpleField "fields" [t| [NonEmptyString] |]
710

    
711
pQueryFilter :: Field
712
pQueryFilter =
713
  withDoc "Query filter" .
714
  optionalField $ simpleField "qfilter" [t| [JSValue] |]
715

    
716
pQueryFieldsFields :: Field
717
pQueryFieldsFields =
718
  withDoc "Requested fields; if not given, all are returned" .
719
  renameField "QueryFieldsFields" $
720
  optionalField pQueryFields
721

    
722
pNodeNames :: Field
723
pNodeNames =
724
  withDoc "List of node names to run the OOB command against" .
725
  defaultField [| [] |] $ simpleField "node_names" [t| [NonEmptyString] |]
726

    
727
pNodeUuids :: Field
728
pNodeUuids =
729
  withDoc "List of node UUIDs" .
730
  optionalField $ simpleField "node_uuids" [t| [NonEmptyString] |]
731

    
732
pOobCommand :: Field
733
pOobCommand =
734
  withDoc "OOB command to run" $
735
  simpleField "command" [t| OobCommand |]
736

    
737
pOobTimeout :: Field
738
pOobTimeout =
739
  withDoc "Timeout before the OOB helper will be terminated" .
740
  defaultField [| C.oobTimeout |] $
741
  simpleField "timeout" [t| Int |]
742

    
743
pIgnoreStatus :: Field
744
pIgnoreStatus =
745
  withDoc "Ignores the node offline status for power off" $
746
  defaultFalse "ignore_status"
747

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

    
757
pRequiredNodes :: Field
758
pRequiredNodes =
759
  withDoc "Required list of node names" .
760
  renameField "ReqNodes " $ simpleField "nodes" [t| [NonEmptyString] |]
761

    
762
pRequiredNodeUuids :: Field
763
pRequiredNodeUuids =
764
  withDoc "Required list of node UUIDs" .
765
  renameField "ReqNodeUuids " . optionalField $
766
  simpleField "node_uuids" [t| [NonEmptyString] |]
767

    
768
pRestrictedCommand :: Field
769
pRestrictedCommand =
770
  withDoc "Restricted command name" .
771
  renameField "RestrictedCommand" $
772
  simpleField "command" [t| NonEmptyString |]
773

    
774
pNodeName :: Field
775
pNodeName =
776
  withDoc "A required node name (for single-node LUs)" $
777
  simpleField "node_name" [t| NonEmptyString |]
778

    
779
pNodeUuid :: Field
780
pNodeUuid =
781
  withDoc "A node UUID (for single-node LUs)" .
782
  optionalField $ simpleField "node_uuid" [t| NonEmptyString |]
783

    
784
pPrimaryIp :: Field
785
pPrimaryIp =
786
  withDoc "Primary IP address" .
787
  optionalField $
788
  simpleField "primary_ip" [t| NonEmptyString |]
789

    
790
pSecondaryIp :: Field
791
pSecondaryIp =
792
  withDoc "Secondary IP address" $
793
  optionalNEStringField "secondary_ip"
794

    
795
pReadd :: Field
796
pReadd =
797
  withDoc "Whether node is re-added to cluster" $
798
  defaultFalse "readd"
799

    
800
pNodeGroup :: Field
801
pNodeGroup =
802
  withDoc "Initial node group" $
803
  optionalNEStringField "group"
804

    
805
pMasterCapable :: Field
806
pMasterCapable =
807
  withDoc "Whether node can become master or master candidate" .
808
  optionalField $ booleanField "master_capable"
809

    
810
pVmCapable :: Field
811
pVmCapable =
812
  withDoc "Whether node can host instances" .
813
  optionalField $ booleanField "vm_capable"
814

    
815
pNdParams :: Field
816
pNdParams =
817
  withDoc "Node parameters" .
818
  renameField "genericNdParams" .
819
  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
820
  
821
pNames :: Field
822
pNames =
823
  withDoc "List of names" .
824
  defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
825

    
826
pNodes :: Field
827
pNodes =
828
  withDoc "List of nodes" .
829
  defaultField [| [] |] $ simpleField "nodes" [t| [NonEmptyString] |]
830

    
831
pStorageType :: Field
832
pStorageType =
833
  withDoc "Storage type" $
834
  simpleField "storage_type" [t| StorageType |]
835

    
836
pStorageName :: Field
837
pStorageName =
838
  withDoc "Storage name" .
839
  renameField "StorageName" .
840
  optionalField $ simpleField "name" [t| NonEmptyString |]
841

    
842
pStorageChanges :: Field
843
pStorageChanges =
844
  withDoc "Requested storage changes" $
845
  simpleField "changes" [t| JSObject JSValue |]
846

    
847
pIgnoreConsistency :: Field
848
pIgnoreConsistency =
849
  withDoc "Whether to ignore disk consistency" $
850
  defaultFalse "ignore_consistency"
851

    
852
pMasterCandidate :: Field
853
pMasterCandidate =
854
  withDoc "Whether the node should become a master candidate" .
855
  optionalField $ booleanField "master_candidate"
856

    
857
pOffline :: Field
858
pOffline =
859
  withDoc "Whether to mark the node or instance offline" .
860
  optionalField $ booleanField "offline"
861

    
862
pDrained ::Field
863
pDrained =
864
  withDoc "Whether to mark the node as drained" .
865
  optionalField $ booleanField "drained"
866

    
867
pAutoPromote :: Field
868
pAutoPromote =
869
  withDoc "Whether node(s) should be promoted to master candidate if\
870
          \ necessary" $
871
  defaultFalse "auto_promote"
872

    
873
pPowered :: Field
874
pPowered =
875
  withDoc "Whether the node should be marked as powered" .
876
  optionalField $ booleanField "powered"
877

    
878
pMigrationMode :: Field
879
pMigrationMode =
880
  withDoc "Migration type (live/non-live)" .
881
  renameField "MigrationMode" .
882
  optionalField $
883
  simpleField "mode" [t| MigrationMode |]
884

    
885
pMigrationLive :: Field
886
pMigrationLive =
887
  withDoc "Obsolete \'live\' migration mode (do not use)" .
888
  renameField "OldLiveMode" . optionalField $ booleanField "live"
889

    
890
pMigrationTargetNode :: Field
891
pMigrationTargetNode =
892
  withDoc "Target node for instance migration/failover" $
893
  optionalNEStringField "target_node"
894

    
895
pMigrationTargetNodeUuid :: Field
896
pMigrationTargetNodeUuid =
897
  withDoc "Target node UUID for instance migration/failover" $
898
  optionalNEStringField "target_node_uuid"
899

    
900
pAllowRuntimeChgs :: Field
901
pAllowRuntimeChgs =
902
  withDoc "Whether to allow runtime changes while migrating" $
903
  defaultTrue "allow_runtime_changes"
904

    
905
pIgnoreIpolicy :: Field
906
pIgnoreIpolicy =
907
  withDoc "Whether to ignore ipolicy violations" $
908
  defaultFalse "ignore_ipolicy"
909
  
910
pIallocator :: Field
911
pIallocator =
912
  withDoc "Iallocator for deciding the target node for shared-storage\
913
          \ instances" $
914
  optionalNEStringField "iallocator"
915

    
916
pEarlyRelease :: Field
917
pEarlyRelease =
918
  withDoc "Whether to release locks as soon as possible" $
919
  defaultFalse "early_release"
920

    
921
pRemoteNode :: Field
922
pRemoteNode =
923
  withDoc "New secondary node" $
924
  optionalNEStringField "remote_node"
925

    
926
pRemoteNodeUuid :: Field
927
pRemoteNodeUuid =
928
  withDoc "New secondary node UUID" $
929
  optionalNEStringField "remote_node_uuid"
930

    
931
pEvacMode :: Field
932
pEvacMode =
933
  withDoc "Node evacuation mode" .
934
  renameField "EvacMode" $ simpleField "mode" [t| EvacMode |]
935

    
936
pInstanceName :: Field
937
pInstanceName =
938
  withDoc "A required instance name (for single-instance LUs)" $
939
  simpleField "instance_name" [t| String |]
940

    
941
pForceVariant :: Field
942
pForceVariant =
943
  withDoc "Whether to force an unknown OS variant" $
944
  defaultFalse "force_variant"
945

    
946
pWaitForSync :: Field
947
pWaitForSync =
948
  withDoc "Whether to wait for the disk to synchronize" $
949
  defaultTrue "wait_for_sync"
950

    
951
pNameCheck :: Field
952
pNameCheck =
953
  withDoc "Whether to check name" $
954
  defaultTrue "name_check"
955

    
956
pInstBeParams :: Field
957
pInstBeParams =
958
  withDoc "Backend parameters for instance" .
959
  renameField "InstBeParams" .
960
  defaultField [| toJSObject [] |] $
961
  simpleField "beparams" [t| JSObject JSValue |]
962

    
963
pInstDisks :: Field
964
pInstDisks =
965
  withDoc "List of instance disks" .
966
  renameField "instDisks" $ simpleField "disks" [t| [IDiskParams] |]
967

    
968
pDiskTemplate :: Field
969
pDiskTemplate =
970
  withDoc "Disk template" $
971
  simpleField "disk_template" [t| DiskTemplate |]
972

    
973
pFileDriver :: Field
974
pFileDriver =
975
  withDoc "Driver for file-backed disks" .
976
  optionalField $ simpleField "file_driver" [t| FileDriver |]
977

    
978
pFileStorageDir :: Field
979
pFileStorageDir =
980
  withDoc "Directory for storing file-backed disks" $
981
  optionalNEStringField "file_storage_dir"
982

    
983
pInstHvParams :: Field
984
pInstHvParams =
985
  withDoc "Hypervisor parameters for instance, hypervisor-dependent" .
986
  renameField "InstHvParams" .
987
  defaultField [| toJSObject [] |] $
988
  simpleField "hvparams" [t| JSObject JSValue |]
989

    
990
pHypervisor :: Field
991
pHypervisor =
992
  withDoc "Selected hypervisor for an instance" .
993
  optionalField $
994
  simpleField "hypervisor" [t| Hypervisor |]
995

    
996
pResetDefaults :: Field
997
pResetDefaults =
998
  withDoc "Reset instance parameters to default if equal" $
999
  defaultFalse "identify_defaults"
1000

    
1001
pIpCheck :: Field
1002
pIpCheck =
1003
  withDoc "Whether to ensure instance's IP address is inactive" $
1004
  defaultTrue "ip_check"
1005

    
1006
pIpConflictsCheck :: Field
1007
pIpConflictsCheck =
1008
  withDoc "Whether to check for conflicting IP addresses" $
1009
  defaultTrue "conflicts_check"
1010

    
1011
pInstCreateMode :: Field
1012
pInstCreateMode =
1013
  withDoc "Instance creation mode" .
1014
  renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
1015

    
1016
pInstNics :: Field
1017
pInstNics =
1018
  withDoc "List of NIC (network interface) definitions" $
1019
  simpleField "nics" [t| [INicParams] |]
1020

    
1021
pNoInstall :: Field
1022
pNoInstall =
1023
  withDoc "Do not install the OS (will disable automatic start)" .
1024
  optionalField $ booleanField "no_install"
1025

    
1026
pInstOs :: Field
1027
pInstOs =
1028
  withDoc "OS type for instance installation" $
1029
  optionalNEStringField "os_type"
1030

    
1031
pInstOsParams :: Field
1032
pInstOsParams =
1033
  withDoc "OS parameters for instance" .
1034
  renameField "InstOsParams" .
1035
  defaultField [| toJSObject [] |] $
1036
  simpleField "osparams" [t| JSObject JSValue |]
1037

    
1038
pPrimaryNode :: Field
1039
pPrimaryNode =
1040
  withDoc "Primary node for an instance" $
1041
  optionalNEStringField "pnode"
1042

    
1043
pPrimaryNodeUuid :: Field
1044
pPrimaryNodeUuid =
1045
  withDoc "Primary node UUID for an instance" $
1046
  optionalNEStringField "pnode_uuid"
1047

    
1048
pSecondaryNode :: Field
1049
pSecondaryNode =
1050
  withDoc "Secondary node for an instance" $
1051
  optionalNEStringField "snode"
1052

    
1053
pSecondaryNodeUuid :: Field
1054
pSecondaryNodeUuid =
1055
  withDoc "Secondary node UUID for an instance" $
1056
  optionalNEStringField "snode_uuid"
1057

    
1058
pSourceHandshake :: Field
1059
pSourceHandshake =
1060
  withDoc "Signed handshake from source (remote import only)" .
1061
  optionalField $ simpleField "source_handshake" [t| [JSValue] |]
1062

    
1063
pSourceInstance :: Field
1064
pSourceInstance =
1065
  withDoc "Source instance name (remote import only)" $
1066
  optionalNEStringField "source_instance_name"
1067

    
1068
-- FIXME: non-negative int, whereas the constant is a plain int.
1069
pSourceShutdownTimeout :: Field
1070
pSourceShutdownTimeout =
1071
  withDoc "How long source instance was given to shut down (remote import\
1072
          \ only)" .
1073
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1074
  simpleField "source_shutdown_timeout" [t| NonNegative Int |]
1075

    
1076
pSourceX509Ca :: Field
1077
pSourceX509Ca =
1078
  withDoc "Source X509 CA in PEM format (remote import only)" $
1079
  optionalNEStringField "source_x509_ca"
1080

    
1081
pSrcNode :: Field
1082
pSrcNode =
1083
  withDoc "Source node for import" $
1084
  optionalNEStringField "src_node"
1085

    
1086
pSrcNodeUuid :: Field
1087
pSrcNodeUuid =
1088
  withDoc "Source node UUID for import" $
1089
  optionalNEStringField "src_node_uuid"
1090

    
1091
pSrcPath :: Field
1092
pSrcPath =
1093
  withDoc "Source directory for import" $
1094
  optionalNEStringField "src_path"
1095

    
1096
pStartInstance :: Field
1097
pStartInstance =
1098
  withDoc "Whether to start instance after creation" $
1099
  defaultTrue "start"
1100

    
1101
-- FIXME: unify/simplify with pTags, once that migrates to NonEmpty String"
1102
pInstTags :: Field
1103
pInstTags =
1104
  withDoc "Instance tags" .
1105
  renameField "InstTags" .
1106
  defaultField [| [] |] $
1107
  simpleField "tags" [t| [NonEmptyString] |]
1108

    
1109
pMultiAllocInstances :: Field
1110
pMultiAllocInstances =
1111
  withDoc "List of instance create opcodes describing the instances to\
1112
          \ allocate" .
1113
  renameField "InstMultiAlloc" .
1114
  defaultField [| [] |] $
1115
  simpleField "instances"[t| [JSValue] |]
1116

    
1117
pOpportunisticLocking :: Field
1118
pOpportunisticLocking =
1119
  withDoc "Whether to employ opportunistic locking for nodes, meaning\
1120
          \ nodes already locked by another opcode won't be considered for\
1121
          \ instance allocation (only when an iallocator is used)" $
1122
  defaultFalse "opportunistic_locking"
1123

    
1124
pInstanceUuid :: Field
1125
pInstanceUuid =
1126
  withDoc "An instance UUID (for single-instance LUs)" .
1127
  optionalField $ simpleField "instance_uuid" [t| NonEmptyString |]
1128

    
1129
pTempOsParams :: Field
1130
pTempOsParams =
1131
  withDoc "Temporary OS parameters (currently only in reinstall, might be\
1132
          \ added to install as well)" .
1133
  renameField "TempOsParams" .
1134
  optionalField $ simpleField "osparams" [t| JSObject JSValue |]
1135

    
1136
pShutdownTimeout :: Field
1137
pShutdownTimeout =
1138
  withDoc "How long to wait for instance to shut down" .
1139
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1140
  simpleField "shutdown_timeout" [t| NonNegative Int |]
1141

    
1142
-- | Another name for the shutdown timeout, because we like to be
1143
-- inconsistent.
1144
pShutdownTimeout' :: Field
1145
pShutdownTimeout' =
1146
  withDoc "How long to wait for instance to shut down" .
1147
  renameField "InstShutdownTimeout" .
1148
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1149
  simpleField "timeout" [t| NonNegative Int |]
1150

    
1151
pIgnoreFailures :: Field
1152
pIgnoreFailures =
1153
  withDoc "Whether to ignore failures during removal" $
1154
  defaultFalse "ignore_failures"
1155

    
1156
pNewName :: Field
1157
pNewName =
1158
  withDoc "New group or instance name" $
1159
  simpleField "new_name" [t| NonEmptyString |]
1160
  
1161
pIgnoreOfflineNodes :: Field
1162
pIgnoreOfflineNodes =
1163
  withDoc "Whether to ignore offline nodes" $
1164
  defaultFalse "ignore_offline_nodes"
1165

    
1166
pTempHvParams :: Field
1167
pTempHvParams =
1168
  withDoc "Temporary hypervisor parameters, hypervisor-dependent" .
1169
  renameField "TempHvParams" .
1170
  defaultField [| toJSObject [] |] $
1171
  simpleField "hvparams" [t| JSObject JSValue |]
1172

    
1173
pTempBeParams :: Field
1174
pTempBeParams =
1175
  withDoc "Temporary backend parameters" .
1176
  renameField "TempBeParams" .
1177
  defaultField [| toJSObject [] |] $
1178
  simpleField "beparams" [t| JSObject JSValue |]
1179

    
1180
pNoRemember :: Field
1181
pNoRemember =
1182
  withDoc "Do not remember instance state changes" $
1183
  defaultFalse "no_remember"
1184

    
1185
pStartupPaused :: Field
1186
pStartupPaused =
1187
  withDoc "Pause instance at startup" $
1188
  defaultFalse "startup_paused"
1189

    
1190
pIgnoreSecondaries :: Field
1191
pIgnoreSecondaries =
1192
  withDoc "Whether to start the instance even if secondary disks are failing" $
1193
  defaultFalse "ignore_secondaries"
1194

    
1195
pRebootType :: Field
1196
pRebootType =
1197
  withDoc "How to reboot the instance" $
1198
  simpleField "reboot_type" [t| RebootType |]
1199

    
1200
pReplaceDisksMode :: Field
1201
pReplaceDisksMode =
1202
  withDoc "Replacement mode" .
1203
  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1204

    
1205
pReplaceDisksList :: Field
1206
pReplaceDisksList =
1207
  withDoc "List of disk indices" .
1208
  renameField "ReplaceDisksList" .
1209
  defaultField [| [] |] $
1210
  simpleField "disks" [t| [DiskIndex] |]
1211

    
1212
pMigrationCleanup :: Field
1213
pMigrationCleanup =
1214
  withDoc "Whether a previously failed migration should be cleaned up" .
1215
  renameField "MigrationCleanup" $ defaultFalse "cleanup"
1216

    
1217
pAllowFailover :: Field
1218
pAllowFailover =
1219
  withDoc "Whether we can fallback to failover if migration is not possible" $
1220
  defaultFalse "allow_failover"
1221

    
1222
pMoveTargetNode :: Field
1223
pMoveTargetNode =
1224
  withDoc "Target node for instance move" .
1225
  renameField "MoveTargetNode" $
1226
  simpleField "target_node" [t| NonEmptyString |]
1227

    
1228
pMoveTargetNodeUuid :: Field
1229
pMoveTargetNodeUuid =
1230
  withDoc "Target node UUID for instance move" .
1231
  renameField "MoveTargetNodeUuid" . optionalField $
1232
  simpleField "target_node_uuid" [t| NonEmptyString |]
1233

    
1234
pIgnoreDiskSize :: Field
1235
pIgnoreDiskSize =
1236
  withDoc "Whether to ignore recorded disk size" $
1237
  defaultFalse "ignore_size"
1238
  
1239
pWaitForSyncFalse :: Field
1240
pWaitForSyncFalse =
1241
  withDoc "Whether to wait for the disk to synchronize (defaults to false)" $
1242
  defaultField [| False |] pWaitForSync
1243
  
1244
pRecreateDisksInfo :: Field
1245
pRecreateDisksInfo =
1246
  withDoc "Disk list for recreate disks" .
1247
  renameField "RecreateDisksInfo" .
1248
  defaultField [| RecreateDisksAll |] $
1249
  simpleField "disks" [t| RecreateDisksInfo |]
1250

    
1251
pStatic :: Field
1252
pStatic =
1253
  withDoc "Whether to only return configuration data without querying nodes" $
1254
  defaultFalse "static"
1255

    
1256
pInstParamsNicChanges :: Field
1257
pInstParamsNicChanges =
1258
  withDoc "List of NIC changes" .
1259
  renameField "InstNicChanges" .
1260
  defaultField [| SetParamsEmpty |] $
1261
  simpleField "nics" [t| SetParamsMods INicParams |]
1262

    
1263
pInstParamsDiskChanges :: Field
1264
pInstParamsDiskChanges =
1265
  withDoc "List of disk changes" .
1266
  renameField "InstDiskChanges" .
1267
  defaultField [| SetParamsEmpty |] $
1268
  simpleField "disks" [t| SetParamsMods IDiskParams |]
1269

    
1270
pRuntimeMem :: Field
1271
pRuntimeMem =
1272
  withDoc "New runtime memory" .
1273
  optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1274

    
1275
pOptDiskTemplate :: Field
1276
pOptDiskTemplate =
1277
  withDoc "Instance disk template" .
1278
  optionalField .
1279
  renameField "OptDiskTemplate" $
1280
  simpleField "disk_template" [t| DiskTemplate |]
1281

    
1282
pOsNameChange :: Field
1283
pOsNameChange =
1284
  withDoc "Change the instance's OS without reinstalling the instance" $
1285
  optionalNEStringField "os_name"
1286

    
1287
pDiskIndex :: Field
1288
pDiskIndex =
1289
  withDoc "Disk index for e.g. grow disk" .
1290
  renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
1291

    
1292
pDiskChgAmount :: Field
1293
pDiskChgAmount =
1294
  withDoc "Disk amount to add or grow to" .
1295
  renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
1296

    
1297
pDiskChgAbsolute :: Field
1298
pDiskChgAbsolute =
1299
  withDoc
1300
    "Whether the amount parameter is an absolute target or a relative one" .
1301
  renameField "DiskChkAbsolute" $ defaultFalse "absolute"
1302

    
1303
pTargetGroups :: Field
1304
pTargetGroups =
1305
  withDoc
1306
    "Destination group names or UUIDs (defaults to \"all but current group\")" .
1307
  optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
1308

    
1309
pNodeGroupAllocPolicy :: Field
1310
pNodeGroupAllocPolicy =
1311
  withDoc "Instance allocation policy" .
1312
  optionalField $
1313
  simpleField "alloc_policy" [t| AllocPolicy |]
1314

    
1315
pGroupNodeParams :: Field
1316
pGroupNodeParams =
1317
  withDoc "Default node parameters for group" .
1318
  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
1319

    
1320
pExportMode :: Field
1321
pExportMode =
1322
  withDoc "Export mode" .
1323
  renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1324

    
1325
-- FIXME: Rename target_node as it changes meaning for different
1326
-- export modes (e.g. "destination")
1327
pExportTargetNode :: Field
1328
pExportTargetNode =
1329
  withDoc "Target node (depends on export mode)" .
1330
  renameField "ExportTarget" $
1331
  simpleField "target_node" [t| ExportTarget |]
1332

    
1333
pExportTargetNodeUuid :: Field
1334
pExportTargetNodeUuid =
1335
  withDoc "Target node UUID (if local export)" .
1336
  renameField "ExportTargetNodeUuid" . optionalField $
1337
  simpleField "target_node_uuid" [t| NonEmptyString |]
1338

    
1339
pShutdownInstance :: Field
1340
pShutdownInstance =
1341
  withDoc "Whether to shutdown the instance before export" $
1342
  defaultTrue "shutdown"
1343

    
1344
pRemoveInstance :: Field
1345
pRemoveInstance =
1346
  withDoc "Whether to remove instance after export" $
1347
  defaultFalse "remove_instance"
1348

    
1349
pIgnoreRemoveFailures :: Field
1350
pIgnoreRemoveFailures =
1351
  withDoc "Whether to ignore failures while removing instances" $
1352
  defaultFalse "ignore_remove_failures"
1353

    
1354
pX509KeyName :: Field
1355
pX509KeyName =
1356
  withDoc "Name of X509 key (remote export only)" .
1357
  optionalField $ simpleField "x509_key_name" [t| [JSValue] |]
1358

    
1359
pX509DestCA :: Field
1360
pX509DestCA =
1361
  withDoc "Destination X509 CA (remote export only)" $
1362
  optionalNEStringField "destination_x509_ca"
1363

    
1364
pTagsObject :: Field
1365
pTagsObject =
1366
  withDoc "Tag kind" $
1367
  simpleField "kind" [t| TagKind |]
1368

    
1369
pTagsName :: Field
1370
pTagsName =
1371
  withDoc "Name of object" .
1372
  renameField "TagsGetName" .
1373
  optionalField $ simpleField "name" [t| String |]
1374

    
1375
pTagsList :: Field
1376
pTagsList =
1377
  withDoc "List of tag names" $
1378
  simpleField "tags" [t| [String] |]
1379

    
1380
-- FIXME: this should be compiled at load time?
1381
pTagSearchPattern :: Field
1382
pTagSearchPattern =
1383
  withDoc "Search pattern (regular expression)" .
1384
  renameField "TagSearchPattern" $
1385
  simpleField "pattern" [t| NonEmptyString |]
1386

    
1387
pDelayDuration :: Field
1388
pDelayDuration =
1389
  withDoc "Duration parameter for 'OpTestDelay'" .
1390
  renameField "DelayDuration" $
1391
  simpleField "duration" [t| Double |]
1392

    
1393
pDelayOnMaster :: Field
1394
pDelayOnMaster =
1395
  withDoc "on_master field for 'OpTestDelay'" .
1396
  renameField "DelayOnMaster" $
1397
  defaultTrue "on_master"
1398

    
1399
pDelayOnNodes :: Field
1400
pDelayOnNodes =
1401
  withDoc "on_nodes field for 'OpTestDelay'" .
1402
  renameField "DelayOnNodes" .
1403
  defaultField [| [] |] $
1404
  simpleField "on_nodes" [t| [NonEmptyString] |]
1405

    
1406
pDelayOnNodeUuids :: Field
1407
pDelayOnNodeUuids =
1408
  withDoc "on_node_uuids field for 'OpTestDelay'" .
1409
  renameField "DelayOnNodeUuids" . optionalField $
1410
  simpleField "on_node_uuids" [t| [NonEmptyString] |]
1411

    
1412
pDelayRepeat :: Field
1413
pDelayRepeat =
1414
  withDoc "Repeat parameter for OpTestDelay" .
1415
  renameField "DelayRepeat" .
1416
  defaultField [| forceNonNeg (0::Int) |] $
1417
  simpleField "repeat" [t| NonNegative Int |]
1418

    
1419
pIAllocatorDirection :: Field
1420
pIAllocatorDirection =
1421
  withDoc "IAllocator test direction" .
1422
  renameField "IAllocatorDirection" $
1423
  simpleField "direction" [t| IAllocatorTestDir |]
1424

    
1425
pIAllocatorMode :: Field
1426
pIAllocatorMode =
1427
  withDoc "IAllocator test mode" .
1428
  renameField "IAllocatorMode" $
1429
  simpleField "mode" [t| IAllocatorMode |]
1430

    
1431
pIAllocatorReqName :: Field
1432
pIAllocatorReqName =
1433
  withDoc "IAllocator target name (new instance, node to evac, etc.)" .
1434
  renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
1435

    
1436
pIAllocatorNics :: Field
1437
pIAllocatorNics =
1438
  withDoc "Custom OpTestIAllocator nics" .
1439
  renameField "IAllocatorNics" .
1440
  optionalField $ simpleField "nics" [t| [INicParams] |]
1441

    
1442
pIAllocatorDisks :: Field
1443
pIAllocatorDisks =
1444
  withDoc "Custom OpTestAllocator disks" .
1445
  renameField "IAllocatorDisks" .
1446
  optionalField $ simpleField "disks" [t| [JSValue] |]
1447

    
1448
pIAllocatorMemory :: Field
1449
pIAllocatorMemory =
1450
  withDoc "IAllocator memory field" .
1451
  renameField "IAllocatorMem" .
1452
  optionalField $
1453
  simpleField "memory" [t| NonNegative Int |]
1454

    
1455
pIAllocatorVCpus :: Field
1456
pIAllocatorVCpus =
1457
  withDoc "IAllocator vcpus field" .
1458
  renameField "IAllocatorVCpus" .
1459
  optionalField $
1460
  simpleField "vcpus" [t| NonNegative Int |]
1461

    
1462
pIAllocatorOs :: Field
1463
pIAllocatorOs =
1464
  withDoc "IAllocator os field" .
1465
  renameField "IAllocatorOs" $ optionalNEStringField "os"
1466

    
1467
pIAllocatorInstances :: Field
1468
pIAllocatorInstances =
1469
  withDoc "IAllocator instances field" .
1470
  renameField "IAllocatorInstances " .
1471
  optionalField $
1472
  simpleField "instances" [t| [NonEmptyString] |]
1473

    
1474
pIAllocatorEvacMode :: Field
1475
pIAllocatorEvacMode =
1476
  withDoc "IAllocator evac mode" .
1477
  renameField "IAllocatorEvacMode" .
1478
  optionalField $
1479
  simpleField "evac_mode" [t| EvacMode |]
1480

    
1481
pIAllocatorSpindleUse :: Field
1482
pIAllocatorSpindleUse =
1483
  withDoc "IAllocator spindle use" .
1484
  renameField "IAllocatorSpindleUse" .
1485
  defaultField [| forceNonNeg (1::Int) |] $
1486
  simpleField "spindle_use" [t| NonNegative Int |]
1487

    
1488
pIAllocatorCount :: Field
1489
pIAllocatorCount =
1490
  withDoc "IAllocator count field" .
1491
  renameField "IAllocatorCount" .
1492
  defaultField [| forceNonNeg (1::Int) |] $
1493
  simpleField "count" [t| NonNegative Int |]
1494

    
1495
pJQueueNotifyWaitLock :: Field
1496
pJQueueNotifyWaitLock =
1497
  withDoc "'OpTestJqueue' notify_waitlock" $
1498
  defaultFalse "notify_waitlock"
1499

    
1500
pJQueueNotifyExec :: Field
1501
pJQueueNotifyExec =
1502
  withDoc "'OpTestJQueue' notify_exec" $
1503
  defaultFalse "notify_exec"
1504

    
1505
pJQueueLogMessages :: Field
1506
pJQueueLogMessages =
1507
  withDoc "'OpTestJQueue' log_messages" .
1508
  defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
1509

    
1510
pJQueueFail :: Field
1511
pJQueueFail =
1512
  withDoc "'OpTestJQueue' fail attribute" .
1513
  renameField "JQueueFail" $ defaultFalse "fail"
1514

    
1515
pTestDummyResult :: Field
1516
pTestDummyResult =
1517
  withDoc "'OpTestDummy' result field" .
1518
  renameField "TestDummyResult" $ simpleField "result" [t| JSValue |]
1519

    
1520
pTestDummyMessages :: Field
1521
pTestDummyMessages =
1522
  withDoc "'OpTestDummy' messages field" .
1523
  renameField "TestDummyMessages" $
1524
  simpleField "messages" [t| JSValue |]
1525

    
1526
pTestDummyFail :: Field
1527
pTestDummyFail =
1528
  withDoc "'OpTestDummy' fail field" .
1529
  renameField "TestDummyFail" $ simpleField "fail" [t| JSValue |]
1530

    
1531
pTestDummySubmitJobs :: Field
1532
pTestDummySubmitJobs =
1533
  withDoc "'OpTestDummy' submit_jobs field" .
1534
  renameField "TestDummySubmitJobs" $
1535
  simpleField "submit_jobs" [t| JSValue |]
1536

    
1537
pNetworkName :: Field
1538
pNetworkName =
1539
  withDoc "Network name" $
1540
  simpleField "network_name" [t| NonEmptyString |]
1541

    
1542
pNetworkAddress4 :: Field
1543
pNetworkAddress4 =
1544
  withDoc "Network address (IPv4 subnet)" .
1545
  renameField "NetworkAddress4" $
1546
  simpleField "network" [t| IPv4Network |]
1547

    
1548
pNetworkGateway4 :: Field
1549
pNetworkGateway4 =
1550
  withDoc "Network gateway (IPv4 address)" .
1551
  renameField "NetworkGateway4" .
1552
  optionalField $ simpleField "gateway" [t| IPv4Address |]
1553

    
1554
pNetworkAddress6 :: Field
1555
pNetworkAddress6 =
1556
  withDoc "Network address (IPv6 subnet)" .
1557
  renameField "NetworkAddress6" .
1558
  optionalField $ simpleField "network6" [t| IPv6Network |]
1559

    
1560
pNetworkGateway6 :: Field
1561
pNetworkGateway6 =
1562
  withDoc "Network gateway (IPv6 address)" .
1563
  renameField "NetworkGateway6" .
1564
  optionalField $ simpleField "gateway6" [t| IPv6Address |]
1565

    
1566
pNetworkMacPrefix :: Field
1567
pNetworkMacPrefix =
1568
  withDoc "Network specific mac prefix (that overrides the cluster one)" .
1569
  renameField "NetMacPrefix" $
1570
  optionalNEStringField "mac_prefix"
1571

    
1572
pNetworkAddRsvdIps :: Field
1573
pNetworkAddRsvdIps =
1574
  withDoc "Which IP addresses to reserve" .
1575
  renameField "NetworkAddRsvdIps" .
1576
  optionalField $
1577
  simpleField "add_reserved_ips" [t| [IPv4Address] |]
1578

    
1579
pNetworkRemoveRsvdIps :: Field
1580
pNetworkRemoveRsvdIps =
1581
  withDoc "Which external IP addresses to release" .
1582
  renameField "NetworkRemoveRsvdIps" .
1583
  optionalField $
1584
  simpleField "remove_reserved_ips" [t| [IPv4Address] |]
1585

    
1586
pNetworkMode :: Field
1587
pNetworkMode =
1588
  withDoc "Network mode when connecting to a group" $
1589
  simpleField "network_mode" [t| NICMode |]
1590

    
1591
pNetworkLink :: Field
1592
pNetworkLink =
1593
  withDoc "Network link when connecting to a group" $
1594
  simpleField "network_link" [t| NonEmptyString |]