Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ 3039e2dc

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

    
259
import Control.Monad (liftM)
260
import qualified Data.Set as Set
261
import Text.JSON (readJSON, showJSON, JSON, JSValue(..), fromJSString,
262
                  JSObject, toJSObject)
263
import qualified Text.JSON
264
import Text.JSON.Pretty (pp_value)
265

    
266
import Ganeti.BasicTypes
267
import qualified Ganeti.Constants as C
268
import Ganeti.THH
269
import Ganeti.JSON
270
import Ganeti.Types
271
import qualified Ganeti.Query.Language as Qlang
272

    
273
-- * Helper functions and types
274

    
275
-- * Type aliases
276

    
277
-- | Build a boolean field.
278
booleanField :: String -> Field
279
booleanField = flip simpleField [t| Bool |]
280

    
281
-- | Default a field to 'False'.
282
defaultFalse :: String -> Field
283
defaultFalse = defaultField [| False |] . booleanField
284

    
285
-- | Default a field to 'True'.
286
defaultTrue :: String -> Field
287
defaultTrue = defaultField [| True |] . booleanField
288

    
289
-- | An alias for a 'String' field.
290
stringField :: String -> Field
291
stringField = flip simpleField [t| String |]
292

    
293
-- | An alias for an optional string field.
294
optionalStringField :: String -> Field
295
optionalStringField = optionalField . stringField
296

    
297
-- | An alias for an optional non-empty string field.
298
optionalNEStringField :: String -> Field
299
optionalNEStringField = optionalField . flip simpleField [t| NonEmptyString |]
300

    
301
-- | Unchecked value, should be replaced by a better definition.
302
type UncheckedValue = JSValue
303

    
304
-- | Unchecked dict, should be replaced by a better definition.
305
type UncheckedDict = JSObject JSValue
306

    
307
-- | Unchecked list, shoild be replaced by a better definition.
308
type UncheckedList = [JSValue]
309

    
310
-- | Function to force a non-negative value, without returning via a
311
-- monad. This is needed for, and should be used /only/ in the case of
312
-- forcing constants. In case the constant is wrong (< 0), this will
313
-- become a runtime error.
314
forceNonNeg :: (Num a, Ord a, Show a) => a -> NonNegative a
315
forceNonNeg i = case mkNonNegative i of
316
                  Ok n -> n
317
                  Bad msg -> error msg
