Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ 06c2fb4a

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

    
251
import Control.Monad (liftM)
252
import qualified Data.Set as Set
253
import Text.JSON (readJSON, showJSON, JSON, JSValue(..), fromJSString,
254
                  JSObject, toJSObject)
255
import qualified Text.JSON
256
import Text.JSON.Pretty (pp_value)
257

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

    
265
-- * Helper functions and types
266

    
267
-- * Type aliases
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
-- | Unchecked value, should be replaced by a better definition.
294
type UncheckedValue = JSValue
295

    
296
-- | Unchecked dict, should be replaced by a better definition.
297
type UncheckedDict = JSObject JSValue
298

    
299
-- | Unchecked list, shoild be replaced by a better definition.
300
type UncheckedList = [JSValue]
301

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

    
311
-- ** Tags
312

    
313
-- | Data type representing what items do the tag operations apply to.
314
$(declareSADT "TagType"
315
  [ ("TagTypeInstance", 'C.tagInstance)
316
  , ("TagTypeNode",     'C.tagNode)
317
  , ("TagTypeGroup",    'C.tagNodegroup)
318
  , ("TagTypeCluster",  'C.tagCluster)
319
  , ("TagTypeNetwork",  'C.tagNetwork)
320
  ])
321
$(makeJSONInstance ''TagType)
322

    
323
-- | Data type holding a tag object (type and object name).
324
data TagObject = TagInstance String
325
               | TagNode     String
326
               | TagGroup    String
327
               | TagNetwork  String
328
               | TagCluster
329
               deriving (Show, Eq)
330

    
331
-- | Tag type for a given tag object.
332
tagTypeOf :: TagObject -> TagType
333
tagTypeOf (TagInstance {}) = TagTypeInstance
334
tagTypeOf (TagNode     {}) = TagTypeNode
335
tagTypeOf (TagGroup    {}) = TagTypeGroup
336
tagTypeOf (TagCluster  {}) = TagTypeCluster
337
tagTypeOf (TagNetwork  {}) = TagTypeNetwork
338

    
339
-- | Gets the potential tag object name.
340
tagNameOf :: TagObject -> Maybe String
341
tagNameOf (TagInstance s) = Just s
342
tagNameOf (TagNode     s) = Just s
343
tagNameOf (TagGroup    s) = Just s
344
tagNameOf (TagNetwork  s) = Just s
345
tagNameOf  TagCluster     = Nothing
346

    
347
-- | Builds a 'TagObject' from a tag type and name.
348
tagObjectFrom :: (Monad m) => TagType -> JSValue -> m TagObject
349
tagObjectFrom TagTypeInstance (JSString s) =
350
  return . TagInstance $ fromJSString s
351
tagObjectFrom TagTypeNode     (JSString s) = return . TagNode $ fromJSString s
352
tagObjectFrom TagTypeGroup    (JSString s) = return . TagGroup $ fromJSString s
353
tagObjectFrom TagTypeNetwork  (JSString s) =
354
  return . TagNetwork $ fromJSString s
355
tagObjectFrom TagTypeCluster   JSNull      = return TagCluster
356
tagObjectFrom t v =
357
  fail $ "Invalid tag type/name combination: " ++ show t ++ "/" ++
358
         show (pp_value v)
359

    
360
-- | Name of the tag \"name\" field.
361
tagNameField :: String
362
tagNameField = "name"
363

    
364
-- | Custom encoder for 'TagObject' as represented in an opcode.
365
encodeTagObject :: TagObject -> (JSValue, [(String, JSValue)])
366
encodeTagObject t = ( showJSON (tagTypeOf t)
367
                    , [(tagNameField, maybe JSNull showJSON (tagNameOf t))] )
368

    
369
-- | Custom decoder for 'TagObject' as represented in an opcode.
370
decodeTagObject :: (Monad m) => [(String, JSValue)] -> JSValue -> m TagObject
371
decodeTagObject obj kind = do
372
  ttype <- fromJVal kind
373
  tname <- fromObj obj tagNameField
374
  tagObjectFrom ttype tname
375

    
376
-- ** Disks
377

    
378
-- | Replace disks type.
379
$(declareSADT "ReplaceDisksMode"
380
  [ ("ReplaceOnPrimary",    'C.replaceDiskPri)
381
  , ("ReplaceOnSecondary",  'C.replaceDiskSec)
382
  , ("ReplaceNewSecondary", 'C.replaceDiskChg)
383
  , ("ReplaceAuto",         'C.replaceDiskAuto)
384
  ])
385
$(makeJSONInstance ''ReplaceDisksMode)
386

    
387
-- | Disk index type (embedding constraints on the index value via a
388
-- smart constructor).
389
newtype DiskIndex = DiskIndex { unDiskIndex :: Int }
390
  deriving (Show, Eq, Ord)
391

    
392
-- | Smart constructor for 'DiskIndex'.
393
mkDiskIndex :: (Monad m) => Int -> m DiskIndex
394
mkDiskIndex i | i >= 0 && i < C.maxDisks = return (DiskIndex i)
395
              | otherwise = fail $ "Invalid value for disk index '" ++
396
                            show i ++ "', required between 0 and " ++
397
                            show C.maxDisks
398

    
399
instance JSON DiskIndex where
400
  readJSON v = readJSON v >>= mkDiskIndex
401
  showJSON = showJSON . unDiskIndex
402

    
403
-- ** I* param types
404

    
405
-- | Type holding disk access modes.
406
$(declareSADT "DiskAccess"
407
  [ ("DiskReadOnly",  'C.diskRdonly)
408
  , ("DiskReadWrite", 'C.diskRdwr)
409
  ])
410
$(makeJSONInstance ''DiskAccess)
411

    
412
-- | NIC modification definition.
413
$(buildObject "INicParams" "inic"
414
  [ optionalField $ simpleField C.inicMac  [t| NonEmptyString |]
415
  , optionalField $ simpleField C.inicIp   [t| String         |]
416
  , optionalField $ simpleField C.inicMode [t| NonEmptyString |]
417
  , optionalField $ simpleField C.inicLink [t| NonEmptyString |]
418
  , optionalField $ simpleField C.inicName [t| NonEmptyString |]
419
  ])
420

    
421
-- | Disk modification definition. FIXME: disksize should be VTYPE_UNIT.
422
$(buildObject "IDiskParams" "idisk"
423
  [ optionalField $ simpleField C.idiskSize   [t| Int            |]
424
  , optionalField $ simpleField C.idiskMode   [t| DiskAccess     |]
425
  , optionalField $ simpleField C.idiskAdopt  [t| NonEmptyString |]
426
  , optionalField $ simpleField C.idiskVg     [t| NonEmptyString |]
427
  , optionalField $ simpleField C.idiskMetavg [t| NonEmptyString |]
428
  , optionalField $ simpleField C.idiskName   [t| NonEmptyString |]
429
  ])
430

    
431
-- | Disk snapshot definition.
432
$(buildObject "ISnapParams" "idisk"
433
  [ simpleField C.idiskSnapshotName [t| NonEmptyString |]])
434

    
435
-- | Disk changes type for OpInstanceRecreateDisks. This is a bit
436
-- strange, because the type in Python is something like Either
437
-- [DiskIndex] [DiskChanges], but we can't represent the type of an
438
-- empty list in JSON, so we have to add a custom case for the empty
439
-- list.
440
data RecreateDisksInfo
441
  = RecreateDisksAll
442
  | RecreateDisksIndices (NonEmpty DiskIndex)
443
  | RecreateDisksParams (NonEmpty (DiskIndex, IDiskParams))
444
    deriving (Eq, Show)
445

    
446
readRecreateDisks :: JSValue -> Text.JSON.Result RecreateDisksInfo
447
readRecreateDisks (JSArray []) = return RecreateDisksAll
448
readRecreateDisks v =
449
  case readJSON v::Text.JSON.Result [DiskIndex] of
450
    Text.JSON.Ok indices -> liftM RecreateDisksIndices (mkNonEmpty indices)
451
    _ -> case readJSON v::Text.JSON.Result [(DiskIndex, IDiskParams)] of
452
           Text.JSON.Ok params -> liftM RecreateDisksParams (mkNonEmpty params)
453
           _ -> fail $ "Can't parse disk information as either list of disk"
454
                ++ " indices or list of disk parameters; value received:"
455
                ++ show (pp_value v)
456

    
457
instance JSON RecreateDisksInfo where
458
  readJSON = readRecreateDisks
459
  showJSON  RecreateDisksAll            = showJSON ()
460
  showJSON (RecreateDisksIndices idx)   = showJSON idx
461
  showJSON (RecreateDisksParams params) = showJSON params
462

    
463
-- | Simple type for old-style ddm changes.
464
data DdmOldChanges = DdmOldIndex (NonNegative Int)
465
                   | DdmOldMod DdmSimple
466
                     deriving (Eq, Show)
467

    
468
readDdmOldChanges :: JSValue -> Text.JSON.Result DdmOldChanges
469
readDdmOldChanges v =
470
  case readJSON v::Text.JSON.Result (NonNegative Int) of
471
    Text.JSON.Ok nn -> return $ DdmOldIndex nn
472
    _ -> case readJSON v::Text.JSON.Result DdmSimple of
473
           Text.JSON.Ok ddms -> return $ DdmOldMod ddms
474
           _ -> fail $ "Can't parse value '" ++ show (pp_value v) ++ "' as"
475
                ++ " either index or modification"
476

    
477
instance JSON DdmOldChanges where
478
  showJSON (DdmOldIndex i) = showJSON i
479
  showJSON (DdmOldMod m)   = showJSON m
480
  readJSON = readDdmOldChanges
481

    
482
-- | Instance disk or nic modifications.
483
data SetParamsMods a
484
  = SetParamsEmpty
485
  | SetParamsDeprecated (NonEmpty (DdmOldChanges, a))
486
  | SetParamsNew (NonEmpty (DdmFull, Int, a))
487
    deriving (Eq, Show)
488

    
489
-- | Custom deserialiser for 'SetParamsMods'.
490
readSetParams :: (JSON a) => JSValue -> Text.JSON.Result (SetParamsMods a)
491
readSetParams (JSArray []) = return SetParamsEmpty
492
readSetParams v =
493
  case readJSON v::Text.JSON.Result [(DdmOldChanges, JSValue)] of
494
    Text.JSON.Ok _ -> liftM SetParamsDeprecated $ readJSON v
495
    _ -> liftM SetParamsNew $ readJSON v
496

    
497
instance (JSON a) => JSON (SetParamsMods a) where
498
  showJSON SetParamsEmpty = showJSON ()
499
  showJSON (SetParamsDeprecated v) = showJSON v
500
  showJSON (SetParamsNew v) = showJSON v
501
  readJSON = readSetParams
502

    
503
-- | Instance snapshot params
504
data SetSnapParams a
505
  = SetSnapParamsEmpty
506
  | SetSnapParamsValid (NonEmpty (Int, a))
507
    deriving (Eq, Show)
508

    
509
readSetSnapParams :: (JSON a) => JSValue -> Text.JSON.Result (SetSnapParams a)
510
readSetSnapParams (JSArray []) = return SetSnapParamsEmpty
511
readSetSnapParams v =
512
  case readJSON v::Text.JSON.Result [(Int, JSValue)] of
513
    Text.JSON.Ok _ -> liftM SetSnapParamsValid $ readJSON v
514
    _ -> fail "Cannot parse snapshot params."
515

    
516
instance (JSON a) => JSON (SetSnapParams a) where
517
  showJSON SetSnapParamsEmpty = showJSON ()
518
  showJSON (SetSnapParamsValid v) = showJSON v
519
  readJSON = readSetSnapParams
520

    
521
-- | Custom type for target_node parameter of OpBackupExport, which
522
-- varies depending on mode. FIXME: this uses an UncheckedList since
523
-- we don't care about individual rows (just like the Python code
524
-- tests). But the proper type could be parsed if we wanted.
525
data ExportTarget = ExportTargetLocal NonEmptyString
526
                  | ExportTargetRemote UncheckedList
527
                    deriving (Eq, Show)
528

    
529
-- | Custom reader for 'ExportTarget'.
530
readExportTarget :: JSValue -> Text.JSON.Result ExportTarget
531
readExportTarget (JSString s) = liftM ExportTargetLocal $
532
                                mkNonEmpty (fromJSString s)
533
readExportTarget (JSArray arr) = return $ ExportTargetRemote arr
534
readExportTarget v = fail $ "Invalid value received for 'target_node': " ++
535
                     show (pp_value v)
536

    
537
instance JSON ExportTarget where
538
  showJSON (ExportTargetLocal s)  = showJSON s
539
  showJSON (ExportTargetRemote l) = showJSON l
540
  readJSON = readExportTarget
541

    
542
-- * Parameters
543

    
544
-- | A required instance name (for single-instance LUs).
545
pInstanceName :: Field
546
pInstanceName = simpleField "instance_name" [t| String |]
547

    
548
-- | A list of instances.
549
pInstances :: Field
550
pInstances = defaultField [| [] |] $
551
             simpleField "instances" [t| [NonEmptyString] |]
552

    
553
-- | A generic name.
554
pName :: Field
555
pName = simpleField "name" [t| NonEmptyString |]
556

    
557
-- | Tags list.
558
pTagsList :: Field
559
pTagsList = simpleField "tags" [t| [String] |]
560

    
561
-- | Tags object.
562
pTagsObject :: Field
563
pTagsObject =
564
  customField 'decodeTagObject 'encodeTagObject [tagNameField] $
565
  simpleField "kind" [t| TagObject |]
566

    
567
-- | Selected output fields.
568
pOutputFields :: Field
569
pOutputFields = simpleField "output_fields" [t| [NonEmptyString] |]
570

    
571
-- | How long to wait for instance to shut down.
572
pShutdownTimeout :: Field
573
pShutdownTimeout = defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
574
                   simpleField "shutdown_timeout" [t| NonNegative Int |]
575

    
576
-- | Another name for the shutdown timeout, because we like to be
577
-- inconsistent.
578
pShutdownTimeout' :: Field
579
pShutdownTimeout' =
580
  renameField "InstShutdownTimeout" .
581
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
582
  simpleField "timeout" [t| NonNegative Int |]
583

    
584
-- | Whether to shutdown the instance in backup-export.
585
pShutdownInstance :: Field
586
pShutdownInstance = defaultTrue "shutdown"
587

    
588
-- | Whether to force the operation.
589
pForce :: Field
590
pForce = defaultFalse "force"
591

    
592
-- | Whether to ignore offline nodes.
593
pIgnoreOfflineNodes :: Field
594
pIgnoreOfflineNodes = defaultFalse "ignore_offline_nodes"
595

    
596
-- | A required node name (for single-node LUs).
597
pNodeName :: Field
598
pNodeName = simpleField "node_name" [t| NonEmptyString |]
599

    
600
-- | List of nodes.
601
pNodeNames :: Field
602
pNodeNames =
603
  defaultField [| [] |] $ simpleField "node_names" [t| [NonEmptyString] |]
604

    
605
-- | A required node group name (for single-group LUs).
606
pGroupName :: Field
607
pGroupName = simpleField "group_name" [t| NonEmptyString |]
608

    
609
-- | Migration type (live\/non-live).
610
pMigrationMode :: Field
611
pMigrationMode =
612
  renameField "MigrationMode" .
613
  optionalField $
614
  simpleField "mode" [t| MigrationMode |]
615

    
616
-- | Obsolete \'live\' migration mode (boolean).
617
pMigrationLive :: Field
618
pMigrationLive =
619
  renameField "OldLiveMode" . optionalField $ booleanField "live"
620

    
621
-- | Migration cleanup parameter.
622
pMigrationCleanup :: Field
623
pMigrationCleanup = renameField "MigrationCleanup" $ defaultFalse "cleanup"
624

    
625
-- | Whether to force an unknown OS variant.
626
pForceVariant :: Field
627
pForceVariant = defaultFalse "force_variant"
628

    
629
-- | Whether to wait for the disk to synchronize.
630
pWaitForSync :: Field
631
pWaitForSync = defaultTrue "wait_for_sync"
632

    
633
-- | Whether to wait for the disk to synchronize (defaults to false).
634
pWaitForSyncFalse :: Field
635
pWaitForSyncFalse = defaultField [| False |] pWaitForSync
636

    
637
-- | Whether to ignore disk consistency
638
pIgnoreConsistency :: Field
639
pIgnoreConsistency = defaultFalse "ignore_consistency"
640

    
641
-- | Storage name.
642
pStorageName :: Field
643
pStorageName =
644
  renameField "StorageName" $ simpleField "name" [t| NonEmptyString |]
645

    
646
-- | Whether to use synchronization.
647
pUseLocking :: Field
648
pUseLocking = defaultFalse "use_locking"
649

    
650
-- | Whether to employ opportunistic locking for nodes, meaning nodes already
651
-- locked by another opcode won't be considered for instance allocation (only
652
-- when an iallocator is used).
653
pOpportunisticLocking :: Field
654
pOpportunisticLocking = defaultFalse "opportunistic_locking"
655

    
656
-- | Whether to check name.
657
pNameCheck :: Field
658
pNameCheck = defaultTrue "name_check"
659

    
660
-- | Instance allocation policy.
661
pNodeGroupAllocPolicy :: Field
662
pNodeGroupAllocPolicy = optionalField $
663
                        simpleField "alloc_policy" [t| AllocPolicy |]
664

    
665
-- | Default node parameters for group.
666
pGroupNodeParams :: Field
667
pGroupNodeParams = optionalField $ simpleField "ndparams" [t| UncheckedDict |]
668

    
669
-- | Resource(s) to query for.
670
pQueryWhat :: Field
671
pQueryWhat = simpleField "what" [t| Qlang.QueryTypeOp |]
672

    
673
-- | Whether to release locks as soon as possible.
674
pEarlyRelease :: Field
675
pEarlyRelease = defaultFalse "early_release"
676

    
677
-- | Whether to ensure instance's IP address is inactive.
678
pIpCheck :: Field
679
pIpCheck = defaultTrue "ip_check"
680

    
681
-- | Check for conflicting IPs.
682
pIpConflictsCheck :: Field
683
pIpConflictsCheck = defaultTrue "conflicts_check"
684

    
685
-- | Do not remember instance state changes.
686
pNoRemember :: Field
687
pNoRemember = defaultFalse "no_remember"
688

    
689
-- | Target node for instance migration/failover.
690
pMigrationTargetNode :: Field
691
pMigrationTargetNode = optionalNEStringField "target_node"
692

    
693
-- | Target node for instance move (required).
694
pMoveTargetNode :: Field
695
pMoveTargetNode =
696
  renameField "MoveTargetNode" $
697
  simpleField "target_node" [t| NonEmptyString |]
698

    
699
-- | Pause instance at startup.
700
pStartupPaused :: Field
701
pStartupPaused = defaultFalse "startup_paused"
702

    
703
-- | Verbose mode.
704
pVerbose :: Field
705
pVerbose = defaultFalse "verbose"
706

    
707
-- ** Parameters for cluster verification
708

    
709
-- | Whether to simulate errors (useful for debugging).
710
pDebugSimulateErrors :: Field
711
pDebugSimulateErrors = defaultFalse "debug_simulate_errors"
712

    
713
-- | Error codes.
714
pErrorCodes :: Field
715
pErrorCodes = defaultFalse "error_codes"
716

    
717
-- | Which checks to skip.
718
pSkipChecks :: Field
719
pSkipChecks = defaultField [| Set.empty |] $
720
              simpleField "skip_checks" [t| Set.Set VerifyOptionalChecks |]
721

    
722
-- | List of error codes that should be treated as warnings.
723
pIgnoreErrors :: Field
724
pIgnoreErrors = defaultField [| Set.empty |] $
725
                simpleField "ignore_errors" [t| Set.Set CVErrorCode |]
726

    
727
-- | Optional group name.
728
pOptGroupName :: Field
729
pOptGroupName = renameField "OptGroupName" .
730
                optionalField $ simpleField "group_name" [t| NonEmptyString |]
731

    
732
-- | Disk templates' parameter defaults.
733
pDiskParams :: Field
734
pDiskParams = optionalField $
735
              simpleField "diskparams" [t| GenericContainer DiskTemplate
736
                                           UncheckedDict |]
737

    
738
-- | Whether to hotplug device.
739
pHotplug :: Field
740
pHotplug = defaultFalse "hotplug"
741

    
742
pHotplugIfPossible :: Field
743
pHotplugIfPossible = defaultFalse "hotplug_if_possible"
744

    
745
-- * Parameters for node resource model
746

    
747
-- | Set hypervisor states.
748
pHvState :: Field
749
pHvState = optionalField $ simpleField "hv_state" [t| UncheckedDict |]
750

    
751
-- | Set disk states.
752
pDiskState :: Field
753
pDiskState = optionalField $ simpleField "disk_state" [t| UncheckedDict |]
754

    
755
-- | Whether to ignore ipolicy violations.
756
pIgnoreIpolicy :: Field
757
pIgnoreIpolicy = defaultFalse "ignore_ipolicy"
758

    
759
-- | Allow runtime changes while migrating.
760
pAllowRuntimeChgs :: Field
761
pAllowRuntimeChgs = defaultTrue "allow_runtime_changes"
762

    
763
-- | Utility type for OpClusterSetParams.
764
type TestClusterOsListItem = (DdmSimple, NonEmptyString)
765

    
766
-- | Utility type of OsList.
767
type TestClusterOsList = [TestClusterOsListItem]
768

    
769
-- Utility type for NIC definitions.
770
--type TestNicDef = INicParams
771

    
772
-- | List of instance disks.
773
pInstDisks :: Field
774
pInstDisks = renameField "instDisks" $ simpleField "disks" [t| [IDiskParams] |]
775

    
776
-- | List of instance snaps.
777
pInstSnaps :: Field
778
pInstSnaps =
779
  renameField "instSnaps" $
780
  simpleField "disks" [t| SetSnapParams ISnapParams |]
781

    
782
-- | Instance disk template.
783
pDiskTemplate :: Field
784
pDiskTemplate = simpleField "disk_template" [t| DiskTemplate |]
785

    
786
-- | Instance disk template.
787
pOptDiskTemplate :: Field
788
pOptDiskTemplate =
789
  optionalField .
790
  renameField "OptDiskTemplate" $
791
  simpleField "disk_template" [t| DiskTemplate |]
792

    
793
-- | File driver.
794
pFileDriver :: Field
795
pFileDriver = optionalField $ simpleField "file_driver" [t| FileDriver |]
796

    
797
-- | Directory for storing file-backed disks.
798
pFileStorageDir :: Field
799
pFileStorageDir = optionalNEStringField "file_storage_dir"
800

    
801
-- | Volume group name.
802
pVgName :: Field
803
pVgName = optionalStringField "vg_name"
804

    
805
-- | List of enabled hypervisors.
806
pEnabledHypervisors :: Field
807
pEnabledHypervisors =
808
  optionalField $
809
  simpleField "enabled_hypervisors" [t| NonEmpty Hypervisor |]
810

    
811
-- | List of enabled disk templates.
812
pEnabledDiskTemplates :: Field
813
pEnabledDiskTemplates =
814
  optionalField $
815
  simpleField "enabled_disk_templates" [t| NonEmpty DiskTemplate |]
816

    
817
-- | Selected hypervisor for an instance.
818
pHypervisor :: Field
819
pHypervisor =
820
  optionalField $
821
  simpleField "hypervisor" [t| Hypervisor |]
822

    
823
-- | Cluster-wide hypervisor parameters, hypervisor-dependent.
824
pClusterHvParams :: Field
825
pClusterHvParams =
826
  renameField "ClusterHvParams" .
827
  optionalField $
828
  simpleField "hvparams" [t| Container UncheckedDict |]
829

    
830
-- | Instance hypervisor parameters.
831
pInstHvParams :: Field
832
pInstHvParams =
833
  renameField "InstHvParams" .
834
  defaultField [| toJSObject [] |] $
835
  simpleField "hvparams" [t| UncheckedDict |]
836

    
837
-- | Cluster-wide beparams.
838
pClusterBeParams :: Field
839
pClusterBeParams =
840
  renameField "ClusterBeParams" .
841
  optionalField $ simpleField "beparams" [t| UncheckedDict |]
842

    
843
-- | Instance beparams.
844
pInstBeParams :: Field
845
pInstBeParams =
846
  renameField "InstBeParams" .
847
  defaultField [| toJSObject [] |] $
848
  simpleField "beparams" [t| UncheckedDict |]
849

    
850
-- | Reset instance parameters to default if equal.
851
pResetDefaults :: Field
852
pResetDefaults = defaultFalse "identify_defaults"
853

    
854
-- | Cluster-wide per-OS hypervisor parameter defaults.
855
pOsHvp :: Field
856
pOsHvp = optionalField $ simpleField "os_hvp" [t| Container UncheckedDict |]
857

    
858
-- | Cluster-wide OS parameter defaults.
859
pClusterOsParams :: Field
860
pClusterOsParams =
861
  renameField "ClusterOsParams" .
862
  optionalField $ simpleField "osparams" [t| Container UncheckedDict |]
863

    
864
-- | Instance OS parameters.
865
pInstOsParams :: Field
866
pInstOsParams =
867
  renameField "InstOsParams" . defaultField [| toJSObject [] |] $
868
  simpleField "osparams" [t| UncheckedDict |]
869

    
870
-- | Temporary OS parameters (currently only in reinstall, might be
871
-- added to install as well).
872
pTempOsParams :: Field
873
pTempOsParams =
874
  renameField "TempOsParams" .
875
  optionalField $ simpleField "osparams" [t| UncheckedDict |]
876

    
877
-- | Temporary hypervisor parameters, hypervisor-dependent.
878
pTempHvParams :: Field
879
pTempHvParams =
880
  renameField "TempHvParams" .
881
  defaultField [| toJSObject [] |] $
882
  simpleField "hvparams" [t| UncheckedDict |]
883

    
884
-- | Temporary backend parameters.
885
pTempBeParams :: Field
886
pTempBeParams =
887
  renameField "TempBeParams" .
888
  defaultField [| toJSObject [] |] $
889
  simpleField "beparams" [t| UncheckedDict |]
890

    
891
-- | Candidate pool size.
892
pCandidatePoolSize :: Field
893
pCandidatePoolSize =
894
  optionalField $ simpleField "candidate_pool_size" [t| Positive Int |]
895

    
896
-- | Set UID pool, must be list of lists describing UID ranges (two
897
-- items, start and end inclusive.
898
pUidPool :: Field
899
pUidPool = optionalField $ simpleField "uid_pool" [t| [[(Int, Int)]] |]
900

    
901
-- | Extend UID pool, must be list of lists describing UID ranges (two
902
-- items, start and end inclusive.
903
pAddUids :: Field
904
pAddUids = optionalField $ simpleField "add_uids" [t| [[(Int, Int)]] |]
905

    
906
-- | Shrink UID pool, must be list of lists describing UID ranges (two
907
-- items, start and end inclusive) to be removed.
908
pRemoveUids :: Field
909
pRemoveUids = optionalField $ simpleField "remove_uids" [t| [[(Int, Int)]] |]
910

    
911
-- | Whether to automatically maintain node health.
912
pMaintainNodeHealth :: Field
913
pMaintainNodeHealth = optionalField $ booleanField "maintain_node_health"
914

    
915
-- | Whether to modify and keep in sync the @/etc/hosts@ files of nodes.
916
pModifyEtcHosts :: Field
917
pModifyEtcHosts = optionalField $ booleanField "modify_etc_hosts"
918

    
919
-- | Whether to wipe disks before allocating them to instances.
920
pPreallocWipeDisks :: Field
921
pPreallocWipeDisks = optionalField $ booleanField "prealloc_wipe_disks"
922

    
923
-- | Cluster-wide NIC parameter defaults.
924
pNicParams :: Field
925
pNicParams = optionalField $ simpleField "nicparams" [t| INicParams |]
926

    
927
-- | Instance NIC definitions.
928
pInstNics :: Field
929
pInstNics = simpleField "nics" [t| [INicParams] |]
930

    
931
-- | Cluster-wide node parameter defaults.
932
pNdParams :: Field
933
pNdParams = optionalField $ simpleField "ndparams" [t| UncheckedDict |]
934

    
935
-- | Cluster-wide ipolicy specs.
936
pIpolicy :: Field
937
pIpolicy = optionalField $ simpleField "ipolicy" [t| UncheckedDict |]
938

    
939
-- | DRBD helper program.
940
pDrbdHelper :: Field
941
pDrbdHelper = optionalStringField "drbd_helper"
942

    
943
-- | Default iallocator for cluster.
944
pDefaultIAllocator :: Field
945
pDefaultIAllocator = optionalStringField "default_iallocator"
946

    
947
-- | Master network device.
948
pMasterNetdev :: Field
949
pMasterNetdev = optionalStringField "master_netdev"
950

    
951
-- | Netmask of the master IP.
952
pMasterNetmask :: Field
953
pMasterNetmask =
954
  optionalField $ simpleField "master_netmask" [t| NonNegative Int |]
955

    
956
-- | List of reserved LVs.
957
pReservedLvs :: Field
958
pReservedLvs =
959
  optionalField $ simpleField "reserved_lvs" [t| [NonEmptyString] |]
960

    
961
-- | Modify list of hidden operating systems: each modification must
962
-- have two items, the operation and the OS name; the operation can be
963
-- add or remove.
964
pHiddenOs :: Field
965
pHiddenOs = optionalField $ simpleField "hidden_os" [t| TestClusterOsList |]
966

    
967
-- | Modify list of blacklisted operating systems: each modification
968
-- must have two items, the operation and the OS name; the operation
969
-- can be add or remove.
970
pBlacklistedOs :: Field
971
pBlacklistedOs =
972
  optionalField $ simpleField "blacklisted_os" [t| TestClusterOsList |]
973

    
974
-- | Whether to use an external master IP address setup script.
975
pUseExternalMipScript :: Field
976
pUseExternalMipScript = optionalField $ booleanField "use_external_mip_script"
977

    
978
-- | Requested fields.
979
pQueryFields :: Field
980
pQueryFields = simpleField "fields" [t| [NonEmptyString] |]
981

    
982
-- | Query filter.
983
pQueryFilter :: Field
984
pQueryFilter = simpleField "qfilter" [t| Qlang.Filter String |]
985

    
986
-- | OOB command to run.
987
pOobCommand :: Field
988
pOobCommand = simpleField "command" [t| OobCommand |]
989

    
990
-- | Timeout before the OOB helper will be terminated.
991
pOobTimeout :: Field
992
pOobTimeout =
993
  defaultField [| C.oobTimeout |] $ simpleField "timeout" [t| Int |]
994

    
995
-- | Ignores the node offline status for power off.
996
pIgnoreStatus :: Field
997
pIgnoreStatus = defaultFalse "ignore_status"
998

    
999
-- | Time in seconds to wait between powering on nodes.
1000
pPowerDelay :: Field
1001
pPowerDelay =
1002
  -- FIXME: we can't use the proper type "NonNegative Double", since
1003
  -- the default constant is a plain Double, not a non-negative one.
1004
  defaultField [| C.oobPowerDelay |] $
1005
  simpleField "power_delay" [t| Double |]
1006

    
1007
-- | Primary IP address.
1008
pPrimaryIp :: Field
1009
pPrimaryIp = optionalStringField "primary_ip"
1010

    
1011
-- | Secondary IP address.
1012
pSecondaryIp :: Field
1013
pSecondaryIp = optionalNEStringField "secondary_ip"
1014

    
1015
-- | Whether node is re-added to cluster.
1016
pReadd :: Field
1017
pReadd = defaultFalse "readd"
1018

    
1019
-- | Initial node group.
1020
pNodeGroup :: Field
1021
pNodeGroup = optionalNEStringField "group"
1022

    
1023
-- | Whether node can become master or master candidate.
1024
pMasterCapable :: Field
1025
pMasterCapable = optionalField $ booleanField "master_capable"
1026

    
1027
-- | Whether node can host instances.
1028
pVmCapable :: Field
1029
pVmCapable = optionalField $ booleanField "vm_capable"
1030

    
1031
-- | List of names.
1032
pNames :: Field
1033
pNames = defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
1034

    
1035
-- | List of node names.
1036
pNodes :: Field
1037
pNodes = defaultField [| [] |] $ simpleField "nodes" [t| [NonEmptyString] |]
1038

    
1039
-- | Required list of node names.
1040
pRequiredNodes :: Field
1041
pRequiredNodes =
1042
  renameField "ReqNodes " $ simpleField "nodes" [t| [NonEmptyString] |]
1043

    
1044
-- | Storage type.
1045
pStorageType :: Field
1046
pStorageType = simpleField "storage_type" [t| StorageType |]
1047

    
1048
-- | Storage changes (unchecked).
1049
pStorageChanges :: Field
1050
pStorageChanges = simpleField "changes" [t| UncheckedDict |]
1051

    
1052
-- | Whether the node should become a master candidate.
1053
pMasterCandidate :: Field
1054
pMasterCandidate = optionalField $ booleanField "master_candidate"
1055

    
1056
-- | Whether the node should be marked as offline.
1057
pOffline :: Field
1058
pOffline = optionalField $ booleanField "offline"
1059

    
1060
-- | Whether the node should be marked as drained.
1061
pDrained ::Field
1062
pDrained = optionalField $ booleanField "drained"
1063

    
1064
-- | Whether node(s) should be promoted to master candidate if necessary.
1065
pAutoPromote :: Field
1066
pAutoPromote = defaultFalse "auto_promote"
1067

    
1068
-- | Whether the node should be marked as powered
1069
pPowered :: Field
1070
pPowered = optionalField $ booleanField "powered"
1071

    
1072
-- | Iallocator for deciding the target node for shared-storage
1073
-- instances during migrate and failover.
1074
pIallocator :: Field
1075
pIallocator = optionalNEStringField "iallocator"
1076

    
1077
-- | New secondary node.
1078
pRemoteNode :: Field
1079
pRemoteNode = optionalNEStringField "remote_node"
1080

    
1081
-- | Node evacuation mode.
1082
pEvacMode :: Field
1083
pEvacMode = renameField "EvacMode" $ simpleField "mode" [t| NodeEvacMode |]
1084

    
1085
-- | Instance creation mode.
1086
pInstCreateMode :: Field
1087
pInstCreateMode =
1088
  renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
1089

    
1090
-- | Do not install the OS (will disable automatic start).
1091
pNoInstall :: Field
1092
pNoInstall = optionalField $ booleanField "no_install"
1093

    
1094
-- | OS type for instance installation.
1095
pInstOs :: Field
1096
pInstOs = optionalNEStringField "os_type"
1097

    
1098
-- | Primary node for an instance.
1099
pPrimaryNode :: Field
1100
pPrimaryNode = optionalNEStringField "pnode"
1101

    
1102
-- | Secondary node for an instance.
1103
pSecondaryNode :: Field
1104
pSecondaryNode = optionalNEStringField "snode"
1105

    
1106
-- | Signed handshake from source (remote import only).
1107
pSourceHandshake :: Field
1108
pSourceHandshake =
1109
  optionalField $ simpleField "source_handshake" [t| UncheckedList |]
1110

    
1111
-- | Source instance name (remote import only).
1112
pSourceInstance :: Field
1113
pSourceInstance = optionalNEStringField "source_instance_name"
1114

    
1115
-- | How long source instance was given to shut down (remote import only).
1116
-- FIXME: non-negative int, whereas the constant is a plain int.
1117
pSourceShutdownTimeout :: Field
1118
pSourceShutdownTimeout =
1119
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1120
  simpleField "source_shutdown_timeout" [t| NonNegative Int |]
1121

    
1122
-- | Source X509 CA in PEM format (remote import only).
1123
pSourceX509Ca :: Field
1124
pSourceX509Ca = optionalNEStringField "source_x509_ca"
1125

    
1126
-- | Source node for import.
1127
pSrcNode :: Field
1128
pSrcNode = optionalNEStringField "src_node"
1129

    
1130
-- | Source directory for import.
1131
pSrcPath :: Field
1132
pSrcPath = optionalNEStringField "src_path"
1133

    
1134
-- | Whether to start instance after creation.
1135
pStartInstance :: Field
1136
pStartInstance = defaultTrue "start"
1137

    
1138
-- | Instance tags. FIXME: unify/simplify with pTags, once that
1139
-- migrates to NonEmpty String.
1140
pInstTags :: Field
1141
pInstTags =
1142
  renameField "InstTags" .
1143
  defaultField [| [] |] $
1144
  simpleField "tags" [t| [NonEmptyString] |]
1145

    
1146
-- | Unchecked list of OpInstanceCreate, used in OpInstanceMultiAlloc.
1147
pMultiAllocInstances :: Field
1148
pMultiAllocInstances =
1149
  renameField "InstMultiAlloc" .
1150
  defaultField [| [] |] $
1151
  simpleField "instances"[t| UncheckedList |]
1152

    
1153
-- | Ignore failures parameter.
1154
pIgnoreFailures :: Field
1155
pIgnoreFailures = defaultFalse "ignore_failures"
1156

    
1157
-- | New instance or cluster name.
1158
pNewName :: Field
1159
pNewName = simpleField "new_name" [t| NonEmptyString |]
1160

    
1161
-- | Whether to start the instance even if secondary disks are failing.
1162
pIgnoreSecondaries :: Field
1163
pIgnoreSecondaries = defaultFalse "ignore_secondaries"
1164

    
1165
-- | How to reboot the instance.
1166
pRebootType :: Field
1167
pRebootType = simpleField "reboot_type" [t| RebootType |]
1168

    
1169
-- | Whether to ignore recorded disk size.
1170
pIgnoreDiskSize :: Field
1171
pIgnoreDiskSize = defaultFalse "ignore_size"
1172

    
1173
-- | Disk list for recreate disks.
1174
pRecreateDisksInfo :: Field
1175
pRecreateDisksInfo =
1176
  renameField "RecreateDisksInfo" .
1177
  defaultField [| RecreateDisksAll |] $
1178
  simpleField "disks" [t| RecreateDisksInfo |]
1179

    
1180
-- | Whether to only return configuration data without querying nodes.
1181
pStatic :: Field
1182
pStatic = defaultFalse "static"
1183

    
1184
-- | InstanceSetParams NIC changes.
1185
pInstParamsNicChanges :: Field
1186
pInstParamsNicChanges =
1187
  renameField "InstNicChanges" .
1188
  defaultField [| SetParamsEmpty |] $
1189
  simpleField "nics" [t| SetParamsMods INicParams |]
1190

    
1191
-- | InstanceSetParams Disk changes.
1192
pInstParamsDiskChanges :: Field
1193
pInstParamsDiskChanges =
1194
  renameField "InstDiskChanges" .
1195
  defaultField [| SetParamsEmpty |] $
1196
  simpleField "disks" [t| SetParamsMods IDiskParams |]
1197

    
1198
-- | New runtime memory.
1199
pRuntimeMem :: Field
1200
pRuntimeMem = optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1201

    
1202
-- | Change the instance's OS without reinstalling the instance
1203
pOsNameChange :: Field
1204
pOsNameChange = optionalNEStringField "os_name"
1205

    
1206
-- | Disk index for e.g. grow disk.
1207
pDiskIndex :: Field
1208
pDiskIndex = renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
1209

    
1210
-- | Disk amount to add or grow to.
1211
pDiskChgAmount :: Field
1212
pDiskChgAmount =
1213
  renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
1214

    
1215
-- | Whether the amount parameter is an absolute target or a relative one.
1216
pDiskChgAbsolute :: Field
1217
pDiskChgAbsolute = renameField "DiskChkAbsolute" $ defaultFalse "absolute"
1218

    
1219
-- | Destination group names or UUIDs (defaults to \"all but current group\".
1220
pTargetGroups :: Field
1221
pTargetGroups =
1222
  optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
1223

    
1224
-- | Export mode field.
1225
pExportMode :: Field
1226
pExportMode =
1227
  renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1228

    
1229
-- | Export target_node field, depends on mode.
1230
pExportTargetNode :: Field
1231
pExportTargetNode =
1232
  renameField "ExportTarget" $
1233
  simpleField "target_node" [t| ExportTarget |]
1234

    
1235
-- | Whether to remove instance after export.
1236
pRemoveInstance :: Field
1237
pRemoveInstance = defaultFalse "remove_instance"
1238

    
1239
-- | Whether to ignore failures while removing instances.
1240
pIgnoreRemoveFailures :: Field
1241
pIgnoreRemoveFailures = defaultFalse "ignore_remove_failures"
1242

    
1243
-- | Name of X509 key (remote export only).
1244
pX509KeyName :: Field
1245
pX509KeyName = optionalField $ simpleField "x509_key_name" [t| UncheckedList |]
1246

    
1247
-- | Destination X509 CA (remote export only).
1248
pX509DestCA :: Field
1249
pX509DestCA = optionalNEStringField "destination_x509_ca"
1250

    
1251
-- | Search pattern (regular expression). FIXME: this should be
1252
-- compiled at load time?
1253
pTagSearchPattern :: Field
1254
pTagSearchPattern =
1255
  renameField "TagSearchPattern" $ simpleField "pattern" [t| NonEmptyString |]
1256

    
1257
-- | Restricted command name.
1258
pRestrictedCommand :: Field
1259
pRestrictedCommand =
1260
  renameField "RestrictedCommand" $
1261
  simpleField "command" [t| NonEmptyString |]
1262

    
1263
-- | Replace disks mode.
1264
pReplaceDisksMode :: Field
1265
pReplaceDisksMode =
1266
  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1267

    
1268
-- | List of disk indices.
1269
pReplaceDisksList :: Field
1270
pReplaceDisksList =
1271
  renameField "ReplaceDisksList" $ simpleField "disks" [t| [DiskIndex] |]
1272

    
1273
-- | Whether do allow failover in migrations.
1274
pAllowFailover :: Field
1275
pAllowFailover = defaultFalse "allow_failover"
1276

    
1277
-- * Test opcode parameters
1278

    
1279
-- | Duration parameter for 'OpTestDelay'.
1280
pDelayDuration :: Field
1281
pDelayDuration =
1282
  renameField "DelayDuration" $ simpleField "duration" [t| Double |]
1283

    
1284
-- | on_master field for 'OpTestDelay'.
1285
pDelayOnMaster :: Field
1286
pDelayOnMaster = renameField "DelayOnMaster" $ defaultTrue "on_master"
1287

    
1288
-- | on_nodes field for 'OpTestDelay'.
1289
pDelayOnNodes :: Field
1290
pDelayOnNodes =
1291
  renameField "DelayOnNodes" .
1292
  defaultField [| [] |] $
1293
  simpleField "on_nodes" [t| [NonEmptyString] |]
1294

    
1295
-- | Repeat parameter for OpTestDelay.
1296
pDelayRepeat :: Field
1297
pDelayRepeat =
1298
  renameField "DelayRepeat" .
1299
  defaultField [| forceNonNeg (0::Int) |] $
1300
  simpleField "repeat" [t| NonNegative Int |]
1301

    
1302
-- | IAllocator test direction.
1303
pIAllocatorDirection :: Field
1304
pIAllocatorDirection =
1305
  renameField "IAllocatorDirection" $
1306
  simpleField "direction" [t| IAllocatorTestDir |]
1307

    
1308
-- | IAllocator test mode.
1309
pIAllocatorMode :: Field
1310
pIAllocatorMode =
1311
  renameField "IAllocatorMode" $
1312
  simpleField "mode" [t| IAllocatorMode |]
1313

    
1314
-- | IAllocator target name (new instance, node to evac, etc.).
1315
pIAllocatorReqName :: Field
1316
pIAllocatorReqName =
1317
  renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
1318

    
1319
-- | Custom OpTestIAllocator nics.
1320
pIAllocatorNics :: Field
1321
pIAllocatorNics =
1322
  renameField "IAllocatorNics" $ simpleField "nics" [t| [UncheckedDict] |]
1323

    
1324
-- | Custom OpTestAllocator disks.
1325
pIAllocatorDisks :: Field
1326
pIAllocatorDisks =
1327
  renameField "IAllocatorDisks" $ simpleField "disks" [t| UncheckedList |]
1328

    
1329
-- | IAllocator memory field.
1330
pIAllocatorMemory :: Field
1331
pIAllocatorMemory =
1332
  renameField "IAllocatorMem" .
1333
  optionalField $
1334
  simpleField "memory" [t| NonNegative Int |]
1335

    
1336
-- | IAllocator vcpus field.
1337
pIAllocatorVCpus :: Field
1338
pIAllocatorVCpus =
1339
  renameField "IAllocatorVCpus" .
1340
  optionalField $
1341
  simpleField "vcpus" [t| NonNegative Int |]
1342

    
1343
-- | IAllocator os field.
1344
pIAllocatorOs :: Field
1345
pIAllocatorOs = renameField "IAllocatorOs" $ optionalNEStringField "os"
1346

    
1347
-- | IAllocator instances field.
1348
pIAllocatorInstances :: Field
1349
pIAllocatorInstances =
1350
  renameField "IAllocatorInstances " .
1351
  optionalField $
1352
  simpleField "instances" [t| [NonEmptyString] |]
1353

    
1354
-- | IAllocator evac mode.
1355
pIAllocatorEvacMode :: Field
1356
pIAllocatorEvacMode =
1357
  renameField "IAllocatorEvacMode" .
1358
  optionalField $
1359
  simpleField "evac_mode" [t| NodeEvacMode |]
1360

    
1361
-- | IAllocator spindle use.
1362
pIAllocatorSpindleUse :: Field
1363
pIAllocatorSpindleUse =
1364
  renameField "IAllocatorSpindleUse" .
1365
  defaultField [| forceNonNeg (1::Int) |] $
1366
  simpleField "spindle_use" [t| NonNegative Int |]
1367

    
1368
-- | IAllocator count field.
1369
pIAllocatorCount :: Field
1370
pIAllocatorCount =
1371
  renameField "IAllocatorCount" .
1372
  defaultField [| forceNonNeg (1::Int) |] $
1373
  simpleField "count" [t| NonNegative Int |]
1374

    
1375
-- | 'OpTestJqueue' notify_waitlock.
1376
pJQueueNotifyWaitLock :: Field
1377
pJQueueNotifyWaitLock = defaultFalse "notify_waitlock"
1378

    
1379
-- | 'OpTestJQueue' notify_exec.
1380
pJQueueNotifyExec :: Field
1381
pJQueueNotifyExec = defaultFalse "notify_exec"
1382

    
1383
-- | 'OpTestJQueue' log_messages.
1384
pJQueueLogMessages :: Field
1385
pJQueueLogMessages =
1386
  defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
1387

    
1388
-- | 'OpTestJQueue' fail attribute.
1389
pJQueueFail :: Field
1390
pJQueueFail =
1391
  renameField "JQueueFail" $ defaultFalse "fail"
1392

    
1393
-- | 'OpTestDummy' result field.
1394
pTestDummyResult :: Field
1395
pTestDummyResult =
1396
  renameField "TestDummyResult" $ simpleField "result" [t| UncheckedValue |]
1397

    
1398
-- | 'OpTestDummy' messages field.
1399
pTestDummyMessages :: Field
1400
pTestDummyMessages =
1401
  renameField "TestDummyMessages" $
1402
  simpleField "messages" [t| UncheckedValue |]
1403

    
1404
-- | 'OpTestDummy' fail field.
1405
pTestDummyFail :: Field
1406
pTestDummyFail =
1407
  renameField "TestDummyFail" $ simpleField "fail" [t| UncheckedValue |]
1408

    
1409
-- | 'OpTestDummy' submit_jobs field.
1410
pTestDummySubmitJobs :: Field
1411
pTestDummySubmitJobs =
1412
  renameField "TestDummySubmitJobs" $
1413
  simpleField "submit_jobs" [t| UncheckedValue |]
1414

    
1415
-- * Network parameters
1416

    
1417
-- | Network name.
1418
pNetworkName :: Field
1419
pNetworkName = simpleField "network_name" [t| NonEmptyString |]
1420

    
1421
-- | Network address (IPv4 subnet). FIXME: no real type for this.
1422
pNetworkAddress4 :: Field
1423
pNetworkAddress4 =
1424
  renameField "NetworkAddress4" $
1425
  simpleField "network" [t| NonEmptyString |]
1426

    
1427
-- | Network gateway (IPv4 address). FIXME: no real type for this.
1428
pNetworkGateway4 :: Field
1429
pNetworkGateway4 =
1430
  renameField "NetworkGateway4" $
1431
  optionalNEStringField "gateway"
1432

    
1433
-- | Network address (IPv6 subnet). FIXME: no real type for this.
1434
pNetworkAddress6 :: Field
1435
pNetworkAddress6 =
1436
  renameField "NetworkAddress6" $
1437
  optionalNEStringField "network6"
1438

    
1439
-- | Network gateway (IPv6 address). FIXME: no real type for this.
1440
pNetworkGateway6 :: Field
1441
pNetworkGateway6 =
1442
  renameField "NetworkGateway6" $
1443
  optionalNEStringField "gateway6"
1444

    
1445
-- | Network specific mac prefix (that overrides the cluster one).
1446
pNetworkMacPrefix :: Field
1447
pNetworkMacPrefix =
1448
  renameField "NetMacPrefix" $
1449
  optionalNEStringField "mac_prefix"
1450

    
1451
-- | Network add reserved IPs.
1452
pNetworkAddRsvdIps :: Field
1453
pNetworkAddRsvdIps =
1454
  renameField "NetworkAddRsvdIps" .
1455
  optionalField $
1456
  simpleField "add_reserved_ips" [t| [NonEmptyString] |]
1457

    
1458
-- | Network remove reserved IPs.
1459
pNetworkRemoveRsvdIps :: Field
1460
pNetworkRemoveRsvdIps =
1461
  renameField "NetworkRemoveRsvdIps" .
1462
  optionalField $
1463
  simpleField "remove_reserved_ips" [t| [NonEmptyString] |]
1464

    
1465
-- | Network mode when connecting to a group.
1466
pNetworkMode :: Field
1467
pNetworkMode = simpleField "network_mode" [t| NICMode |]
1468

    
1469
-- | Network link when connecting to a group.
1470
pNetworkLink :: Field
1471
pNetworkLink = simpleField "network_link" [t| NonEmptyString |]
1472

    
1473
-- * Common opcode parameters
1474

    
1475
-- | Run checks only, don't execute.
1476
pDryRun :: Field
1477
pDryRun = optionalField $ booleanField "dry_run"
1478

    
1479
-- | Debug level.
1480
pDebugLevel :: Field
1481
pDebugLevel = optionalField $ simpleField "debug_level" [t| NonNegative Int |]
1482

    
1483
-- | Opcode priority. Note: python uses a separate constant, we're
1484
-- using the actual value we know it's the default.
1485
pOpPriority :: Field
1486
pOpPriority =
1487
  defaultField [| OpPrioNormal |] $
1488
  simpleField "priority" [t| OpSubmitPriority |]
1489

    
1490
-- | Job dependencies.
1491
pDependencies :: Field
1492
pDependencies =
1493
  optionalNullSerField $ simpleField "depends" [t| [JobDependency] |]
1494

    
1495
-- | Comment field.
1496
pComment :: Field
1497
pComment = optionalNullSerField $ stringField "comment"
1498

    
1499
-- | Reason trail field.
1500
pReason :: Field
1501
pReason = simpleField C.opcodeReason [t| ReasonTrail |]
1502

    
1503
-- * Entire opcode parameter list
1504

    
1505
-- | Old-style query opcode, with locking.
1506
dOldQuery :: [Field]
1507
dOldQuery =
1508
  [ pOutputFields
1509
  , pNames
1510
  , pUseLocking
1511
  ]
1512

    
1513
-- | Old-style query opcode, without locking.
1514
dOldQueryNoLocking :: [Field]
1515
dOldQueryNoLocking =
1516
  [ pOutputFields
1517
  , pNames
1518
  ]