Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ 4fe04580

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

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

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

    
259
-- * Helper functions and types
260

    
261
-- * Type aliases
262

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

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

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

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

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

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

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

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

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

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

    
305
-- ** Tags
306

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

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

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

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

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

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

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

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

    
364
-- ** Disks
365

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

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

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

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

    
391
-- ** I* param types
392

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
508
-- * Parameters
509

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
673
-- ** Parameters for cluster verification
674

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

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

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

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

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

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

    
704
-- * Parameters for node resource model
705

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
868
-- | Whether to wipe disks before allocating them to instances.
869
pPreallocWipeDisks :: Field
870
pPreallocWipeDisks = optionalField $ booleanField "prealloc_wipe_disks"
871

    
872
-- | Cluster-wide NIC parameter defaults.
873
pNicParams :: Field
874
pNicParams = optionalField $ simpleField "nicparams" [t| INicParams |]
875

    
876
-- | Instance NIC definitions.
877
pInstNics :: Field
878
pInstNics = simpleField "nics" [t| [INicParams] |]
879

    
880
-- | Cluster-wide node parameter defaults.
881
pNdParams :: Field
882
pNdParams = optionalField $ simpleField "ndparams" [t| UncheckedDict |]
883

    
884
-- | Cluster-wide ipolicy specs.
885
pIpolicy :: Field
886
pIpolicy = optionalField $ simpleField "ipolicy" [t| UncheckedDict |]
887

    
888
-- | DRBD helper program.
889
pDrbdHelper :: Field
890
pDrbdHelper = optionalStringField "drbd_helper"
891

    
892
-- | Default iallocator for cluster.
893
pDefaultIAllocator :: Field
894
pDefaultIAllocator = optionalStringField "default_iallocator"
895

    
896
-- | Master network device.
897
pMasterNetdev :: Field
898
pMasterNetdev = optionalStringField "master_netdev"
899

    
900
-- | Netmask of the master IP.
901
pMasterNetmask :: Field
902
pMasterNetmask =
903
  optionalField $ simpleField "master_netmask" [t| NonNegative Int |]
904

    
905
-- | List of reserved LVs.
906
pReservedLvs :: Field
907
pReservedLvs =
908
  optionalField $ simpleField "reserved_lvs" [t| [NonEmptyString] |]
909

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

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

    
923
-- | Whether to use an external master IP address setup script.
924
pUseExternalMipScript :: Field
925
pUseExternalMipScript = optionalField $ booleanField "use_external_mip_script"
926

    
927
-- | Requested fields.
928
pQueryFields :: Field
929
pQueryFields = simpleField "fields" [t| [NonEmptyString] |]
930

    
931
-- | Query filter.
932
pQueryFilter :: Field
933
pQueryFilter = simpleField "qfilter" [t| Qlang.Filter String |]
934

    
935
-- | OOB command to run.
936
pOobCommand :: Field
937
pOobCommand = simpleField "command" [t| OobCommand |]
938

    
939
-- | Timeout before the OOB helper will be terminated.
940
pOobTimeout :: Field
941
pOobTimeout =
942
  defaultField [| C.oobTimeout |] $ simpleField "timeout" [t| Int |]
943

    
944
-- | Ignores the node offline status for power off.
945
pIgnoreStatus :: Field
946
pIgnoreStatus = defaultFalse "ignore_status"
947

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

    
956
-- | Primary IP address.
957
pPrimaryIp :: Field
958
pPrimaryIp = optionalStringField "primary_ip"
959

    
960
-- | Secondary IP address.
961
pSecondaryIp :: Field
962
pSecondaryIp = optionalNEStringField "secondary_ip"
963

    
964
-- | Whether node is re-added to cluster.
965
pReadd :: Field
966
pReadd = defaultFalse "readd"
967

    
968
-- | Initial node group.
969
pNodeGroup :: Field
970
pNodeGroup = optionalNEStringField "group"
971

    
972
-- | Whether node can become master or master candidate.
973
pMasterCapable :: Field
974
pMasterCapable = optionalField $ booleanField "master_capable"
975

    
976
-- | Whether node can host instances.
977
pVmCapable :: Field
978
pVmCapable = optionalField $ booleanField "vm_capable"
979

    
980
-- | List of names.
981
pNames :: Field
982
pNames = defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
983

    
984
-- | List of node names.
985
pNodes :: Field
986
pNodes = defaultField [| [] |] $ simpleField "nodes" [t| [NonEmptyString] |]
987

    
988
-- | Required list of node names.
989
pRequiredNodes :: Field
990
pRequiredNodes =
991
  renameField "ReqNodes " $ simpleField "nodes" [t| [NonEmptyString] |]