318

    
319
-- ** Tags
320

    
321
-- | Data type representing what items do the tag operations apply to.
322
$(declareSADT "TagType"
323
  [ ("TagTypeInstance", 'C.tagInstance)
324
  , ("TagTypeNode",     'C.tagNode)
325
  , ("TagTypeGroup",    'C.tagNodegroup)
326
  , ("TagTypeCluster",  'C.tagCluster)
327
  ])
328
$(makeJSONInstance ''TagType)
329

    
330
-- | Data type holding a tag object (type and object name).
331
data TagObject = TagInstance String
332
               | TagNode     String
333
               | TagGroup    String
334
               | TagCluster
335
               deriving (Show, Eq)
336

    
337
-- | Tag type for a given tag object.
338
tagTypeOf :: TagObject -> TagType
339
tagTypeOf (TagInstance {}) = TagTypeInstance
340
tagTypeOf (TagNode     {}) = TagTypeNode
341
tagTypeOf (TagGroup    {}) = TagTypeGroup
342
tagTypeOf (TagCluster  {}) = TagTypeCluster
343

    
344
-- | Gets the potential tag object name.
345
tagNameOf :: TagObject -> Maybe String
346
tagNameOf (TagInstance s) = Just s
347
tagNameOf (TagNode     s) = Just s
348
tagNameOf (TagGroup    s) = Just s
349
tagNameOf  TagCluster     = Nothing
350

    
351
-- | Builds a 'TagObject' from a tag type and name.
352
tagObjectFrom :: (Monad m) => TagType -> JSValue -> m TagObject
353
tagObjectFrom TagTypeInstance (JSString s) =
354
  return . TagInstance $ fromJSString s
355
tagObjectFrom TagTypeNode     (JSString s) = return . TagNode $ fromJSString s
356
tagObjectFrom TagTypeGroup    (JSString s) = return . TagGroup $ fromJSString s
357
tagObjectFrom TagTypeCluster   JSNull      = return TagCluster
358
tagObjectFrom t v =
359
  fail $ "Invalid tag type/name combination: " ++ show t ++ "/" ++
360
         show (pp_value v)
361

    
362
-- | Name of the tag \"name\" field.
363
tagNameField :: String
364
tagNameField = "name"
365

    
366
-- | Custom encoder for 'TagObject' as represented in an opcode.
367
encodeTagObject :: TagObject -> (JSValue, [(String, JSValue)])
368
encodeTagObject t = ( showJSON (tagTypeOf t)
369
                    , [(tagNameField, maybe JSNull showJSON (tagNameOf t))] )
370

    
371
-- | Custom decoder for 'TagObject' as represented in an opcode.
372
decodeTagObject :: (Monad m) => [(String, JSValue)] -> JSValue -> m TagObject
373
decodeTagObject obj kind = do
374
  ttype <- fromJVal kind
375
  tname <- fromObj obj tagNameField
376
  tagObjectFrom ttype tname
377

    
378
-- ** Disks
379

    
380
-- | Replace disks type.
381
$(declareSADT "ReplaceDisksMode"
382
  [ ("ReplaceOnPrimary",    'C.replaceDiskPri)
383
  , ("ReplaceOnSecondary",  'C.replaceDiskSec)
384
  , ("ReplaceNewSecondary", 'C.replaceDiskChg)
385
  , ("ReplaceAuto",         'C.replaceDiskAuto)
386
  ])
387
$(makeJSONInstance ''ReplaceDisksMode)
388

    
389
-- | Disk index type (embedding constraints on the index value via a
390
-- smart constructor).
391
newtype DiskIndex = DiskIndex { unDiskIndex :: Int }
392
  deriving (Show, Eq, Ord)
393

    
394
-- | Smart constructor for 'DiskIndex'.
395
mkDiskIndex :: (Monad m) => Int -> m DiskIndex
396
mkDiskIndex i | i >= 0 && i < C.maxDisks = return (DiskIndex i)
397
              | otherwise = fail $ "Invalid value for disk index '" ++
398
                            show i ++ "', required between 0 and " ++
399
                            show C.maxDisks
400

    
401
instance JSON DiskIndex where
402
  readJSON v = readJSON v >>= mkDiskIndex
403
  showJSON = showJSON . unDiskIndex
404

    
405
-- ** I* param types
406

    
407
-- | Type holding disk access modes.
408
$(declareSADT "DiskAccess"
409
  [ ("DiskReadOnly",  'C.diskRdonly)
410
  , ("DiskReadWrite", 'C.diskRdwr)
411
  ])
412
$(makeJSONInstance ''DiskAccess)
413

    
414
-- | NIC modification definition.
415
$(buildObject "INicParams" "inic"
416
  [ optionalField $ simpleField C.inicMac  [t| NonEmptyString |]
417
  , optionalField $ simpleField C.inicIp   [t| String         |]
418
  , optionalField $ simpleField C.inicMode [t| NonEmptyString |]
419
  , optionalField $ simpleField C.inicLink [t| NonEmptyString |]
420
  , optionalField $ simpleField C.inicName [t| NonEmptyString |]
421
  ])
422

    
423
-- | Disk modification definition. FIXME: disksize should be VTYPE_UNIT.
424
$(buildObject "IDiskParams" "idisk"
425
  [ optionalField $ simpleField C.idiskSize   [t| Int            |]
426
  , optionalField $ simpleField C.idiskMode   [t| DiskAccess     |]
427
  , optionalField $ simpleField C.idiskAdopt  [t| NonEmptyString |]
428
  , optionalField $ simpleField C.idiskVg     [t| NonEmptyString |]
429
  , optionalField $ simpleField C.idiskMetavg [t| NonEmptyString |]
430
  , optionalField $ simpleField C.idiskName   [t| NonEmptyString |]
431
  ])
432

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

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

    
455
instance JSON RecreateDisksInfo where
456
  readJSON = readRecreateDisks
457
  showJSON  RecreateDisksAll            = showJSON ()
458
  showJSON (RecreateDisksIndices idx)   = showJSON idx
459
  showJSON (RecreateDisksParams params) = showJSON params
460

    
461
-- | Simple type for old-style ddm changes.
462
data DdmOldChanges = DdmOldIndex (NonNegative Int)
463
                   | DdmOldMod DdmSimple
464
                     deriving (Eq, Show)
465

    
466
readDdmOldChanges :: JSValue -> Text.JSON.Result DdmOldChanges
467
readDdmOldChanges v =
468
  case readJSON v::Text.JSON.Result (NonNegative Int) of
469
    Text.JSON.Ok nn -> return $ DdmOldIndex nn
470
    _ -> case readJSON v::Text.JSON.Result DdmSimple of
471
           Text.JSON.Ok ddms -> return $ DdmOldMod ddms
472
           _ -> fail $ "Can't parse value '" ++ show (pp_value v) ++ "' as"
473
                ++ " either index or modification"
474

    
475
instance JSON DdmOldChanges where
476
  showJSON (DdmOldIndex i) = showJSON i
477
  showJSON (DdmOldMod m)   = showJSON m
478
  readJSON = readDdmOldChanges
479

    
480
-- | Instance disk or nic modifications.
481
data SetParamsMods a
482
  = SetParamsEmpty
483
  | SetParamsDeprecated (NonEmpty (DdmOldChanges, a))
484
  | SetParamsNew (NonEmpty (DdmFull, Int, a))
485
    deriving (Eq, Show)
486

    
487
-- | Custom deserialiser for 'SetParamsMods'.
488
readSetParams :: (JSON a) => JSValue -> Text.JSON.Result (SetParamsMods a)
489
readSetParams (JSArray []) = return SetParamsEmpty
490
readSetParams v =
491
  case readJSON v::Text.JSON.Result [(DdmOldChanges, JSValue)] of
492
    Text.JSON.Ok _ -> liftM SetParamsDeprecated $ readJSON v
493
    _ -> liftM SetParamsNew $ readJSON v
494

    
495
instance (JSON a) => JSON (SetParamsMods a) where
496
  showJSON SetParamsEmpty = showJSON ()
497
  showJSON (SetParamsDeprecated v) = showJSON v
498
  showJSON (SetParamsNew v) = showJSON v
499
  readJSON = readSetParams
500

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

    
509
-- | Custom reader for 'ExportTarget'.
510
readExportTarget :: JSValue -> Text.JSON.Result ExportTarget
511
readExportTarget (JSString s) = liftM ExportTargetLocal $
512
                                mkNonEmpty (fromJSString s)
513
readExportTarget (JSArray arr) = return $ ExportTargetRemote arr
514
readExportTarget v = fail $ "Invalid value received for 'target_node': " ++
515
                     show (pp_value v)
516

    
517
instance JSON ExportTarget where
518
  showJSON (ExportTargetLocal s)  = showJSON s
519
  showJSON (ExportTargetRemote l) = showJSON l
520
  readJSON = readExportTarget
521

    
522
-- * Parameters
523

    
524
-- | A required instance name (for single-instance LUs).
525
pInstanceName :: Field
526
pInstanceName = simpleField "instance_name" [t| String |]
527

    
528
-- | An instance UUID (for single-instance LUs).
529
pInstanceUuid :: Field
530
pInstanceUuid = optionalField $ simpleField "instance_uuid" [t| String |]
531

    
532
-- | A list of instances.
533
pInstances :: Field
534
pInstances = defaultField [| [] |] $
535
             simpleField "instances" [t| [NonEmptyString] |]
536

    
537
-- | A generic name.
538
pName :: Field
539
pName = simpleField "name" [t| NonEmptyString |]
540

    
541
-- | Tags list.
542
pTagsList :: Field
543
pTagsList = simpleField "tags" [t| [String] |]
544

    
545
-- | Tags object.
546
pTagsObject :: Field
547
pTagsObject =
548
  customField 'decodeTagObject 'encodeTagObject [tagNameField] $
549
  simpleField "kind" [t| TagObject |]
550

    
551
-- | Selected output fields.
552
pOutputFields :: Field
553
pOutputFields = simpleField "output_fields" [t| [NonEmptyString] |]
554

    
555
-- | How long to wait for instance to shut down.
556
pShutdownTimeout :: Field
557
pShutdownTimeout = defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
558
                   simpleField "shutdown_timeout" [t| NonNegative Int |]
559

    
560
-- | Another name for the shutdown timeout, because we like to be
561
-- inconsistent.
562
pShutdownTimeout' :: Field
563
pShutdownTimeout' =
564
  renameField "InstShutdownTimeout" .
565
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
566
  simpleField "timeout" [t| NonNegative Int |]
567

    
568
-- | Whether to shutdown the instance in backup-export.
569
pShutdownInstance :: Field
570
pShutdownInstance = defaultTrue "shutdown"
571

    
572
-- | Whether to force the operation.
573
pForce :: Field
574
pForce = defaultFalse "force"
575

    
576
-- | Whether to ignore offline nodes.
577
pIgnoreOfflineNodes :: Field
578
pIgnoreOfflineNodes = defaultFalse "ignore_offline_nodes"
579

    
580
-- | A required node name (for single-node LUs).
581
pNodeName :: Field
582
pNodeName = simpleField "node_name" [t| NonEmptyString |]
583

    
584
-- | A node UUID (for single-node LUs).
585
pNodeUuid :: Field
586
pNodeUuid = optionalField $ simpleField "node_uuid" [t| NonEmptyString |]
587

    
588
-- | List of nodes.
589
pNodeNames :: Field
590
pNodeNames =
591
  defaultField [| [] |] $ simpleField "node_names" [t| [NonEmptyString] |]
592

    
593
-- | List of node UUIDs.
594
pNodeUuids :: Field
595
pNodeUuids =
596
  optionalField $ simpleField "node_uuids" [t| [NonEmptyString] |]
597

    
598
-- | A required node group name (for single-group LUs).
599
pGroupName :: Field
600
pGroupName = simpleField "group_name" [t| NonEmptyString |]
601

    
602
-- | Migration type (live\/non-live).
603
pMigrationMode :: Field
604
pMigrationMode =
605
  renameField "MigrationMode" .
606
  optionalField $
607
  simpleField "mode" [t| MigrationMode |]
608

    
609
-- | Obsolete \'live\' migration mode (boolean).
610
pMigrationLive :: Field
611
pMigrationLive =
612
  renameField "OldLiveMode" . optionalField $ booleanField "live"
613

    
614
-- | Migration cleanup parameter.
615
pMigrationCleanup :: Field
616
pMigrationCleanup = renameField "MigrationCleanup" $ defaultFalse "cleanup"
617

    
618
-- | Whether to force an unknown OS variant.
619
pForceVariant :: Field
620
pForceVariant = defaultFalse "force_variant"
621

    
622
-- | Whether to wait for the disk to synchronize.
623
pWaitForSync :: Field
624
pWaitForSync = defaultTrue "wait_for_sync"
625

    
626
-- | Whether to wait for the disk to synchronize (defaults to false).
627
pWaitForSyncFalse :: Field
628
pWaitForSyncFalse = defaultField [| False |] pWaitForSync
629

    
630
-- | Whether to ignore disk consistency
631
pIgnoreConsistency :: Field
632
pIgnoreConsistency = defaultFalse "ignore_consistency"
633

    
634
-- | Storage name.
635
pStorageName :: Field
636
pStorageName =
637
  renameField "StorageName" $ simpleField "name" [t| NonEmptyString |]
638

    
639
-- | Whether to use synchronization.
640
pUseLocking :: Field
641
pUseLocking = defaultFalse "use_locking"
642

    
643
-- | Whether to employ opportunistic locking for nodes, meaning nodes already
644
-- locked by another opcode won't be considered for instance allocation (only
645
-- when an iallocator is used).
646
pOpportunisticLocking :: Field
647
pOpportunisticLocking = defaultFalse "opportunistic_locking"
648

    
649
-- | Whether to check name.
650
pNameCheck :: Field
651
pNameCheck = defaultTrue "name_check"
652

    
653
-- | Instance allocation policy.
654
pNodeGroupAllocPolicy :: Field
655
pNodeGroupAllocPolicy = optionalField $
656
                        simpleField "alloc_policy" [t| AllocPolicy |]
657

    
658
-- | Default node parameters for group.
659
pGroupNodeParams :: Field
660
pGroupNodeParams = optionalField $ simpleField "ndparams" [t| UncheckedDict |]
661

    
662
-- | Resource(s) to query for.
663
pQueryWhat :: Field
664
pQueryWhat = simpleField "what" [t| Qlang.QueryTypeOp |]
665

    
666
-- | Whether to release locks as soon as possible.
667
pEarlyRelease :: Field
668
pEarlyRelease = defaultFalse "early_release"
669

    
670
-- | Whether to ensure instance's IP address is inactive.
671
pIpCheck :: Field
672
pIpCheck = defaultTrue "ip_check"
673

    
674
-- | Check for conflicting IPs.
675
pIpConflictsCheck :: Field
676
pIpConflictsCheck = defaultTrue "conflicts_check"
677

    
678
-- | Do not remember instance state changes.
679
pNoRemember :: Field
680
pNoRemember = defaultFalse "no_remember"
681

    
682
-- | Target node for instance migration/failover.
683
pMigrationTargetNode :: Field
684
pMigrationTargetNode = optionalNEStringField "target_node"
685

    
686
-- | Target node UUID for instance migration/failover.
687
pMigrationTargetNodeUuid :: Field
688
pMigrationTargetNodeUuid = optionalNEStringField "target_node_uuid"
689

    
690
-- | Target node for instance move (required).
691
pMoveTargetNode :: Field
692
pMoveTargetNode =
693
  renameField "MoveTargetNode" $
694
  simpleField "target_node" [t| NonEmptyString |]
695

    
696
-- | Target node UUID for instance move.
697
pMoveTargetNodeUuid :: Field
698
pMoveTargetNodeUuid =
699
  renameField "MoveTargetNodeUuid" . optionalField $
700
  simpleField "target_node_uuid" [t| NonEmptyString |]
701

    
702
-- | Pause instance at startup.
703
pStartupPaused :: Field
704
pStartupPaused = defaultFalse "startup_paused"
705

    
706
-- | Verbose mode.
707
pVerbose :: Field
708
pVerbose = defaultFalse "verbose"
709

    
710
-- ** Parameters for cluster verification
711

    
712
-- | Whether to simulate errors (useful for debugging).
713
pDebugSimulateErrors :: Field
714
pDebugSimulateErrors = defaultFalse "debug_simulate_errors"
715

    
716
-- | Error codes.
717
pErrorCodes :: Field
718
pErrorCodes = defaultFalse "error_codes"
719

    
720
-- | Which checks to skip.
721
pSkipChecks :: Field
722
pSkipChecks = defaultField [| Set.empty |] $
723
              simpleField "skip_checks" [t| Set.Set VerifyOptionalChecks |]
724

    
725
-- | List of error codes that should be treated as warnings.
726
pIgnoreErrors :: Field
727
pIgnoreErrors = defaultField [| Set.empty |] $
728
                simpleField "ignore_errors" [t| Set.Set CVErrorCode |]
729

    
730
-- | Optional group name.
731
pOptGroupName :: Field
732
pOptGroupName = renameField "OptGroupName" .
733
                optionalField $ simpleField "group_name" [t| NonEmptyString |]
734

    
735
-- | Disk templates' parameter defaults.
736
pDiskParams :: Field
737
pDiskParams = optionalField $
738
              simpleField "diskparams" [t| GenericContainer DiskTemplate
739
                                           UncheckedDict |]
740

    
741
-- * Parameters for node resource model
742

    
743
-- | Set hypervisor states.
744
pHvState :: Field
745
pHvState = optionalField $ simpleField "hv_state" [t| UncheckedDict |]
746

    
747
-- | Set disk states.
748
pDiskState :: Field
749
pDiskState = optionalField $ simpleField "disk_state" [t| UncheckedDict |]
750

    
751
-- | Whether to ignore ipolicy violations.
752
pIgnoreIpolicy :: Field
753
pIgnoreIpolicy = defaultFalse "ignore_ipolicy"
754

    
755
-- | Allow runtime changes while migrating.
756
pAllowRuntimeChgs :: Field
757
pAllowRuntimeChgs = defaultTrue "allow_runtime_changes"
758

    
759
-- | Utility type for OpClusterSetParams.
760
type TestClusterOsListItem = (DdmSimple, NonEmptyString)
761

    
762
-- | Utility type of OsList.
763
type TestClusterOsList = [TestClusterOsListItem]
764

    
765
-- Utility type for NIC definitions.
766
--type TestNicDef = INicParams
767

    
768
-- | List of instance disks.
769
pInstDisks :: Field
770
pInstDisks = renameField "instDisks" $ simpleField "disks" [t| [IDiskParams] |]
771

    
772
-- | Instance disk template.
773
pDiskTemplate :: Field
774
pDiskTemplate = simpleField "disk_template" [t| DiskTemplate |]
775

    
776
-- | Instance disk template.
777
pOptDiskTemplate :: Field
778
pOptDiskTemplate =
779
  optionalField .
780
  renameField "OptDiskTemplate" $
781
  simpleField "disk_template" [t| DiskTemplate |]
782

    
783
-- | File driver.
784
pFileDriver :: Field
785
pFileDriver = optionalField $ simpleField "file_driver" [t| FileDriver |]
786

    
787
-- | Directory for storing file-backed disks.
788
pFileStorageDir :: Field
789
pFileStorageDir = optionalNEStringField "file_storage_dir"
790

    
791
-- | Global directory for storing file-backed disks.
792
pGlobalFileStorageDir :: Field
793
pGlobalFileStorageDir = optionalNEStringField "file_storage_dir"
794

    
795
-- | Volume group name.
796
pVgName :: Field
797
pVgName = optionalStringField "vg_name"
798

    
799
-- | List of enabled hypervisors.
800
pEnabledHypervisors :: Field
801
pEnabledHypervisors =
802
  optionalField $
803
  simpleField "enabled_hypervisors" [t| NonEmpty Hypervisor |]
804

    
805
-- | List of enabled disk templates.
806
pEnabledDiskTemplates :: Field
807
pEnabledDiskTemplates =
808
  optionalField $
809
  simpleField "enabled_disk_templates" [t| NonEmpty DiskTemplate |]
810

    
811
-- | Selected hypervisor for an instance.
812
pHypervisor :: Field
813
pHypervisor =
814
  optionalField $
815
  simpleField "hypervisor" [t| Hypervisor |]
816

    
817
-- | Cluster-wide hypervisor parameters, hypervisor-dependent.
818
pClusterHvParams :: Field
819
pClusterHvParams =
820
  renameField "ClusterHvParams" .
821
  optionalField $
822
  simpleField "hvparams" [t| Container UncheckedDict |]
823

    
824
-- | Instance hypervisor parameters.
825
pInstHvParams :: Field
826
pInstHvParams =
827
  renameField "InstHvParams" .
828
  defaultField [| toJSObject [] |] $
829
  simpleField "hvparams" [t| UncheckedDict |]
830

    
831
-- | Cluster-wide beparams.
832
pClusterBeParams :: Field
833
pClusterBeParams =
834
  renameField "ClusterBeParams" .
835
  optionalField $ simpleField "beparams" [t| UncheckedDict |]
836

    
837
-- | Instance beparams.
838
pInstBeParams :: Field
839
pInstBeParams =
840
  renameField "InstBeParams" .
841
  defaultField [| toJSObject [] |] $
842
  simpleField "beparams" [t| UncheckedDict |]
843

    
844
-- | Reset instance parameters to default if equal.
845
pResetDefaults :: Field
846
pResetDefaults = defaultFalse "identify_defaults"
847

    
848
-- | Cluster-wide per-OS hypervisor parameter defaults.
849
pOsHvp :: Field
850
pOsHvp = optionalField $ simpleField "os_hvp" [t| Container UncheckedDict |]
851

    
852
-- | Cluster-wide OS parameter defaults.
853
pClusterOsParams :: Field
854
pClusterOsParams =
855
  renameField "ClusterOsParams" .
856
  optionalField $ simpleField "osparams" [t| Container UncheckedDict |]
857

    
858
-- | Instance OS parameters.
859
pInstOsParams :: Field
860
pInstOsParams =
861
  renameField "InstOsParams" . defaultField [| toJSObject [] |] $
862
  simpleField "osparams" [t| UncheckedDict |]
863

    
864
-- | Temporary OS parameters (currently only in reinstall, might be
865
-- added to install as well).
866
pTempOsParams :: Field
867
pTempOsParams =
868
  renameField "TempOsParams" .
869
  optionalField $ simpleField "osparams" [t| UncheckedDict |]
870

    
871
-- | Temporary hypervisor parameters, hypervisor-dependent.
872
pTempHvParams :: Field
873
pTempHvParams =
874
  renameField "TempHvParams" .
875
  defaultField [| toJSObject [] |] $
876
  simpleField "hvparams" [t| UncheckedDict |]
877

    
878
-- | Temporary backend parameters.
879
pTempBeParams :: Field
880
pTempBeParams =
881
  renameField "TempBeParams" .
882
  defaultField [| toJSObject [] |] $
883
  simpleField "beparams" [t| UncheckedDict |]
884

    
885
-- | Candidate pool size.
886
pCandidatePoolSize :: Field
887
pCandidatePoolSize =
888
  optionalField $ simpleField "candidate_pool_size" [t| Positive Int |]
889

    
890
-- | Set UID pool, must be list of lists describing UID ranges (two
891
-- items, start and end inclusive.
892
pUidPool :: Field
893
pUidPool = optionalField $ simpleField "uid_pool" [t| [[(Int, Int)]] |]
894

    
895
-- | Extend UID pool, must be list of lists describing UID ranges (two
896
-- items, start and end inclusive.
897
pAddUids :: Field
898
pAddUids = optionalField $ simpleField "add_uids" [t| [[(Int, Int)]] |]
899

    
900
-- | Shrink UID pool, must be list of lists describing UID ranges (two
901
-- items, start and end inclusive) to be removed.
902
pRemoveUids :: Field
903
pRemoveUids = optionalField $ simpleField "remove_uids" [t| [[(Int, Int)]] |]
904

    
905
-- | Whether to automatically maintain node health.
906
pMaintainNodeHealth :: Field
907
pMaintainNodeHealth = optionalField $ booleanField "maintain_node_health"
908

    
909
-- | Whether to modify and keep in sync the @/etc/hosts@ files of nodes.
910
pModifyEtcHosts :: Field
911
pModifyEtcHosts = optionalField $ booleanField "modify_etc_hosts"
912

    
913
-- | Whether to wipe disks before allocating them to instances.
914
pPreallocWipeDisks :: Field
915
pPreallocWipeDisks = optionalField $ booleanField "prealloc_wipe_disks"
916

    
917
-- | Cluster-wide NIC parameter defaults.
918
pNicParams :: Field
919
pNicParams = optionalField $ simpleField "nicparams" [t| INicParams |]
920

    
921
-- | Instance NIC definitions.
922
pInstNics :: Field
923
pInstNics = simpleField "nics" [t| [INicParams] |]
924

    
925
-- | Cluster-wide node parameter defaults.
926
pNdParams :: Field
927
pNdParams = optionalField $ simpleField "ndparams" [t| UncheckedDict |]
928

    
929
-- | Cluster-wide ipolicy specs.
930
pIpolicy :: Field
931
pIpolicy = optionalField $ simpleField "ipolicy" [t| UncheckedDict |]
932

    
933
-- | DRBD helper program.
934
pDrbdHelper :: Field
935
pDrbdHelper = optionalStringField "drbd_helper"
936

    
937
-- | Default iallocator for cluster.
938
pDefaultIAllocator :: Field
939
pDefaultIAllocator = optionalStringField "default_iallocator"
940

    
941
-- | Master network device.
942
pMasterNetdev :: Field
943
pMasterNetdev = optionalStringField "master_netdev"
944

    
945
-- | Netmask of the master IP.
946
pMasterNetmask :: Field
947
pMasterNetmask =
948
  optionalField $ simpleField "master_netmask" [t| NonNegative Int |]
949

    
950
-- | List of reserved LVs.
951
pReservedLvs :: Field
952
pReservedLvs =
953
  optionalField $ simpleField "reserved_lvs" [t| [NonEmptyString] |]
954

    
955
-- | Modify list of hidden operating systems: each modification must
956
-- have two items, the operation and the OS name; the operation can be
957
-- add or remove.
958
pHiddenOs :: Field
959
pHiddenOs = optionalField $ simpleField "hidden_os" [t| TestClusterOsList |]
960

    
961
-- | Modify list of blacklisted operating systems: each modification
962
-- must have two items, the operation and the OS name; the operation
963
-- can be add or remove.
964
pBlacklistedOs :: Field
965
pBlacklistedOs =
966
  optionalField $ simpleField "blacklisted_os" [t| TestClusterOsList |]
967

    
968
-- | Whether to use an external master IP address setup script.
969
pUseExternalMipScript :: Field
970
pUseExternalMipScript = optionalField $ booleanField "use_external_mip_script"
971

    
972
-- | Requested fields.
973
pQueryFields :: Field
974
pQueryFields = simpleField "fields" [t| [NonEmptyString] |]
975

    
976
-- | Query filter.
977
pQueryFilter :: Field
978
pQueryFilter = simpleField "qfilter" [t| Qlang.Filter String |]
979

    
980
-- | OOB command to run.
981
pOobCommand :: Field
982
pOobCommand = simpleField "command" [t| OobCommand |]
983

    
984
-- | Timeout before the OOB helper will be terminated.
985
pOobTimeout :: Field
986
pOobTimeout =
987
  defaultField [| C.oobTimeout |] $ simpleField "timeout" [t| Int |]
988

    
989
-- | Ignores the node offline status for power off.
990
pIgnoreStatus :: Field
991
pIgnoreStatus = defaultFalse "ignore_status"
992

    
993
-- | Time in seconds to wait between powering on nodes.
994
pPowerDelay :: Field
995
pPowerDelay =
996
  -- FIXME: we can't use the proper type "NonNegative Double", since
997
  -- the default constant is a plain Double, not a non-negative one.
998
  defaultField [| C.oobPowerDelay |] $
999
  simpleField "power_delay" [t| Double |]
1000

    
1001
-- | Primary IP address.
1002
pPrimaryIp :: Field
1003
pPrimaryIp = optionalStringField "primary_ip"
1004

    
1005
-- | Secondary IP address.
1006
pSecondaryIp :: Field
1007
pSecondaryIp = optionalNEStringField "secondary_ip"
1008

    
1009
-- | Whether node is re-added to cluster.
1010
pReadd :: Field
1011
pReadd = defaultFalse "readd"
1012

    
1013
-- | Initial node group.
1014
pNodeGroup :: Field
1015
pNodeGroup = optionalNEStringField "group"
1016

    
1017
-- | Whether node can become master or master candidate.
1018
pMasterCapable :: Field
1019
pMasterCapable = optionalField $ booleanField "master_capable"
1020

    
1021
-- | Whether node can host instances.
1022
pVmCapable :: Field
1023
pVmCapable = optionalField $ booleanField "vm_capable"
1024

    
1025
-- | List of names.
1026
pNames :: Field
1027
pNames = defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
1028

    
1029
-- | List of node names.
1030
pNodes :: Field
1031
pNodes = defaultField [| [] |] $ simpleField "nodes" [t| [NonEmptyString] |]
1032

    
1033
-- | Required list of node names.
1034
pRequiredNodes :: Field
1035
pRequiredNodes =
1036
  renameField "ReqNodes " $ simpleField "nodes" [t| [NonEmptyString] |]
1037

    
1038
-- | Required list of node names.
1039
pRequiredNodeUuids :: Field
1040
pRequiredNodeUuids =
1041
  renameField "ReqNodeUuids " . optionalField $
1042
    simpleField "node_uuids" [t| [NonEmptyString] |]
1043

    
1044
-- | Storage type.
1045
pStorageType :: Field
1046
pStorageType = simpleField "storage_type" [t| StorageType |]
1047

    
1048
-- | Storage changes (unchecked).
1049
pStorageChanges :: Field
1050
pStorageChanges = simpleField "changes" [t| UncheckedDict |]
1051

    
1052
-- | Whether the node should become a master candidate.
1053
pMasterCandidate :: Field
1054
pMasterCandidate = optionalField $ booleanField "master_candidate"
1055

    
1056
-- | Whether the node should be marked as offline.
1057
pOffline :: Field
1058
pOffline = optionalField $ booleanField "offline"
1059

    
1060
-- | Whether the node should be marked as drained.
1061
pDrained ::Field
1062
pDrained = optionalField $ booleanField "drained"
1063

    
1064
-- | Whether node(s) should be promoted to master candidate if necessary.
1065
pAutoPromote :: Field
1066
pAutoPromote = defaultFalse "auto_promote"
1067

    
1068
-- | Whether the node should be marked as powered
1069
pPowered :: Field
1070
pPowered = optionalField $ booleanField "powered"
1071

    
1072
-- | Iallocator for deciding the target node for shared-storage
1073
-- instances during migrate and failover.
1074
pIallocator :: Field
1075
pIallocator = optionalNEStringField "iallocator"
1076

    
1077
-- | New secondary node.
1078
pRemoteNode :: Field
1079
pRemoteNode = optionalNEStringField "remote_node"
1080

    
1081
-- | New secondary node UUID.
1082
pRemoteNodeUuid :: Field
1083
pRemoteNodeUuid = optionalNEStringField "remote_node_uuid"
1084

    
1085
-- | Node evacuation mode.
1086
pEvacMode :: Field
1087
pEvacMode = renameField "EvacMode" $ simpleField "mode" [t| NodeEvacMode |]
1088

    
1089
-- | Instance creation mode.
1090
pInstCreateMode :: Field
1091
pInstCreateMode =
1092
  renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
1093

    
1094
-- | Do not install the OS (will disable automatic start).
1095
pNoInstall :: Field
1096
pNoInstall = optionalField $ booleanField "no_install"
1097

    
1098
-- | OS type for instance installation.
1099
pInstOs :: Field
1100
pInstOs = optionalNEStringField "os_type"
1101

    
1102
-- | Primary node for an instance.
1103
pPrimaryNode :: Field
1104
pPrimaryNode = optionalNEStringField "pnode"
1105

    
1106
-- | Primary node UUID for an instance.
1107
pPrimaryNodeUuid :: Field
1108
pPrimaryNodeUuid = optionalNEStringField "pnode_uuid"
1109

    
1110
-- | Secondary node for an instance.
1111
pSecondaryNode :: Field
1112
pSecondaryNode = optionalNEStringField "snode"
1113

    
1114
-- | Secondary node UUID for an instance.
1115
pSecondaryNodeUuid :: Field
1116
pSecondaryNodeUuid = optionalNEStringField "snode_uuid"
1117

    
1118
-- | Signed handshake from source (remote import only).
1119
pSourceHandshake :: Field
1120
pSourceHandshake =
1121
  optionalField $ simpleField "source_handshake" [t| UncheckedList |]
1122

    
1123
-- | Source instance name (remote import only).
1124
pSourceInstance :: Field
1125
pSourceInstance = optionalNEStringField "source_instance_name"
1126

    
1127
-- | How long source instance was given to shut down (remote import only).
1128
-- FIXME: non-negative int, whereas the constant is a plain int.
1129
pSourceShutdownTimeout :: Field
1130
pSourceShutdownTimeout =
1131
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1132
  simpleField "source_shutdown_timeout" [t| NonNegative Int |]
1133

    
1134
-- | Source X509 CA in PEM format (remote import only).
1135
pSourceX509Ca :: Field
1136
pSourceX509Ca = optionalNEStringField "source_x509_ca"
1137

    
1138
-- | Source node for import.
1139
pSrcNode :: Field
1140
pSrcNode = optionalNEStringField "src_node"
1141

    
1142
-- | Source node for import.
1143
pSrcNodeUuid :: Field
1144
pSrcNodeUuid = optionalNEStringField "src_node_uuid"
1145

    
1146
-- | Source directory for import.
1147
pSrcPath :: Field
1148
pSrcPath = optionalNEStringField "src_path"
1149

    
1150
-- | Whether to start instance after creation.
1151
pStartInstance :: Field
1152
pStartInstance = defaultTrue "start"
1153

    
1154
-- | Instance tags. FIXME: unify/simplify with pTags, once that
1155
-- migrates to NonEmpty String.
1156
pInstTags :: Field
1157
pInstTags =
1158
  renameField "InstTags" .
1159
  defaultField [| [] |] $
1160
  simpleField "tags" [t| [NonEmptyString] |]
1161

    
1162
-- | Unchecked list of OpInstanceCreate, used in OpInstanceMultiAlloc.
1163
pMultiAllocInstances :: Field
1164
pMultiAllocInstances =
1165
  renameField "InstMultiAlloc" .
1166
  defaultField [| [] |] $
1167
  simpleField "instances"[t| UncheckedList |]
1168

    
1169
-- | Ignore failures parameter.
1170
pIgnoreFailures :: Field
1171
pIgnoreFailures = defaultFalse "ignore_failures"
1172

    
1173
-- | New instance or cluster name.
1174
pNewName :: Field
1175
pNewName = simpleField "new_name" [t| NonEmptyString |]
1176

    
1177
-- | Whether to start the instance even if secondary disks are failing.
1178
pIgnoreSecondaries :: Field
1179
pIgnoreSecondaries = defaultFalse "ignore_secondaries"
1180

    
1181
-- | How to reboot the instance.
1182
pRebootType :: Field
1183
pRebootType = simpleField "reboot_type" [t| RebootType |]
1184

    
1185
-- | Whether to ignore recorded disk size.
1186
pIgnoreDiskSize :: Field
1187
pIgnoreDiskSize = defaultFalse "ignore_size"
1188

    
1189
-- | Disk list for recreate disks.
1190
pRecreateDisksInfo :: Field
1191
pRecreateDisksInfo =
1192
  renameField "RecreateDisksInfo" .
1193
  defaultField [| RecreateDisksAll |] $
1194
  simpleField "disks" [t| RecreateDisksInfo |]
1195

    
1196
-- | Whether to only return configuration data without querying nodes.
1197
pStatic :: Field
1198
pStatic = defaultFalse "static"
1199

    
1200
-- | InstanceSetParams NIC changes.
1201
pInstParamsNicChanges :: Field
1202
pInstParamsNicChanges =
1203
  renameField "InstNicChanges" .
1204
  defaultField [| SetParamsEmpty |] $
1205
  simpleField "nics" [t| SetParamsMods INicParams |]
1206

    
1207
-- | InstanceSetParams Disk changes.
1208
pInstParamsDiskChanges :: Field
1209
pInstParamsDiskChanges =
1210
  renameField "InstDiskChanges" .
1211
  defaultField [| SetParamsEmpty |] $
1212
  simpleField "disks" [t| SetParamsMods IDiskParams |]
1213

    
1214
-- | New runtime memory.
1215
pRuntimeMem :: Field
1216
pRuntimeMem = optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1217

    
1218
-- | Change the instance's OS without reinstalling the instance
1219
pOsNameChange :: Field
1220
pOsNameChange = optionalNEStringField "os_name"
1221

    
1222
-- | Disk index for e.g. grow disk.
1223
pDiskIndex :: Field
1224
pDiskIndex = renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
1225

    
1226
-- | Disk amount to add or grow to.
1227
pDiskChgAmount :: Field
1228
pDiskChgAmount =
1229
  renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
1230

    
1231
-- | Whether the amount parameter is an absolute target or a relative one.
1232
pDiskChgAbsolute :: Field
1233
pDiskChgAbsolute = renameField "DiskChkAbsolute" $ defaultFalse "absolute"
1234

    
1235
-- | Destination group names or UUIDs (defaults to \"all but current group\".
1236
pTargetGroups :: Field
1237
pTargetGroups =
1238
  optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
1239

    
1240
-- | Export mode field.
1241
pExportMode :: Field
1242
pExportMode =
1243
  renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1244

    
1245
-- | Export target_node field, depends on mode.
1246
pExportTargetNode :: Field
1247
pExportTargetNode =
1248
  renameField "ExportTarget" $
1249
  simpleField "target_node" [t| ExportTarget |]
1250

    
1251
-- | Export target node UUID field.
1252
pExportTargetNodeUuid :: Field
1253
pExportTargetNodeUuid =
1254
  renameField "ExportTargetNodeUuid" . optionalField $
1255
  simpleField "target_node_uuid" [t| NonEmptyString |]
1256

    
1257
-- | Whether to remove instance after export.
1258
pRemoveInstance :: Field
1259
pRemoveInstance = defaultFalse "remove_instance"
1260

    
1261
-- | Whether to ignore failures while removing instances.
1262
pIgnoreRemoveFailures :: Field
1263
pIgnoreRemoveFailures = defaultFalse "ignore_remove_failures"
1264

    
1265
-- | Name of X509 key (remote export only).
1266
pX509KeyName :: Field
1267
pX509KeyName = optionalField $ simpleField "x509_key_name" [t| UncheckedList |]
1268

    
1269
-- | Destination X509 CA (remote export only).
1270
pX509DestCA :: Field
1271
pX509DestCA = optionalNEStringField "destination_x509_ca"
1272

    
1273
-- | Search pattern (regular expression). FIXME: this should be
1274
-- compiled at load time?
1275
pTagSearchPattern :: Field
1276
pTagSearchPattern =
1277
  renameField "TagSearchPattern" $ simpleField "pattern" [t| NonEmptyString |]
1278

    
1279
-- | Restricted command name.
1280
pRestrictedCommand :: Field
1281
pRestrictedCommand =
1282
  renameField "RestrictedCommand" $
1283
  simpleField "command" [t| NonEmptyString |]
1284

    
1285
-- | Replace disks mode.
1286
pReplaceDisksMode :: Field
1287
pReplaceDisksMode =
1288
  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1289

    
1290
-- | List of disk indices.
1291
pReplaceDisksList :: Field
1292
pReplaceDisksList =
1293
  renameField "ReplaceDisksList" $ simpleField "disks" [t| [DiskIndex] |]
1294

    
1295
-- | Whether do allow failover in migrations.
1296
pAllowFailover :: Field
1297
pAllowFailover = defaultFalse "allow_failover"
1298

    
1299
-- * Test opcode parameters
1300

    
1301
-- | Duration parameter for 'OpTestDelay'.
1302
pDelayDuration :: Field
1303
pDelayDuration =
1304
  renameField "DelayDuration" $ simpleField "duration" [t| Double |]
1305

    
1306
-- | on_master field for 'OpTestDelay'.
1307
pDelayOnMaster :: Field
1308
pDelayOnMaster = renameField "DelayOnMaster" $ defaultTrue "on_master"
1309

    
1310
-- | on_nodes field for 'OpTestDelay'.
1311
pDelayOnNodes :: Field
1312
pDelayOnNodes =
1313
  renameField "DelayOnNodes" .
1314
  defaultField [| [] |] $
1315
  simpleField "on_nodes" [t| [NonEmptyString] |]
1316

    
1317
-- | on_node_uuids field for 'OpTestDelay'.
1318
pDelayOnNodeUuids :: Field
1319
pDelayOnNodeUuids =
1320
  renameField "DelayOnNodeUuids" . optionalField $
1321
  simpleField "on_node_uuids" [t| [NonEmptyString] |]
1322

    
1323
-- | Repeat parameter for OpTestDelay.
1324
pDelayRepeat :: Field
1325
pDelayRepeat =
1326
  renameField "DelayRepeat" .
1327
  defaultField [| forceNonNeg (0::Int) |] $
1328
  simpleField "repeat" [t| NonNegative Int |]
1329

    
1330
-- | IAllocator test direction.
1331
pIAllocatorDirection :: Field
1332
pIAllocatorDirection =
1333
  renameField "IAllocatorDirection" $
1334
  simpleField "direction" [t| IAllocatorTestDir |]
1335

    
1336
-- | IAllocator test mode.
1337
pIAllocatorMode :: Field
1338
pIAllocatorMode =
1339
  renameField "IAllocatorMode" $
1340
  simpleField "mode" [t| IAllocatorMode |]
1341

    
1342
-- | IAllocator target name (new instance, node to evac, etc.).
1343
pIAllocatorReqName :: Field
1344
pIAllocatorReqName =
1345
  renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
1346

    
1347
-- | Custom OpTestIAllocator nics.
1348
pIAllocatorNics :: Field
1349
pIAllocatorNics =
1350
  renameField "IAllocatorNics" $ simpleField "nics" [t| [UncheckedDict] |]
1351

    
1352
-- | Custom OpTestAllocator disks.
1353
pIAllocatorDisks :: Field
1354
pIAllocatorDisks =
1355
  renameField "IAllocatorDisks" $ simpleField "disks" [t| UncheckedList |]
1356

    
1357
-- | IAllocator memory field.
1358
pIAllocatorMemory :: Field
1359
pIAllocatorMemory =
1360
  renameField "IAllocatorMem" .
1361
  optionalField $
1362
  simpleField "memory" [t| NonNegative Int |]
1363

    
1364
-- | IAllocator vcpus field.
1365
pIAllocatorVCpus :: Field
1366
pIAllocatorVCpus =
1367
  renameField "IAllocatorVCpus" .
1368
  optionalField $
1369
  simpleField "vcpus" [t| NonNegative Int |]
1370

    
1371
-- | IAllocator os field.
1372
pIAllocatorOs :: Field
1373
pIAllocatorOs = renameField "IAllocatorOs" $ optionalNEStringField "os"
1374

    
1375
-- | IAllocator instances field.
1376
pIAllocatorInstances :: Field
1377
pIAllocatorInstances =
1378
  renameField "IAllocatorInstances " .
1379
  optionalField $
1380
  simpleField "instances" [t| [NonEmptyString] |]
1381

    
1382
-- | IAllocator evac mode.
1383
pIAllocatorEvacMode :: Field
1384
pIAllocatorEvacMode =
1385
  renameField "IAllocatorEvacMode" .
1386
  optionalField $
1387
  simpleField "evac_mode" [t| NodeEvacMode |]
1388

    
1389
-- | IAllocator spindle use.
1390
pIAllocatorSpindleUse :: Field
1391
pIAllocatorSpindleUse =
1392
  renameField "IAllocatorSpindleUse" .
1393
  defaultField [| forceNonNeg (1::Int) |] $
1394
  simpleField "spindle_use" [t| NonNegative Int |]
1395

    
1396
-- | IAllocator count field.
1397
pIAllocatorCount :: Field
1398
pIAllocatorCount =
1399
  renameField "IAllocatorCount" .
1400
  defaultField [| forceNonNeg (1::Int) |] $
1401
  simpleField "count" [t| NonNegative Int |]
1402

    
1403
-- | 'OpTestJqueue' notify_waitlock.
1404
pJQueueNotifyWaitLock :: Field
1405
pJQueueNotifyWaitLock = defaultFalse "notify_waitlock"
1406

    
1407
-- | 'OpTestJQueue' notify_exec.
1408
pJQueueNotifyExec :: Field
1409
pJQueueNotifyExec = defaultFalse "notify_exec"
1410

    
1411
-- | 'OpTestJQueue' log_messages.
1412
pJQueueLogMessages :: Field
1413
pJQueueLogMessages =
1414
  defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
1415

    
1416
-- | 'OpTestJQueue' fail attribute.
1417
pJQueueFail :: Field
1418
pJQueueFail =
1419
  renameField "JQueueFail" $ defaultFalse "fail"
1420

    
1421
-- | 'OpTestDummy' result field.
1422
pTestDummyResult :: Field
1423
pTestDummyResult =
1424
  renameField "TestDummyResult" $ simpleField "result" [t| UncheckedValue |]
1425

    
1426
-- | 'OpTestDummy' messages field.
1427
pTestDummyMessages :: Field
1428
pTestDummyMessages =
1429
  renameField "TestDummyMessages" $
1430
  simpleField "messages" [t| UncheckedValue |]
1431

    
1432
-- | 'OpTestDummy' fail field.
1433
pTestDummyFail :: Field
1434
pTestDummyFail =
1435
  renameField "TestDummyFail" $ simpleField "fail" [t| UncheckedValue |]
1436

    
1437
-- | 'OpTestDummy' submit_jobs field.
1438
pTestDummySubmitJobs :: Field
1439
pTestDummySubmitJobs =
1440
  renameField "TestDummySubmitJobs" $
1441
  simpleField "submit_jobs" [t| UncheckedValue |]
1442

    
1443
-- * Network parameters
1444

    
1445
-- | Network name.
1446
pNetworkName :: Field
1447
pNetworkName = simpleField "network_name" [t| NonEmptyString |]
1448

    
1449
-- | Network address (IPv4 subnet). FIXME: no real type for this.
1450
pNetworkAddress4 :: Field
1451
pNetworkAddress4 =
1452
  renameField "NetworkAddress4" $
1453
  simpleField "network" [t| NonEmptyString |]
1454

    
1455
-- | Network gateway (IPv4 address). FIXME: no real type for this.
1456
pNetworkGateway4 :: Field
1457
pNetworkGateway4 =
1458
  renameField "NetworkGateway4" $
1459
  optionalNEStringField "gateway"
1460

    
1461
-- | Network address (IPv6 subnet). FIXME: no real type for this.
1462
pNetworkAddress6 :: Field
1463
pNetworkAddress6 =
1464
  renameField "NetworkAddress6" $
1465
  optionalNEStringField "network6"
1466

    
1467
-- | Network gateway (IPv6 address). FIXME: no real type for this.
1468
pNetworkGateway6 :: Field
1469
pNetworkGateway6 =
1470
  renameField "NetworkGateway6" $
1471
  optionalNEStringField "gateway6"
1472

    
1473
-- | Network specific mac prefix (that overrides the cluster one).
1474
pNetworkMacPrefix :: Field
1475
pNetworkMacPrefix =
1476
  renameField "NetMacPrefix" $
1477
  optionalNEStringField "mac_prefix"
1478

    
1479
-- | Network add reserved IPs.
1480
pNetworkAddRsvdIps :: Field
1481
pNetworkAddRsvdIps =
1482
  renameField "NetworkAddRsvdIps" .
1483
  optionalField $
1484
  simpleField "add_reserved_ips" [t| [NonEmptyString] |]
1485

    
1486
-- | Network remove reserved IPs.
1487
pNetworkRemoveRsvdIps :: Field
1488
pNetworkRemoveRsvdIps =
1489
  renameField "NetworkRemoveRsvdIps" .
1490
  optionalField $
1491
  simpleField "remove_reserved_ips" [t| [NonEmptyString] |]
1492

    
1493
-- | Network mode when connecting to a group.
1494
pNetworkMode :: Field
1495
pNetworkMode = simpleField "network_mode" [t| NICMode |]
1496

    
1497
-- | Network link when connecting to a group.
1498
pNetworkLink :: Field
1499
pNetworkLink = simpleField "network_link" [t| NonEmptyString |]
1500

    
1501
-- * Common opcode parameters
1502

    
1503
-- | Run checks only, don't execute.
1504
pDryRun :: Field
1505
pDryRun = optionalField $ booleanField "dry_run"
1506

    
1507
-- | Debug level.
1508
pDebugLevel :: Field
1509
pDebugLevel = optionalField $ simpleField "debug_level" [t| NonNegative Int |]
1510

    
1511
-- | Opcode priority. Note: python uses a separate constant, we're
1512
-- using the actual value we know it's the default.
1513
pOpPriority :: Field
1514
pOpPriority =
1515
  defaultField [| OpPrioNormal |] $
1516
  simpleField "priority" [t| OpSubmitPriority |]
1517

    
1518
-- | Job dependencies.
1519
pDependencies :: Field
1520
pDependencies =
1521
  optionalNullSerField $ simpleField "depends" [t| [JobDependency] |]
1522

    
1523
-- | Comment field.
1524
pComment :: Field
1525
pComment = optionalNullSerField $ stringField "comment"
1526

    
1527
-- | Reason trail field.
1528
pReason :: Field
1529
pReason = simpleField C.opcodeReason [t| ReasonTrail |]
1530

    
1531
-- * Entire opcode parameter list
1532

    
1533
-- | Old-style query opcode, with locking.
1534
dOldQuery :: [Field]
1535
dOldQuery =
1536
  [ pOutputFields
1537
  , pNames
1538
  , pUseLocking
1539
  ]
1540

    
1541
-- | Old-style query opcode, without locking.
1542
dOldQueryNoLocking :: [Field]
1543
dOldQueryNoLocking =
1544
  [ pOutputFields
1545
  , pNames
1546
  ]