Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ 82b948e4

History | View | Annotate | Download (43.2 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

    
3
{-| Implementation of opcodes parameters.
4

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

    
11
-}
12

    
13
{-
14

    
15
Copyright (C) 2012 Google Inc.
16

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

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

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

    
32
-}
33

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

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

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

    
261
-- * Helper functions and types
262

    
263
-- * Type aliases
264

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

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

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

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

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

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

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

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

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

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

    
307
-- ** Tags
308

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

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

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

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

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

    
356
-- | Name of the tag \"name\" field.
357
tagNameField :: String
358
tagNameField = "name"
359

    
360
-- | Custom encoder for 'TagObject' as represented in an opcode.
361
encodeTagObject :: TagObject -> (JSValue, [(String, JSValue)])
362
encodeTagObject t = ( showJSON (tagTypeOf t)
363
                    , [(tagNameField, maybe JSNull showJSON (tagNameOf t))] )
364

    
365
-- | Custom decoder for 'TagObject' as represented in an opcode.
366
decodeTagObject :: (Monad m) => [(String, JSValue)] -> JSValue -> m TagObject
367
decodeTagObject obj kind = do
368
  ttype <- fromJVal kind
369
  tname <- fromObj obj tagNameField
370
  tagObjectFrom ttype tname
371

    
372
-- ** Disks
373

    
374
-- | Replace disks type.
375
$(declareSADT "ReplaceDisksMode"
376
  [ ("ReplaceOnPrimary",    'C.replaceDiskPri)
377
  , ("ReplaceOnSecondary",  'C.replaceDiskSec)
378
  , ("ReplaceNewSecondary", 'C.replaceDiskChg)
379
  , ("ReplaceAuto",         'C.replaceDiskAuto)
380
  ])
381
$(makeJSONInstance ''ReplaceDisksMode)
382

    
383
-- | Disk index type (embedding constraints on the index value via a
384
-- smart constructor).
385
newtype DiskIndex = DiskIndex { unDiskIndex :: Int }
386
  deriving (Show, Eq, Ord)
387

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

    
395
instance JSON DiskIndex where
396
  readJSON v = readJSON v >>= mkDiskIndex
397
  showJSON = showJSON . unDiskIndex
398

    
399
-- ** I* param types
400

    
401
-- | Type holding disk access modes.
402
$(declareSADT "DiskAccess"
403
  [ ("DiskReadOnly",  'C.diskRdonly)
404
  , ("DiskReadWrite", 'C.diskRdwr)
405
  ])
406
$(makeJSONInstance ''DiskAccess)
407

    
408
-- | NIC modification definition.
409
$(buildObject "INicParams" "inic"
410
  [ optionalField $ simpleField C.inicMac  [t| NonEmptyString |]
411
  , optionalField $ simpleField C.inicIp   [t| String         |]
412
  , optionalField $ simpleField C.inicMode [t| NonEmptyString |]
413
  , optionalField $ simpleField C.inicLink [t| NonEmptyString |]
414
  , optionalField $ simpleField C.inicName [t| NonEmptyString |]
415
  ])
416

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

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

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

    
449
instance JSON RecreateDisksInfo where
450
  readJSON = readRecreateDisks
451
  showJSON  RecreateDisksAll            = showJSON ()
452
  showJSON (RecreateDisksIndices idx)   = showJSON idx
453
  showJSON (RecreateDisksParams params) = showJSON params
454

    
455
-- | Simple type for old-style ddm changes.
456
data DdmOldChanges = DdmOldIndex (NonNegative Int)
457
                   | DdmOldMod DdmSimple
458
                     deriving (Eq, Show)
459

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

    
469
instance JSON DdmOldChanges where
470
  showJSON (DdmOldIndex i) = showJSON i
471
  showJSON (DdmOldMod m)   = showJSON m
472
  readJSON = readDdmOldChanges
473

    
474
-- | Instance disk or nic modifications.
475
data SetParamsMods a
476
  = SetParamsEmpty
477
  | SetParamsDeprecated (NonEmpty (DdmOldChanges, a))
478
  | SetParamsNew (NonEmpty (DdmFull, Int, a))
479
    deriving (Eq, Show)
480

    
481
-- | Custom deserialiser for 'SetParamsMods'.
482
readSetParams :: (JSON a) => JSValue -> Text.JSON.Result (SetParamsMods a)
483
readSetParams (JSArray []) = return SetParamsEmpty
484
readSetParams v =
485
  case readJSON v::Text.JSON.Result [(DdmOldChanges, JSValue)] of
486
    Text.JSON.Ok _ -> liftM SetParamsDeprecated $ readJSON v
487
    _ -> liftM SetParamsNew $ readJSON v
488

    
489
instance (JSON a) => JSON (SetParamsMods a) where
490
  showJSON SetParamsEmpty = showJSON ()
491
  showJSON (SetParamsDeprecated v) = showJSON v
492
  showJSON (SetParamsNew v) = showJSON v
493
  readJSON = readSetParams
494

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

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

    
511
instance JSON ExportTarget where
512
  showJSON (ExportTargetLocal s)  = showJSON s
513
  showJSON (ExportTargetRemote l) = showJSON l
514
  readJSON = readExportTarget
515

    
516
-- * Parameters
517

    
518
-- | A required instance name (for single-instance LUs).
519
pInstanceName :: Field
520
pInstanceName = simpleField "instance_name" [t| String |]
521

    
522
-- | A list of instances.
523
pInstances :: Field
524
pInstances = defaultField [| [] |] $
525
             simpleField "instances" [t| [NonEmptyString] |]
526

    
527
-- | A generic name.
528
pName :: Field
529
pName = simpleField "name" [t| NonEmptyString |]
530

    
531
-- | Tags list.
532
pTagsList :: Field
533
pTagsList = simpleField "tags" [t| [String] |]
534

    
535
-- | Tags object.
536
pTagsObject :: Field
537
pTagsObject =
538
  customField 'decodeTagObject 'encodeTagObject [tagNameField] $
539
  simpleField "kind" [t| TagObject |]
540

    
541
-- | Selected output fields.
542
pOutputFields :: Field
543
pOutputFields = simpleField "output_fields" [t| [NonEmptyString] |]
544

    
545
-- | How long to wait for instance to shut down.
546
pShutdownTimeout :: Field
547
pShutdownTimeout = defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
548
                   simpleField "shutdown_timeout" [t| NonNegative Int |]
549

    
550
-- | Another name for the shutdown timeout, because we like to be
551
-- inconsistent.
552
pShutdownTimeout' :: Field
553
pShutdownTimeout' =
554
  renameField "InstShutdownTimeout" .
555
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
556
  simpleField "timeout" [t| NonNegative Int |]
557

    
558
-- | Whether to shutdown the instance in backup-export.
559
pShutdownInstance :: Field
560
pShutdownInstance = defaultTrue "shutdown"
561

    
562
-- | Whether to force the operation.
563
pForce :: Field
564
pForce = defaultFalse "force"
565

    
566
-- | Whether to ignore offline nodes.
567
pIgnoreOfflineNodes :: Field
568
pIgnoreOfflineNodes = defaultFalse "ignore_offline_nodes"
569

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

    
574
-- | List of nodes.
575
pNodeNames :: Field
576
pNodeNames =
577
  defaultField [| [] |] $ simpleField "node_names" [t| [NonEmptyString] |]
578

    
579
-- | A required node group name (for single-group LUs).
580
pGroupName :: Field
581
pGroupName = simpleField "group_name" [t| NonEmptyString |]
582

    
583
-- | Migration type (live\/non-live).
584
pMigrationMode :: Field
585
pMigrationMode =
586
  renameField "MigrationMode" .
587
  optionalField $
588
  simpleField "mode" [t| MigrationMode |]
589

    
590
-- | Obsolete \'live\' migration mode (boolean).
591
pMigrationLive :: Field
592
pMigrationLive =
593
  renameField "OldLiveMode" . optionalField $ booleanField "live"
594

    
595
-- | Migration cleanup parameter.
596
pMigrationCleanup :: Field
597
pMigrationCleanup = renameField "MigrationCleanup" $ defaultFalse "cleanup"
598

    
599
-- | Whether to force an unknown OS variant.
600
pForceVariant :: Field
601
pForceVariant = defaultFalse "force_variant"
602

    
603
-- | Whether to wait for the disk to synchronize.
604
pWaitForSync :: Field
605
pWaitForSync = defaultTrue "wait_for_sync"
606

    
607
-- | Whether to wait for the disk to synchronize (defaults to false).
608
pWaitForSyncFalse :: Field
609
pWaitForSyncFalse = defaultField [| False |] pWaitForSync
610

    
611
-- | Whether to ignore disk consistency
612
pIgnoreConsistency :: Field
613
pIgnoreConsistency = defaultFalse "ignore_consistency"
614

    
615
-- | Storage name.
616
pStorageName :: Field
617
pStorageName =
618
  renameField "StorageName" $ simpleField "name" [t| NonEmptyString |]
619

    
620
-- | Whether to use synchronization.
621
pUseLocking :: Field
622
pUseLocking = defaultFalse "use_locking"
623

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

    
630
-- | Whether to check name.
631
pNameCheck :: Field
632
pNameCheck = defaultTrue "name_check"
633

    
634
-- | Instance allocation policy.
635
pNodeGroupAllocPolicy :: Field
636
pNodeGroupAllocPolicy = optionalField $
637
                        simpleField "alloc_policy" [t| AllocPolicy |]
638

    
639
-- | Default node parameters for group.
640
pGroupNodeParams :: Field
641
pGroupNodeParams = optionalField $ simpleField "ndparams" [t| UncheckedDict |]
642

    
643
-- | Resource(s) to query for.
644
pQueryWhat :: Field
645
pQueryWhat = simpleField "what" [t| Qlang.QueryTypeOp |]
646

    
647
-- | Whether to release locks as soon as possible.
648
pEarlyRelease :: Field
649
pEarlyRelease = defaultFalse "early_release"
650

    
651
-- | Whether to ensure instance's IP address is inactive.
652
pIpCheck :: Field
653
pIpCheck = defaultTrue "ip_check"
654

    
655
-- | Check for conflicting IPs.
656
pIpConflictsCheck :: Field
657
pIpConflictsCheck = defaultTrue "conflicts_check"
658

    
659
-- | Do not remember instance state changes.
660
pNoRemember :: Field
661
pNoRemember = defaultFalse "no_remember"
662

    
663
-- | Target node for instance migration/failover.
664
pMigrationTargetNode :: Field
665
pMigrationTargetNode = optionalNEStringField "target_node"
666

    
667
-- | Target node for instance move (required).
668
pMoveTargetNode :: Field
669
pMoveTargetNode =
670
  renameField "MoveTargetNode" $
671
  simpleField "target_node" [t| NonEmptyString |]
672

    
673
-- | Pause instance at startup.
674
pStartupPaused :: Field
675
pStartupPaused = defaultFalse "startup_paused"
676

    
677
-- | Verbose mode.
678
pVerbose :: Field
679
pVerbose = defaultFalse "verbose"
680

    
681
-- ** Parameters for cluster verification
682

    
683
-- | Whether to simulate errors (useful for debugging).
684
pDebugSimulateErrors :: Field
685
pDebugSimulateErrors = defaultFalse "debug_simulate_errors"
686

    
687
-- | Error codes.
688
pErrorCodes :: Field
689
pErrorCodes = defaultFalse "error_codes"
690

    
691
-- | Which checks to skip.
692
pSkipChecks :: Field
693
pSkipChecks = defaultField [| Set.empty |] $
694
              simpleField "skip_checks" [t| Set.Set VerifyOptionalChecks |]
695

    
696
-- | List of error codes that should be treated as warnings.
697
pIgnoreErrors :: Field
698
pIgnoreErrors = defaultField [| Set.empty |] $
699
                simpleField "ignore_errors" [t| Set.Set CVErrorCode |]
700

    
701
-- | Optional group name.
702
pOptGroupName :: Field
703
pOptGroupName = renameField "OptGroupName" .
704
                optionalField $ simpleField "group_name" [t| NonEmptyString |]
705

    
706
-- | Disk templates' parameter defaults.
707
pDiskParams :: Field
708
pDiskParams = optionalField $
709
              simpleField "diskparams" [t| GenericContainer DiskTemplate
710
                                           UncheckedDict |]
711

    
712
-- | Whether to hotplug device.
713
pHotplug :: Field
714
pHotplug = defaultFalse "hotplug"
715

    
716
-- * Parameters for node resource model
717

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

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

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

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

    
734
-- | Utility type for OpClusterSetParams.
735
type TestClusterOsListItem = (DdmSimple, NonEmptyString)
736

    
737
-- | Utility type of OsList.
738
type TestClusterOsList = [TestClusterOsListItem]
739

    
740
-- Utility type for NIC definitions.
741
--type TestNicDef = INicParams
742

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

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

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

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

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

    
766
-- | Volume group name.
767
pVgName :: Field
768
pVgName = optionalStringField "vg_name"
769

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
904
-- | DRBD helper program.
905
pDrbdHelper :: Field
906
pDrbdHelper = optionalStringField "drbd_helper"
907

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

    
912
-- | Master network device.
913
pMasterNetdev :: Field
914
pMasterNetdev = optionalStringField "master_netdev"
915

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

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

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

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

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

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

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

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

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

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

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

    
972
-- | Primary IP address.
973
pPrimaryIp :: Field
974
pPrimaryIp = optionalStringField "primary_ip"
975

    
976
-- | Secondary IP address.
977
pSecondaryIp :: Field
978
pSecondaryIp = optionalNEStringField "secondary_ip"
979

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

    
984
-- | Initial node group.
985
pNodeGroup :: Field
986
pNodeGroup = optionalNEStringField "group"
987

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

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

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

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

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

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

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

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

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

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

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

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

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

    
1042
-- | New secondary node.
1043
pRemoteNode :: Field
1044
pRemoteNode = optionalNEStringField "remote_node"
1045

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
1118
-- | Ignore failures parameter.
1119
pIgnoreFailures :: Field
1120
pIgnoreFailures = defaultFalse "ignore_failures"
1121

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
1242
-- * Test opcode parameters
1243

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
1340
-- | 'OpTestJqueue' notify_waitlock.
1341
pJQueueNotifyWaitLock :: Field
1342
pJQueueNotifyWaitLock = defaultFalse "notify_waitlock"
1343

    
1344
-- | 'OpTestJQueue' notify_exec.
1345
pJQueueNotifyExec :: Field
1346
pJQueueNotifyExec = defaultFalse "notify_exec"
1347

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

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

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

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

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

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

    
1380
-- * Network parameters
1381

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

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

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

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

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

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

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

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

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

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

    
1438
-- * Common opcode parameters
1439

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

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

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

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

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

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

    
1468
-- * Entire opcode parameter list
1469

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

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