Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ a59d5fa1

History | View | Annotate | Download (42.4 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
  , dOldQuery
241
  , dOldQueryNoLocking
242
  ) where
243

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

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

    
258
-- * Helper functions and types
259

    
260
-- * Type aliases
261

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

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

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

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

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

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

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

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

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

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

    
304
-- ** Tags
305

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

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

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

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

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

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

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

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

    
363
-- ** Disks
364

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

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

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

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

    
390
-- ** I* param types
391

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

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

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

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

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

    
438
instance JSON RecreateDisksInfo where
439
  readJSON = readRecreateDisks
440
  showJSON  RecreateDisksAll            = showJSON ()
441
  showJSON (RecreateDisksIndices idx)   = showJSON idx
442
  showJSON (RecreateDisksParams params) = showJSON params
443

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

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

    
458
instance JSON DdmOldChanges where
459
  showJSON (DdmOldIndex i) = showJSON i
460
  showJSON (DdmOldMod m)   = showJSON m
461
  readJSON = readDdmOldChanges
462

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

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

    
478
instance (JSON a) => JSON (SetParamsMods a) where
479
  showJSON SetParamsEmpty = showJSON ()
480
  showJSON (SetParamsDeprecated v) = showJSON v
481
  showJSON (SetParamsNew v) = showJSON v
482
  readJSON = readSetParams
483

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

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

    
500
instance JSON ExportTarget where
501
  showJSON (ExportTargetLocal s)  = showJSON s
502
  showJSON (ExportTargetRemote l) = showJSON l
503
  readJSON = readExportTarget
504

    
505
-- * Parameters
506

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

    
511
-- | A list of instances.
512
pInstances :: Field
513
pInstances = defaultField [| [] |] $
514
             simpleField "instances" [t| [NonEmptyString] |]
515

    
516
-- | A generic name.
517
pName :: Field
518
pName = simpleField "name" [t| NonEmptyString |]
519

    
520
-- | Tags list.
521
pTagsList :: Field
522
pTagsList = simpleField "tags" [t| [String] |]
523

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

    
530
-- | Selected output fields.
531
pOutputFields :: Field
532
pOutputFields = simpleField "output_fields" [t| [NonEmptyString] |]
533

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

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

    
547
-- | Whether to shutdown the instance in backup-export.
548
pShutdownInstance :: Field
549
pShutdownInstance = defaultTrue "shutdown"
550

    
551
-- | Whether to force the operation.
552
pForce :: Field
553
pForce = defaultFalse "force"
554

    
555
-- | Whether to ignore offline nodes.
556
pIgnoreOfflineNodes :: Field
557
pIgnoreOfflineNodes = defaultFalse "ignore_offline_nodes"
558

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

    
563
-- | List of nodes.
564
pNodeNames :: Field
565
pNodeNames =
566
  defaultField [| [] |] $ simpleField "node_names" [t| [NonEmptyString] |]
567

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

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

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

    
584
-- | Migration cleanup parameter.
585
pMigrationCleanup :: Field
586
pMigrationCleanup = renameField "MigrationCleanup" $ defaultFalse "cleanup"
587

    
588
-- | Whether to force an unknown OS variant.
589
pForceVariant :: Field
590
pForceVariant = defaultFalse "force_variant"
591

    
592
-- | Whether to wait for the disk to synchronize.
593
pWaitForSync :: Field
594
pWaitForSync = defaultTrue "wait_for_sync"
595

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

    
600
-- | Whether to ignore disk consistency
601
pIgnoreConsistency :: Field
602
pIgnoreConsistency = defaultFalse "ignore_consistency"
603

    
604
-- | Storage name.
605
pStorageName :: Field
606
pStorageName =
607
  renameField "StorageName" $ simpleField "name" [t| NonEmptyString |]
608

    
609
-- | Whether to use synchronization.
610
pUseLocking :: Field
611
pUseLocking = defaultFalse "use_locking"
612

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

    
619
-- | Whether to check name.
620
pNameCheck :: Field
621
pNameCheck = defaultTrue "name_check"
622

    
623
-- | Instance allocation policy.
624
pNodeGroupAllocPolicy :: Field
625
pNodeGroupAllocPolicy = optionalField $
626
                        simpleField "alloc_policy" [t| AllocPolicy |]
