Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ 9d0b521e

History | View | Annotate | Download (43.1 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

    
3
{-| Implementation of opcodes parameters.
4

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

    
11
-}
12

    
13
{-
14

    
15
Copyright (C) 2012 Google Inc.
16

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

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

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

    
32
-}
33

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

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

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

    
260
-- * Helper functions and types
261

    
262
-- * Type aliases
263

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

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

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

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

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

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

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

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

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

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

    
306
-- ** Tags
307

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

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

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

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

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

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

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

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

    
371
-- ** Disks
372

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

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

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

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

    
398
-- ** I* param types
399

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
515
-- * Parameters
516

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
680
-- ** Parameters for cluster verification
681

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

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

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

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

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

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

    
711
-- * Parameters for node resource model
712

    
713
-- | Set hypervisor states.
714
pHvState :: Field
715
pHvState = optionalField $ simpleField "hv_state" [t| UncheckedDict |]
716

    
717
-- | Set disk states.
718
pDiskState :: Field
719
pDiskState = optionalField $ simpleField "disk_state" [t| UncheckedDict |]
720

    
721
-- | Whether to ignore ipolicy violations.
722
pIgnoreIpolicy :: Field
723
pIgnoreIpolicy = defaultFalse "ignore_ipolicy"
724

    
725
-- | Allow runtime changes while migrating.
726
pAllowRuntimeChgs :: Field
727
pAllowRuntimeChgs = defaultTrue "allow_runtime_changes"
728

    
729
-- | Utility type for OpClusterSetParams.
730
type TestClusterOsListItem = (DdmSimple, NonEmptyString)
731

    
732
-- | Utility type of OsList.
733
type TestClusterOsList = [TestClusterOsListItem]
734

    
735
-- Utility type for NIC definitions.
736
--type TestNicDef = INicParams
737

    
738
-- | List of instance disks.
739
pInstDisks :: Field
740
pInstDisks = renameField "instDisks" $ simpleField "disks" [t| [IDiskParams] |]
741

    
742
-- | Instance disk template.
743
pDiskTemplate :: Field
744
pDiskTemplate = simpleField "disk_template" [t| DiskTemplate |]
745

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

    
753
-- | File driver.
754
pFileDriver :: Field
755
pFileDriver = optionalField $ simpleField "file_driver" [t| FileDriver |]
756

    
757
-- | Directory for storing file-backed disks.
758
pFileStorageDir :: Field
759
pFileStorageDir = optionalNEStringField "file_storage_dir"
760

    
761
-- | Volume group name.
762
pVgName :: Field
763
pVgName = optionalStringField "vg_name"
764

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

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

    
777
-- | Selected hypervisor for an instance.
778
pHypervisor :: Field
779
pHypervisor =
780
  optionalField $
781
  simpleField "hypervisor" [t| Hypervisor |]
782

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

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

    
797
-- | Cluster-wide beparams.
798
pClusterBeParams :: Field
799
pClusterBeParams =
800
  renameField "ClusterBeParams" .
801
  optionalField $ simpleField "beparams" [t| UncheckedDict |]
802

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

    
810
-- | Reset instance parameters to default if equal.
811
pResetDefaults :: Field
812
pResetDefaults = defaultFalse "identify_defaults"
813

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

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

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

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

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

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

    
851
-- | Candidate pool size.
852
pCandidatePoolSize :: Field
853
pCandidatePoolSize =
854
  optionalField $ simpleField "candidate_pool_size" [t| Positive Int |]
855

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

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

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

    
871
-- | Whether to automatically maintain node health.
872
pMaintainNodeHealth :: Field
873
pMaintainNodeHealth = optionalField $ booleanField "maintain_node_health"
874

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

    
879
-- | Whether to wipe disks before allocating them to instances.
880
pPreallocWipeDisks :: Field
881
pPreallocWipeDisks = optionalField $ booleanField "prealloc_wipe_disks"
882

    
883
-- | Cluster-wide NIC parameter defaults.
884
pNicParams :: Field
885
pNicParams = optionalField $ simpleField "nicparams" [t| INicParams |]
886

    
887
-- | Instance NIC definitions.
888
pInstNics :: Field
889
pInstNics = simpleField "nics" [t| [INicParams] |]
890

    
891
-- | Cluster-wide node parameter defaults.
892
pNdParams :: Field
893
pNdParams = optionalField $ simpleField "ndparams" [t| UncheckedDict |]
894

    
895
-- | Cluster-wide ipolicy specs.
896
pIpolicy :: Field
897
pIpolicy = optionalField $ simpleField "ipolicy" [t| UncheckedDict |]
898

    
899
-- | DRBD helper program.
900
pDrbdHelper :: Field
901
pDrbdHelper = optionalStringField "drbd_helper"
902

    
903
-- | Default iallocator for cluster.
904
pDefaultIAllocator :: Field
905
pDefaultIAllocator = optionalStringField "default_iallocator"
906

    
907
-- | Master network device.
908
pMasterNetdev :: Field
909
pMasterNetdev = optionalStringField "master_netdev"
910

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

    
916
-- | List of reserved LVs.
917
pReservedLvs :: Field
918
pReservedLvs =
919
  optionalField $ simpleField "reserved_lvs" [t| [NonEmptyString] |]
920

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

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

    
934
-- | Whether to use an external master IP address setup script.
935
pUseExternalMipScript :: Field
936
pUseExternalMipScript = optionalField $ booleanField "use_external_mip_script"
937

    
938
-- | Requested fields.
939
pQueryFields :: Field
940
pQueryFields = simpleField "fields" [t| [NonEmptyString] |]
941

    
942
-- | Query filter.
943
pQueryFilter :: Field
944
pQueryFilter = simpleField "qfilter" [t| Qlang.Filter String |]
945

    
946
-- | OOB command to run.
947
pOobCommand :: Field
948
pOobCommand = simpleField "command" [t| OobCommand |]
949

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

    
955
-- | Ignores the node offline status for power off.
956
pIgnoreStatus :: Field
957
pIgnoreStatus = defaultFalse "ignore_status"
958

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

    
967
-- | Primary IP address.
968
pPrimaryIp :: Field
969
pPrimaryIp = optionalStringField "primary_ip"
970

    
971
-- | Secondary IP address.
972
pSecondaryIp :: Field
973
pSecondaryIp = optionalNEStringField "secondary_ip"
974

    
975
-- | Whether node is re-added to cluster.
976
pReadd :: Field
977
pReadd = defaultFalse "readd"
978

    
979
-- | Initial node group.
980
pNodeGroup :: Field
981
pNodeGroup = optionalNEStringField "group"
982

    
983
-- | Whether node can become master or master candidate.
984
pMasterCapable :: Field
985
pMasterCapable = optionalField $ booleanField "master_capable"
986

    
987
-- | Whether node can host instances.
988
pVmCapable :: Field
989
pVmCapable = optionalField $ booleanField "vm_capable"
990

    
991
-- | List of names.
992
pNames :: Field
993
pNames = defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
994

    
995
-- | List of node names.
996
pNodes :: Field
997
pNodes = defaultField [| [] |] $ simpleField "nodes" [t| [NonEmptyString] |]
998

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

    
1004
-- | Storage type.
1005
pStorageType :: Field
1006
pStorageType = simpleField "storage_type" [t| StorageType |]
1007

    
1008
-- | Storage changes (unchecked).
1009
pStorageChanges :: Field
1010
pStorageChanges = simpleField "changes" [t| UncheckedDict |]
1011

    
1012
-- | Whether the node should become a master candidate.
1013
pMasterCandidate :: Field
1014
pMasterCandidate = optionalField $ booleanField "master_candidate"
1015

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

    
1020
-- | Whether the node should be marked as drained.
1021
pDrained ::Field
1022
pDrained = optionalField $ booleanField "drained"
1023

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

    
1028
-- | Whether the node should be marked as powered
1029
pPowered :: Field
1030
pPowered = optionalField $ booleanField "powered"
1031

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

    
1037
-- | New secondary node.
1038
pRemoteNode :: Field
1039
pRemoteNode = optionalNEStringField "remote_node"
1040

    
1041
-- | Node evacuation mode.
1042
pEvacMode :: Field
1043
pEvacMode = renameField "EvacMode" $ simpleField "mode" [t| NodeEvacMode |]
1044

    
1045
-- | Instance creation mode.
1046
pInstCreateMode :: Field
1047
pInstCreateMode =
1048
  renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
1049

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

    
1054
-- | OS type for instance installation.
1055
pInstOs :: Field
1056
pInstOs = optionalNEStringField "os_type"
1057

    
1058
-- | Primary node for an instance.
1059
pPrimaryNode :: Field
1060
pPrimaryNode = optionalNEStringField "pnode"
1061

    
1062
-- | Secondary node for an instance.
1063
pSecondaryNode :: Field
1064
pSecondaryNode = optionalNEStringField "snode"
1065

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

    
1071
-- | Source instance name (remote import only).
1072
pSourceInstance :: Field
1073
pSourceInstance = optionalNEStringField "source_instance_name"
1074

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

    
1082
-- | Source X509 CA in PEM format (remote import only).
1083
pSourceX509Ca :: Field
1084
pSourceX509Ca = optionalNEStringField "source_x509_ca"
1085

    
1086
-- | Source node for import.
1087
pSrcNode :: Field
1088
pSrcNode = optionalNEStringField "src_node"
1089

    
1090
-- | Source directory for import.
1091
pSrcPath :: Field
1092
pSrcPath = optionalNEStringField "src_path"
1093

    
1094
-- | Whether to start instance after creation.
1095
pStartInstance :: Field
1096
pStartInstance = defaultTrue "start"
1097

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

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

    
1113
-- | Ignore failures parameter.
1114
pIgnoreFailures :: Field
1115
pIgnoreFailures = defaultFalse "ignore_failures"
1116

    
1117
-- | New instance or cluster name.
1118
pNewName :: Field
1119
pNewName = simpleField "new_name" [t| NonEmptyString |]
1120

    
1121
-- | Whether to start the instance even if secondary disks are failing.
1122
pIgnoreSecondaries :: Field
1123
pIgnoreSecondaries = defaultFalse "ignore_secondaries"
1124

    
1125
-- | How to reboot the instance.
1126
pRebootType :: Field
1127
pRebootType = simpleField "reboot_type" [t| RebootType |]
1128

    
1129
-- | Whether to ignore recorded disk size.
1130
pIgnoreDiskSize :: Field
1131
pIgnoreDiskSize = defaultFalse "ignore_size"
1132

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

    
1140
-- | Whether to only return configuration data without querying nodes.
1141
pStatic :: Field
1142
pStatic = defaultFalse "static"
1143

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

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

    
1158
-- | New runtime memory.
1159
pRuntimeMem :: Field
1160
pRuntimeMem = optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1161

    
1162
-- | Change the instance's OS without reinstalling the instance
1163
pOsNameChange :: Field
1164
pOsNameChange = optionalNEStringField "os_name"
1165

    
1166
-- | Disk index for e.g. grow disk.
1167
pDiskIndex :: Field
1168
pDiskIndex = renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
1169

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

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

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

    
1184
-- | Export mode field.
1185
pExportMode :: Field
1186
pExportMode =
1187
  renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1188

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

    
1195
-- | Whether to remove instance after export.
1196
pRemoveInstance :: Field
1197
pRemoveInstance = defaultFalse "remove_instance"
1198

    
1199
-- | Whether to ignore failures while removing instances.
1200
pIgnoreRemoveFailures :: Field
1201
pIgnoreRemoveFailures = defaultFalse "ignore_remove_failures"
1202

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

    
1207
-- | Destination X509 CA (remote export only).
1208
pX509DestCA :: Field
1209
pX509DestCA = optionalNEStringField "destination_x509_ca"
1210

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

    
1217
-- | Restricted command name.
1218
pRestrictedCommand :: Field
1219
pRestrictedCommand =
1220
  renameField "RestrictedCommand" $
1221
  simpleField "command" [t| NonEmptyString |]
1222

    
1223
-- | Replace disks mode.
1224
pReplaceDisksMode :: Field
1225
pReplaceDisksMode =
1226
  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1227

    
1228
-- | List of disk indices.
1229
pReplaceDisksList :: Field
1230
pReplaceDisksList =
1231
  renameField "ReplaceDisksList" $ simpleField "disks" [t| [DiskIndex] |]
1232

    
1233
-- | Whether do allow failover in migrations.
1234
pAllowFailover :: Field
1235
pAllowFailover = defaultFalse "allow_failover"
1236

    
1237
-- * Test opcode parameters
1238

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

    
1244
-- | on_master field for 'OpTestDelay'.
1245
pDelayOnMaster :: Field
1246
pDelayOnMaster = renameField "DelayOnMaster" $ defaultTrue "on_master"
1247

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

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

    
1262
-- | IAllocator test direction.
1263
pIAllocatorDirection :: Field
1264
pIAllocatorDirection =
1265
  renameField "IAllocatorDirection" $
1266
  simpleField "direction" [t| IAllocatorTestDir |]
1267

    
1268
-- | IAllocator test mode.
1269
pIAllocatorMode :: Field
1270
pIAllocatorMode =
1271
  renameField "IAllocatorMode" $
1272
  simpleField "mode" [t| IAllocatorMode |]
1273

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

    
1279
-- | Custom OpTestIAllocator nics.
1280
pIAllocatorNics :: Field
1281
pIAllocatorNics =
1282
  renameField "IAllocatorNics" $ simpleField "nics" [t| [UncheckedDict] |]
1283

    
1284
-- | Custom OpTestAllocator disks.
1285
pIAllocatorDisks :: Field
1286
pIAllocatorDisks =
1287
  renameField "IAllocatorDisks" $ simpleField "disks" [t| UncheckedList |]
1288

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

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

    
1303
-- | IAllocator os field.
1304
pIAllocatorOs :: Field
1305
pIAllocatorOs = renameField "IAllocatorOs" $ optionalNEStringField "os"
1306

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

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

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

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

    
1335
-- | 'OpTestJqueue' notify_waitlock.
1336
pJQueueNotifyWaitLock :: Field
1337
pJQueueNotifyWaitLock = defaultFalse "notify_waitlock"
1338

    
1339
-- | 'OpTestJQueue' notify_exec.
1340
pJQueueNotifyExec :: Field
1341
pJQueueNotifyExec = defaultFalse "notify_exec"
1342

    
1343
-- | 'OpTestJQueue' log_messages.
1344
pJQueueLogMessages :: Field
1345
pJQueueLogMessages =
1346
  defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
1347

    
1348
-- | 'OpTestJQueue' fail attribute.
1349
pJQueueFail :: Field
1350
pJQueueFail =
1351
  renameField "JQueueFail" $ defaultFalse "fail"
1352

    
1353
-- | 'OpTestDummy' result field.
1354
pTestDummyResult :: Field
1355
pTestDummyResult =
1356
  renameField "TestDummyResult" $ simpleField "result" [t| UncheckedValue |]
1357

    
1358
-- | 'OpTestDummy' messages field.
1359
pTestDummyMessages :: Field
1360
pTestDummyMessages =
1361
  renameField "TestDummyMessages" $
1362
  simpleField "messages" [t| UncheckedValue |]
1363

    
1364
-- | 'OpTestDummy' fail field.
1365
pTestDummyFail :: Field
1366
pTestDummyFail =
1367
  renameField "TestDummyFail" $ simpleField "fail" [t| UncheckedValue |]
1368

    
1369
-- | 'OpTestDummy' submit_jobs field.
1370
pTestDummySubmitJobs :: Field
1371
pTestDummySubmitJobs =
1372
  renameField "TestDummySubmitJobs" $
1373
  simpleField "submit_jobs" [t| UncheckedValue |]
1374

    
1375
-- * Network parameters
1376

    
1377
-- | Network name.
1378
pNetworkName :: Field
1379
pNetworkName = simpleField "network_name" [t| NonEmptyString |]
1380

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

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

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

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

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

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

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

    
1425
-- | Network mode when connecting to a group.
1426
pNetworkMode :: Field
1427
pNetworkMode = simpleField "network_mode" [t| NICMode |]
1428

    
1429
-- | Network link when connecting to a group.
1430
pNetworkLink :: Field
1431
pNetworkLink = simpleField "network_link" [t| NonEmptyString |]
1432

    
1433
-- * Common opcode parameters
1434

    
1435
-- | Run checks only, don't execute.
1436
pDryRun :: Field
1437
pDryRun = optionalField $ booleanField "dry_run"
1438

    
1439
-- | Debug level.
1440
pDebugLevel :: Field
1441
pDebugLevel = optionalField $ simpleField "debug_level" [t| NonNegative Int |]
1442

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

    
1450
-- | Job dependencies.
1451
pDependencies :: Field
1452
pDependencies =
1453
  optionalNullSerField $ simpleField "depends" [t| [JobDependency] |]
1454

    
1455
-- | Comment field.
1456
pComment :: Field
1457
pComment = optionalNullSerField $ stringField "comment"
1458

    
1459
-- | Reason trail field.
1460
pReason :: Field
1461
pReason = simpleField C.opcodeReason [t| ReasonTrail |]
1462

    
1463
-- * Entire opcode parameter list
1464

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

    
1473
-- | Old-style query opcode, without locking.
1474
dOldQueryNoLocking :: [Field]
1475
dOldQueryNoLocking =
1476
  [ pOutputFields
1477
  , pNames
1478
  ]