Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ aa922d64

History | View | Annotate | Download (42.6 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
  , pEnabledDiskTemplates
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
  , optionalField $ simpleField C.inicName [t| NonEmptyString |]
406
  ])
407

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

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

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

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

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

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

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

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

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

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

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

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

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

    
507
-- * Parameters
508

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
672
-- ** Parameters for cluster verification
673

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

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

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

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

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

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

    
703
-- * Parameters for node resource model
704

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
1225
-- * Test opcode parameters
1226

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
1363
-- * Network parameters
1364

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

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

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

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

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

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

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

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

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

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

    
1421
-- * Common opcode parameters
1422

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

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

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

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

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

    
1447
-- * Entire opcode parameter list
1448

    
1449
-- | Old-style query opcode, with locking.
1450
dOldQuery :: [Field]
1451
dOldQuery =
1452
  [ pOutputFields
1453
  , pNames
1454
  , pUseLocking
1455
  ]
1456

    
1457
-- | Old-style query opcode, without locking.
1458
dOldQueryNoLocking :: [Field]
1459
dOldQueryNoLocking =
1460
  [ pOutputFields
1461
  , pNames
1462
  ]