Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ 289e7fcc

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

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

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

    
260
-- * Helper functions and types
261

    
262
-- * Type aliases
263

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

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

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

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

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

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

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

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

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

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

    
306
-- ** Tags
307

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

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

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

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

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

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

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

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

    
365
-- ** Disks
366

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

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

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

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

    
392
-- ** I* param types
393

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
509
-- * Parameters
510

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
674
-- ** Parameters for cluster verification
675

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

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

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

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

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

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

    
705
-- * Parameters for node resource model
706

    
707
-- | Set hypervisor states.
708
pHvState :: Field
709
pHvState = optionalField $ simpleField "hv_state" [t| UncheckedDict |]
710

    
711
-- | Set disk states.
712
pDiskState :: Field
713
pDiskState = optionalField $ simpleField "disk_state" [t| UncheckedDict |]
714

    
715
-- | Whether to ignore ipolicy violations.
716
pIgnoreIpolicy :: Field
717
pIgnoreIpolicy = defaultFalse "ignore_ipolicy"
718

    
719
-- | Allow runtime changes while migrating.
720
pAllowRuntimeChgs :: Field
721
pAllowRuntimeChgs = defaultTrue "allow_runtime_changes"
722

    
723
-- | Utility type for OpClusterSetParams.
724
type TestClusterOsListItem = (DdmSimple, NonEmptyString)
725

    
726
-- | Utility type of OsList.
727
type TestClusterOsList = [TestClusterOsListItem]
728

    
729
-- Utility type for NIC definitions.
730
--type TestNicDef = INicParams
731

    
732
-- | List of instance disks.
733
pInstDisks :: Field
734
pInstDisks = renameField "instDisks" $ simpleField "disks" [t| [IDiskParams] |]
735

    
736
-- | Instance disk template.
737
pDiskTemplate :: Field
738
pDiskTemplate = simpleField "disk_template" [t| DiskTemplate |]
739

    
740
-- | Instance disk template.
741
pOptDiskTemplate :: Field
742
pOptDiskTemplate =
743
  optionalField .
744
  renameField "OptDiskTemplate" $
745
  simpleField "disk_template" [t| DiskTemplate |]
746

    
747
-- | File driver.
748
pFileDriver :: Field
749
pFileDriver = optionalField $ simpleField "file_driver" [t| FileDriver |]
750

    
751
-- | Directory for storing file-backed disks.
752
pFileStorageDir :: Field
753
pFileStorageDir = optionalNEStringField "file_storage_dir"
754

    
755
-- | Volume group name.
756
pVgName :: Field
757
pVgName = optionalStringField "vg_name"
758

    
759
-- | List of enabled hypervisors.
760
pEnabledHypervisors :: Field
761
pEnabledHypervisors =
762
  optionalField $
763
  simpleField "enabled_hypervisors" [t| NonEmpty Hypervisor |]
764

    
765
-- | List of enabled disk templates.
766
pEnabledDiskTemplates :: Field
767
pEnabledDiskTemplates =
768
  optionalField $
769
  simpleField "enabled_disk_templates" [t| NonEmpty DiskTemplate |]
770

    
771
-- | Selected hypervisor for an instance.
772
pHypervisor :: Field
773
pHypervisor =
774
  optionalField $
775
  simpleField "hypervisor" [t| Hypervisor |]
776

    
777
-- | Cluster-wide hypervisor parameters, hypervisor-dependent.
778
pClusterHvParams :: Field
779
pClusterHvParams =
780
  renameField "ClusterHvParams" .
781
  optionalField $
782
  simpleField "hvparams" [t| Container UncheckedDict |]
783

    
784
-- | Instance hypervisor parameters.
785
pInstHvParams :: Field
786
pInstHvParams =
787
  renameField "InstHvParams" .
788
  defaultField [| toJSObject [] |] $
789
  simpleField "hvparams" [t| UncheckedDict |]
