Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ fc01b92b

History | View | Annotate | Download (43.1 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

    
3
{-| Implementation of opcodes parameters.
4

    
5
These are defined in a separate module only due to TemplateHaskell
6
stage restrictions - expressions defined in the current module can't
7
be passed to splices. So we have to either parameters/repeat each
8
parameter definition multiple times, or separate them into this
9
module.
10

    
11
-}
12

    
13
{-
14

    
15
Copyright (C) 2012 Google Inc.
16

    
17
This program is free software; you can redistribute it and/or modify
18
it under the terms of the GNU General Public License as published by
19
the Free Software Foundation; either version 2 of the License, or
20
(at your option) any later version.
21

    
22
This program is distributed in the hope that it will be useful, but
23
WITHOUT ANY WARRANTY; without even the implied warranty of
24
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
25
General Public License for more details.
26

    
27
You should have received a copy of the GNU General Public License
28
along with this program; if not, write to the Free Software
29
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
30
02110-1301, USA.
31

    
32
-}
33

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

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

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

    
262
-- * Helper functions and types
263

    
264
-- * Type aliases
265

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

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

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

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

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

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

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

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

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

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

    
308
-- ** Tags
309

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

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

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

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

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

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

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

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

    
367
-- ** Disks
368

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

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

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

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

    
394
-- ** I* param types
395

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
511
-- * Parameters
512

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
676
-- ** Parameters for cluster verification
677

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

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

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

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

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

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

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

    
711
pHotplugIfPossible :: Field
712
pHotplugIfPossible = defaultFalse "hotplug_if_possible"
713

    
714
-- * Parameters for node resource model
715

    
716
-- | Set hypervisor states.
717
pHvState :: Field
718
pHvState = optionalField $ simpleField "hv_state" [t| UncheckedDict |]
719

    
720
-- | Set disk states.
721
pDiskState :: Field
722
pDiskState = optionalField $ simpleField "disk_state" [t| UncheckedDict |]
723

    
724
-- | Whether to ignore ipolicy violations.
725
pIgnoreIpolicy :: Field
726
pIgnoreIpolicy = defaultFalse "ignore_ipolicy"
727

    
728
-- | Allow runtime changes while migrating.
729
pAllowRuntimeChgs :: Field
730
pAllowRuntimeChgs = defaultTrue "allow_runtime_changes"
731

    
732
-- | Utility type for OpClusterSetParams.
733
type TestClusterOsListItem = (DdmSimple, NonEmptyString)
734

    
735
-- | Utility type of OsList.
736
type TestClusterOsList = [TestClusterOsListItem]
737

    
738
-- Utility type for NIC definitions.
739
--type TestNicDef = INicParams
740

    
741
-- | List of instance disks.
742
pInstDisks :: Field
743
pInstDisks = renameField "instDisks" $ simpleField "disks" [t| [IDiskParams] |]
744

    
745
-- | Instance disk template.
746
pDiskTemplate :: Field
747
pDiskTemplate = simpleField "disk_template" [t| DiskTemplate |]
748

    
749
-- | Instance disk template.
750
pOptDiskTemplate :: Field
751
pOptDiskTemplate =
752
  optionalField .
753
  renameField "OptDiskTemplate" $
754
  simpleField "disk_template" [t| DiskTemplate |]
755

    
756
-- | File driver.
757
pFileDriver :: Field
758
pFileDriver = optionalField $ simpleField "file_driver" [t| FileDriver |]
759

    
760
-- | Directory for storing file-backed disks.
761
pFileStorageDir :: Field
762
pFileStorageDir = optionalNEStringField "file_storage_dir"
763

    
764
-- | Volume group name.
765
pVgName :: Field
766
pVgName = optionalStringField "vg_name"
767

    
768
-- | List of enabled hypervisors.
769
pEnabledHypervisors :: Field
770
pEnabledHypervisors =
771
  optionalField $
772
  simpleField "enabled_hypervisors" [t| NonEmpty Hypervisor |]
773

    
774
-- | List of enabled disk templates.
775
pEnabledDiskTemplates :: Field
776
pEnabledDiskTemplates =
777
  optionalField $
778
  simpleField "enabled_disk_templates" [t| NonEmpty DiskTemplate |]
779

    
780
-- | Selected hypervisor for an instance.
781
pHypervisor :: Field
782
pHypervisor =
783
  optionalField $
784
  simpleField "hypervisor" [t| Hypervisor |]
785

    
786
-- | Cluster-wide hypervisor parameters, hypervisor-dependent.
787
pClusterHvParams :: Field
788
pClusterHvParams =
789
  renameField "ClusterHvParams" .
790
  optionalField $
791
  simpleField "hvparams" [t| Container UncheckedDict |]
792

    
793
-- | Instance hypervisor parameters.
794
pInstHvParams :: Field
795
pInstHvParams =
796
  renameField "InstHvParams" .
797
  defaultField [| toJSObject [] |] $
798
  simpleField "hvparams" [t| UncheckedDict |]
799

    
800
-- | Cluster-wide beparams.
801
pClusterBeParams :: Field
802
pClusterBeParams =
803
  renameField "ClusterBeParams" .
804
  optionalField $ simpleField "beparams" [t| UncheckedDict |]
805

    
806
-- | Instance beparams.
807
pInstBeParams :: Field
808
pInstBeParams =
809
  renameField "InstBeParams" .
810
  defaultField [| toJSObject [] |] $
811
  simpleField "beparams" [t| UncheckedDict |]
812

    
813
-- | Reset instance parameters to default if equal.
814
pResetDefaults :: Field
815
pResetDefaults = defaultFalse "identify_defaults"
816

    
817
-- | Cluster-wide per-OS hypervisor parameter defaults.
818
pOsHvp :: Field
819
pOsHvp = optionalField $ simpleField "os_hvp" [t| Container UncheckedDict |]
820

    
821
-- | Cluster-wide OS parameter defaults.
822
pClusterOsParams :: Field
823
pClusterOsParams =
824
  renameField "ClusterOsParams" .
825
  optionalField $ simpleField "osparams" [t| Container UncheckedDict |]
826

    
827
-- | Instance OS parameters.
828
pInstOsParams :: Field
829
pInstOsParams =
830
  renameField "InstOsParams" . defaultField [| toJSObject [] |] $
831
  simpleField "osparams" [t| UncheckedDict |]
832

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

    
840
-- | Temporary hypervisor parameters, hypervisor-dependent.
841
pTempHvParams :: Field
842
pTempHvParams =
843
  renameField "TempHvParams" .
844
  defaultField [| toJSObject [] |] $
845
  simpleField "hvparams" [t| UncheckedDict |]
846

    
847
-- | Temporary backend parameters.
848
pTempBeParams :: Field
849
pTempBeParams =
850
  renameField "TempBeParams" .
851
  defaultField [| toJSObject [] |] $
852
  simpleField "beparams" [t| UncheckedDict |]
853

    
854
-- | Candidate pool size.
855
pCandidatePoolSize :: Field
856
pCandidatePoolSize =
857
  optionalField $ simpleField "candidate_pool_size" [t| Positive Int |]
858

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

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

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

    
874
-- | Whether to automatically maintain node health.
875
pMaintainNodeHealth :: Field
876
pMaintainNodeHealth = optionalField $ booleanField "maintain_node_health"
877

    
878
-- | Whether to modify and keep in sync the @/etc/hosts@ files of nodes.
879
pModifyEtcHosts :: Field
880
pModifyEtcHosts = optionalField $ booleanField "modify_etc_hosts"
881

    
882
-- | Whether to wipe disks before allocating them to instances.
883
pPreallocWipeDisks :: Field
884
pPreallocWipeDisks = optionalField $ booleanField "prealloc_wipe_disks"
885

    
886
-- | Cluster-wide NIC parameter defaults.
887
pNicParams :: Field
888
pNicParams = optionalField $ simpleField "nicparams" [t| INicParams |]
889

    
890
-- | Instance NIC definitions.
891
pInstNics :: Field
892
pInstNics = simpleField "nics" [t| [INicParams] |]
893

    
894
-- | Cluster-wide node parameter defaults.
895
pNdParams :: Field
896
pNdParams = optionalField $ simpleField "ndparams" [t| UncheckedDict |]
897

    
898
-- | Cluster-wide ipolicy specs.
899
pIpolicy :: Field
900
pIpolicy = optionalField $ simpleField "ipolicy" [t| UncheckedDict |]
901

    
902
-- | DRBD helper program.
903
pDrbdHelper :: Field
904
pDrbdHelper = optionalStringField "drbd_helper"
905

    
906
-- | Default iallocator for cluster.
907
pDefaultIAllocator :: Field
908
pDefaultIAllocator = optionalStringField "default_iallocator"
909

    
910
-- | Master network device.
911
pMasterNetdev :: Field
912
pMasterNetdev = optionalStringField "master_netdev"
913

    
914
-- | Netmask of the master IP.
915
pMasterNetmask :: Field
916
pMasterNetmask =
917
  optionalField $ simpleField "master_netmask" [t| NonNegative Int |]
918

    
919
-- | List of reserved LVs.
920
pReservedLvs :: Field
921
pReservedLvs =
922
  optionalField $ simpleField "reserved_lvs" [t| [NonEmptyString] |]
923

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

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

    
937
-- | Whether to use an external master IP address setup script.
938
pUseExternalMipScript :: Field
939
pUseExternalMipScript = optionalField $ booleanField "use_external_mip_script"
940

    
941
-- | Requested fields.
942
pQueryFields :: Field
943
pQueryFields = simpleField "fields" [t| [NonEmptyString] |]
944

    
945
-- | Query filter.
946
pQueryFilter :: Field
947
pQueryFilter = simpleField "qfilter" [t| Qlang.Filter String |]
948

    
949
-- | OOB command to run.
950
pOobCommand :: Field
951
pOobCommand = simpleField "command" [t| OobCommand |]
952

    
953
-- | Timeout before the OOB helper will be terminated.
954
pOobTimeout :: Field
955
pOobTimeout =
956
  defaultField [| C.oobTimeout |] $ simpleField "timeout" [t| Int |]
957

    
958
-- | Ignores the node offline status for power off.
959
pIgnoreStatus :: Field
960
pIgnoreStatus = defaultFalse "ignore_status"
961

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

    
970
-- | Primary IP address.
971
pPrimaryIp :: Field
972
pPrimaryIp = optionalStringField "primary_ip"
973

    
974
-- | Secondary IP address.
975
pSecondaryIp :: Field
976
pSecondaryIp = optionalNEStringField "secondary_ip"
977

    
978
-- | Whether node is re-added to cluster.
979
pReadd :: Field
980
pReadd = defaultFalse "readd"
981

    
982
-- | Initial node group.
983
pNodeGroup :: Field
984
pNodeGroup = optionalNEStringField "group"
985

    
986
-- | Whether node can become master or master candidate.
987
pMasterCapable :: Field
988
pMasterCapable = optionalField $ booleanField "master_capable"
989

    
990
-- | Whether node can host instances.
991
pVmCapable :: Field
992
pVmCapable = optionalField $ booleanField "vm_capable"
993

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

    
998
-- | List of node names.
999
pNodes :: Field
1000
pNodes = defaultField [| [] |] $ simpleField "nodes" [t| [NonEmptyString] |]
1001

    
1002
-- | Required list of node names.
1003
pRequiredNodes :: Field
1004
pRequiredNodes =
1005
  renameField "ReqNodes " $ simpleField "nodes" [t| [NonEmptyString] |]
1006

    
1007
-- | Storage type.
1008
pStorageType :: Field
1009
pStorageType = simpleField "storage_type" [t| StorageType |]
1010

    
1011
-- | Storage changes (unchecked).
1012
pStorageChanges :: Field
1013
pStorageChanges = simpleField "changes" [t| UncheckedDict |]
1014

    
1015
-- | Whether the node should become a master candidate.
1016
pMasterCandidate :: Field
1017
pMasterCandidate = optionalField $ booleanField "master_candidate"
1018

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

    
1023
-- | Whether the node should be marked as drained.
1024
pDrained ::Field
1025
pDrained = optionalField $ booleanField "drained"
1026

    
1027
-- | Whether node(s) should be promoted to master candidate if necessary.
1028
pAutoPromote :: Field
1029
pAutoPromote = defaultFalse "auto_promote"
1030

    
1031
-- | Whether the node should be marked as powered
1032
pPowered :: Field
1033
pPowered = optionalField $ booleanField "powered"
1034

    
1035
-- | Iallocator for deciding the target node for shared-storage
1036
-- instances during migrate and failover.
1037
pIallocator :: Field
1038
pIallocator = optionalNEStringField "iallocator"
1039

    
1040
-- | New secondary node.
1041
pRemoteNode :: Field
1042
pRemoteNode = optionalNEStringField "remote_node"
1043

    
1044
-- | Node evacuation mode.
1045
pEvacMode :: Field
1046
pEvacMode = renameField "EvacMode" $ simpleField "mode" [t| NodeEvacMode |]
1047

    
1048
-- | Instance creation mode.
1049
pInstCreateMode :: Field
1050
pInstCreateMode =
1051
  renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
1052

    
1053
-- | Do not install the OS (will disable automatic start).
1054
pNoInstall :: Field
1055
pNoInstall = optionalField $ booleanField "no_install"
1056

    
1057
-- | OS type for instance installation.
1058
pInstOs :: Field
1059
pInstOs = optionalNEStringField "os_type"
1060

    
1061
-- | Primary node for an instance.
1062
pPrimaryNode :: Field
1063
pPrimaryNode = optionalNEStringField "pnode"
1064

    
1065
-- | Secondary node for an instance.
1066
pSecondaryNode :: Field
1067
pSecondaryNode = optionalNEStringField "snode"
1068

    
1069
-- | Signed handshake from source (remote import only).
1070
pSourceHandshake :: Field
1071
pSourceHandshake =
1072
  optionalField $ simpleField "source_handshake" [t| UncheckedList |]
1073

    
1074
-- | Source instance name (remote import only).
1075
pSourceInstance :: Field
1076
pSourceInstance = optionalNEStringField "source_instance_name"
1077

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

    
1085
-- | Source X509 CA in PEM format (remote import only).
1086
pSourceX509Ca :: Field
1087
pSourceX509Ca = optionalNEStringField "source_x509_ca"
1088

    
1089
-- | Source node for import.
1090
pSrcNode :: Field
1091
pSrcNode = optionalNEStringField "src_node"
1092

    
1093
-- | Source directory for import.
1094
pSrcPath :: Field
1095
pSrcPath = optionalNEStringField "src_path"
1096

    
1097
-- | Whether to start instance after creation.
1098
pStartInstance :: Field
1099
pStartInstance = defaultTrue "start"
1100

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

    
1109
-- | Unchecked list of OpInstanceCreate, used in OpInstanceMultiAlloc.
1110
pMultiAllocInstances :: Field
1111
pMultiAllocInstances =
1112
  renameField "InstMultiAlloc" .
1113
  defaultField [| [] |] $
1114
  simpleField "instances"[t| UncheckedList |]
1115

    
1116
-- | Ignore failures parameter.
1117
pIgnoreFailures :: Field
1118
pIgnoreFailures = defaultFalse "ignore_failures"
1119

    
1120
-- | New instance or cluster name.
1121
pNewName :: Field
1122
pNewName = simpleField "new_name" [t| NonEmptyString |]
1123

    
1124
-- | Whether to start the instance even if secondary disks are failing.
1125
pIgnoreSecondaries :: Field
1126
pIgnoreSecondaries = defaultFalse "ignore_secondaries"
1127

    
1128
-- | How to reboot the instance.
1129
pRebootType :: Field
1130
pRebootType = simpleField "reboot_type" [t| RebootType |]
1131

    
1132
-- | Whether to ignore recorded disk size.
1133
pIgnoreDiskSize :: Field
1134
pIgnoreDiskSize = defaultFalse "ignore_size"
1135

    
1136
-- | Disk list for recreate disks.
1137
pRecreateDisksInfo :: Field
1138
pRecreateDisksInfo =
1139
  renameField "RecreateDisksInfo" .
1140
  defaultField [| RecreateDisksAll |] $
1141
  simpleField "disks" [t| RecreateDisksInfo |]
1142

    
1143
-- | Whether to only return configuration data without querying nodes.
1144
pStatic :: Field
1145
pStatic = defaultFalse "static"
1146

    
1147
-- | InstanceSetParams NIC changes.
1148
pInstParamsNicChanges :: Field
1149
pInstParamsNicChanges =
1150
  renameField "InstNicChanges" .
1151
  defaultField [| SetParamsEmpty |] $
1152
  simpleField "nics" [t| SetParamsMods INicParams |]
1153

    
1154
-- | InstanceSetParams Disk changes.
1155
pInstParamsDiskChanges :: Field
1156
pInstParamsDiskChanges =
1157
  renameField "InstDiskChanges" .
1158
  defaultField [| SetParamsEmpty |] $
1159
  simpleField "disks" [t| SetParamsMods IDiskParams |]
1160

    
1161
-- | New runtime memory.
1162
pRuntimeMem :: Field
1163
pRuntimeMem = optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1164

    
1165
-- | Change the instance's OS without reinstalling the instance
1166
pOsNameChange :: Field
1167
pOsNameChange = optionalNEStringField "os_name"
1168

    
1169
-- | Disk index for e.g. grow disk.
1170
pDiskIndex :: Field
1171
pDiskIndex = renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
1172

    
1173
-- | Disk amount to add or grow to.
1174
pDiskChgAmount :: Field
1175
pDiskChgAmount =
1176
  renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
1177

    
1178
-- | Whether the amount parameter is an absolute target or a relative one.
1179
pDiskChgAbsolute :: Field
1180
pDiskChgAbsolute = renameField "DiskChkAbsolute" $ defaultFalse "absolute"
1181

    
1182
-- | Destination group names or UUIDs (defaults to \"all but current group\".
1183
pTargetGroups :: Field
1184
pTargetGroups =
1185
  optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
1186

    
1187
-- | Export mode field.
1188
pExportMode :: Field
1189
pExportMode =
1190
  renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1191

    
1192
-- | Export target_node field, depends on mode.
1193
pExportTargetNode :: Field
1194
pExportTargetNode =
1195
  renameField "ExportTarget" $
1196
  simpleField "target_node" [t| ExportTarget |]
1197

    
1198
-- | Whether to remove instance after export.
1199
pRemoveInstance :: Field
1200
pRemoveInstance = defaultFalse "remove_instance"
1201

    
1202
-- | Whether to ignore failures while removing instances.
1203
pIgnoreRemoveFailures :: Field
1204
pIgnoreRemoveFailures = defaultFalse "ignore_remove_failures"
1205

    
1206
-- | Name of X509 key (remote export only).
1207
pX509KeyName :: Field
1208
pX509KeyName = optionalField $ simpleField "x509_key_name" [t| UncheckedList |]
1209

    
1210
-- | Destination X509 CA (remote export only).
1211
pX509DestCA :: Field
1212
pX509DestCA = optionalNEStringField "destination_x509_ca"
1213

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

    
1220
-- | Restricted command name.
1221
pRestrictedCommand :: Field
1222
pRestrictedCommand =
1223
  renameField "RestrictedCommand" $
1224
  simpleField "command" [t| NonEmptyString |]
1225

    
1226
-- | Replace disks mode.
1227
pReplaceDisksMode :: Field
1228
pReplaceDisksMode =
1229
  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1230

    
1231
-- | List of disk indices.
1232
pReplaceDisksList :: Field
1233
pReplaceDisksList =
1234
  renameField "ReplaceDisksList" $ simpleField "disks" [t| [DiskIndex] |]
1235

    
1236
-- | Whether do allow failover in migrations.
1237
pAllowFailover :: Field
1238
pAllowFailover = defaultFalse "allow_failover"
1239

    
1240
-- * Test opcode parameters
1241

    
1242
-- | Duration parameter for 'OpTestDelay'.
1243
pDelayDuration :: Field
1244
pDelayDuration =
1245
  renameField "DelayDuration" $ simpleField "duration" [t| Double |]
1246

    
1247
-- | on_master field for 'OpTestDelay'.
1248
pDelayOnMaster :: Field
1249
pDelayOnMaster = renameField "DelayOnMaster" $ defaultTrue "on_master"
1250

    
1251
-- | on_nodes field for 'OpTestDelay'.
1252
pDelayOnNodes :: Field
1253
pDelayOnNodes =
1254
  renameField "DelayOnNodes" .
1255
  defaultField [| [] |] $
1256
  simpleField "on_nodes" [t| [NonEmptyString] |]
1257

    
1258
-- | Repeat parameter for OpTestDelay.
1259
pDelayRepeat :: Field
1260
pDelayRepeat =
1261
  renameField "DelayRepeat" .
1262
  defaultField [| forceNonNeg (0::Int) |] $
1263
  simpleField "repeat" [t| NonNegative Int |]
1264

    
1265
-- | IAllocator test direction.
1266
pIAllocatorDirection :: Field
1267
pIAllocatorDirection =
1268
  renameField "IAllocatorDirection" $
1269
  simpleField "direction" [t| IAllocatorTestDir |]
1270

    
1271
-- | IAllocator test mode.
1272
pIAllocatorMode :: Field
1273
pIAllocatorMode =
1274
  renameField "IAllocatorMode" $
1275
  simpleField "mode" [t| IAllocatorMode |]
1276

    
1277
-- | IAllocator target name (new instance, node to evac, etc.).
1278
pIAllocatorReqName :: Field
1279
pIAllocatorReqName =
1280
  renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
1281

    
1282
-- | Custom OpTestIAllocator nics.
1283
pIAllocatorNics :: Field
1284
pIAllocatorNics =
1285
  renameField "IAllocatorNics" $ simpleField "nics" [t| [UncheckedDict] |]
1286

    
1287
-- | Custom OpTestAllocator disks.
1288
pIAllocatorDisks :: Field
1289
pIAllocatorDisks =
1290
  renameField "IAllocatorDisks" $ simpleField "disks" [t| UncheckedList |]
1291

    
1292
-- | IAllocator memory field.
1293
pIAllocatorMemory :: Field
1294
pIAllocatorMemory =
1295
  renameField "IAllocatorMem" .
1296
  optionalField $
1297
  simpleField "memory" [t| NonNegative Int |]
1298

    
1299
-- | IAllocator vcpus field.
1300
pIAllocatorVCpus :: Field
1301
pIAllocatorVCpus =
1302
  renameField "IAllocatorVCpus" .
1303
  optionalField $
1304
  simpleField "vcpus" [t| NonNegative Int |]
1305

    
1306
-- | IAllocator os field.
1307
pIAllocatorOs :: Field
1308
pIAllocatorOs = renameField "IAllocatorOs" $ optionalNEStringField "os"
1309

    
1310
-- | IAllocator instances field.
1311
pIAllocatorInstances :: Field
1312
pIAllocatorInstances =
1313
  renameField "IAllocatorInstances " .
1314
  optionalField $
1315
  simpleField "instances" [t| [NonEmptyString] |]
1316

    
1317
-- | IAllocator evac mode.
1318
pIAllocatorEvacMode :: Field
1319
pIAllocatorEvacMode =
1320
  renameField "IAllocatorEvacMode" .
1321
  optionalField $
1322
  simpleField "evac_mode" [t| NodeEvacMode |]
1323

    
1324
-- | IAllocator spindle use.
1325
pIAllocatorSpindleUse :: Field
1326
pIAllocatorSpindleUse =
1327
  renameField "IAllocatorSpindleUse" .
1328
  defaultField [| forceNonNeg (1::Int) |] $
1329
  simpleField "spindle_use" [t| NonNegative Int |]
1330

    
1331
-- | IAllocator count field.
1332
pIAllocatorCount :: Field
1333
pIAllocatorCount =
1334
  renameField "IAllocatorCount" .
1335
  defaultField [| forceNonNeg (1::Int) |] $
1336
  simpleField "count" [t| NonNegative Int |]
1337

    
1338
-- | 'OpTestJqueue' notify_waitlock.
1339
pJQueueNotifyWaitLock :: Field
1340
pJQueueNotifyWaitLock = defaultFalse "notify_waitlock"
1341

    
1342
-- | 'OpTestJQueue' notify_exec.
1343
pJQueueNotifyExec :: Field
1344
pJQueueNotifyExec = defaultFalse "notify_exec"
1345

    
1346
-- | 'OpTestJQueue' log_messages.
1347
pJQueueLogMessages :: Field
1348
pJQueueLogMessages =
1349
  defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
1350

    
1351
-- | 'OpTestJQueue' fail attribute.
1352
pJQueueFail :: Field
1353
pJQueueFail =
1354
  renameField "JQueueFail" $ defaultFalse "fail"
1355

    
1356
-- | 'OpTestDummy' result field.
1357
pTestDummyResult :: Field
1358
pTestDummyResult =
1359
  renameField "TestDummyResult" $ simpleField "result" [t| UncheckedValue |]
1360

    
1361
-- | 'OpTestDummy' messages field.
1362
pTestDummyMessages :: Field
1363
pTestDummyMessages =
1364
  renameField "TestDummyMessages" $
1365
  simpleField "messages" [t| UncheckedValue |]
1366

    
1367
-- | 'OpTestDummy' fail field.
1368
pTestDummyFail :: Field
1369
pTestDummyFail =
1370
  renameField "TestDummyFail" $ simpleField "fail" [t| UncheckedValue |]
1371

    
1372
-- | 'OpTestDummy' submit_jobs field.
1373
pTestDummySubmitJobs :: Field
1374
pTestDummySubmitJobs =
1375
  renameField "TestDummySubmitJobs" $
1376
  simpleField "submit_jobs" [t| UncheckedValue |]
1377

    
1378
-- * Network parameters
1379

    
1380
-- | Network name.
1381
pNetworkName :: Field
1382
pNetworkName = simpleField "network_name" [t| NonEmptyString |]
1383

    
1384
-- | Network address (IPv4 subnet). FIXME: no real type for this.
1385
pNetworkAddress4 :: Field
1386
pNetworkAddress4 =
1387
  renameField "NetworkAddress4" $
1388
  simpleField "network" [t| NonEmptyString |]
1389

    
1390
-- | Network gateway (IPv4 address). FIXME: no real type for this.
1391
pNetworkGateway4 :: Field
1392
pNetworkGateway4 =
1393
  renameField "NetworkGateway4" $
1394
  optionalNEStringField "gateway"
1395

    
1396
-- | Network address (IPv6 subnet). FIXME: no real type for this.
1397
pNetworkAddress6 :: Field
1398
pNetworkAddress6 =
1399
  renameField "NetworkAddress6" $
1400
  optionalNEStringField "network6"
1401

    
1402
-- | Network gateway (IPv6 address). FIXME: no real type for this.
1403
pNetworkGateway6 :: Field
1404
pNetworkGateway6 =
1405
  renameField "NetworkGateway6" $
1406
  optionalNEStringField "gateway6"
1407

    
1408
-- | Network specific mac prefix (that overrides the cluster one).
1409
pNetworkMacPrefix :: Field
1410
pNetworkMacPrefix =
1411
  renameField "NetMacPrefix" $
1412
  optionalNEStringField "mac_prefix"
1413

    
1414
-- | Network add reserved IPs.
1415
pNetworkAddRsvdIps :: Field
1416
pNetworkAddRsvdIps =
1417
  renameField "NetworkAddRsvdIps" .
1418
  optionalField $
1419
  simpleField "add_reserved_ips" [t| [NonEmptyString] |]
1420

    
1421
-- | Network remove reserved IPs.
1422
pNetworkRemoveRsvdIps :: Field
1423
pNetworkRemoveRsvdIps =
1424
  renameField "NetworkRemoveRsvdIps" .
1425
  optionalField $
1426
  simpleField "remove_reserved_ips" [t| [NonEmptyString] |]
1427

    
1428
-- | Network mode when connecting to a group.
1429
pNetworkMode :: Field
1430
pNetworkMode = simpleField "network_mode" [t| NICMode |]
1431

    
1432
-- | Network link when connecting to a group.
1433
pNetworkLink :: Field
1434
pNetworkLink = simpleField "network_link" [t| NonEmptyString |]
1435

    
1436
-- * Common opcode parameters
1437

    
1438
-- | Run checks only, don't execute.
1439
pDryRun :: Field
1440
pDryRun = optionalField $ booleanField "dry_run"
1441

    
1442
-- | Debug level.
1443
pDebugLevel :: Field
1444
pDebugLevel = optionalField $ simpleField "debug_level" [t| NonNegative Int |]
1445

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

    
1453
-- | Job dependencies.
1454
pDependencies :: Field
1455
pDependencies =
1456
  optionalNullSerField $ simpleField "depends" [t| [JobDependency] |]
1457

    
1458
-- | Comment field.
1459
pComment :: Field
1460
pComment = optionalNullSerField $ stringField "comment"
1461

    
1462
-- | Reason trail field.
1463
pReason :: Field
1464
pReason = simpleField C.opcodeReason [t| ReasonTrail |]
1465

    
1466
-- * Entire opcode parameter list
1467

    
1468
-- | Old-style query opcode, with locking.
1469
dOldQuery :: [Field]
1470
dOldQuery =
1471
  [ pOutputFields
1472
  , pNames
1473
  , pUseLocking
1474
  ]
1475

    
1476
-- | Old-style query opcode, without locking.
1477
dOldQueryNoLocking :: [Field]
1478
dOldQueryNoLocking =
1479
  [ pOutputFields
1480
  , pNames
1481
  ]