627

    
628
-- | Default node parameters for group.
629
pGroupNodeParams :: Field
630
pGroupNodeParams = optionalField $ simpleField "ndparams" [t| UncheckedDict |]
631

    
632
-- | Resource(s) to query for.
633
pQueryWhat :: Field
634
pQueryWhat = simpleField "what" [t| Qlang.QueryTypeOp |]
635

    
636
-- | Whether to release locks as soon as possible.
637
pEarlyRelease :: Field
638
pEarlyRelease = defaultFalse "early_release"
639

    
640
-- | Whether to ensure instance's IP address is inactive.
641
pIpCheck :: Field
642
pIpCheck = defaultTrue "ip_check"
643

    
644
-- | Check for conflicting IPs.
645
pIpConflictsCheck :: Field
646
pIpConflictsCheck = defaultTrue "conflicts_check"
647

    
648
-- | Do not remember instance state changes.
649
pNoRemember :: Field
650
pNoRemember = defaultFalse "no_remember"
651

    
652
-- | Target node for instance migration/failover.
653
pMigrationTargetNode :: Field
654
pMigrationTargetNode = optionalNEStringField "target_node"
655

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

    
662
-- | Pause instance at startup.
663
pStartupPaused :: Field
664
pStartupPaused = defaultFalse "startup_paused"
665

    
666
-- | Verbose mode.
667
pVerbose :: Field
668
pVerbose = defaultFalse "verbose"
669

    
670
-- ** Parameters for cluster verification
671

    
672
-- | Whether to simulate errors (useful for debugging).
673
pDebugSimulateErrors :: Field
674
pDebugSimulateErrors = defaultFalse "debug_simulate_errors"
675

    
676
-- | Error codes.
677
pErrorCodes :: Field
678
pErrorCodes = defaultFalse "error_codes"
679

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

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

    
690
-- | Optional group name.
691
pOptGroupName :: Field
692
pOptGroupName = renameField "OptGroupName" .
693
                optionalField $ simpleField "group_name" [t| NonEmptyString |]
694

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

    
701
-- * Parameters for node resource model
702

    
703
-- | Set hypervisor states.
704
pHvState :: Field
705
pHvState = optionalField $ simpleField "hv_state" [t| UncheckedDict |]
706

    
707
-- | Set disk states.
708
pDiskState :: Field
709
pDiskState = optionalField $ simpleField "disk_state" [t| UncheckedDict |]
710

    
711
-- | Whether to ignore ipolicy violations.
712
pIgnoreIpolicy :: Field
713
pIgnoreIpolicy = defaultFalse "ignore_ipolicy"
714

    
715
-- | Allow runtime changes while migrating.
716
pAllowRuntimeChgs :: Field
717
pAllowRuntimeChgs = defaultTrue "allow_runtime_changes"
718

    
719
-- | Utility type for OpClusterSetParams.
720
type TestClusterOsListItem = (DdmSimple, NonEmptyString)
721

    
722
-- | Utility type of OsList.
723
type TestClusterOsList = [TestClusterOsListItem]
724

    
725
-- Utility type for NIC definitions.
726
--type TestNicDef = INicParams
727

    
728
-- | List of instance disks.
729
pInstDisks :: Field
730
pInstDisks = renameField "instDisks" $ simpleField "disks" [t| [IDiskParams] |]
731

    
732
-- | Instance disk template.
733
pDiskTemplate :: Field
734
pDiskTemplate = simpleField "disk_template" [t| DiskTemplate |]
735

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

    
743
-- | File driver.
744
pFileDriver :: Field
745
pFileDriver = optionalField $ simpleField "file_driver" [t| FileDriver |]
746

    
747
-- | Directory for storing file-backed disks.
748
pFileStorageDir :: Field
749
pFileStorageDir = optionalNEStringField "file_storage_dir"
750

    
751
-- | Volume group name.
752
pVgName :: Field
753
pVgName = optionalStringField "vg_name"
754

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

    
761
-- | Selected hypervisor for an instance.
762
pHypervisor :: Field
763
pHypervisor =
764
  optionalField $
765
  simpleField "hypervisor" [t| Hypervisor |]
766

    
767
-- | Cluster-wide hypervisor parameters, hypervisor-dependent.
768
pClusterHvParams :: Field
769
pClusterHvParams =
770
  renameField "ClusterHvParams" .
771
  optionalField $
772
  simpleField "hvparams" [t| Container UncheckedDict |]
773

    
774
-- | Instance hypervisor parameters.
775
pInstHvParams :: Field
776
pInstHvParams =
777
  renameField "InstHvParams" .
778
  defaultField [| toJSObject [] |] $
779
  simpleField "hvparams" [t| UncheckedDict |]
780

    
781
-- | Cluster-wide beparams.
782
pClusterBeParams :: Field
783
pClusterBeParams =
784
  renameField "ClusterBeParams" .
785
  optionalField $ simpleField "beparams" [t| UncheckedDict |]
786

    
787
-- | Instance beparams.
788
pInstBeParams :: Field
789
pInstBeParams =
790
  renameField "InstBeParams" .