790

    
791
-- | Cluster-wide beparams.
792
pClusterBeParams :: Field
793
pClusterBeParams =
794
  renameField "ClusterBeParams" .
795
  optionalField $ simpleField "beparams" [t| UncheckedDict |]
796

    
797
-- | Instance beparams.
798
pInstBeParams :: Field
799
pInstBeParams =
800
  renameField "InstBeParams" .
801
  defaultField [| toJSObject [] |] $
802
  simpleField "beparams" [t| UncheckedDict |]
803

    
804
-- | Reset instance parameters to default if equal.
805
pResetDefaults :: Field
806
pResetDefaults = defaultFalse "identify_defaults"
807

    
808
-- | Cluster-wide per-OS hypervisor parameter defaults.
809
pOsHvp :: Field
810
pOsHvp = optionalField $ simpleField "os_hvp" [t| Container UncheckedDict |]
811

    
812
-- | Cluster-wide OS parameter defaults.
813
pClusterOsParams :: Field
814
pClusterOsParams =
815
  renameField "ClusterOsParams" .
816
  optionalField $ simpleField "osparams" [t| Container UncheckedDict |]
817

    
818
-- | Instance OS parameters.
819
pInstOsParams :: Field
820
pInstOsParams =
821
  renameField "InstOsParams" . defaultField [| toJSObject [] |] $
822
  simpleField "osparams" [t| UncheckedDict |]
823

    
824
-- | Temporary OS parameters (currently only in reinstall, might be
825
-- added to install as well).
826
pTempOsParams :: Field
827
pTempOsParams =
828
  renameField "TempOsParams" .
829
  optionalField $ simpleField "osparams" [t| UncheckedDict |]
830

    
831
-- | Temporary hypervisor parameters, hypervisor-dependent.
832
pTempHvParams :: Field
833
pTempHvParams =
834
  renameField "TempHvParams" .
835
  defaultField [| toJSObject [] |] $
836
  simpleField "hvparams" [t| UncheckedDict |]
837

    
838
-- | Temporary backend parameters.
839
pTempBeParams :: Field
840
pTempBeParams =
841
  renameField "TempBeParams" .
842
  defaultField [| toJSObject [] |] $
843
  simpleField "beparams" [t| UncheckedDict |]
844

    
845
-- | Candidate pool size.
846
pCandidatePoolSize :: Field
847
pCandidatePoolSize =
848
  optionalField $ simpleField "candidate_pool_size" [t| Positive Int |]
