Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ d9f1d93c

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

    
252
import Control.Monad (liftM)
253
import Data.Set (Set)
254
import qualified Data.Set as Set
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

    
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
-- | Replace disks type.
306
$(declareSADT "ReplaceDisksMode"
307
  [ ("ReplaceOnPrimary",    'C.replaceDiskPri)
308
  , ("ReplaceOnSecondary",  'C.replaceDiskSec)
309
  , ("ReplaceNewSecondary", 'C.replaceDiskChg)
310
  , ("ReplaceAuto",         'C.replaceDiskAuto)
311
  ])
312
$(makeJSONInstance ''ReplaceDisksMode)
313

    
314
-- | Disk index type (embedding constraints on the index value via a
315
-- smart constructor).
316
newtype DiskIndex = DiskIndex { unDiskIndex :: Int }
317
  deriving (Show, Eq, Ord)
318

    
319
-- | Smart constructor for 'DiskIndex'.
320
mkDiskIndex :: (Monad m) => Int -> m DiskIndex
321
mkDiskIndex i | i >= 0 && i < C.maxDisks = return (DiskIndex i)
322
              | otherwise = fail $ "Invalid value for disk index '" ++
323
                            show i ++ "', required between 0 and " ++
324
                            show C.maxDisks
325

    
326
instance JSON DiskIndex where
327
  readJSON v = readJSON v >>= mkDiskIndex
328
  showJSON = showJSON . unDiskIndex
329

    
330
-- ** I* param types
331

    
332
-- | Type holding disk access modes.
333
$(declareSADT "DiskAccess"
334
  [ ("DiskReadOnly",  'C.diskRdonly)
335
  , ("DiskReadWrite", 'C.diskRdwr)
336
  ])
337
$(makeJSONInstance ''DiskAccess)
338

    
339
-- | NIC modification definition.
340
$(buildObject "INicParams" "inic"
341
  [ optionalField $ simpleField C.inicMac    [t| NonEmptyString |]
342
  , optionalField $ simpleField C.inicIp     [t| String         |]
343
  , optionalField $ simpleField C.inicMode   [t| NonEmptyString |]
344
  , optionalField $ simpleField C.inicLink   [t| NonEmptyString |]
345
  , optionalField $ simpleField C.inicName   [t| NonEmptyString |]
346
  , optionalField $ simpleField C.inicVlan   [t| NonEmptyString |]
347
  , optionalField $ simpleField C.inicBridge [t| NonEmptyString |]
348
  ])
349

    
350
-- | Disk modification definition. FIXME: disksize should be VTYPE_UNIT.
351
$(buildObject "IDiskParams" "idisk"
352
  [ optionalField $ simpleField C.idiskSize   [t| Int            |]
353
  , optionalField $ simpleField C.idiskMode   [t| DiskAccess     |]
354
  , optionalField $ simpleField C.idiskAdopt  [t| NonEmptyString |]
355
  , optionalField $ simpleField C.idiskVg     [t| NonEmptyString |]
356
  , optionalField $ simpleField C.idiskMetavg [t| NonEmptyString |]
357
  , optionalField $ simpleField C.idiskName   [t| NonEmptyString |]
358
  ])
359

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

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

    
382
instance JSON RecreateDisksInfo where
383
  readJSON = readRecreateDisks
384
  showJSON  RecreateDisksAll            = showJSON ()
385
  showJSON (RecreateDisksIndices idx)   = showJSON idx
386
  showJSON (RecreateDisksParams params) = showJSON params
387

    
388
-- | Simple type for old-style ddm changes.
389
data DdmOldChanges = DdmOldIndex (NonNegative Int)
390
                   | DdmOldMod DdmSimple
391
                     deriving (Eq, Show)
392

    
393
readDdmOldChanges :: JSValue -> Text.JSON.Result DdmOldChanges
394
readDdmOldChanges v =
395
  case readJSON v::Text.JSON.Result (NonNegative Int) of
396
    Text.JSON.Ok nn -> return $ DdmOldIndex nn
397
    _ -> case readJSON v::Text.JSON.Result DdmSimple of
398
           Text.JSON.Ok ddms -> return $ DdmOldMod ddms
399
           _ -> fail $ "Can't parse value '" ++ show (pp_value v) ++ "' as"
400
                ++ " either index or modification"
401

    
402
instance JSON DdmOldChanges where
403
  showJSON (DdmOldIndex i) = showJSON i
404
  showJSON (DdmOldMod m)   = showJSON m
405
  readJSON = readDdmOldChanges
406

    
407
-- | Instance disk or nic modifications.
408
data SetParamsMods a
409
  = SetParamsEmpty
410
  | SetParamsDeprecated (NonEmpty (DdmOldChanges, a))
411
  | SetParamsNew (NonEmpty (DdmFull, Int, a))
412
    deriving (Eq, Show)
413

    
414
-- | Custom deserialiser for 'SetParamsMods'.
415
readSetParams :: (JSON a) => JSValue -> Text.JSON.Result (SetParamsMods a)
416
readSetParams (JSArray []) = return SetParamsEmpty
417
readSetParams v =
418
  case readJSON v::Text.JSON.Result [(DdmOldChanges, JSValue)] of
419
    Text.JSON.Ok _ -> liftM SetParamsDeprecated $ readJSON v
420
    _ -> liftM SetParamsNew $ readJSON v
421

    
422
instance (JSON a) => JSON (SetParamsMods a) where
423
  showJSON SetParamsEmpty = showJSON ()
424
  showJSON (SetParamsDeprecated v) = showJSON v
425
  showJSON (SetParamsNew v) = showJSON v
426
  readJSON = readSetParams
427

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

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

    
444
instance JSON ExportTarget where
445
  showJSON (ExportTargetLocal s)  = showJSON s
446
  showJSON (ExportTargetRemote l) = showJSON l
447
  readJSON = readExportTarget
448

    
449

    
450
-- * Common opcode parameters
451

    
452
pDryRun :: Field
453
pDryRun =
454
  withDoc "Run checks only, don't execute" .
455
  optionalField $ booleanField "dry_run"
456

    
457
pDebugLevel :: Field
458
pDebugLevel =
459
  withDoc "Debug level" .
460
  optionalField $ simpleField "debug_level" [t| NonNegative Int |]
461

    
462
pOpPriority :: Field
463
pOpPriority =
464
  withDoc "Opcode priority. Note: python uses a separate constant,\
465
          \ we're using the actual value we know it's the default" .
466
  defaultField [| OpPrioNormal |] $
467
  simpleField "priority" [t| OpSubmitPriority |]
468

    
469
pDependencies :: Field
470
pDependencies =
471
  withDoc "Job dependencies" .
472
  optionalNullSerField $ simpleField "depends" [t| [JobDependency] |]
473

    
474
pComment :: Field
475
pComment =
476
  withDoc "Comment field" .
477
  optionalNullSerField $ stringField "comment"
478

    
479
pReason :: Field
480
pReason =
481
  withDoc "Reason trail field" $
482
  simpleField C.opcodeReason [t| ReasonTrail |]
483

    
484

    
485
-- * Parameters
486

    
487
pDebugSimulateErrors :: Field
488
pDebugSimulateErrors =
489
  withDoc "Whether to simulate errors (useful for debugging)" $
490
  defaultFalse "debug_simulate_errors"
491

    
492
pErrorCodes :: Field
493
pErrorCodes = 
494
  withDoc "Error codes" $
495
  defaultFalse "error_codes"
496

    
497
pSkipChecks :: Field
498
pSkipChecks = 
499
  withDoc "Which checks to skip" .
500
  defaultField [| Set.empty |] $
501
  simpleField "skip_checks" [t| Set VerifyOptionalChecks |]
502

    
503
pIgnoreErrors :: Field
504
pIgnoreErrors =
505
  withDoc "List of error codes that should be treated as warnings" .
506
  defaultField [| Set.empty |] $
507
  simpleField "ignore_errors" [t| Set CVErrorCode |]
508

    
509
pVerbose :: Field
510
pVerbose =
511
  withDoc "Verbose mode" $
512
  defaultFalse "verbose"
513

    
514
pOptGroupName :: Field
515
pOptGroupName =
516
  withDoc "Optional group name" .
517
  renameField "OptGroupName" .
518
  optionalField $ simpleField "group_name" [t| NonEmptyString |]
519

    
520
pGroupName :: Field
521
pGroupName =
522
  withDoc "Group name" $
523
  simpleField "group_name" [t| NonEmptyString |]
524

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

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

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

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

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

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

    
556
-- | Global directory for storing file-backed disks.
557
pGlobalFileStorageDir :: Field
558
pGlobalFileStorageDir = optionalNEStringField "file_storage_dir"
559

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
653
pDrbdHelper :: Field
654
pDrbdHelper =
655
  withDoc "DRBD helper program" $
656
  optionalStringField "drbd_helper"
657

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

    
663
pMasterNetdev :: Field
664
pMasterNetdev =
665
  withDoc "Master network device" $
666
  optionalStringField "master_netdev"
667

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
792
pPrimaryIp :: Field
793
pPrimaryIp =
794
  withDoc "Primary IP address" $
795
  simpleField "primary_ip" [t| NonEmptyString |]
796

    
797
pSecondaryIp :: Field
798
pSecondaryIp =
799
  withDoc "Secondary IP address" $
800
  optionalNEStringField "secondary_ip"
801

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

    
807
pNodeGroup :: Field
808
pNodeGroup =
809
  withDoc "Initial node group" $
810
  optionalNEStringField "group"
811

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

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

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

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

    
838
pStorageType :: Field
839
pStorageType =
840
  withDoc "Storage type" $
841
  simpleField "storage_type" [t| StorageType |]
842

    
843
pStorageName :: Field
844
pStorageName =
845
  withDoc "Storage name" .
846
  renameField "StorageName" .
847
  optionalField $ simpleField "name" [t| NonEmptyString |]
848

    
849
pStorageChanges :: Field
850
pStorageChanges =
851
  withDoc "Requested storage changes" $
852
  simpleField "changes" [t| JSObject JSValue |]
853

    
854
pIgnoreConsistency :: Field
855
pIgnoreConsistency =
856
  withDoc "Whether to ignore disk consistency" $
857
  defaultFalse "ignore_consistency"
858

    
859
pMasterCandidate :: Field
860
pMasterCandidate =
861
  withDoc "Whether the node should become a master candidate" .
862
  optionalField $ booleanField "master_candidate"
863

    
864
pOffline :: Field
865
pOffline =
866
  withDoc "Whether to mark the node or instance offline" .
867
  optionalField $ booleanField "offline"
868

    
869
pDrained ::Field
870
pDrained =
871
  withDoc "Whether to mark the node as drained" .
872
  optionalField $ booleanField "drained"
873

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

    
880
pPowered :: Field
881
pPowered =
882
  withDoc "Whether the node should be marked as powered" .
883
  optionalField $ booleanField "powered"
884

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

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

    
897
pMigrationTargetNode :: Field
898
pMigrationTargetNode =
899
  withDoc "Target node for instance migration/failover" $
900
  optionalNEStringField "target_node"
901

    
902
pMigrationTargetNodeUuid :: Field
903
pMigrationTargetNodeUuid =
904
  withDoc "Target node UUID for instance migration/failover" $
905
  optionalNEStringField "target_node_uuid"
906

    
907
pAllowRuntimeChgs :: Field
908
pAllowRuntimeChgs =
909
  withDoc "Whether to allow runtime changes while migrating" $
910
  defaultTrue "allow_runtime_changes"
911

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

    
923
pEarlyRelease :: Field
924
pEarlyRelease =
925
  withDoc "Whether to release locks as soon as possible" $
926
  defaultFalse "early_release"
927

    
928
pRemoteNode :: Field
929
pRemoteNode =
930
  withDoc "New secondary node" $
931
  optionalNEStringField "remote_node"
932

    
933
pRemoteNodeUuid :: Field
934
pRemoteNodeUuid =
935
  withDoc "New secondary node UUID" $
936
  optionalNEStringField "remote_node_uuid"
937

    
938
pEvacMode :: Field
939
pEvacMode =
940
  withDoc "Node evacuation mode" .
941
  renameField "EvacMode" $ simpleField "mode" [t| NodeEvacMode |]
942

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

    
948
pForceVariant :: Field
949
pForceVariant =
950
  withDoc "Whether to force an unknown OS variant" $
951
  defaultFalse "force_variant"
952

    
953
pWaitForSync :: Field
954
pWaitForSync =
955
  withDoc "Whether to wait for the disk to synchronize" $
956
  defaultTrue "wait_for_sync"
957

    
958
pNameCheck :: Field
959
pNameCheck =
960
  withDoc "Whether to check name" $
961
  defaultTrue "name_check"
962

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

    
970
pInstDisks :: Field
971
pInstDisks =
972
  withDoc "List of instance disks" .
973
  renameField "instDisks" $ simpleField "disks" [t| [IDiskParams] |]
974

    
975
pDiskTemplate :: Field
976
pDiskTemplate =
977
  withDoc "List of instance disks" $
978
  simpleField "disk_template" [t| DiskTemplate |]
979

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

    
985
pFileStorageDir :: Field
986
pFileStorageDir =
987
  withDoc "Directory for storing file-backed disks" $
988
  optionalNEStringField "file_storage_dir"
989

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

    
997
pHypervisor :: Field
998
pHypervisor =
999
  withDoc "Selected hypervisor for an instance" .
1000
  optionalField $
1001
  simpleField "hypervisor" [t| Hypervisor |]
1002

    
1003
pResetDefaults :: Field
1004
pResetDefaults =
1005
  withDoc "Reset instance parameters to default if equal" $
1006
  defaultFalse "identify_defaults"
1007

    
1008
pIpCheck :: Field
1009
pIpCheck =
1010
  withDoc "Whether to ensure instance's IP address is inactive" $
1011
  defaultTrue "ip_check"
1012

    
1013
pIpConflictsCheck :: Field
1014
pIpConflictsCheck =
1015
  withDoc "Whether to check for conflicting IP addresses" $
1016
  defaultTrue "conflicts_check"
1017

    
1018
pInstCreateMode :: Field
1019
pInstCreateMode =
1020
  withDoc "Instance creation mode" .
1021
  renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
1022

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

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

    
1033
pInstOs :: Field
1034
pInstOs =
1035
  withDoc "OS type for instance installation" $
1036
  optionalNEStringField "os_type"
1037

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

    
1045
pPrimaryNode :: Field
1046
pPrimaryNode =
1047
  withDoc "Primary node for an instance" $
1048
  optionalNEStringField "pnode"
1049

    
1050
pPrimaryNodeUuid :: Field
1051
pPrimaryNodeUuid =
1052
  withDoc "Primary node UUID for an instance" $
1053
  optionalNEStringField "pnode_uuid"
1054

    
1055
pSecondaryNode :: Field
1056
pSecondaryNode =
1057
  withDoc "Secondary node for an instance" $
1058
  optionalNEStringField "snode"
1059

    
1060
pSecondaryNodeUuid :: Field
1061
pSecondaryNodeUuid =
1062
  withDoc "Secondary node UUID for an instance" $
1063
  optionalNEStringField "snode_uuid"
1064

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

    
1070
pSourceInstance :: Field
1071
pSourceInstance =
1072
  withDoc "Source instance name (remote import only)" $
1073
  optionalNEStringField "source_instance_name"
1074

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

    
1083
pSourceX509Ca :: Field
1084
pSourceX509Ca =
1085
  withDoc "Source X509 CA in PEM format (remote import only)" $
1086
  optionalNEStringField "source_x509_ca"
1087

    
1088
pSrcNode :: Field
1089
pSrcNode =
1090
  withDoc "Source node for import" $
1091
  optionalNEStringField "src_node"
1092

    
1093
pSrcNodeUuid :: Field
1094
pSrcNodeUuid =
1095
  withDoc "Source node UUID for import" $
1096
  optionalNEStringField "src_node_uuid"
1097

    
1098
pSrcPath :: Field
1099
pSrcPath =
1100
  withDoc "Source directory for import" $
1101
  optionalNEStringField "src_path"
1102

    
1103
pStartInstance :: Field
1104
pStartInstance =
1105
  withDoc "Whether to start instance after creation" $
1106
  defaultTrue "start"
1107

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
1493
pJQueueNotifyWaitLock :: Field
1494
pJQueueNotifyWaitLock =
1495
  withDoc "'OpTestJqueue' notify_waitlock" $
1496
  defaultFalse "notify_waitlock"
1497

    
1498
pJQueueNotifyExec :: Field
1499
pJQueueNotifyExec =
1500
  withDoc "'OpTestJQueue' notify_exec" $
1501
  defaultFalse "notify_exec"
1502

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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