791
  defaultField [| toJSObject [] |] $
792
  simpleField "beparams" [t| UncheckedDict |]
793

    
794
-- | Reset instance parameters to default if equal.
795
pResetDefaults :: Field
796
pResetDefaults = defaultFalse "identify_defaults"
797

    
798
-- | Cluster-wide per-OS hypervisor parameter defaults.
799
pOsHvp :: Field
800
pOsHvp = optionalField $ simpleField "os_hvp" [t| Container UncheckedDict |]
801

    
802
-- | Cluster-wide OS parameter defaults.
803
pClusterOsParams :: Field
804
pClusterOsParams =
805
  renameField "ClusterOsParams" .
806
  optionalField $ simpleField "osparams" [t| Container UncheckedDict |]
807

    
808
-- | Instance OS parameters.
809
pInstOsParams :: Field
810
pInstOsParams =
811
  renameField "InstOsParams" . defaultField [| toJSObject [] |] $
812
  simpleField "osparams" [t| UncheckedDict |]
813

    
814
-- | Temporary OS parameters (currently only in reinstall, might be
815
-- added to install as well).
816
pTempOsParams :: Field
817
pTempOsParams =
818
  renameField "TempOsParams" .
819
  optionalField $ simpleField "osparams" [t| UncheckedDict |]
820

    
821
-- | Temporary hypervisor parameters, hypervisor-dependent.
822
pTempHvParams :: Field
823
pTempHvParams =
824
  renameField "TempHvParams" .
825
  defaultField [| toJSObject [] |] $
826
  simpleField "hvparams" [t| UncheckedDict |]
827

    
828
-- | Temporary backend parameters.
829
pTempBeParams :: Field
830
pTempBeParams =
831
  renameField "TempBeParams" .
832
  defaultField [| toJSObject [] |] $
833
  simpleField "beparams" [t| UncheckedDict |]
834

    
835
-- | Candidate pool size.
836
pCandidatePoolSize :: Field
837
pCandidatePoolSize =
838
  optionalField $ simpleField "candidate_pool_size" [t| Positive Int |]