849

    
850
-- | Set UID pool, must be list of lists describing UID ranges (two
851
-- items, start and end inclusive.
852
pUidPool :: Field
853
pUidPool = optionalField $ simpleField "uid_pool" [t| [[(Int, Int)]] |]
854

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

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

    
865
-- | Whether to automatically maintain node health.
866
pMaintainNodeHealth :: Field
867
pMaintainNodeHealth = optionalField $ booleanField "maintain_node_health"
868

    
869
-- | Whether to modify and keep in sync the @/etc/hosts@ files of nodes.
870
pModifyEtcHosts :: Field
871
pModifyEtcHosts = optionalField $ booleanField "modify_etc_hosts"
872

    
873
-- | Whether to wipe disks before allocating them to instances.
874
pPreallocWipeDisks :: Field
875
pPreallocWipeDisks = optionalField $ booleanField "prealloc_wipe_disks"
876

    
877
-- | Cluster-wide NIC parameter defaults.
878
pNicParams :: Field
879
pNicParams = optionalField $ simpleField "nicparams" [t| INicParams |]
880

    
881
-- | Instance NIC definitions.
882
pInstNics :: Field
883
pInstNics = simpleField "nics" [t| [INicParams] |]
884

    
885
-- | Cluster-wide node parameter defaults.
886
pNdParams :: Field
887
pNdParams = optionalField $ simpleField "ndparams" [t| UncheckedDict |]
888

    
889
-- | Cluster-wide ipolicy specs.
890
pIpolicy :: Field
891
pIpolicy = optionalField $ simpleField "ipolicy" [t| UncheckedDict |]
892

    
893
-- | DRBD helper program.
894
pDrbdHelper :: Field
895
pDrbdHelper = optionalStringField "drbd_helper"
896

    
897
-- | Default iallocator for cluster.
898
pDefaultIAllocator :: Field
899
pDefaultIAllocator = optionalStringField "default_iallocator"
900

    
901
-- | Master network device.
902
pMasterNetdev :: Field
903
pMasterNetdev = optionalStringField "master_netdev"
904

    
905
-- | Netmask of the master IP.
906
pMasterNetmask :: Field
907
pMasterNetmask =
908
  optionalField $ simpleField "master_netmask" [t| NonNegative Int |]
909

    
910
-- | List of reserved LVs.
911
pReservedLvs :: Field
912
pReservedLvs =
913
  optionalField $ simpleField "reserved_lvs" [t| [NonEmptyString] |]
914

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

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

    
928
-- | Whether to use an external master IP address setup script.
929
pUseExternalMipScript :: Field
930
pUseExternalMipScript = optionalField $ booleanField "use_external_mip_script"
931

    
932
-- | Requested fields.
933
pQueryFields :: Field
934
pQueryFields = simpleField "fields" [t| [NonEmptyString] |]
935

    
936
-- | Query filter.
937
pQueryFilter :: Field
938
pQueryFilter = simpleField "qfilter" [t| Qlang.Filter String |]
939

    
940
-- | OOB command to run.
941
pOobCommand :: Field
942
pOobCommand = simpleField "command" [t| OobCommand |]
943

    
944
-- | Timeout before the OOB helper will be terminated.
945
pOobTimeout :: Field
946
pOobTimeout =
947
  defaultField [| C.oobTimeout |] $ simpleField "timeout" [t| Int |]
948

    
949
-- | Ignores the node offline status for power off.
950
pIgnoreStatus :: Field
951
pIgnoreStatus = defaultFalse "ignore_status"
952

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

    
961
-- | Primary IP address.
962
pPrimaryIp :: Field
963
pPrimaryIp = optionalStringField "primary_ip"
964

    
965
-- | Secondary IP address.
966
pSecondaryIp :: Field
967
pSecondaryIp = optionalNEStringField "secondary_ip"
968

    
969
-- | Whether node is re-added to cluster.
970
pReadd :: Field
971
pReadd = defaultFalse "readd"
972

    
973
-- | Initial node group.
974
pNodeGroup :: Field
975
pNodeGroup = optionalNEStringField "group"
976

    
977
-- | Whether node can become master or master candidate.
978
pMasterCapable :: Field
979
pMasterCapable = optionalField $ booleanField "master_capable"
980

    
981
-- | Whether node can host instances.
982
pVmCapable :: Field
983
pVmCapable = optionalField $ booleanField "vm_capable"
984

    
985
-- | List of names.
986
pNames :: Field
987
pNames = defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
988

    
989
-- | List of node names.
990
pNodes :: Field
991
pNodes = defaultField [| [] |] $ simpleField "nodes" [t| [NonEmptyString] |]
992

    
993
-- | Required list of node names.
994
pRequiredNodes :: Field
995
pRequiredNodes =
996
  renameField "ReqNodes " $ simpleField "nodes" [t| [NonEmptyString] |]
997

    
998
-- | Storage type.
999
pStorageType :: Field
1000
pStorageType = simpleField "storage_type" [t| StorageType |]
1001

    
1002
-- | Storage changes (unchecked).
1003
pStorageChanges :: Field
1004
pStorageChanges = simpleField "changes" [t| UncheckedDict |]
1005

    
1006
-- | Whether the node should become a master candidate.
1007
pMasterCandidate :: Field
1008
pMasterCandidate = optionalField $ booleanField "master_candidate"
1009

    
1010
-- | Whether the node should be marked as offline.
1011
pOffline :: Field
1012
pOffline = optionalField $ booleanField "offline"
1013

    
1014
-- | Whether the node should be marked as drained.
1015
pDrained ::Field
1016
pDrained = optionalField $ booleanField "drained"
1017

    
1018
-- | Whether node(s) should be promoted to master candidate if necessary.
1019
pAutoPromote :: Field
1020
pAutoPromote = defaultFalse "auto_promote"
1021

    
1022
-- | Whether the node should be marked as powered
1023
pPowered :: Field
1024
pPowered = optionalField $ booleanField "powered"
1025

    
1026
-- | Iallocator for deciding the target node for shared-storage
1027
-- instances during migrate and failover.
1028
pIallocator :: Field
1029
pIallocator = optionalNEStringField "iallocator"
1030

    
1031
-- | New secondary node.
1032
pRemoteNode :: Field
1033
pRemoteNode = optionalNEStringField "remote_node"
1034

    
1035
-- | Node evacuation mode.
1036
pEvacMode :: Field
1037
pEvacMode = renameField "EvacMode" $ simpleField "mode" [t| NodeEvacMode |]
1038

    
1039
-- | Instance creation mode.
1040
pInstCreateMode :: Field
1041
pInstCreateMode =
1042
  renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
1043

    
1044
-- | Do not install the OS (will disable automatic start).
1045
pNoInstall :: Field
1046
pNoInstall = optionalField $ booleanField "no_install"
1047

    
1048
-- | OS type for instance installation.
1049
pInstOs :: Field
1050
pInstOs = optionalNEStringField "os_type"
1051

    
1052
-- | Primary node for an instance.
1053
pPrimaryNode :: Field
1054
pPrimaryNode = optionalNEStringField "pnode"
1055

    
1056
-- | Secondary node for an instance.
1057
pSecondaryNode :: Field
1058
pSecondaryNode = optionalNEStringField "snode"
1059

    
1060
-- | Signed handshake from source (remote import only).
1061
pSourceHandshake :: Field
1062
pSourceHandshake =
1063
  optionalField $ simpleField "source_handshake" [t| UncheckedList |]
1064

    
1065
-- | Source instance name (remote import only).
1066
pSourceInstance :: Field
1067
pSourceInstance = optionalNEStringField "source_instance_name"
1068

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

    
1076
-- | Source X509 CA in PEM format (remote import only).
1077
pSourceX509Ca :: Field
1078
pSourceX509Ca = optionalNEStringField "source_x509_ca"
1079

    
1080
-- | Source node for import.
1081
pSrcNode :: Field
1082
pSrcNode = optionalNEStringField "src_node"
1083

    
1084
-- | Source directory for import.
1085
pSrcPath :: Field
1086
pSrcPath = optionalNEStringField "src_path"
1087

    
1088
-- | Whether to start instance after creation.
1089
pStartInstance :: Field
1090
pStartInstance = defaultTrue "start"
1091

    
1092
-- | Instance tags. FIXME: unify/simplify with pTags, once that
1093
-- migrates to NonEmpty String.
1094
pInstTags :: Field
1095
pInstTags =
1096
  renameField "InstTags" .
1097
  defaultField [| [] |] $
1098
  simpleField "tags" [t| [NonEmptyString] |]
1099

    
1100
-- | Unchecked list of OpInstanceCreate, used in OpInstanceMultiAlloc.
1101
pMultiAllocInstances :: Field
1102
pMultiAllocInstances =
1103
  renameField "InstMultiAlloc" .
1104
  defaultField [| [] |] $
1105
  simpleField "instances"[t| UncheckedList |]
1106

    
1107
-- | Ignore failures parameter.
1108
pIgnoreFailures :: Field
1109
pIgnoreFailures = defaultFalse "ignore_failures"
1110

    
1111
-- | New instance or cluster name.
1112
pNewName :: Field
1113
pNewName = simpleField "new_name" [t| NonEmptyString |]
1114

    
1115
-- | Whether to start the instance even if secondary disks are failing.
1116
pIgnoreSecondaries :: Field
1117
pIgnoreSecondaries = defaultFalse "ignore_secondaries"
1118

    
1119
-- | How to reboot the instance.
1120
pRebootType :: Field
1121
pRebootType = simpleField "reboot_type" [t| RebootType |]
1122

    
1123
-- | Whether to ignore recorded disk size.
1124
pIgnoreDiskSize :: Field
1125
pIgnoreDiskSize = defaultFalse "ignore_size"
1126

    
1127
-- | Disk list for recreate disks.
1128
pRecreateDisksInfo :: Field
1129
pRecreateDisksInfo =
1130
  renameField "RecreateDisksInfo" .
1131
  defaultField [| RecreateDisksAll |] $
1132
  simpleField "disks" [t| RecreateDisksInfo |]
1133

    
1134
-- | Whether to only return configuration data without querying nodes.
1135
pStatic :: Field
1136
pStatic = defaultFalse "static"
1137

    
1138
-- | InstanceSetParams NIC changes.
1139
pInstParamsNicChanges :: Field
1140
pInstParamsNicChanges =
1141
  renameField "InstNicChanges" .
1142
  defaultField [| SetParamsEmpty |] $
1143
  simpleField "nics" [t| SetParamsMods INicParams |]
1144

    
1145
-- | InstanceSetParams Disk changes.
1146
pInstParamsDiskChanges :: Field
1147
pInstParamsDiskChanges =
1148
  renameField "InstDiskChanges" .
1149
  defaultField [| SetParamsEmpty |] $
1150
  simpleField "disks" [t| SetParamsMods IDiskParams |]
1151

    
1152
-- | New runtime memory.
1153
pRuntimeMem :: Field
1154
pRuntimeMem = optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1155

    
1156
-- | Change the instance's OS without reinstalling the instance
1157
pOsNameChange :: Field
1158
pOsNameChange = optionalNEStringField "os_name"
1159

    
1160
-- | Disk index for e.g. grow disk.
1161
pDiskIndex :: Field
1162
pDiskIndex = renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
1163

    
1164
-- | Disk amount to add or grow to.
1165
pDiskChgAmount :: Field
1166
pDiskChgAmount =
1167
  renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
1168

    
1169
-- | Whether the amount parameter is an absolute target or a relative one.
1170
pDiskChgAbsolute :: Field
1171
pDiskChgAbsolute = renameField "DiskChkAbsolute" $ defaultFalse "absolute"
1172

    
1173
-- | Destination group names or UUIDs (defaults to \"all but current group\".
1174
pTargetGroups :: Field
1175
pTargetGroups =
1176
  optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
1177

    
1178
-- | Export mode field.
1179
pExportMode :: Field
1180
pExportMode =
1181
  renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1182

    
1183
-- | Export target_node field, depends on mode.
1184
pExportTargetNode :: Field
1185
pExportTargetNode =
1186
  renameField "ExportTarget" $
1187
  simpleField "target_node" [t| ExportTarget |]
1188

    
1189
-- | Whether to remove instance after export.
1190
pRemoveInstance :: Field
1191
pRemoveInstance = defaultFalse "remove_instance"
1192

    
1193
-- | Whether to ignore failures while removing instances.
1194
pIgnoreRemoveFailures :: Field
1195
pIgnoreRemoveFailures = defaultFalse "ignore_remove_failures"
1196

    
1197
-- | Name of X509 key (remote export only).
1198
pX509KeyName :: Field
1199
pX509KeyName = optionalField $ simpleField "x509_key_name" [t| UncheckedList |]
1200

    
1201
-- | Destination X509 CA (remote export only).
1202
pX509DestCA :: Field
1203
pX509DestCA = optionalNEStringField "destination_x509_ca"
1204

    
1205
-- | Search pattern (regular expression). FIXME: this should be
1206
-- compiled at load time?
1207
pTagSearchPattern :: Field
1208
pTagSearchPattern =
1209
  renameField "TagSearchPattern" $ simpleField "pattern" [t| NonEmptyString |]
1210

    
1211
-- | Restricted command name.
1212
pRestrictedCommand :: Field
1213
pRestrictedCommand =
1214
  renameField "RestrictedCommand" $
1215
  simpleField "command" [t| NonEmptyString |]
1216

    
1217
-- | Replace disks mode.
1218
pReplaceDisksMode :: Field
1219
pReplaceDisksMode =
1220
  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1221

    
1222
-- | List of disk indices.
1223
pReplaceDisksList :: Field
1224
pReplaceDisksList =
1225
  renameField "ReplaceDisksList" $ simpleField "disks" [t| [DiskIndex] |]
1226

    
1227
-- | Whether do allow failover in migrations.
1228
pAllowFailover :: Field
1229
pAllowFailover = defaultFalse "allow_failover"
1230

    
1231
-- * Test opcode parameters
1232

    
1233
-- | Duration parameter for 'OpTestDelay'.
1234
pDelayDuration :: Field
1235
pDelayDuration =
1236
  renameField "DelayDuration" $ simpleField "duration" [t| Double |]
1237

    
1238
-- | on_master field for 'OpTestDelay'.
1239
pDelayOnMaster :: Field
1240
pDelayOnMaster = renameField "DelayOnMaster" $ defaultTrue "on_master"
1241

    
1242
-- | on_nodes field for 'OpTestDelay'.
1243
pDelayOnNodes :: Field
1244
pDelayOnNodes =
1245
  renameField "DelayOnNodes" .
1246
  defaultField [| [] |] $
1247
  simpleField "on_nodes" [t| [NonEmptyString] |]
1248

    
1249
-- | Repeat parameter for OpTestDelay.
1250
pDelayRepeat :: Field
1251
pDelayRepeat =
1252
  renameField "DelayRepeat" .
1253
  defaultField [| forceNonNeg (0::Int) |] $
1254
  simpleField "repeat" [t| NonNegative Int |]
1255

    
1256
-- | IAllocator test direction.
1257
pIAllocatorDirection :: Field
1258
pIAllocatorDirection =
1259
  renameField "IAllocatorDirection" $
1260
  simpleField "direction" [t| IAllocatorTestDir |]
1261

    
1262
-- | IAllocator test mode.
1263
pIAllocatorMode :: Field
1264
pIAllocatorMode =
1265
  renameField "IAllocatorMode" $
1266
  simpleField "mode" [t| IAllocatorMode |]
1267

    
1268
-- | IAllocator target name (new instance, node to evac, etc.).
1269
pIAllocatorReqName :: Field
1270
pIAllocatorReqName =
1271
  renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
1272

    
1273
-- | Custom OpTestIAllocator nics.
1274
pIAllocatorNics :: Field
1275
pIAllocatorNics =
1276
  renameField "IAllocatorNics" $ simpleField "nics" [t| [UncheckedDict] |]
1277

    
1278
-- | Custom OpTestAllocator disks.
1279
pIAllocatorDisks :: Field
1280
pIAllocatorDisks =
1281
  renameField "IAllocatorDisks" $ simpleField "disks" [t| UncheckedList |]
1282

    
1283
-- | IAllocator memory field.
1284
pIAllocatorMemory :: Field
1285
pIAllocatorMemory =
1286
  renameField "IAllocatorMem" .
1287
  optionalField $
1288
  simpleField "memory" [t| NonNegative Int |]
1289

    
1290
-- | IAllocator vcpus field.
1291
pIAllocatorVCpus :: Field
1292
pIAllocatorVCpus =
1293
  renameField "IAllocatorVCpus" .
1294
  optionalField $
1295
  simpleField "vcpus" [t| NonNegative Int |]
1296

    
1297
-- | IAllocator os field.
1298
pIAllocatorOs :: Field
1299
pIAllocatorOs = renameField "IAllocatorOs" $ optionalNEStringField "os"
1300

    
1301
-- | IAllocator instances field.
1302
pIAllocatorInstances :: Field
1303
pIAllocatorInstances =
1304
  renameField "IAllocatorInstances " .
1305
  optionalField $
1306
  simpleField "instances" [t| [NonEmptyString] |]
1307

    
1308
-- | IAllocator evac mode.
1309
pIAllocatorEvacMode :: Field
1310
pIAllocatorEvacMode =
1311
  renameField "IAllocatorEvacMode" .
1312
  optionalField $
1313
  simpleField "evac_mode" [t| NodeEvacMode |]
1314

    
1315
-- | IAllocator spindle use.
1316
pIAllocatorSpindleUse :: Field
1317
pIAllocatorSpindleUse =
1318
  renameField "IAllocatorSpindleUse" .
1319
  defaultField [| forceNonNeg (1::Int) |] $
1320
  simpleField "spindle_use" [t| NonNegative Int |]
1321

    
1322
-- | IAllocator count field.
1323
pIAllocatorCount :: Field
1324
pIAllocatorCount =
1325
  renameField "IAllocatorCount" .
1326
  defaultField [| forceNonNeg (1::Int) |] $
1327
  simpleField "count" [t| NonNegative Int |]
1328

    
1329
-- | 'OpTestJqueue' notify_waitlock.
1330
pJQueueNotifyWaitLock :: Field
1331
pJQueueNotifyWaitLock = defaultFalse "notify_waitlock"
1332

    
1333
-- | 'OpTestJQueue' notify_exec.
1334
pJQueueNotifyExec :: Field
1335
pJQueueNotifyExec = defaultFalse "notify_exec"
1336

    
1337
-- | 'OpTestJQueue' log_messages.
1338
pJQueueLogMessages :: Field
1339
pJQueueLogMessages =
1340
  defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
1341

    
1342
-- | 'OpTestJQueue' fail attribute.
1343
pJQueueFail :: Field
1344
pJQueueFail =
1345
  renameField "JQueueFail" $ defaultFalse "fail"
1346

    
1347
-- | 'OpTestDummy' result field.
1348
pTestDummyResult :: Field
1349
pTestDummyResult =
1350
  renameField "TestDummyResult" $ simpleField "result" [t| UncheckedValue |]
1351

    
1352
-- | 'OpTestDummy' messages field.
1353
pTestDummyMessages :: Field
1354
pTestDummyMessages =
1355
  renameField "TestDummyMessages" $
1356
  simpleField "messages" [t| UncheckedValue |]
1357

    
1358
-- | 'OpTestDummy' fail field.
1359
pTestDummyFail :: Field
1360
pTestDummyFail =
1361
  renameField "TestDummyFail" $ simpleField "fail" [t| UncheckedValue |]
1362

    
1363
-- | 'OpTestDummy' submit_jobs field.
1364
pTestDummySubmitJobs :: Field
1365
pTestDummySubmitJobs =
1366
  renameField "TestDummySubmitJobs" $
1367
  simpleField "submit_jobs" [t| UncheckedValue |]
1368

    
1369
-- * Network parameters
1370

    
1371
-- | Network name.
1372
pNetworkName :: Field
1373
pNetworkName = simpleField "network_name" [t| NonEmptyString |]
1374

    
1375
-- | Network address (IPv4 subnet). FIXME: no real type for this.
1376
pNetworkAddress4 :: Field
1377
pNetworkAddress4 =
1378
  renameField "NetworkAddress4" $
1379
  simpleField "network" [t| NonEmptyString |]
1380

    
1381
-- | Network gateway (IPv4 address). FIXME: no real type for this.
1382
pNetworkGateway4 :: Field
1383
pNetworkGateway4 =
1384
  renameField "NetworkGateway4" $
1385
  optionalNEStringField "gateway"
1386

    
1387
-- | Network address (IPv6 subnet). FIXME: no real type for this.
1388
pNetworkAddress6 :: Field
1389
pNetworkAddress6 =
1390
  renameField "NetworkAddress6" $
1391
  optionalNEStringField "network6"
1392

    
1393
-- | Network gateway (IPv6 address). FIXME: no real type for this.
1394
pNetworkGateway6 :: Field
1395
pNetworkGateway6 =
1396
  renameField "NetworkGateway6" $
1397
  optionalNEStringField "gateway6"
1398

    
1399
-- | Network specific mac prefix (that overrides the cluster one).
1400
pNetworkMacPrefix :: Field
1401
pNetworkMacPrefix =
1402
  renameField "NetMacPrefix" $
1403
  optionalNEStringField "mac_prefix"
1404

    
1405
-- | Network add reserved IPs.
1406
pNetworkAddRsvdIps :: Field
1407
pNetworkAddRsvdIps =
1408
  renameField "NetworkAddRsvdIps" .
1409
  optionalField $
1410
  simpleField "add_reserved_ips" [t| [NonEmptyString] |]
1411

    
1412
-- | Network remove reserved IPs.
1413
pNetworkRemoveRsvdIps :: Field
1414
pNetworkRemoveRsvdIps =
1415
  renameField "NetworkRemoveRsvdIps" .
1416
  optionalField $
1417
  simpleField "remove_reserved_ips" [t| [NonEmptyString] |]
1418

    
1419
-- | Network mode when connecting to a group.
1420
pNetworkMode :: Field
1421
pNetworkMode = simpleField "network_mode" [t| NICMode |]
1422

    
1423
-- | Network link when connecting to a group.
1424
pNetworkLink :: Field
1425
pNetworkLink = simpleField "network_link" [t| NonEmptyString |]
1426

    
1427
-- * Common opcode parameters
1428

    
1429
-- | Run checks only, don't execute.
1430
pDryRun :: Field
1431
pDryRun = optionalField $ booleanField "dry_run"
1432

    
1433
-- | Debug level.
1434
pDebugLevel :: Field
1435
pDebugLevel = optionalField $ simpleField "debug_level" [t| NonNegative Int |]
1436

    
1437
-- | Opcode priority. Note: python uses a separate constant, we're
1438
-- using the actual value we know it's the default.
1439
pOpPriority :: Field
1440
pOpPriority =
1441
  defaultField [| OpPrioNormal |] $
1442
  simpleField "priority" [t| OpSubmitPriority |]
1443

    
1444
-- | Job dependencies.
1445
pDependencies :: Field
1446
pDependencies =
1447
  optionalNullSerField $ simpleField "depends" [t| [JobDependency] |]
1448

    
1449
-- | Comment field.
1450
pComment :: Field
1451
pComment = optionalNullSerField $ stringField "comment"
1452

    
1453
-- | Reason trail field.
1454
pReason :: Field
1455
pReason = simpleField C.opcodeReason [t| ReasonTrail |]
1456

    
1457
-- * Entire opcode parameter list
1458

    
1459
-- | Old-style query opcode, with locking.
1460
dOldQuery :: [Field]
1461
dOldQuery =
1462
  [ pOutputFields
1463
  , pNames
1464
  , pUseLocking
1465
  ]
1466

    
1467
-- | Old-style query opcode, without locking.
1468
dOldQueryNoLocking :: [Field]
1469
dOldQueryNoLocking =
1470
  [ pOutputFields
1471
  , pNames
1472
  ]