Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ 40827683

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

    
247
import Control.Monad (liftM)
248
import qualified Data.Set as Set
249
import Text.JSON (readJSON, showJSON, JSON, JSValue(..), fromJSString,
250
                  JSObject, toJSObject)
251
import qualified Text.JSON
252
import Text.JSON.Pretty (pp_value)
253

    
254
import Ganeti.BasicTypes
255
import qualified Ganeti.Constants as C
256
import Ganeti.THH
257
import Ganeti.JSON
258
import Ganeti.Types
259
import qualified Ganeti.Query.Language as Qlang
260

    
261
-- * Helper functions and types
262

    
263
-- * Type aliases
264

    
265
-- | Build a boolean field.
266
booleanField :: String -> Field
267
booleanField = flip simpleField [t| Bool |]
268

    
269
-- | Default a field to 'False'.
270
defaultFalse :: String -> Field
271
defaultFalse = defaultField [| False |] . booleanField
272

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

    
277
-- | An alias for a 'String' field.
278
stringField :: String -> Field
279
stringField = flip simpleField [t| String |]
280

    
281
-- | An alias for an optional string field.
282
optionalStringField :: String -> Field
283
optionalStringField = optionalField . stringField
284

    
285
-- | An alias for an optional non-empty string field.
286
optionalNEStringField :: String -> Field
287
optionalNEStringField = optionalField . flip simpleField [t| NonEmptyString |]
288

    
289
-- | Unchecked value, should be replaced by a better definition.
290
type UncheckedValue = JSValue
291

    
292
-- | Unchecked dict, should be replaced by a better definition.
293
type UncheckedDict = JSObject JSValue
294

    
295
-- | Unchecked list, shoild be replaced by a better definition.
296
type UncheckedList = [JSValue]
297

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

    
307
-- ** Tags
308

    
309
-- | Data type representing what items do the tag operations apply to.
310
$(declareSADT "TagType"
311
  [ ("TagTypeInstance", 'C.tagInstance)
312
  , ("TagTypeNode",     'C.tagNode)
313
  , ("TagTypeGroup",    'C.tagNodegroup)
314
  , ("TagTypeCluster",  'C.tagCluster)
315
  ])
316
$(makeJSONInstance ''TagType)
317

    
318
-- | Data type holding a tag object (type and object name).
319
data TagObject = TagInstance String
320
               | TagNode     String
321
               | TagGroup    String
322
               | TagCluster
323
               deriving (Show, Eq)
324

    
325
-- | Tag type for a given tag object.
326
tagTypeOf :: TagObject -> TagType
327
tagTypeOf (TagInstance {}) = TagTypeInstance
328
tagTypeOf (TagNode     {}) = TagTypeNode
329
tagTypeOf (TagGroup    {}) = TagTypeGroup
330
tagTypeOf (TagCluster  {}) = TagTypeCluster
331

    
332
-- | Gets the potential tag object name.
333
tagNameOf :: TagObject -> Maybe String
334
tagNameOf (TagInstance s) = Just s
335
tagNameOf (TagNode     s) = Just s
336
tagNameOf (TagGroup    s) = Just s
337
tagNameOf  TagCluster     = Nothing
338

    
339
-- | Builds a 'TagObject' from a tag type and name.
340
tagObjectFrom :: (Monad m) => TagType -> JSValue -> m TagObject
341
tagObjectFrom TagTypeInstance (JSString s) =
342
  return . TagInstance $ fromJSString s
343
tagObjectFrom TagTypeNode     (JSString s) = return . TagNode $ fromJSString s
344
tagObjectFrom TagTypeGroup    (JSString s) = return . TagGroup $ fromJSString s
345
tagObjectFrom TagTypeCluster   JSNull      = return TagCluster
346
tagObjectFrom t v =
347
  fail $ "Invalid tag type/name combination: " ++ show t ++ "/" ++
348
         show (pp_value v)
349

    
350
-- | Name of the tag \"name\" field.
351
tagNameField :: String
352
tagNameField = "name"
353

    
354
-- | Custom encoder for 'TagObject' as represented in an opcode.
355
encodeTagObject :: TagObject -> (JSValue, [(String, JSValue)])
356
encodeTagObject t = ( showJSON (tagTypeOf t)
357
                    , [(tagNameField, maybe JSNull showJSON (tagNameOf t))] )
358

    
359
-- | Custom decoder for 'TagObject' as represented in an opcode.
360
decodeTagObject :: (Monad m) => [(String, JSValue)] -> JSValue -> m TagObject
361
decodeTagObject obj kind = do
362
  ttype <- fromJVal kind
363
  tname <- fromObj obj tagNameField
364
  tagObjectFrom ttype tname
365

    
366
-- ** Disks
367

    
368
-- | Replace disks type.
369
$(declareSADT "ReplaceDisksMode"
370
  [ ("ReplaceOnPrimary",    'C.replaceDiskPri)
371
  , ("ReplaceOnSecondary",  'C.replaceDiskSec)
372
  , ("ReplaceNewSecondary", 'C.replaceDiskChg)
373
  , ("ReplaceAuto",         'C.replaceDiskAuto)
374
  ])
375
$(makeJSONInstance ''ReplaceDisksMode)
376

    
377
-- | Disk index type (embedding constraints on the index value via a
378
-- smart constructor).
379
newtype DiskIndex = DiskIndex { unDiskIndex :: Int }
380
  deriving (Show, Eq, Ord)
381

    
382
-- | Smart constructor for 'DiskIndex'.
383
mkDiskIndex :: (Monad m) => Int -> m DiskIndex
384
mkDiskIndex i | i >= 0 && i < C.maxDisks = return (DiskIndex i)
385
              | otherwise = fail $ "Invalid value for disk index '" ++
386
                            show i ++ "', required between 0 and " ++
387
                            show C.maxDisks
388

    
389
instance JSON DiskIndex where
390
  readJSON v = readJSON v >>= mkDiskIndex
391
  showJSON = showJSON . unDiskIndex
392

    
393
-- ** I* param types
394

    
395
-- | Type holding disk access modes.
396
$(declareSADT "DiskAccess"
397
  [ ("DiskReadOnly",  'C.diskRdonly)
398
  , ("DiskReadWrite", 'C.diskRdwr)
399
  ])
400
$(makeJSONInstance ''DiskAccess)
401

    
402
-- | NIC modification definition.
403
$(buildObject "INicParams" "inic"
404
  [ optionalField $ simpleField C.inicMac  [t| NonEmptyString |]
405
  , optionalField $ simpleField C.inicIp   [t| String         |]
406
  , optionalField $ simpleField C.inicMode [t| NonEmptyString |]
407
  , optionalField $ simpleField C.inicLink [t| NonEmptyString |]
408
  , optionalField $ simpleField C.inicName [t| NonEmptyString |]
409
  ])
410

    
411
-- | Disk modification definition. FIXME: disksize should be VTYPE_UNIT.
412
$(buildObject "IDiskParams" "idisk"
413
  [ optionalField $ simpleField C.idiskSize   [t| Int            |]
414
  , optionalField $ simpleField C.idiskMode   [t| DiskAccess     |]
415
  , optionalField $ simpleField C.idiskAdopt  [t| NonEmptyString |]
416
  , optionalField $ simpleField C.idiskVg     [t| NonEmptyString |]
417
  , optionalField $ simpleField C.idiskMetavg [t| NonEmptyString |]
418
  , optionalField $ simpleField C.idiskName   [t| NonEmptyString |]
419
  ])
420

    
421
-- | Disk changes type for OpInstanceRecreateDisks. This is a bit
422
-- strange, because the type in Python is something like Either
423
-- [DiskIndex] [DiskChanges], but we can't represent the type of an
424
-- empty list in JSON, so we have to add a custom case for the empty
425
-- list.
426
data RecreateDisksInfo
427
  = RecreateDisksAll
428
  | RecreateDisksIndices (NonEmpty DiskIndex)
429
  | RecreateDisksParams (NonEmpty (DiskIndex, IDiskParams))
430
    deriving (Eq, Show)
431

    
432
readRecreateDisks :: JSValue -> Text.JSON.Result RecreateDisksInfo
433
readRecreateDisks (JSArray []) = return RecreateDisksAll
434
readRecreateDisks v =
435
  case readJSON v::Text.JSON.Result [DiskIndex] of
436
    Text.JSON.Ok indices -> liftM RecreateDisksIndices (mkNonEmpty indices)
437
    _ -> case readJSON v::Text.JSON.Result [(DiskIndex, IDiskParams)] of
438
           Text.JSON.Ok params -> liftM RecreateDisksParams (mkNonEmpty params)
439
           _ -> fail $ "Can't parse disk information as either list of disk"
440
                ++ " indices or list of disk parameters; value received:"
441
                ++ show (pp_value v)
442

    
443
instance JSON RecreateDisksInfo where
444
  readJSON = readRecreateDisks
445
  showJSON  RecreateDisksAll            = showJSON ()
446
  showJSON (RecreateDisksIndices idx)   = showJSON idx
447
  showJSON (RecreateDisksParams params) = showJSON params
448

    
449
-- | Simple type for old-style ddm changes.
450
data DdmOldChanges = DdmOldIndex (NonNegative Int)
451
                   | DdmOldMod DdmSimple
452
                     deriving (Eq, Show)
453

    
454
readDdmOldChanges :: JSValue -> Text.JSON.Result DdmOldChanges
455
readDdmOldChanges v =
456
  case readJSON v::Text.JSON.Result (NonNegative Int) of
457
    Text.JSON.Ok nn -> return $ DdmOldIndex nn
458
    _ -> case readJSON v::Text.JSON.Result DdmSimple of
459
           Text.JSON.Ok ddms -> return $ DdmOldMod ddms
460
           _ -> fail $ "Can't parse value '" ++ show (pp_value v) ++ "' as"
461
                ++ " either index or modification"
462

    
463
instance JSON DdmOldChanges where
464
  showJSON (DdmOldIndex i) = showJSON i
465
  showJSON (DdmOldMod m)   = showJSON m
466
  readJSON = readDdmOldChanges
467

    
468
-- | Instance disk or nic modifications.
469
data SetParamsMods a
470
  = SetParamsEmpty
471
  | SetParamsDeprecated (NonEmpty (DdmOldChanges, a))
472
  | SetParamsNew (NonEmpty (DdmFull, Int, a))
473
    deriving (Eq, Show)
474

    
475
-- | Custom deserialiser for 'SetParamsMods'.
476
readSetParams :: (JSON a) => JSValue -> Text.JSON.Result (SetParamsMods a)
477
readSetParams (JSArray []) = return SetParamsEmpty
478
readSetParams v =
479
  case readJSON v::Text.JSON.Result [(DdmOldChanges, JSValue)] of
480
    Text.JSON.Ok _ -> liftM SetParamsDeprecated $ readJSON v
481
    _ -> liftM SetParamsNew $ readJSON v
482

    
483
instance (JSON a) => JSON (SetParamsMods a) where
484
  showJSON SetParamsEmpty = showJSON ()
485
  showJSON (SetParamsDeprecated v) = showJSON v
486
  showJSON (SetParamsNew v) = showJSON v
487
  readJSON = readSetParams
488

    
489
-- | Custom type for target_node parameter of OpBackupExport, which
490
-- varies depending on mode. FIXME: this uses an UncheckedList since
491
-- we don't care about individual rows (just like the Python code
492
-- tests). But the proper type could be parsed if we wanted.
493
data ExportTarget = ExportTargetLocal NonEmptyString
494
                  | ExportTargetRemote UncheckedList
495
                    deriving (Eq, Show)
496

    
497
-- | Custom reader for 'ExportTarget'.
498
readExportTarget :: JSValue -> Text.JSON.Result ExportTarget
499
readExportTarget (JSString s) = liftM ExportTargetLocal $
500
                                mkNonEmpty (fromJSString s)
501
readExportTarget (JSArray arr) = return $ ExportTargetRemote arr
502
readExportTarget v = fail $ "Invalid value received for 'target_node': " ++
503
                     show (pp_value v)
504

    
505
instance JSON ExportTarget where
506
  showJSON (ExportTargetLocal s)  = showJSON s
507
  showJSON (ExportTargetRemote l) = showJSON l
508
  readJSON = readExportTarget
509

    
510
-- * Parameters
511

    
512
-- | A required instance name (for single-instance LUs).
513
pInstanceName :: Field
514
pInstanceName = simpleField "instance_name" [t| String |]
515

    
516
-- | A list of instances.
517
pInstances :: Field
518
pInstances = defaultField [| [] |] $
519
             simpleField "instances" [t| [NonEmptyString] |]
520

    
521
-- | A generic name.
522
pName :: Field
523
pName = simpleField "name" [t| NonEmptyString |]
524

    
525
-- | Tags list.
526
pTagsList :: Field
527
pTagsList = simpleField "tags" [t| [String] |]
528

    
529
-- | Tags object.
530
pTagsObject :: Field
531
pTagsObject =
532
  customField 'decodeTagObject 'encodeTagObject [tagNameField] $
533
  simpleField "kind" [t| TagObject |]
534

    
535
-- | Selected output fields.
536
pOutputFields :: Field
537
pOutputFields = simpleField "output_fields" [t| [NonEmptyString] |]
538

    
539
-- | How long to wait for instance to shut down.
540
pShutdownTimeout :: Field
541
pShutdownTimeout = defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
542
                   simpleField "shutdown_timeout" [t| NonNegative Int |]
543

    
544
-- | Another name for the shutdown timeout, because we like to be
545
-- inconsistent.
546
pShutdownTimeout' :: Field
547
pShutdownTimeout' =
548
  renameField "InstShutdownTimeout" .
549
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
550
  simpleField "timeout" [t| NonNegative Int |]
551

    
552
-- | Whether to shutdown the instance in backup-export.
553
pShutdownInstance :: Field
554
pShutdownInstance = defaultTrue "shutdown"
555

    
556
-- | Whether to force the operation.
557
pForce :: Field
558
pForce = defaultFalse "force"
559

    
560
-- | Whether to ignore offline nodes.
561
pIgnoreOfflineNodes :: Field
562
pIgnoreOfflineNodes = defaultFalse "ignore_offline_nodes"
563

    
564
-- | A required node name (for single-node LUs).
565
pNodeName :: Field
566
pNodeName = simpleField "node_name" [t| NonEmptyString |]
567

    
568
-- | List of nodes.
569
pNodeNames :: Field
570
pNodeNames =
571
  defaultField [| [] |] $ simpleField "node_names" [t| [NonEmptyString] |]
572

    
573
-- | A required node group name (for single-group LUs).
574
pGroupName :: Field
575
pGroupName = simpleField "group_name" [t| NonEmptyString |]
576

    
577
-- | Migration type (live\/non-live).
578
pMigrationMode :: Field
579
pMigrationMode =
580
  renameField "MigrationMode" .
581
  optionalField $
582
  simpleField "mode" [t| MigrationMode |]
583

    
584
-- | Obsolete \'live\' migration mode (boolean).
585
pMigrationLive :: Field
586
pMigrationLive =
587
  renameField "OldLiveMode" . optionalField $ booleanField "live"
588

    
589
-- | Migration cleanup parameter.
590
pMigrationCleanup :: Field
591
pMigrationCleanup = renameField "MigrationCleanup" $ defaultFalse "cleanup"
592

    
593
-- | Whether to force an unknown OS variant.
594
pForceVariant :: Field
595
pForceVariant = defaultFalse "force_variant"
596

    
597
-- | Whether to wait for the disk to synchronize.
598
pWaitForSync :: Field
599
pWaitForSync = defaultTrue "wait_for_sync"
600

    
601
-- | Whether to wait for the disk to synchronize (defaults to false).
602
pWaitForSyncFalse :: Field
603
pWaitForSyncFalse = defaultField [| False |] pWaitForSync
604

    
605
-- | Whether to ignore disk consistency
606
pIgnoreConsistency :: Field
607
pIgnoreConsistency = defaultFalse "ignore_consistency"
608

    
609
-- | Storage name.
610
pStorageName :: Field
611
pStorageName =
612
  renameField "StorageName" $ simpleField "name" [t| NonEmptyString |]
613

    
614
-- | Whether to use synchronization.
615
pUseLocking :: Field
616
pUseLocking = defaultFalse "use_locking"
617

    
618
-- | Whether to employ opportunistic locking for nodes, meaning nodes already
619
-- locked by another opcode won't be considered for instance allocation (only
620
-- when an iallocator is used).
621
pOpportunisticLocking :: Field
622
pOpportunisticLocking = defaultFalse "opportunistic_locking"
623

    
624
-- | Whether to check name.
625
pNameCheck :: Field
626
pNameCheck = defaultTrue "name_check"
627

    
628
-- | Instance allocation policy.
629
pNodeGroupAllocPolicy :: Field
630
pNodeGroupAllocPolicy = optionalField $
631
                        simpleField "alloc_policy" [t| AllocPolicy |]
632

    
633
-- | Default node parameters for group.
634
pGroupNodeParams :: Field
635
pGroupNodeParams = optionalField $ simpleField "ndparams" [t| UncheckedDict |]
636

    
637
-- | Resource(s) to query for.
638
pQueryWhat :: Field
639
pQueryWhat = simpleField "what" [t| Qlang.QueryTypeOp |]
640

    
641
-- | Whether to release locks as soon as possible.
642
pEarlyRelease :: Field
643
pEarlyRelease = defaultFalse "early_release"
644

    
645
-- | Whether to ensure instance's IP address is inactive.
646
pIpCheck :: Field
647
pIpCheck = defaultTrue "ip_check"
648

    
649
-- | Check for conflicting IPs.
650
pIpConflictsCheck :: Field
651
pIpConflictsCheck = defaultTrue "conflicts_check"
652

    
653
-- | Do not remember instance state changes.
654
pNoRemember :: Field
655
pNoRemember = defaultFalse "no_remember"
656

    
657
-- | Target node for instance migration/failover.
658
pMigrationTargetNode :: Field
659
pMigrationTargetNode = optionalNEStringField "target_node"
660

    
661
-- | Target node for instance move (required).
662
pMoveTargetNode :: Field
663
pMoveTargetNode =
664
  renameField "MoveTargetNode" $
665
  simpleField "target_node" [t| NonEmptyString |]
666

    
667
-- | Pause instance at startup.
668
pStartupPaused :: Field
669
pStartupPaused = defaultFalse "startup_paused"
670

    
671
-- | Verbose mode.
672
pVerbose :: Field
673
pVerbose = defaultFalse "verbose"
674

    
675
-- ** Parameters for cluster verification
676

    
677
-- | Whether to simulate errors (useful for debugging).
678
pDebugSimulateErrors :: Field
679
pDebugSimulateErrors = defaultFalse "debug_simulate_errors"
680

    
681
-- | Error codes.
682
pErrorCodes :: Field
683
pErrorCodes = defaultFalse "error_codes"
684

    
685
-- | Which checks to skip.
686
pSkipChecks :: Field
687
pSkipChecks = defaultField [| Set.empty |] $
688
              simpleField "skip_checks" [t| Set.Set VerifyOptionalChecks |]
689

    
690
-- | List of error codes that should be treated as warnings.
691
pIgnoreErrors :: Field
692
pIgnoreErrors = defaultField [| Set.empty |] $
693
                simpleField "ignore_errors" [t| Set.Set CVErrorCode |]
694

    
695
-- | Optional group name.
696
pOptGroupName :: Field
697
pOptGroupName = renameField "OptGroupName" .
698
                optionalField $ simpleField "group_name" [t| NonEmptyString |]
699

    
700
-- | Disk templates' parameter defaults.
701
pDiskParams :: Field
702
pDiskParams = optionalField $
703
              simpleField "diskparams" [t| GenericContainer DiskTemplate
704
                                           UncheckedDict |]
705

    
706
-- | Whether to hotplug device.
707
pHotplug :: Field
708
pHotplug = defaultFalse "hotplug"
709

    
710
-- * Parameters for node resource model
711

    
712
-- | Set hypervisor states.
713
pHvState :: Field
714
pHvState = optionalField $ simpleField "hv_state" [t| UncheckedDict |]
715

    
716
-- | Set disk states.
717
pDiskState :: Field
718
pDiskState = optionalField $ simpleField "disk_state" [t| UncheckedDict |]
719

    
720
-- | Whether to ignore ipolicy violations.
721
pIgnoreIpolicy :: Field
722
pIgnoreIpolicy = defaultFalse "ignore_ipolicy"
723

    
724
-- | Allow runtime changes while migrating.
725
pAllowRuntimeChgs :: Field
726
pAllowRuntimeChgs = defaultTrue "allow_runtime_changes"
727

    
728
-- | Utility type for OpClusterSetParams.
729
type TestClusterOsListItem = (DdmSimple, NonEmptyString)
730

    
731
-- | Utility type of OsList.
732
type TestClusterOsList = [TestClusterOsListItem]
733

    
734
-- Utility type for NIC definitions.
735
--type TestNicDef = INicParams
736

    
737
-- | List of instance disks.
738
pInstDisks :: Field
739
pInstDisks = renameField "instDisks" $ simpleField "disks" [t| [IDiskParams] |]
740

    
741
-- | Instance disk template.
742
pDiskTemplate :: Field
743
pDiskTemplate = simpleField "disk_template" [t| DiskTemplate |]
744

    
745
-- | Instance disk template.
746
pOptDiskTemplate :: Field
747
pOptDiskTemplate =
748
  optionalField .
749
  renameField "OptDiskTemplate" $
750
  simpleField "disk_template" [t| DiskTemplate |]
751

    
752
-- | File driver.
753
pFileDriver :: Field
754
pFileDriver = optionalField $ simpleField "file_driver" [t| FileDriver |]
755

    
756
-- | Directory for storing file-backed disks.
757
pFileStorageDir :: Field
758
pFileStorageDir = optionalNEStringField "file_storage_dir"
759

    
760
-- | Volume group name.
761
pVgName :: Field
762
pVgName = optionalStringField "vg_name"
763

    
764
-- | List of enabled hypervisors.
765
pEnabledHypervisors :: Field
766
pEnabledHypervisors =
767
  optionalField $
768
  simpleField "enabled_hypervisors" [t| NonEmpty Hypervisor |]
769

    
770
-- | List of enabled disk templates.
771
pEnabledDiskTemplates :: Field
772
pEnabledDiskTemplates =
773
  optionalField $
774
  simpleField "enabled_disk_templates" [t| NonEmpty DiskTemplate |]
775

    
776
-- | Selected hypervisor for an instance.
777
pHypervisor :: Field
778
pHypervisor =
779
  optionalField $
780
  simpleField "hypervisor" [t| Hypervisor |]
781

    
782
-- | Cluster-wide hypervisor parameters, hypervisor-dependent.
783
pClusterHvParams :: Field
784
pClusterHvParams =
785
  renameField "ClusterHvParams" .
786
  optionalField $
787
  simpleField "hvparams" [t| Container UncheckedDict |]
788

    
789
-- | Instance hypervisor parameters.
790
pInstHvParams :: Field
791
pInstHvParams =
792
  renameField "InstHvParams" .
793
  defaultField [| toJSObject [] |] $
794
  simpleField "hvparams" [t| UncheckedDict |]
795

    
796
-- | Cluster-wide beparams.
797
pClusterBeParams :: Field
798
pClusterBeParams =
799
  renameField "ClusterBeParams" .
800
  optionalField $ simpleField "beparams" [t| UncheckedDict |]
801

    
802
-- | Instance beparams.
803
pInstBeParams :: Field
804
pInstBeParams =
805
  renameField "InstBeParams" .
806
  defaultField [| toJSObject [] |] $
807
  simpleField "beparams" [t| UncheckedDict |]
808

    
809
-- | Reset instance parameters to default if equal.
810
pResetDefaults :: Field
811
pResetDefaults = defaultFalse "identify_defaults"
812

    
813
-- | Cluster-wide per-OS hypervisor parameter defaults.
814
pOsHvp :: Field
815
pOsHvp = optionalField $ simpleField "os_hvp" [t| Container UncheckedDict |]
816

    
817
-- | Cluster-wide OS parameter defaults.
818
pClusterOsParams :: Field
819
pClusterOsParams =
820
  renameField "ClusterOsParams" .
821
  optionalField $ simpleField "osparams" [t| Container UncheckedDict |]
822

    
823
-- | Instance OS parameters.
824
pInstOsParams :: Field
825
pInstOsParams =
826
  renameField "InstOsParams" . defaultField [| toJSObject [] |] $
827
  simpleField "osparams" [t| UncheckedDict |]
828

    
829
-- | Temporary OS parameters (currently only in reinstall, might be
830
-- added to install as well).
831
pTempOsParams :: Field
832
pTempOsParams =
833
  renameField "TempOsParams" .
834
  optionalField $ simpleField "osparams" [t| UncheckedDict |]
835

    
836
-- | Temporary hypervisor parameters, hypervisor-dependent.
837
pTempHvParams :: Field
838
pTempHvParams =
839
  renameField "TempHvParams" .
840
  defaultField [| toJSObject [] |] $
841
  simpleField "hvparams" [t| UncheckedDict |]
842

    
843
-- | Temporary backend parameters.
844
pTempBeParams :: Field
845
pTempBeParams =
846
  renameField "TempBeParams" .
847
  defaultField [| toJSObject [] |] $
848
  simpleField "beparams" [t| UncheckedDict |]
849

    
850
-- | Candidate pool size.
851
pCandidatePoolSize :: Field
852
pCandidatePoolSize =
853
  optionalField $ simpleField "candidate_pool_size" [t| Positive Int |]
854

    
855
-- | Set UID pool, must be list of lists describing UID ranges (two
856
-- items, start and end inclusive.
857
pUidPool :: Field
858
pUidPool = optionalField $ simpleField "uid_pool" [t| [[(Int, Int)]] |]
859

    
860
-- | Extend UID pool, must be list of lists describing UID ranges (two
861
-- items, start and end inclusive.
862
pAddUids :: Field
863
pAddUids = optionalField $ simpleField "add_uids" [t| [[(Int, Int)]] |]
864

    
865
-- | Shrink UID pool, must be list of lists describing UID ranges (two
866
-- items, start and end inclusive) to be removed.
867
pRemoveUids :: Field
868
pRemoveUids = optionalField $ simpleField "remove_uids" [t| [[(Int, Int)]] |]
869

    
870
-- | Whether to automatically maintain node health.
871
pMaintainNodeHealth :: Field
872
pMaintainNodeHealth = optionalField $ booleanField "maintain_node_health"
873

    
874
-- | Whether to modify and keep in sync the @/etc/hosts@ files of nodes.
875
pModifyEtcHosts :: Field
876
pModifyEtcHosts = optionalField $ booleanField "modify_etc_hosts"
877

    
878
-- | Whether to wipe disks before allocating them to instances.
879
pPreallocWipeDisks :: Field
880
pPreallocWipeDisks = optionalField $ booleanField "prealloc_wipe_disks"
881

    
882
-- | Cluster-wide NIC parameter defaults.
883
pNicParams :: Field
884
pNicParams = optionalField $ simpleField "nicparams" [t| INicParams |]
885

    
886
-- | Instance NIC definitions.
887
pInstNics :: Field
888
pInstNics = simpleField "nics" [t| [INicParams] |]
889

    
890
-- | Cluster-wide node parameter defaults.
891
pNdParams :: Field
892
pNdParams = optionalField $ simpleField "ndparams" [t| UncheckedDict |]
893

    
894
-- | Cluster-wide ipolicy specs.
895
pIpolicy :: Field
896
pIpolicy = optionalField $ simpleField "ipolicy" [t| UncheckedDict |]
897

    
898
-- | DRBD helper program.
899
pDrbdHelper :: Field
900
pDrbdHelper = optionalStringField "drbd_helper"
901

    
902
-- | Default iallocator for cluster.
903
pDefaultIAllocator :: Field
904
pDefaultIAllocator = optionalStringField "default_iallocator"
905

    
906
-- | Master network device.
907
pMasterNetdev :: Field
908
pMasterNetdev = optionalStringField "master_netdev"
909

    
910
-- | Netmask of the master IP.
911
pMasterNetmask :: Field
912
pMasterNetmask =
913
  optionalField $ simpleField "master_netmask" [t| NonNegative Int |]
914

    
915
-- | List of reserved LVs.
916
pReservedLvs :: Field
917
pReservedLvs =
918
  optionalField $ simpleField "reserved_lvs" [t| [NonEmptyString] |]
919

    
920
-- | Modify list of hidden operating systems: each modification must
921
-- have two items, the operation and the OS name; the operation can be
922
-- add or remove.
923
pHiddenOs :: Field
924
pHiddenOs = optionalField $ simpleField "hidden_os" [t| TestClusterOsList |]
925

    
926
-- | Modify list of blacklisted operating systems: each modification
927
-- must have two items, the operation and the OS name; the operation
928
-- can be add or remove.
929
pBlacklistedOs :: Field
930
pBlacklistedOs =
931
  optionalField $ simpleField "blacklisted_os" [t| TestClusterOsList |]
932

    
933
-- | Whether to use an external master IP address setup script.
934
pUseExternalMipScript :: Field
935
pUseExternalMipScript = optionalField $ booleanField "use_external_mip_script"
936

    
937
-- | Requested fields.
938
pQueryFields :: Field
939
pQueryFields = simpleField "fields" [t| [NonEmptyString] |]
940

    
941
-- | Query filter.
942
pQueryFilter :: Field
943
pQueryFilter = simpleField "qfilter" [t| Qlang.Filter String |]
944

    
945
-- | OOB command to run.
946
pOobCommand :: Field
947
pOobCommand = simpleField "command" [t| OobCommand |]
948

    
949
-- | Timeout before the OOB helper will be terminated.
950
pOobTimeout :: Field
951
pOobTimeout =
952
  defaultField [| C.oobTimeout |] $ simpleField "timeout" [t| Int |]
953

    
954
-- | Ignores the node offline status for power off.
955
pIgnoreStatus :: Field
956
pIgnoreStatus = defaultFalse "ignore_status"
957

    
958
-- | Time in seconds to wait between powering on nodes.
959
pPowerDelay :: Field
960
pPowerDelay =
961
  -- FIXME: we can't use the proper type "NonNegative Double", since
962
  -- the default constant is a plain Double, not a non-negative one.
963
  defaultField [| C.oobPowerDelay |] $
964
  simpleField "power_delay" [t| Double |]
965

    
966
-- | Primary IP address.
967
pPrimaryIp :: Field
968
pPrimaryIp = optionalStringField "primary_ip"
969

    
970
-- | Secondary IP address.
971
pSecondaryIp :: Field
972
pSecondaryIp = optionalNEStringField "secondary_ip"
973

    
974
-- | Whether node is re-added to cluster.
975
pReadd :: Field
976
pReadd = defaultFalse "readd"
977

    
978
-- | Initial node group.
979
pNodeGroup :: Field
980
pNodeGroup = optionalNEStringField "group"
981

    
982
-- | Whether node can become master or master candidate.
983
pMasterCapable :: Field
984
pMasterCapable = optionalField $ booleanField "master_capable"
985

    
986
-- | Whether node can host instances.
987
pVmCapable :: Field
988
pVmCapable = optionalField $ booleanField "vm_capable"
989

    
990
-- | List of names.
991
pNames :: Field
992
pNames = defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
993

    
994
-- | List of node names.
995
pNodes :: Field
996
pNodes = defaultField [| [] |] $ simpleField "nodes" [t| [NonEmptyString] |]
997

    
998
-- | Required list of node names.
999
pRequiredNodes :: Field
1000
pRequiredNodes =
1001
  renameField "ReqNodes " $ simpleField "nodes" [t| [NonEmptyString] |]
1002

    
1003
-- | Storage type.
1004
pStorageType :: Field
1005
pStorageType = simpleField "storage_type" [t| StorageType |]
1006

    
1007
-- | Storage changes (unchecked).
1008
pStorageChanges :: Field
1009
pStorageChanges = simpleField "changes" [t| UncheckedDict |]
1010

    
1011
-- | Whether the node should become a master candidate.
1012
pMasterCandidate :: Field
1013
pMasterCandidate = optionalField $ booleanField "master_candidate"
1014

    
1015
-- | Whether the node should be marked as offline.
1016
pOffline :: Field
1017
pOffline = optionalField $ booleanField "offline"
1018

    
1019
-- | Whether the node should be marked as drained.
1020
pDrained ::Field
1021
pDrained = optionalField $ booleanField "drained"
1022

    
1023
-- | Whether node(s) should be promoted to master candidate if necessary.
1024
pAutoPromote :: Field
1025
pAutoPromote = defaultFalse "auto_promote"
1026

    
1027
-- | Whether the node should be marked as powered
1028
pPowered :: Field
1029
pPowered = optionalField $ booleanField "powered"
1030

    
1031
-- | Iallocator for deciding the target node for shared-storage
1032
-- instances during migrate and failover.
1033
pIallocator :: Field
1034
pIallocator = optionalNEStringField "iallocator"
1035

    
1036
-- | New secondary node.
1037
pRemoteNode :: Field
1038
pRemoteNode = optionalNEStringField "remote_node"
1039

    
1040
-- | Node evacuation mode.
1041
pEvacMode :: Field
1042
pEvacMode = renameField "EvacMode" $ simpleField "mode" [t| NodeEvacMode |]
1043

    
1044
-- | Instance creation mode.
1045
pInstCreateMode :: Field
1046
pInstCreateMode =
1047
  renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
1048

    
1049
-- | Do not install the OS (will disable automatic start).
1050
pNoInstall :: Field
1051
pNoInstall = optionalField $ booleanField "no_install"
1052

    
1053
-- | OS type for instance installation.
1054
pInstOs :: Field
1055
pInstOs = optionalNEStringField "os_type"
1056

    
1057
-- | Primary node for an instance.
1058
pPrimaryNode :: Field
1059
pPrimaryNode = optionalNEStringField "pnode"
1060

    
1061
-- | Secondary node for an instance.
1062
pSecondaryNode :: Field
1063
pSecondaryNode = optionalNEStringField "snode"
1064

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

    
1070
-- | Source instance name (remote import only).
1071
pSourceInstance :: Field
1072
pSourceInstance = optionalNEStringField "source_instance_name"
1073

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

    
1081
-- | Source X509 CA in PEM format (remote import only).
1082
pSourceX509Ca :: Field
1083
pSourceX509Ca = optionalNEStringField "source_x509_ca"
1084

    
1085
-- | Source node for import.
1086
pSrcNode :: Field
1087
pSrcNode = optionalNEStringField "src_node"
1088

    
1089
-- | Source directory for import.
1090
pSrcPath :: Field
1091
pSrcPath = optionalNEStringField "src_path"
1092

    
1093
-- | Whether to start instance after creation.
1094
pStartInstance :: Field
1095
pStartInstance = defaultTrue "start"
1096

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

    
1105
-- | Unchecked list of OpInstanceCreate, used in OpInstanceMultiAlloc.
1106
pMultiAllocInstances :: Field
1107
pMultiAllocInstances =
1108
  renameField "InstMultiAlloc" .
1109
  defaultField [| [] |] $
1110
  simpleField "instances"[t| UncheckedList |]
1111

    
1112
-- | Ignore failures parameter.
1113
pIgnoreFailures :: Field
1114
pIgnoreFailures = defaultFalse "ignore_failures"
1115

    
1116
-- | New instance or cluster name.
1117
pNewName :: Field
1118
pNewName = simpleField "new_name" [t| NonEmptyString |]
1119

    
1120
-- | Whether to start the instance even if secondary disks are failing.
1121
pIgnoreSecondaries :: Field
1122
pIgnoreSecondaries = defaultFalse "ignore_secondaries"
1123

    
1124
-- | How to reboot the instance.
1125
pRebootType :: Field
1126
pRebootType = simpleField "reboot_type" [t| RebootType |]
1127

    
1128
-- | Whether to ignore recorded disk size.
1129
pIgnoreDiskSize :: Field
1130
pIgnoreDiskSize = defaultFalse "ignore_size"
1131

    
1132
-- | Disk list for recreate disks.
1133
pRecreateDisksInfo :: Field
1134
pRecreateDisksInfo =
1135
  renameField "RecreateDisksInfo" .
1136
  defaultField [| RecreateDisksAll |] $
1137
  simpleField "disks" [t| RecreateDisksInfo |]
1138

    
1139
-- | Whether to only return configuration data without querying nodes.
1140
pStatic :: Field
1141
pStatic = defaultFalse "static"
1142

    
1143
-- | InstanceSetParams NIC changes.
1144
pInstParamsNicChanges :: Field
1145
pInstParamsNicChanges =
1146
  renameField "InstNicChanges" .
1147
  defaultField [| SetParamsEmpty |] $
1148
  simpleField "nics" [t| SetParamsMods INicParams |]
1149

    
1150
-- | InstanceSetParams Disk changes.
1151
pInstParamsDiskChanges :: Field
1152
pInstParamsDiskChanges =
1153
  renameField "InstDiskChanges" .
1154
  defaultField [| SetParamsEmpty |] $
1155
  simpleField "disks" [t| SetParamsMods IDiskParams |]
1156

    
1157
-- | New runtime memory.
1158
pRuntimeMem :: Field
1159
pRuntimeMem = optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1160

    
1161
-- | Change the instance's OS without reinstalling the instance
1162
pOsNameChange :: Field
1163
pOsNameChange = optionalNEStringField "os_name"
1164

    
1165
-- | Disk index for e.g. grow disk.
1166
pDiskIndex :: Field
1167
pDiskIndex = renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
1168

    
1169
-- | Disk amount to add or grow to.
1170
pDiskChgAmount :: Field
1171
pDiskChgAmount =
1172
  renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
1173

    
1174
-- | Whether the amount parameter is an absolute target or a relative one.
1175
pDiskChgAbsolute :: Field
1176
pDiskChgAbsolute = renameField "DiskChkAbsolute" $ defaultFalse "absolute"
1177

    
1178
-- | Destination group names or UUIDs (defaults to \"all but current group\".
1179
pTargetGroups :: Field
1180
pTargetGroups =
1181
  optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
1182

    
1183
-- | Export mode field.
1184
pExportMode :: Field
1185
pExportMode =
1186
  renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1187

    
1188
-- | Export target_node field, depends on mode.
1189
pExportTargetNode :: Field
1190
pExportTargetNode =
1191
  renameField "ExportTarget" $
1192
  simpleField "target_node" [t| ExportTarget |]
1193

    
1194
-- | Whether to remove instance after export.
1195
pRemoveInstance :: Field
1196
pRemoveInstance = defaultFalse "remove_instance"
1197

    
1198
-- | Whether to ignore failures while removing instances.
1199
pIgnoreRemoveFailures :: Field
1200
pIgnoreRemoveFailures = defaultFalse "ignore_remove_failures"
1201

    
1202
-- | Name of X509 key (remote export only).
1203
pX509KeyName :: Field
1204
pX509KeyName = optionalField $ simpleField "x509_key_name" [t| UncheckedList |]
1205

    
1206
-- | Destination X509 CA (remote export only).
1207
pX509DestCA :: Field
1208
pX509DestCA = optionalNEStringField "destination_x509_ca"
1209

    
1210
-- | Search pattern (regular expression). FIXME: this should be
1211
-- compiled at load time?
1212
pTagSearchPattern :: Field
1213
pTagSearchPattern =
1214
  renameField "TagSearchPattern" $ simpleField "pattern" [t| NonEmptyString |]
1215

    
1216
-- | Restricted command name.
1217
pRestrictedCommand :: Field
1218
pRestrictedCommand =
1219
  renameField "RestrictedCommand" $
1220
  simpleField "command" [t| NonEmptyString |]
1221

    
1222
-- | Replace disks mode.
1223
pReplaceDisksMode :: Field
1224
pReplaceDisksMode =
1225
  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1226

    
1227
-- | List of disk indices.
1228
pReplaceDisksList :: Field
1229
pReplaceDisksList =
1230
  renameField "ReplaceDisksList" $ simpleField "disks" [t| [DiskIndex] |]
1231

    
1232
-- | Whether do allow failover in migrations.
1233
pAllowFailover :: Field
1234
pAllowFailover = defaultFalse "allow_failover"
1235

    
1236
-- * Test opcode parameters
1237

    
1238
-- | Duration parameter for 'OpTestDelay'.
1239
pDelayDuration :: Field
1240
pDelayDuration =
1241
  renameField "DelayDuration" $ simpleField "duration" [t| Double |]
1242

    
1243
-- | on_master field for 'OpTestDelay'.
1244
pDelayOnMaster :: Field
1245
pDelayOnMaster = renameField "DelayOnMaster" $ defaultTrue "on_master"
1246

    
1247
-- | on_nodes field for 'OpTestDelay'.
1248
pDelayOnNodes :: Field
1249
pDelayOnNodes =
1250
  renameField "DelayOnNodes" .
1251
  defaultField [| [] |] $
1252
  simpleField "on_nodes" [t| [NonEmptyString] |]
1253

    
1254
-- | Repeat parameter for OpTestDelay.
1255
pDelayRepeat :: Field
1256
pDelayRepeat =
1257
  renameField "DelayRepeat" .
1258
  defaultField [| forceNonNeg (0::Int) |] $
1259
  simpleField "repeat" [t| NonNegative Int |]
1260

    
1261
-- | IAllocator test direction.
1262
pIAllocatorDirection :: Field
1263
pIAllocatorDirection =
1264
  renameField "IAllocatorDirection" $
1265
  simpleField "direction" [t| IAllocatorTestDir |]
1266

    
1267
-- | IAllocator test mode.
1268
pIAllocatorMode :: Field
1269
pIAllocatorMode =
1270
  renameField "IAllocatorMode" $
1271
  simpleField "mode" [t| IAllocatorMode |]
1272

    
1273
-- | IAllocator target name (new instance, node to evac, etc.).
1274
pIAllocatorReqName :: Field
1275
pIAllocatorReqName =
1276
  renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
1277

    
1278
-- | Custom OpTestIAllocator nics.
1279
pIAllocatorNics :: Field
1280
pIAllocatorNics =
1281
  renameField "IAllocatorNics" $ simpleField "nics" [t| [UncheckedDict] |]
1282

    
1283
-- | Custom OpTestAllocator disks.
1284
pIAllocatorDisks :: Field
1285
pIAllocatorDisks =
1286
  renameField "IAllocatorDisks" $ simpleField "disks" [t| UncheckedList |]
1287

    
1288
-- | IAllocator memory field.
1289
pIAllocatorMemory :: Field
1290
pIAllocatorMemory =
1291
  renameField "IAllocatorMem" .
1292
  optionalField $
1293
  simpleField "memory" [t| NonNegative Int |]
1294

    
1295
-- | IAllocator vcpus field.
1296
pIAllocatorVCpus :: Field
1297
pIAllocatorVCpus =
1298
  renameField "IAllocatorVCpus" .
1299
  optionalField $
1300
  simpleField "vcpus" [t| NonNegative Int |]
1301

    
1302
-- | IAllocator os field.
1303
pIAllocatorOs :: Field
1304
pIAllocatorOs = renameField "IAllocatorOs" $ optionalNEStringField "os"
1305

    
1306
-- | IAllocator instances field.
1307
pIAllocatorInstances :: Field
1308
pIAllocatorInstances =
1309
  renameField "IAllocatorInstances " .
1310
  optionalField $
1311
  simpleField "instances" [t| [NonEmptyString] |]
1312

    
1313
-- | IAllocator evac mode.
1314
pIAllocatorEvacMode :: Field
1315
pIAllocatorEvacMode =
1316
  renameField "IAllocatorEvacMode" .
1317
  optionalField $
1318
  simpleField "evac_mode" [t| NodeEvacMode |]
1319

    
1320
-- | IAllocator spindle use.
1321
pIAllocatorSpindleUse :: Field
1322
pIAllocatorSpindleUse =
1323
  renameField "IAllocatorSpindleUse" .
1324
  defaultField [| forceNonNeg (1::Int) |] $
1325
  simpleField "spindle_use" [t| NonNegative Int |]
1326

    
1327
-- | IAllocator count field.
1328
pIAllocatorCount :: Field
1329
pIAllocatorCount =
1330
  renameField "IAllocatorCount" .
1331
  defaultField [| forceNonNeg (1::Int) |] $
1332
  simpleField "count" [t| NonNegative Int |]
1333

    
1334
-- | 'OpTestJqueue' notify_waitlock.
1335
pJQueueNotifyWaitLock :: Field
1336
pJQueueNotifyWaitLock = defaultFalse "notify_waitlock"
1337

    
1338
-- | 'OpTestJQueue' notify_exec.
1339
pJQueueNotifyExec :: Field
1340
pJQueueNotifyExec = defaultFalse "notify_exec"
1341

    
1342
-- | 'OpTestJQueue' log_messages.
1343
pJQueueLogMessages :: Field
1344
pJQueueLogMessages =
1345
  defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
1346

    
1347
-- | 'OpTestJQueue' fail attribute.
1348
pJQueueFail :: Field
1349
pJQueueFail =
1350
  renameField "JQueueFail" $ defaultFalse "fail"
1351

    
1352
-- | 'OpTestDummy' result field.
1353
pTestDummyResult :: Field
1354
pTestDummyResult =
1355
  renameField "TestDummyResult" $ simpleField "result" [t| UncheckedValue |]
1356

    
1357
-- | 'OpTestDummy' messages field.
1358
pTestDummyMessages :: Field
1359
pTestDummyMessages =
1360
  renameField "TestDummyMessages" $
1361
  simpleField "messages" [t| UncheckedValue |]
1362

    
1363
-- | 'OpTestDummy' fail field.
1364
pTestDummyFail :: Field
1365
pTestDummyFail =
1366
  renameField "TestDummyFail" $ simpleField "fail" [t| UncheckedValue |]
1367

    
1368
-- | 'OpTestDummy' submit_jobs field.
1369
pTestDummySubmitJobs :: Field
1370
pTestDummySubmitJobs =
1371
  renameField "TestDummySubmitJobs" $
1372
  simpleField "submit_jobs" [t| UncheckedValue |]
1373

    
1374
-- * Network parameters
1375

    
1376
-- | Network name.
1377
pNetworkName :: Field
1378
pNetworkName = simpleField "network_name" [t| NonEmptyString |]
1379

    
1380
-- | Network address (IPv4 subnet). FIXME: no real type for this.
1381
pNetworkAddress4 :: Field
1382
pNetworkAddress4 =
1383
  renameField "NetworkAddress4" $
1384
  simpleField "network" [t| NonEmptyString |]
1385

    
1386
-- | Network gateway (IPv4 address). FIXME: no real type for this.
1387
pNetworkGateway4 :: Field
1388
pNetworkGateway4 =
1389
  renameField "NetworkGateway4" $
1390
  optionalNEStringField "gateway"
1391

    
1392
-- | Network address (IPv6 subnet). FIXME: no real type for this.
1393
pNetworkAddress6 :: Field
1394
pNetworkAddress6 =
1395
  renameField "NetworkAddress6" $
1396
  optionalNEStringField "network6"
1397

    
1398
-- | Network gateway (IPv6 address). FIXME: no real type for this.
1399
pNetworkGateway6 :: Field
1400
pNetworkGateway6 =
1401
  renameField "NetworkGateway6" $
1402
  optionalNEStringField "gateway6"
1403

    
1404
-- | Network specific mac prefix (that overrides the cluster one).
1405
pNetworkMacPrefix :: Field
1406
pNetworkMacPrefix =
1407
  renameField "NetMacPrefix" $
1408
  optionalNEStringField "mac_prefix"
1409

    
1410
-- | Network add reserved IPs.
1411
pNetworkAddRsvdIps :: Field
1412
pNetworkAddRsvdIps =
1413
  renameField "NetworkAddRsvdIps" .
1414
  optionalField $
1415
  simpleField "add_reserved_ips" [t| [NonEmptyString] |]
1416

    
1417
-- | Network remove reserved IPs.
1418
pNetworkRemoveRsvdIps :: Field
1419
pNetworkRemoveRsvdIps =
1420
  renameField "NetworkRemoveRsvdIps" .
1421
  optionalField $
1422
  simpleField "remove_reserved_ips" [t| [NonEmptyString] |]
1423

    
1424
-- | Network mode when connecting to a group.
1425
pNetworkMode :: Field
1426
pNetworkMode = simpleField "network_mode" [t| NICMode |]
1427

    
1428
-- | Network link when connecting to a group.
1429
pNetworkLink :: Field
1430
pNetworkLink = simpleField "network_link" [t| NonEmptyString |]
1431

    
1432
-- * Common opcode parameters
1433

    
1434
-- | Run checks only, don't execute.
1435
pDryRun :: Field
1436
pDryRun = optionalField $ booleanField "dry_run"
1437

    
1438
-- | Debug level.
1439
pDebugLevel :: Field
1440
pDebugLevel = optionalField $ simpleField "debug_level" [t| NonNegative Int |]
1441

    
1442
-- | Opcode priority. Note: python uses a separate constant, we're
1443
-- using the actual value we know it's the default.
1444
pOpPriority :: Field
1445
pOpPriority =
1446
  defaultField [| OpPrioNormal |] $
1447
  simpleField "priority" [t| OpSubmitPriority |]
1448

    
1449
-- | Job dependencies.
1450
pDependencies :: Field
1451
pDependencies =
1452
  optionalNullSerField $ simpleField "depends" [t| [JobDependency] |]
1453

    
1454
-- | Comment field.
1455
pComment :: Field
1456
pComment = optionalNullSerField $ stringField "comment"
1457

    
1458
-- | Reason trail field.
1459
pReason :: Field
1460
pReason = simpleField C.opcodeReason [t| ReasonTrail |]
1461

    
1462
-- * Entire opcode parameter list
1463

    
1464
-- | Old-style query opcode, with locking.
1465
dOldQuery :: [Field]
1466
dOldQuery =
1467
  [ pOutputFields
1468
  , pNames
1469
  , pUseLocking
1470
  ]
1471

    
1472
-- | Old-style query opcode, without locking.
1473
dOldQueryNoLocking :: [Field]
1474
dOldQueryNoLocking =
1475
  [ pOutputFields
1476
  , pNames
1477
  ]