839

    
840
-- | Set UID pool, must be list of lists describing UID ranges (two
841
-- items, start and end inclusive.
842
pUidPool :: Field
843
pUidPool = optionalField $ simpleField "uid_pool" [t| [[(Int, Int)]] |]
844

    
845
-- | Extend UID pool, must be list of lists describing UID ranges (two
846
-- items, start and end inclusive.
847
pAddUids :: Field
848
pAddUids = optionalField $ simpleField "add_uids" [t| [[(Int, Int)]] |]
849

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

    
855
-- | Whether to automatically maintain node health.
856
pMaintainNodeHealth :: Field
857
pMaintainNodeHealth = optionalField $ booleanField "maintain_node_health"
858

    
859
-- | Whether to wipe disks before allocating them to instances.
860
pPreallocWipeDisks :: Field
861
pPreallocWipeDisks = optionalField $ booleanField "prealloc_wipe_disks"
862

    
863
-- | Cluster-wide NIC parameter defaults.
864
pNicParams :: Field
865
pNicParams = optionalField $ simpleField "nicparams" [t| INicParams |]
866

    
867
-- | Instance NIC definitions.
868
pInstNics :: Field
869
pInstNics = simpleField "nics" [t| [INicParams] |]
870

    
871
-- | Cluster-wide node parameter defaults.
872
pNdParams :: Field
873
pNdParams = optionalField $ simpleField "ndparams" [t| UncheckedDict |]
874

    
875
-- | Cluster-wide ipolicy specs.
876
pIpolicy :: Field
877
pIpolicy = optionalField $ simpleField "ipolicy" [t| UncheckedDict |]
878

    
879
-- | DRBD helper program.
880
pDrbdHelper :: Field
881
pDrbdHelper = optionalStringField "drbd_helper"
882

    
883
-- | Default iallocator for cluster.
884
pDefaultIAllocator :: Field
885
pDefaultIAllocator = optionalStringField "default_iallocator"
886

    
887
-- | Master network device.
888
pMasterNetdev :: Field
889
pMasterNetdev = optionalStringField "master_netdev"
890

    
891
-- | Netmask of the master IP.
892
pMasterNetmask :: Field
893
pMasterNetmask =
894
  optionalField $ simpleField "master_netmask" [t| NonNegative Int |]
895

    
896
-- | List of reserved LVs.
897
pReservedLvs :: Field
898
pReservedLvs =
899
  optionalField $ simpleField "reserved_lvs" [t| [NonEmptyString] |]
900

    
901
-- | Modify list of hidden operating systems: each modification must
902
-- have two items, the operation and the OS name; the operation can be
903
-- add or remove.
904
pHiddenOs :: Field
905
pHiddenOs = optionalField $ simpleField "hidden_os" [t| TestClusterOsList |]
906

    
907
-- | Modify list of blacklisted operating systems: each modification
908
-- must have two items, the operation and the OS name; the operation
909
-- can be add or remove.
910
pBlacklistedOs :: Field
911
pBlacklistedOs =
912
  optionalField $ simpleField "blacklisted_os" [t| TestClusterOsList |]
913

    
914
-- | Whether to use an external master IP address setup script.
915
pUseExternalMipScript :: Field
916
pUseExternalMipScript = optionalField $ booleanField "use_external_mip_script"
917

    
918
-- | Requested fields.
919
pQueryFields :: Field
920
pQueryFields = simpleField "fields" [t| [NonEmptyString] |]
921

    
922
-- | Query filter.
923
pQueryFilter :: Field
924
pQueryFilter = simpleField "qfilter" [t| Qlang.Filter String |]
925

    
926
-- | OOB command to run.
927
pOobCommand :: Field
928
pOobCommand = simpleField "command" [t| OobCommand |]
929

    
930
-- | Timeout before the OOB helper will be terminated.
931
pOobTimeout :: Field
932
pOobTimeout =
933
  defaultField [| C.oobTimeout |] $ simpleField "timeout" [t| Int |]
934

    
935
-- | Ignores the node offline status for power off.
936
pIgnoreStatus :: Field
937
pIgnoreStatus = defaultFalse "ignore_status"
938

    
939
-- | Time in seconds to wait between powering on nodes.
940
pPowerDelay :: Field
941
pPowerDelay =
942
  -- FIXME: we can't use the proper type "NonNegative Double", since
943
  -- the default constant is a plain Double, not a non-negative one.
944
  defaultField [| C.oobPowerDelay |] $
945
  simpleField "power_delay" [t| Double |]
946

    
947
-- | Primary IP address.
948
pPrimaryIp :: Field
949
pPrimaryIp = optionalStringField "primary_ip"
950

    
951
-- | Secondary IP address.
952
pSecondaryIp :: Field
953
pSecondaryIp = optionalNEStringField "secondary_ip"
954

    
955
-- | Whether node is re-added to cluster.
956
pReadd :: Field
957
pReadd = defaultFalse "readd"
958

    
959
-- | Initial node group.
960
pNodeGroup :: Field
961
pNodeGroup = optionalNEStringField "group"
962

    
963
-- | Whether node can become master or master candidate.
964
pMasterCapable :: Field
965
pMasterCapable = optionalField $ booleanField "master_capable"
966

    
967
-- | Whether node can host instances.
968
pVmCapable :: Field
969
pVmCapable = optionalField $ booleanField "vm_capable"
970

    
971
-- | List of names.
972
pNames :: Field
973
pNames = defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
974

    
975
-- | List of node names.
976
pNodes :: Field
977
pNodes = defaultField [| [] |] $ simpleField "nodes" [t| [NonEmptyString] |]
978

    
979
-- | Required list of node names.
980
pRequiredNodes :: Field
981
pRequiredNodes =
982
  renameField "ReqNodes " $ simpleField "nodes" [t| [NonEmptyString] |]
983

    
984
-- | Storage type.
985
pStorageType :: Field
986
pStorageType = simpleField "storage_type" [t| StorageType |]
987

    
988
-- | Storage changes (unchecked).
989
pStorageChanges :: Field
990
pStorageChanges = simpleField "changes" [t| UncheckedDict |]
991

    
992
-- | Whether the node should become a master candidate.
993
pMasterCandidate :: Field
994
pMasterCandidate = optionalField $ booleanField "master_candidate"
995

    
996
-- | Whether the node should be marked as offline.
997
pOffline :: Field
998
pOffline = optionalField $ booleanField "offline"
999

    
1000
-- | Whether the node should be marked as drained.
1001
pDrained ::Field
1002
pDrained = optionalField $ booleanField "drained"
1003

    
1004
-- | Whether node(s) should be promoted to master candidate if necessary.
1005
pAutoPromote :: Field
1006
pAutoPromote = defaultFalse "auto_promote"
1007

    
1008
-- | Whether the node should be marked as powered
1009
pPowered :: Field
1010
pPowered = optionalField $ booleanField "powered"
1011

    
1012
-- | Iallocator for deciding the target node for shared-storage
1013
-- instances during migrate and failover.
1014
pIallocator :: Field
1015
pIallocator = optionalNEStringField "iallocator"
1016

    
1017
-- | New secondary node.
1018
pRemoteNode :: Field
1019
pRemoteNode = optionalNEStringField "remote_node"
1020

    
1021
-- | Node evacuation mode.
1022
pEvacMode :: Field
1023
pEvacMode = renameField "EvacMode" $ simpleField "mode" [t| NodeEvacMode |]
1024

    
1025
-- | Instance creation mode.
1026
pInstCreateMode :: Field
1027
pInstCreateMode =
1028
  renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
1029

    
1030
-- | Do not install the OS (will disable automatic start).
1031
pNoInstall :: Field
1032
pNoInstall = optionalField $ booleanField "no_install"
1033

    
1034
-- | OS type for instance installation.
1035
pInstOs :: Field
1036
pInstOs = optionalNEStringField "os_type"
1037

    
1038
-- | Primary node for an instance.
1039
pPrimaryNode :: Field
1040
pPrimaryNode = optionalNEStringField "pnode"
1041

    
1042
-- | Secondary node for an instance.
1043
pSecondaryNode :: Field
1044
pSecondaryNode = optionalNEStringField "snode"
1045

    
1046
-- | Signed handshake from source (remote import only).
1047
pSourceHandshake :: Field
1048
pSourceHandshake =
1049
  optionalField $ simpleField "source_handshake" [t| UncheckedList |]
1050

    
1051
-- | Source instance name (remote import only).
1052
pSourceInstance :: Field
1053
pSourceInstance = optionalNEStringField "source_instance_name"
1054

    
1055
-- | How long source instance was given to shut down (remote import only).
1056
-- FIXME: non-negative int, whereas the constant is a plain int.
1057
pSourceShutdownTimeout :: Field
1058
pSourceShutdownTimeout =
1059
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1060
  simpleField "source_shutdown_timeout" [t| NonNegative Int |]
1061

    
1062
-- | Source X509 CA in PEM format (remote import only).
1063
pSourceX509Ca :: Field
1064
pSourceX509Ca = optionalNEStringField "source_x509_ca"
1065

    
1066
-- | Source node for import.
1067
pSrcNode :: Field
1068
pSrcNode = optionalNEStringField "src_node"
1069

    
1070
-- | Source directory for import.
1071
pSrcPath :: Field
1072
pSrcPath = optionalNEStringField "src_path"
1073

    
1074
-- | Whether to start instance after creation.
1075
pStartInstance :: Field
1076
pStartInstance = defaultTrue "start"
1077

    
1078
-- | Instance tags. FIXME: unify/simplify with pTags, once that
1079
-- migrates to NonEmpty String.
1080
pInstTags :: Field
1081
pInstTags =
1082
  renameField "InstTags" .
1083
  defaultField [| [] |] $
1084
  simpleField "tags" [t| [NonEmptyString] |]
1085

    
1086
-- | Unchecked list of OpInstanceCreate, used in OpInstanceMultiAlloc.
1087
pMultiAllocInstances :: Field
1088
pMultiAllocInstances =
1089
  renameField "InstMultiAlloc" .
1090
  defaultField [| [] |] $
1091
  simpleField "instances"[t| UncheckedList |]
1092

    
1093
-- | Ignore failures parameter.
1094
pIgnoreFailures :: Field
1095
pIgnoreFailures = defaultFalse "ignore_failures"
1096

    
1097
-- | New instance or cluster name.
1098
pNewName :: Field
1099
pNewName = simpleField "new_name" [t| NonEmptyString |]
1100

    
1101
-- | Whether to start the instance even if secondary disks are failing.
1102
pIgnoreSecondaries :: Field
1103
pIgnoreSecondaries = defaultFalse "ignore_secondaries"
1104

    
1105
-- | How to reboot the instance.
1106
pRebootType :: Field
1107
pRebootType = simpleField "reboot_type" [t| RebootType |]
1108

    
1109
-- | Whether to ignore recorded disk size.
1110
pIgnoreDiskSize :: Field
1111
pIgnoreDiskSize = defaultFalse "ignore_size"
1112

    
1113
-- | Disk list for recreate disks.
1114
pRecreateDisksInfo :: Field
1115
pRecreateDisksInfo =
1116
  renameField "RecreateDisksInfo" .
1117
  defaultField [| RecreateDisksAll |] $
1118
  simpleField "disks" [t| RecreateDisksInfo |]
1119

    
1120
-- | Whether to only return configuration data without querying nodes.
1121
pStatic :: Field
1122
pStatic = defaultFalse "static"
1123

    
1124
-- | InstanceSetParams NIC changes.
1125
pInstParamsNicChanges :: Field
1126
pInstParamsNicChanges =
1127
  renameField "InstNicChanges" .
1128
  defaultField [| SetParamsEmpty |] $
1129
  simpleField "nics" [t| SetParamsMods INicParams |]
1130

    
1131
-- | InstanceSetParams Disk changes.
1132
pInstParamsDiskChanges :: Field
1133
pInstParamsDiskChanges =
1134
  renameField "InstDiskChanges" .
1135
  defaultField [| SetParamsEmpty |] $
1136
  simpleField "disks" [t| SetParamsMods IDiskParams |]
1137

    
1138
-- | New runtime memory.
1139
pRuntimeMem :: Field
1140
pRuntimeMem = optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1141

    
1142
-- | Change the instance's OS without reinstalling the instance
1143
pOsNameChange :: Field
1144
pOsNameChange = optionalNEStringField "os_name"
1145

    
1146
-- | Disk index for e.g. grow disk.
1147
pDiskIndex :: Field
1148
pDiskIndex = renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
1149

    
1150
-- | Disk amount to add or grow to.
1151
pDiskChgAmount :: Field
1152
pDiskChgAmount =
1153
  renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
1154

    
1155
-- | Whether the amount parameter is an absolute target or a relative one.
1156
pDiskChgAbsolute :: Field
1157
pDiskChgAbsolute = renameField "DiskChkAbsolute" $ defaultFalse "absolute"
1158

    
1159
-- | Destination group names or UUIDs (defaults to \"all but current group\".
1160
pTargetGroups :: Field
1161
pTargetGroups =
1162
  optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
1163

    
1164
-- | Export mode field.
1165
pExportMode :: Field
1166
pExportMode =
1167
  renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1168

    
1169
-- | Export target_node field, depends on mode.
1170
pExportTargetNode :: Field
1171
pExportTargetNode =
1172
  renameField "ExportTarget" $
1173
  simpleField "target_node" [t| ExportTarget |]
1174

    
1175
-- | Whether to remove instance after export.
1176
pRemoveInstance :: Field
1177
pRemoveInstance = defaultFalse "remove_instance"
1178

    
1179
-- | Whether to ignore failures while removing instances.
1180
pIgnoreRemoveFailures :: Field
1181
pIgnoreRemoveFailures = defaultFalse "ignore_remove_failures"
1182

    
1183
-- | Name of X509 key (remote export only).
1184
pX509KeyName :: Field
1185
pX509KeyName = optionalField $ simpleField "x509_key_name" [t| UncheckedList |]
1186

    
1187
-- | Destination X509 CA (remote export only).
1188
pX509DestCA :: Field
1189
pX509DestCA = optionalNEStringField "destination_x509_ca"
1190

    
1191
-- | Search pattern (regular expression). FIXME: this should be
1192
-- compiled at load time?
1193
pTagSearchPattern :: Field
1194
pTagSearchPattern =
1195
  renameField "TagSearchPattern" $ simpleField "pattern" [t| NonEmptyString |]
1196

    
1197
-- | Restricted command name.
1198
pRestrictedCommand :: Field
1199
pRestrictedCommand =
1200
  renameField "RestrictedCommand" $
1201
  simpleField "command" [t| NonEmptyString |]
1202

    
1203
-- | Replace disks mode.
1204
pReplaceDisksMode :: Field
1205
pReplaceDisksMode =
1206
  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1207

    
1208
-- | List of disk indices.
1209
pReplaceDisksList :: Field
1210
pReplaceDisksList =
1211
  renameField "ReplaceDisksList" $ simpleField "disks" [t| [DiskIndex] |]
1212

    
1213
-- | Whether do allow failover in migrations.
1214
pAllowFailover :: Field
1215
pAllowFailover = defaultFalse "allow_failover"
1216

    
1217
-- * Test opcode parameters
1218

    
1219
-- | Duration parameter for 'OpTestDelay'.
1220
pDelayDuration :: Field
1221
pDelayDuration =
1222
  renameField "DelayDuration" $ simpleField "duration" [t| Double |]
1223

    
1224
-- | on_master field for 'OpTestDelay'.
1225
pDelayOnMaster :: Field
1226
pDelayOnMaster = renameField "DelayOnMaster" $ defaultTrue "on_master"
1227

    
1228
-- | on_nodes field for 'OpTestDelay'.
1229
pDelayOnNodes :: Field
1230
pDelayOnNodes =
1231
  renameField "DelayOnNodes" .
1232
  defaultField [| [] |] $
1233
  simpleField "on_nodes" [t| [NonEmptyString] |]
1234

    
1235
-- | Repeat parameter for OpTestDelay.
1236
pDelayRepeat :: Field
1237
pDelayRepeat =
1238
  renameField "DelayRepeat" .
1239
  defaultField [| forceNonNeg (0::Int) |] $
1240
  simpleField "repeat" [t| NonNegative Int |]
1241

    
1242
-- | IAllocator test direction.
1243
pIAllocatorDirection :: Field
1244
pIAllocatorDirection =
1245
  renameField "IAllocatorDirection" $
1246
  simpleField "direction" [t| IAllocatorTestDir |]
1247

    
1248
-- | IAllocator test mode.
1249
pIAllocatorMode :: Field
1250
pIAllocatorMode =
1251
  renameField "IAllocatorMode" $
1252
  simpleField "mode" [t| IAllocatorMode |]
1253

    
1254
-- | IAllocator target name (new instance, node to evac, etc.).
1255
pIAllocatorReqName :: Field
1256
pIAllocatorReqName =
1257
  renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
1258

    
1259
-- | Custom OpTestIAllocator nics.
1260
pIAllocatorNics :: Field
1261
pIAllocatorNics =
1262
  renameField "IAllocatorNics" $ simpleField "nics" [t| [UncheckedDict] |]
1263

    
1264
-- | Custom OpTestAllocator disks.
1265
pIAllocatorDisks :: Field
1266
pIAllocatorDisks =
1267
  renameField "IAllocatorDisks" $ simpleField "disks" [t| UncheckedList |]
1268

    
1269
-- | IAllocator memory field.
1270
pIAllocatorMemory :: Field
1271
pIAllocatorMemory =
1272
  renameField "IAllocatorMem" .
1273
  optionalField $
1274
  simpleField "memory" [t| NonNegative Int |]
1275

    
1276
-- | IAllocator vcpus field.
1277
pIAllocatorVCpus :: Field
1278
pIAllocatorVCpus =
1279
  renameField "IAllocatorVCpus" .
1280
  optionalField $
1281
  simpleField "vcpus" [t| NonNegative Int |]
1282

    
1283
-- | IAllocator os field.
1284
pIAllocatorOs :: Field
1285
pIAllocatorOs = renameField "IAllocatorOs" $ optionalNEStringField "os"
1286

    
1287
-- | IAllocator instances field.
1288
pIAllocatorInstances :: Field
1289
pIAllocatorInstances =
1290
  renameField "IAllocatorInstances " .
1291
  optionalField $
1292
  simpleField "instances" [t| [NonEmptyString] |]
1293

    
1294
-- | IAllocator evac mode.
1295
pIAllocatorEvacMode :: Field
1296
pIAllocatorEvacMode =
1297
  renameField "IAllocatorEvacMode" .
1298
  optionalField $
1299
  simpleField "evac_mode" [t| NodeEvacMode |]
1300

    
1301
-- | IAllocator spindle use.
1302
pIAllocatorSpindleUse :: Field
1303
pIAllocatorSpindleUse =
1304
  renameField "IAllocatorSpindleUse" .
1305
  defaultField [| forceNonNeg (1::Int) |] $
1306
  simpleField "spindle_use" [t| NonNegative Int |]
1307

    
1308
-- | IAllocator count field.
1309
pIAllocatorCount :: Field
1310
pIAllocatorCount =
1311
  renameField "IAllocatorCount" .
1312
  defaultField [| forceNonNeg (1::Int) |] $
1313
  simpleField "count" [t| NonNegative Int |]
1314

    
1315
-- | 'OpTestJqueue' notify_waitlock.
1316
pJQueueNotifyWaitLock :: Field
1317
pJQueueNotifyWaitLock = defaultFalse "notify_waitlock"
1318

    
1319
-- | 'OpTestJQueue' notify_exec.
1320
pJQueueNotifyExec :: Field
1321
pJQueueNotifyExec = defaultFalse "notify_exec"
1322

    
1323
-- | 'OpTestJQueue' log_messages.
1324
pJQueueLogMessages :: Field
1325
pJQueueLogMessages =
1326
  defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
1327

    
1328
-- | 'OpTestJQueue' fail attribute.
1329
pJQueueFail :: Field
1330
pJQueueFail =
1331
  renameField "JQueueFail" $ defaultFalse "fail"
1332

    
1333
-- | 'OpTestDummy' result field.
1334
pTestDummyResult :: Field
1335
pTestDummyResult =
1336
  renameField "TestDummyResult" $ simpleField "result" [t| UncheckedValue |]
1337

    
1338
-- | 'OpTestDummy' messages field.
1339
pTestDummyMessages :: Field
1340
pTestDummyMessages =
1341
  renameField "TestDummyMessages" $
1342
  simpleField "messages" [t| UncheckedValue |]
1343

    
1344
-- | 'OpTestDummy' fail field.
1345
pTestDummyFail :: Field
1346
pTestDummyFail =
1347
  renameField "TestDummyFail" $ simpleField "fail" [t| UncheckedValue |]
1348

    
1349
-- | 'OpTestDummy' submit_jobs field.
1350
pTestDummySubmitJobs :: Field
1351
pTestDummySubmitJobs =
1352
  renameField "TestDummySubmitJobs" $
1353
  simpleField "submit_jobs" [t| UncheckedValue |]
1354

    
1355
-- * Network parameters
1356

    
1357
-- | Network name.
1358
pNetworkName :: Field
1359
pNetworkName = simpleField "network_name" [t| NonEmptyString |]
1360

    
1361
-- | Network address (IPv4 subnet). FIXME: no real type for this.
1362
pNetworkAddress4 :: Field
1363
pNetworkAddress4 =
1364
  renameField "NetworkAddress4" $
1365
  simpleField "network" [t| NonEmptyString |]
1366

    
1367
-- | Network gateway (IPv4 address). FIXME: no real type for this.
1368
pNetworkGateway4 :: Field
1369
pNetworkGateway4 =
1370
  renameField "NetworkGateway4" $
1371
  optionalNEStringField "gateway"
1372

    
1373
-- | Network address (IPv6 subnet). FIXME: no real type for this.
1374
pNetworkAddress6 :: Field
1375
pNetworkAddress6 =
1376
  renameField "NetworkAddress6" $
1377
  optionalNEStringField "network6"
1378

    
1379
-- | Network gateway (IPv6 address). FIXME: no real type for this.
1380
pNetworkGateway6 :: Field
1381
pNetworkGateway6 =
1382
  renameField "NetworkGateway6" $
1383
  optionalNEStringField "gateway6"
1384

    
1385
-- | Network specific mac prefix (that overrides the cluster one).
1386
pNetworkMacPrefix :: Field
1387
pNetworkMacPrefix =
1388
  renameField "NetMacPrefix" $
1389
  optionalNEStringField "mac_prefix"
1390

    
1391
-- | Network add reserved IPs.
1392
pNetworkAddRsvdIps :: Field
1393
pNetworkAddRsvdIps =
1394
  renameField "NetworkAddRsvdIps" .
1395
  optionalField $
1396
  simpleField "add_reserved_ips" [t| [NonEmptyString] |]
1397

    
1398
-- | Network remove reserved IPs.
1399
pNetworkRemoveRsvdIps :: Field
1400
pNetworkRemoveRsvdIps =
1401
  renameField "NetworkRemoveRsvdIps" .
1402
  optionalField $
1403
  simpleField "remove_reserved_ips" [t| [NonEmptyString] |]
1404

    
1405
-- | Network mode when connecting to a group.
1406
pNetworkMode :: Field
1407
pNetworkMode = simpleField "network_mode" [t| NICMode |]
1408

    
1409
-- | Network link when connecting to a group.
1410
pNetworkLink :: Field
1411
pNetworkLink = simpleField "network_link" [t| NonEmptyString |]
1412

    
1413
-- * Common opcode parameters
1414

    
1415
-- | Run checks only, don't execute.
1416
pDryRun :: Field
1417
pDryRun = optionalField $ booleanField "dry_run"
1418

    
1419
-- | Debug level.
1420
pDebugLevel :: Field
1421
pDebugLevel = optionalField $ simpleField "debug_level" [t| NonNegative Int |]
1422

    
1423
-- | Opcode priority. Note: python uses a separate constant, we're
1424
-- using the actual value we know it's the default.
1425
pOpPriority :: Field
1426
pOpPriority =
1427
  defaultField [| OpPrioNormal |] $
1428
  simpleField "priority" [t| OpSubmitPriority |]
1429

    
1430
-- | Job dependencies.
1431
pDependencies :: Field
1432
pDependencies =
1433
  optionalNullSerField $ simpleField "depends" [t| [JobDependency] |]
1434

    
1435
-- | Comment field.
1436
pComment :: Field
1437
pComment = optionalNullSerField $ stringField "comment"
1438

    
1439
-- | The description of the state change reason.
1440
pReason :: Field
1441
pReason = simpleField "reason" [t| (InstReasonSrc, NonEmptyString) |]
1442

    
1443
-- * Entire opcode parameter list
1444

    
1445
-- | Old-style query opcode, with locking.
1446
dOldQuery :: [Field]
1447
dOldQuery =
1448
  [ pOutputFields
1449
  , pNames
1450
  , pUseLocking
1451
  ]
1452

    
1453
-- | Old-style query opcode, without locking.
1454
dOldQueryNoLocking :: [Field]
1455
dOldQueryNoLocking =
1456
  [ pOutputFields
1457
  , pNames
1458
  ]