992

    
993
-- | Storage type.
994
pStorageType :: Field
995
pStorageType = simpleField "storage_type" [t| StorageType |]
996

    
997
-- | Storage changes (unchecked).
998
pStorageChanges :: Field
999
pStorageChanges = simpleField "changes" [t| UncheckedDict |]
1000

    
1001
-- | Whether the node should become a master candidate.
1002
pMasterCandidate :: Field
1003
pMasterCandidate = optionalField $ booleanField "master_candidate"
1004

    
1005
-- | Whether the node should be marked as offline.
1006
pOffline :: Field
1007
pOffline = optionalField $ booleanField "offline"
1008

    
1009
-- | Whether the node should be marked as drained.
1010
pDrained ::Field
1011
pDrained = optionalField $ booleanField "drained"
1012

    
1013
-- | Whether node(s) should be promoted to master candidate if necessary.
1014
pAutoPromote :: Field
1015
pAutoPromote = defaultFalse "auto_promote"
1016

    
1017
-- | Whether the node should be marked as powered
1018
pPowered :: Field
1019
pPowered = optionalField $ booleanField "powered"
1020

    
1021
-- | Iallocator for deciding the target node for shared-storage
1022
-- instances during migrate and failover.
1023
pIallocator :: Field
1024
pIallocator = optionalNEStringField "iallocator"
1025

    
1026
-- | New secondary node.
1027
pRemoteNode :: Field
1028
pRemoteNode = optionalNEStringField "remote_node"
1029

    
1030
-- | Node evacuation mode.
1031
pEvacMode :: Field
1032
pEvacMode = renameField "EvacMode" $ simpleField "mode" [t| NodeEvacMode |]
1033

    
1034
-- | Instance creation mode.
1035
pInstCreateMode :: Field
1036
pInstCreateMode =
1037
  renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
1038

    
1039
-- | Do not install the OS (will disable automatic start).
1040
pNoInstall :: Field
1041
pNoInstall = optionalField $ booleanField "no_install"
1042

    
1043
-- | OS type for instance installation.
1044
pInstOs :: Field
1045
pInstOs = optionalNEStringField "os_type"
1046

    
1047
-- | Primary node for an instance.
1048
pPrimaryNode :: Field
1049
pPrimaryNode = optionalNEStringField "pnode"
1050

    
1051
-- | Secondary node for an instance.
1052
pSecondaryNode :: Field
1053
pSecondaryNode = optionalNEStringField "snode"
1054

    
1055
-- | Signed handshake from source (remote import only).
1056
pSourceHandshake :: Field
1057
pSourceHandshake =
1058
  optionalField $ simpleField "source_handshake" [t| UncheckedList |]
1059

    
1060
-- | Source instance name (remote import only).
1061
pSourceInstance :: Field
1062
pSourceInstance = optionalNEStringField "source_instance_name"
1063

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

    
1071
-- | Source X509 CA in PEM format (remote import only).
1072
pSourceX509Ca :: Field
1073
pSourceX509Ca = optionalNEStringField "source_x509_ca"
1074

    
1075
-- | Source node for import.
1076
pSrcNode :: Field
1077
pSrcNode = optionalNEStringField "src_node"
1078

    
1079
-- | Source directory for import.
1080
pSrcPath :: Field
1081
pSrcPath = optionalNEStringField "src_path"
1082

    
1083
-- | Whether to start instance after creation.
1084
pStartInstance :: Field
1085
pStartInstance = defaultTrue "start"
1086

    
1087
-- | Instance tags. FIXME: unify/simplify with pTags, once that
1088
-- migrates to NonEmpty String.
1089
pInstTags :: Field
1090
pInstTags =
1091
  renameField "InstTags" .
