Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ 95c0c0bc

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
  , pHotplug
103
  , pAllowRuntimeChgs
104
  , pInstDisks
105
  , pDiskTemplate
106
  , pOptDiskTemplate
107
  , pFileDriver
108
  , pFileStorageDir
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
  , optionalField $ simpleField C.inicVlan [t| NonEmptyString |]
422
  ])
423

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

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

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

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

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

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

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

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

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

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

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

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

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

    
523
-- * Parameters
524

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
711
-- ** Parameters for cluster verification
712

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

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

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

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

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

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

    
742
-- * Parameters for node resource model
743

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

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

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

    
756
-- | Whether to hotplug device.
757
pHotplug :: Field
758
pHotplug = defaultFalse "hotplug"
759

    
760
-- | Allow runtime changes while migrating.
761
pAllowRuntimeChgs :: Field
762
pAllowRuntimeChgs = defaultTrue "allow_runtime_changes"
763

    
764
-- | Utility type for OpClusterSetParams.
765
type TestClusterOsListItem = (DdmSimple, NonEmptyString)
766

    
767
-- | Utility type of OsList.
768
type TestClusterOsList = [TestClusterOsListItem]
769

    
770
-- Utility type for NIC definitions.
771
--type TestNicDef = INicParams
772

    
773
-- | List of instance disks.
774
pInstDisks :: Field
775
pInstDisks = renameField "instDisks" $ simpleField "disks" [t| [IDiskParams] |]
776

    
777
-- | Instance disk template.
778
pDiskTemplate :: Field
779
pDiskTemplate = simpleField "disk_template" [t| DiskTemplate |]
780

    
781
-- | Instance disk template.
782
pOptDiskTemplate :: Field
783
pOptDiskTemplate =
784
  optionalField .
785
  renameField "OptDiskTemplate" $
786
  simpleField "disk_template" [t| DiskTemplate |]
787

    
788
-- | File driver.
789
pFileDriver :: Field
790
pFileDriver = optionalField $ simpleField "file_driver" [t| FileDriver |]
791

    
792
-- | Directory for storing file-backed disks.
793
pFileStorageDir :: Field
794
pFileStorageDir = optionalNEStringField "file_storage_dir"
795

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
1300
-- * Test opcode parameters
1301

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
1444
-- * Network parameters
1445

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

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

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

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

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

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

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

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

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

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

    
1502
-- * Common opcode parameters
1503

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

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

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

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

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

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

    
1532
-- * Entire opcode parameter list
1533

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

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