1092
  defaultField [| [] |] $
1093
  simpleField "tags" [t| [NonEmptyString] |]
1094

    
1095
-- | Unchecked list of OpInstanceCreate, used in OpInstanceMultiAlloc.
1096
pMultiAllocInstances :: Field
1097
pMultiAllocInstances =
1098
  renameField "InstMultiAlloc" .
1099
  defaultField [| [] |] $
1100
  simpleField "instances"[t| UncheckedList |]
1101

    
1102
-- | Ignore failures parameter.
1103
pIgnoreFailures :: Field
1104
pIgnoreFailures = defaultFalse "ignore_failures"
1105

    
1106
-- | New instance or cluster name.
1107
pNewName :: Field
1108
pNewName = simpleField "new_name" [t| NonEmptyString |]
1109

    
1110
-- | Whether to start the instance even if secondary disks are failing.
1111
pIgnoreSecondaries :: Field
1112
pIgnoreSecondaries = defaultFalse "ignore_secondaries"
1113

    
1114
-- | How to reboot the instance.
1115
pRebootType :: Field
1116
pRebootType = simpleField "reboot_type" [t| RebootType |]
1117

    
1118
-- | Whether to ignore recorded disk size.
1119
pIgnoreDiskSize :: Field
1120
pIgnoreDiskSize = defaultFalse "ignore_size"
1121

    
1122
-- | Disk list for recreate disks.
1123
pRecreateDisksInfo :: Field
1124
pRecreateDisksInfo =
1125
  renameField "RecreateDisksInfo" .
1126
  defaultField [| RecreateDisksAll |] $
1127
  simpleField "disks" [t| RecreateDisksInfo |]
1128

    
1129
-- | Whether to only return configuration data without querying nodes.
1130
pStatic :: Field
1131
pStatic = defaultFalse "static"
1132

    
1133
-- | InstanceSetParams NIC changes.
1134
pInstParamsNicChanges :: Field
1135
pInstParamsNicChanges =
1136
  renameField "InstNicChanges" .
1137
  defaultField [| SetParamsEmpty |] $
1138
  simpleField "nics" [t| SetParamsMods INicParams |]
1139

    
1140
-- | InstanceSetParams Disk changes.
1141
pInstParamsDiskChanges :: Field
1142
pInstParamsDiskChanges =
1143
  renameField "InstDiskChanges" .
1144
  defaultField [| SetParamsEmpty |] $
1145
  simpleField "disks" [t| SetParamsMods IDiskParams |]
1146

    
1147
-- | New runtime memory.
1148
pRuntimeMem :: Field
1149
pRuntimeMem = optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1150

    
1151
-- | Change the instance's OS without reinstalling the instance
1152
pOsNameChange :: Field
1153
pOsNameChange = optionalNEStringField "os_name"
1154

    
1155
-- | Disk index for e.g. grow disk.
1156
pDiskIndex :: Field
1157
pDiskIndex = renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
1158

    
1159
-- | Disk amount to add or grow to.
1160
pDiskChgAmount :: Field
1161
pDiskChgAmount =
1162
  renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
1163

    
1164
-- | Whether the amount parameter is an absolute target or a relative one.
1165
pDiskChgAbsolute :: Field
1166
pDiskChgAbsolute = renameField "DiskChkAbsolute" $ defaultFalse "absolute"
1167

    
1168
-- | Destination group names or UUIDs (defaults to \"all but current group\".
1169
pTargetGroups :: Field
1170
pTargetGroups =
1171
  optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
1172

    
1173
-- | Export mode field.
1174
pExportMode :: Field
1175
pExportMode =
1176
  renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1177

    
1178
-- | Export target_node field, depends on mode.
1179
pExportTargetNode :: Field
1180
pExportTargetNode =
1181
  renameField "ExportTarget" $
1182
  simpleField "target_node" [t| ExportTarget |]
1183

    
1184
-- | Whether to remove instance after export.
1185
pRemoveInstance :: Field
1186
pRemoveInstance = defaultFalse "remove_instance"
1187

    
1188
-- | Whether to ignore failures while removing instances.
1189
pIgnoreRemoveFailures :: Field
1190
pIgnoreRemoveFailures = defaultFalse "ignore_remove_failures"
1191

    
1192
-- | Name of X509 key (remote export only).
1193
pX509KeyName :: Field
1194
pX509KeyName = optionalField $ simpleField "x509_key_name" [t| UncheckedList |]
1195

    
1196
-- | Destination X509 CA (remote export only).
1197
pX509DestCA :: Field
1198
pX509DestCA = optionalNEStringField "destination_x509_ca"
1199

    
1200
-- | Search pattern (regular expression). FIXME: this should be
1201
-- compiled at load time?
1202
pTagSearchPattern :: Field
1203
pTagSearchPattern =
1204
  renameField "TagSearchPattern" $ simpleField "pattern" [t| NonEmptyString |]
1205

    
1206
-- | Restricted command name.
1207
pRestrictedCommand :: Field
1208
pRestrictedCommand =
1209
  renameField "RestrictedCommand" $
1210
  simpleField "command" [t| NonEmptyString |]
1211

    
1212
-- | Replace disks mode.
1213
pReplaceDisksMode :: Field
1214
pReplaceDisksMode =
1215
  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1216

    
1217
-- | List of disk indices.
1218
pReplaceDisksList :: Field
1219
pReplaceDisksList =
1220
  renameField "ReplaceDisksList" $ simpleField "disks" [t| [DiskIndex] |]
1221

    
1222
-- | Whether do allow failover in migrations.
1223
pAllowFailover :: Field
1224
pAllowFailover = defaultFalse "allow_failover"
1225

    
1226
-- * Test opcode parameters
1227

    
1228
-- | Duration parameter for 'OpTestDelay'.
1229
pDelayDuration :: Field
1230
pDelayDuration =
1231
  renameField "DelayDuration" $ simpleField "duration" [t| Double |]
1232

    
1233
-- | on_master field for 'OpTestDelay'.
1234
pDelayOnMaster :: Field
1235
pDelayOnMaster = renameField "DelayOnMaster" $ defaultTrue "on_master"
1236

    
1237
-- | on_nodes field for 'OpTestDelay'.
1238
pDelayOnNodes :: Field
1239
pDelayOnNodes =
1240
  renameField "DelayOnNodes" .
1241
  defaultField [| [] |] $
1242
  simpleField "on_nodes" [t| [NonEmptyString] |]
1243

    
1244
-- | Repeat parameter for OpTestDelay.
1245
pDelayRepeat :: Field
1246
pDelayRepeat =
1247
  renameField "DelayRepeat" .
1248
  defaultField [| forceNonNeg (0::Int) |] $
1249
  simpleField "repeat" [t| NonNegative Int |]
1250

    
1251
-- | IAllocator test direction.
1252
pIAllocatorDirection :: Field
1253
pIAllocatorDirection =
1254
  renameField "IAllocatorDirection" $
1255
  simpleField "direction" [t| IAllocatorTestDir |]
1256

    
1257
-- | IAllocator test mode.
1258
pIAllocatorMode :: Field
1259
pIAllocatorMode =
1260
  renameField "IAllocatorMode" $
1261
  simpleField "mode" [t| IAllocatorMode |]
1262

    
1263
-- | IAllocator target name (new instance, node to evac, etc.).
1264
pIAllocatorReqName :: Field
1265
pIAllocatorReqName =
1266
  renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
1267

    
1268
-- | Custom OpTestIAllocator nics.
1269
pIAllocatorNics :: Field
1270
pIAllocatorNics =
1271
  renameField "IAllocatorNics" $ simpleField "nics" [t| [UncheckedDict] |]
1272

    
1273
-- | Custom OpTestAllocator disks.
1274
pIAllocatorDisks :: Field
1275
pIAllocatorDisks =
1276
  renameField "IAllocatorDisks" $ simpleField "disks" [t| UncheckedList |]
1277

    
1278
-- | IAllocator memory field.
1279
pIAllocatorMemory :: Field
1280
pIAllocatorMemory =
1281
  renameField "IAllocatorMem" .
1282
  optionalField $
1283
  simpleField "memory" [t| NonNegative Int |]
1284

    
1285
-- | IAllocator vcpus field.
1286
pIAllocatorVCpus :: Field
1287
pIAllocatorVCpus =
1288
  renameField "IAllocatorVCpus" .
1289
  optionalField $
1290
  simpleField "vcpus" [t| NonNegative Int |]
1291

    
1292
-- | IAllocator os field.
1293
pIAllocatorOs :: Field
1294
pIAllocatorOs = renameField "IAllocatorOs" $ optionalNEStringField "os"
1295

    
1296
-- | IAllocator instances field.
1297
pIAllocatorInstances :: Field
1298
pIAllocatorInstances =
1299
  renameField "IAllocatorInstances " .
1300
  optionalField $
1301
  simpleField "instances" [t| [NonEmptyString] |]
1302

    
1303
-- | IAllocator evac mode.
1304
pIAllocatorEvacMode :: Field
1305
pIAllocatorEvacMode =
1306
  renameField "IAllocatorEvacMode" .
1307
  optionalField $
1308
  simpleField "evac_mode" [t| NodeEvacMode |]
1309

    
1310
-- | IAllocator spindle use.
1311
pIAllocatorSpindleUse :: Field
1312
pIAllocatorSpindleUse =
1313
  renameField "IAllocatorSpindleUse" .
1314
  defaultField [| forceNonNeg (1::Int) |] $
1315
  simpleField "spindle_use" [t| NonNegative Int |]
1316

    
1317
-- | IAllocator count field.
1318
pIAllocatorCount :: Field
1319
pIAllocatorCount =
1320
  renameField "IAllocatorCount" .
1321
  defaultField [| forceNonNeg (1::Int) |] $
1322
  simpleField "count" [t| NonNegative Int |]
1323

    
1324
-- | 'OpTestJqueue' notify_waitlock.
1325
pJQueueNotifyWaitLock :: Field
1326
pJQueueNotifyWaitLock = defaultFalse "notify_waitlock"
1327

    
1328
-- | 'OpTestJQueue' notify_exec.
1329
pJQueueNotifyExec :: Field
1330
pJQueueNotifyExec = defaultFalse "notify_exec"
1331

    
1332
-- | 'OpTestJQueue' log_messages.
1333
pJQueueLogMessages :: Field
1334
pJQueueLogMessages =
1335
  defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
1336

    
1337
-- | 'OpTestJQueue' fail attribute.
1338
pJQueueFail :: Field
1339
pJQueueFail =
1340
  renameField "JQueueFail" $ defaultFalse "fail"
1341

    
1342
-- | 'OpTestDummy' result field.
1343
pTestDummyResult :: Field
1344
pTestDummyResult =
1345
  renameField "TestDummyResult" $ simpleField "result" [t| UncheckedValue |]
1346

    
1347
-- | 'OpTestDummy' messages field.
1348
pTestDummyMessages :: Field
1349
pTestDummyMessages =
1350
  renameField "TestDummyMessages" $
1351
  simpleField "messages" [t| UncheckedValue |]
1352

    
1353
-- | 'OpTestDummy' fail field.
1354
pTestDummyFail :: Field
1355
pTestDummyFail =
1356
  renameField "TestDummyFail" $ simpleField "fail" [t| UncheckedValue |]
1357

    
1358
-- | 'OpTestDummy' submit_jobs field.
1359
pTestDummySubmitJobs :: Field
1360
pTestDummySubmitJobs =
1361
  renameField "TestDummySubmitJobs" $
1362
  simpleField "submit_jobs" [t| UncheckedValue |]
1363

    
1364
-- * Network parameters
1365

    
1366
-- | Network name.
1367
pNetworkName :: Field
1368
pNetworkName = simpleField "network_name" [t| NonEmptyString |]
1369

    
1370
-- | Network address (IPv4 subnet). FIXME: no real type for this.
1371
pNetworkAddress4 :: Field
1372
pNetworkAddress4 =
1373
  renameField "NetworkAddress4" $
1374
  simpleField "network" [t| NonEmptyString |]
1375

    
1376
-- | Network gateway (IPv4 address). FIXME: no real type for this.
1377
pNetworkGateway4 :: Field
1378
pNetworkGateway4 =
1379
  renameField "NetworkGateway4" $
1380
  optionalNEStringField "gateway"
1381

    
1382
-- | Network address (IPv6 subnet). FIXME: no real type for this.
1383
pNetworkAddress6 :: Field
1384
pNetworkAddress6 =
1385
  renameField "NetworkAddress6" $
1386
  optionalNEStringField "network6"
1387

    
1388
-- | Network gateway (IPv6 address). FIXME: no real type for this.
1389
pNetworkGateway6 :: Field
1390
pNetworkGateway6 =
1391
  renameField "NetworkGateway6" $
1392
  optionalNEStringField "gateway6"
1393

    
1394
-- | Network specific mac prefix (that overrides the cluster one).
1395
pNetworkMacPrefix :: Field
1396
pNetworkMacPrefix =
1397
  renameField "NetMacPrefix" $
1398
  optionalNEStringField "mac_prefix"
1399

    
1400
-- | Network add reserved IPs.
1401
pNetworkAddRsvdIps :: Field
1402
pNetworkAddRsvdIps =
1403
  renameField "NetworkAddRsvdIps" .
1404
  optionalField $
1405
  simpleField "add_reserved_ips" [t| [NonEmptyString] |]
1406

    
1407
-- | Network remove reserved IPs.
1408
pNetworkRemoveRsvdIps :: Field
1409
pNetworkRemoveRsvdIps =
1410
  renameField "NetworkRemoveRsvdIps" .
1411
  optionalField $
1412
  simpleField "remove_reserved_ips" [t| [NonEmptyString] |]
1413

    
1414
-- | Network mode when connecting to a group.
1415
pNetworkMode :: Field
1416
pNetworkMode = simpleField "network_mode" [t| NICMode |]
1417

    
1418
-- | Network link when connecting to a group.
1419
pNetworkLink :: Field
1420
pNetworkLink = simpleField "network_link" [t| NonEmptyString |]
1421

    
1422
-- * Common opcode parameters
1423

    
1424
-- | Run checks only, don't execute.
1425
pDryRun :: Field
1426
pDryRun = optionalField $ booleanField "dry_run"
1427

    
1428
-- | Debug level.
1429
pDebugLevel :: Field
1430
pDebugLevel = optionalField $ simpleField "debug_level" [t| NonNegative Int |]
1431

    
1432
-- | Opcode priority. Note: python uses a separate constant, we're
1433
-- using the actual value we know it's the default.
1434
pOpPriority :: Field
1435
pOpPriority =
1436
  defaultField [| OpPrioNormal |] $
1437
  simpleField "priority" [t| OpSubmitPriority |]
1438

    
1439
-- | Job dependencies.
1440
pDependencies :: Field
1441
pDependencies =
1442
  optionalNullSerField $ simpleField "depends" [t| [JobDependency] |]
1443

    
1444
-- | Comment field.
1445
pComment :: Field
1446
pComment = optionalNullSerField $ stringField "comment"
1447

    
1448
-- | Reason trail field.
1449
pReason :: Field
1450
pReason = simpleField C.opcodeReason [t| ReasonTrail |]
1451

    
1452
-- * Entire opcode parameter list
1453

    
1454
-- | Old-style query opcode, with locking.
1455
dOldQuery :: [Field]
1456
dOldQuery =
1457
  [ pOutputFields
1458
  , pNames
1459
  , pUseLocking
1460
  ]
1461

    
1462
-- | Old-style query opcode, without locking.
1463
dOldQueryNoLocking :: [Field]
1464
dOldQueryNoLocking =
1465
  [ pOutputFields
1466
  , pNames
1467
  ]