Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ 7002d873

History | View | Annotate | Download (44.8 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
  , pPreallocWipeDisks
126
  , pNicParams
127
  , pInstNics
128
  , pNdParams
129
  , pIpolicy
130
  , pDrbdHelper
131
  , pDefaultIAllocator
132
  , pMasterNetdev
133
  , pMasterNetmask
134
  , pReservedLvs
135
  , pHiddenOs
136
  , pBlacklistedOs
137
  , pUseExternalMipScript
138
  , pQueryFields
139
  , pQueryFilter
140
  , pOobCommand
141
  , pOobTimeout
142
  , pIgnoreStatus
143
  , pPowerDelay
144
  , pPrimaryIp
145
  , pSecondaryIp
146
  , pReadd
147
  , pNodeGroup
148
  , pMasterCapable
149
  , pVmCapable
150
  , pNames
151
  , pNodes
152
  , pRequiredNodes
153
  , pRequiredNodeUuids
154
  , pStorageType
155
  , pStorageChanges
156
  , pMasterCandidate
157
  , pOffline
158
  , pDrained
159
  , pAutoPromote
160
  , pPowered
161
  , pIallocator
162
  , pRemoteNode
163
  , pRemoteNodeUuid
164
  , pEvacMode
165
  , pInstCreateMode
166
  , pNoInstall
167
  , pInstOs
168
  , pPrimaryNode
169
  , pPrimaryNodeUuid
170
  , pSecondaryNode
171
  , pSecondaryNodeUuid
172
  , pSourceHandshake
173
  , pSourceInstance
174
  , pSourceShutdownTimeout
175
  , pSourceX509Ca
176
  , pSrcNode
177
  , pSrcNodeUuid
178
  , pSrcPath
179
  , pStartInstance
180
  , pInstTags
181
  , pMultiAllocInstances
182
  , pTempOsParams
183
  , pTempHvParams
184
  , pTempBeParams
185
  , pIgnoreFailures
186
  , pNewName
187
  , pIgnoreSecondaries
188
  , pRebootType
189
  , pIgnoreDiskSize
190
  , pRecreateDisksInfo
191
  , pStatic
192
  , pInstParamsNicChanges
193
  , pInstParamsDiskChanges
194
  , pRuntimeMem
195
  , pOsNameChange
196
  , pDiskIndex
197
  , pDiskChgAmount
198
  , pDiskChgAbsolute
199
  , pTargetGroups
200
  , pExportMode
201
  , pExportTargetNode
202
  , pExportTargetNodeUuid
203
  , pRemoveInstance
204
  , pIgnoreRemoveFailures
205
  , pX509KeyName
206
  , pX509DestCA
207
  , pTagSearchPattern
208
  , pRestrictedCommand
209
  , pReplaceDisksMode
210
  , pReplaceDisksList
211
  , pAllowFailover
212
  , pDelayDuration
213
  , pDelayOnMaster
214
  , pDelayOnNodes
215
  , pDelayOnNodeUuids
216
  , pDelayRepeat
217
  , pIAllocatorDirection
218
  , pIAllocatorMode
219
  , pIAllocatorReqName
220
  , pIAllocatorNics
221
  , pIAllocatorDisks
222
  , pIAllocatorMemory
223
  , pIAllocatorVCpus
224
  , pIAllocatorOs
225
  , pIAllocatorInstances
226
  , pIAllocatorEvacMode
227
  , pIAllocatorSpindleUse
228
  , pIAllocatorCount
229
  , pJQueueNotifyWaitLock
230
  , pJQueueNotifyExec
231
  , pJQueueLogMessages
232
  , pJQueueFail
233
  , pTestDummyResult
234
  , pTestDummyMessages
235
  , pTestDummyFail
236
  , pTestDummySubmitJobs
237
  , pNetworkName
238
  , pNetworkAddress4
239
  , pNetworkGateway4
240
  , pNetworkAddress6
241
  , pNetworkGateway6
242
  , pNetworkMacPrefix
243
  , pNetworkAddRsvdIps
244
  , pNetworkRemoveRsvdIps
245
  , pNetworkMode
246
  , pNetworkLink
247
  , pDryRun
248
  , pDebugLevel
249
  , pOpPriority
250
  , pDependencies
251
  , pComment
252
  , pReason
253
  , pEnabledDiskTemplates
254
  , dOldQuery
255
  , dOldQueryNoLocking
256
  ) where
257

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

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

    
272
-- * Helper functions and types
273

    
274
-- * Type aliases
275

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

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

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

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

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

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

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

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

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

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

    
318
-- ** Tags
319

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

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

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

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

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

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

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

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

    
377
-- ** Disks
378

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

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

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

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

    
404
-- ** I* param types
405

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
521
-- * Parameters
522

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
709
-- ** Parameters for cluster verification
710

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

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

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

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

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

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

    
740
-- * Parameters for node resource model
741

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

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

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

    
754
-- | Whether to hotplug device.
755
pHotplug :: Field
756
pHotplug = defaultFalse "hotplug"
757

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

    
762
-- | Utility type for OpClusterSetParams.
763
type TestClusterOsListItem = (DdmSimple, NonEmptyString)
764

    
765
-- | Utility type of OsList.
766
type TestClusterOsList = [TestClusterOsListItem]
767

    
768
-- Utility type for NIC definitions.
769
--type TestNicDef = INicParams
770

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
908
-- | Whether to wipe disks before allocating them to instances.
909
pPreallocWipeDisks :: Field
910
pPreallocWipeDisks = optionalField $ booleanField "prealloc_wipe_disks"
911

    
912
-- | Cluster-wide NIC parameter defaults.
913
pNicParams :: Field
914
pNicParams = optionalField $ simpleField "nicparams" [t| INicParams |]
915

    
916
-- | Instance NIC definitions.
917
pInstNics :: Field
918
pInstNics = simpleField "nics" [t| [INicParams] |]
919

    
920
-- | Cluster-wide node parameter defaults.
921
pNdParams :: Field
922
pNdParams = optionalField $ simpleField "ndparams" [t| UncheckedDict |]
923

    
924
-- | Cluster-wide ipolicy specs.
925
pIpolicy :: Field
926
pIpolicy = optionalField $ simpleField "ipolicy" [t| UncheckedDict |]
927

    
928
-- | DRBD helper program.
929
pDrbdHelper :: Field
930
pDrbdHelper = optionalStringField "drbd_helper"
931

    
932
-- | Default iallocator for cluster.
933
pDefaultIAllocator :: Field
934
pDefaultIAllocator = optionalStringField "default_iallocator"
935

    
936
-- | Master network device.
937
pMasterNetdev :: Field
938
pMasterNetdev = optionalStringField "master_netdev"
939

    
940
-- | Netmask of the master IP.
941
pMasterNetmask :: Field
942
pMasterNetmask =
943
  optionalField $ simpleField "master_netmask" [t| NonNegative Int |]
944

    
945
-- | List of reserved LVs.
946
pReservedLvs :: Field
947
pReservedLvs =
948
  optionalField $ simpleField "reserved_lvs" [t| [NonEmptyString] |]
949

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

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

    
963
-- | Whether to use an external master IP address setup script.
964
pUseExternalMipScript :: Field
965
pUseExternalMipScript = optionalField $ booleanField "use_external_mip_script"
966

    
967
-- | Requested fields.
968
pQueryFields :: Field
969
pQueryFields = simpleField "fields" [t| [NonEmptyString] |]
970

    
971
-- | Query filter.
972
pQueryFilter :: Field
973
pQueryFilter = simpleField "qfilter" [t| Qlang.Filter String |]
974

    
975
-- | OOB command to run.
976
pOobCommand :: Field
977
pOobCommand = simpleField "command" [t| OobCommand |]
978

    
979
-- | Timeout before the OOB helper will be terminated.
980
pOobTimeout :: Field
981
pOobTimeout =
982
  defaultField [| C.oobTimeout |] $ simpleField "timeout" [t| Int |]
983

    
984
-- | Ignores the node offline status for power off.
985
pIgnoreStatus :: Field
986
pIgnoreStatus = defaultFalse "ignore_status"
987

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

    
996
-- | Primary IP address.
997
pPrimaryIp :: Field
998
pPrimaryIp = optionalStringField "primary_ip"
999

    
1000
-- | Secondary IP address.
1001
pSecondaryIp :: Field
1002
pSecondaryIp = optionalNEStringField "secondary_ip"
1003

    
1004
-- | Whether node is re-added to cluster.
1005
pReadd :: Field
1006
pReadd = defaultFalse "readd"
1007

    
1008
-- | Initial node group.
1009
pNodeGroup :: Field
1010
pNodeGroup = optionalNEStringField "group"
1011

    
1012
-- | Whether node can become master or master candidate.
1013
pMasterCapable :: Field
1014
pMasterCapable = optionalField $ booleanField "master_capable"
1015

    
1016
-- | Whether node can host instances.
1017
pVmCapable :: Field
1018
pVmCapable = optionalField $ booleanField "vm_capable"
1019

    
1020
-- | List of names.
1021
pNames :: Field
1022
pNames = defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
1023

    
1024
-- | List of node names.
1025
pNodes :: Field
1026
pNodes = defaultField [| [] |] $ simpleField "nodes" [t| [NonEmptyString] |]
1027

    
1028
-- | Required list of node names.
1029
pRequiredNodes :: Field
1030
pRequiredNodes =
1031
  renameField "ReqNodes " $ simpleField "nodes" [t| [NonEmptyString] |]
1032

    
1033
-- | Required list of node names.
1034
pRequiredNodeUuids :: Field
1035
pRequiredNodeUuids =
1036
  renameField "ReqNodeUuids " . optionalField $
1037
    simpleField "node_uuids" [t| [NonEmptyString] |]
1038

    
1039
-- | Storage type.
1040
pStorageType :: Field
1041
pStorageType = simpleField "storage_type" [t| StorageType |]
1042

    
1043
-- | Storage changes (unchecked).
1044
pStorageChanges :: Field
1045
pStorageChanges = simpleField "changes" [t| UncheckedDict |]
1046

    
1047
-- | Whether the node should become a master candidate.
1048
pMasterCandidate :: Field
1049
pMasterCandidate = optionalField $ booleanField "master_candidate"
1050

    
1051
-- | Whether the node should be marked as offline.
1052
pOffline :: Field
1053
pOffline = optionalField $ booleanField "offline"
1054

    
1055
-- | Whether the node should be marked as drained.
1056
pDrained ::Field
1057
pDrained = optionalField $ booleanField "drained"
1058

    
1059
-- | Whether node(s) should be promoted to master candidate if necessary.
1060
pAutoPromote :: Field
1061
pAutoPromote = defaultFalse "auto_promote"
1062

    
1063
-- | Whether the node should be marked as powered
1064
pPowered :: Field
1065
pPowered = optionalField $ booleanField "powered"
1066

    
1067
-- | Iallocator for deciding the target node for shared-storage
1068
-- instances during migrate and failover.
1069
pIallocator :: Field
1070
pIallocator = optionalNEStringField "iallocator"
1071

    
1072
-- | New secondary node.
1073
pRemoteNode :: Field
1074
pRemoteNode = optionalNEStringField "remote_node"
1075

    
1076
-- | New secondary node UUID.
1077
pRemoteNodeUuid :: Field
1078
pRemoteNodeUuid = optionalNEStringField "remote_node_uuid"
1079

    
1080
-- | Node evacuation mode.
1081
pEvacMode :: Field
1082
pEvacMode = renameField "EvacMode" $ simpleField "mode" [t| NodeEvacMode |]
1083

    
1084
-- | Instance creation mode.
1085
pInstCreateMode :: Field
1086
pInstCreateMode =
1087
  renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
1088

    
1089
-- | Do not install the OS (will disable automatic start).
1090
pNoInstall :: Field
1091
pNoInstall = optionalField $ booleanField "no_install"
1092

    
1093
-- | OS type for instance installation.
1094
pInstOs :: Field
1095
pInstOs = optionalNEStringField "os_type"
1096

    
1097
-- | Primary node for an instance.
1098
pPrimaryNode :: Field
1099
pPrimaryNode = optionalNEStringField "pnode"
1100

    
1101
-- | Primary node UUID for an instance.
1102
pPrimaryNodeUuid :: Field
1103
pPrimaryNodeUuid = optionalNEStringField "pnode_uuid"
1104

    
1105
-- | Secondary node for an instance.
1106
pSecondaryNode :: Field
1107
pSecondaryNode = optionalNEStringField "snode"
1108

    
1109
-- | Secondary node UUID for an instance.
1110
pSecondaryNodeUuid :: Field
1111
pSecondaryNodeUuid = optionalNEStringField "snode_uuid"
1112

    
1113
-- | Signed handshake from source (remote import only).
1114
pSourceHandshake :: Field
1115
pSourceHandshake =
1116
  optionalField $ simpleField "source_handshake" [t| UncheckedList |]
1117

    
1118
-- | Source instance name (remote import only).
1119
pSourceInstance :: Field
1120
pSourceInstance = optionalNEStringField "source_instance_name"
1121

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

    
1129
-- | Source X509 CA in PEM format (remote import only).
1130
pSourceX509Ca :: Field
1131
pSourceX509Ca = optionalNEStringField "source_x509_ca"
1132

    
1133
-- | Source node for import.
1134
pSrcNode :: Field
1135
pSrcNode = optionalNEStringField "src_node"
1136

    
1137
-- | Source node for import.
1138
pSrcNodeUuid :: Field
1139
pSrcNodeUuid = optionalNEStringField "src_node_uuid"
1140

    
1141
-- | Source directory for import.
1142
pSrcPath :: Field
1143
pSrcPath = optionalNEStringField "src_path"
1144

    
1145
-- | Whether to start instance after creation.
1146
pStartInstance :: Field
1147
pStartInstance = defaultTrue "start"
1148

    
1149
-- | Instance tags. FIXME: unify/simplify with pTags, once that
1150
-- migrates to NonEmpty String.
1151
pInstTags :: Field
1152
pInstTags =
1153
  renameField "InstTags" .
1154
  defaultField [| [] |] $
1155
  simpleField "tags" [t| [NonEmptyString] |]
1156

    
1157
-- | Unchecked list of OpInstanceCreate, used in OpInstanceMultiAlloc.
1158
pMultiAllocInstances :: Field
1159
pMultiAllocInstances =
1160
  renameField "InstMultiAlloc" .
1161
  defaultField [| [] |] $
1162
  simpleField "instances"[t| UncheckedList |]
1163

    
1164
-- | Ignore failures parameter.
1165
pIgnoreFailures :: Field
1166
pIgnoreFailures = defaultFalse "ignore_failures"
1167

    
1168
-- | New instance or cluster name.
1169
pNewName :: Field
1170
pNewName = simpleField "new_name" [t| NonEmptyString |]
1171

    
1172
-- | Whether to start the instance even if secondary disks are failing.
1173
pIgnoreSecondaries :: Field
1174
pIgnoreSecondaries = defaultFalse "ignore_secondaries"
1175

    
1176
-- | How to reboot the instance.
1177
pRebootType :: Field
1178
pRebootType = simpleField "reboot_type" [t| RebootType |]
1179

    
1180
-- | Whether to ignore recorded disk size.
1181
pIgnoreDiskSize :: Field
1182
pIgnoreDiskSize = defaultFalse "ignore_size"
1183

    
1184
-- | Disk list for recreate disks.
1185
pRecreateDisksInfo :: Field
1186
pRecreateDisksInfo =
1187
  renameField "RecreateDisksInfo" .
1188
  defaultField [| RecreateDisksAll |] $
1189
  simpleField "disks" [t| RecreateDisksInfo |]
1190

    
1191
-- | Whether to only return configuration data without querying nodes.
1192
pStatic :: Field
1193
pStatic = defaultFalse "static"
1194

    
1195
-- | InstanceSetParams NIC changes.
1196
pInstParamsNicChanges :: Field
1197
pInstParamsNicChanges =
1198
  renameField "InstNicChanges" .
1199
  defaultField [| SetParamsEmpty |] $
1200
  simpleField "nics" [t| SetParamsMods INicParams |]
1201

    
1202
-- | InstanceSetParams Disk changes.
1203
pInstParamsDiskChanges :: Field
1204
pInstParamsDiskChanges =
1205
  renameField "InstDiskChanges" .
1206
  defaultField [| SetParamsEmpty |] $
1207
  simpleField "disks" [t| SetParamsMods IDiskParams |]
1208

    
1209
-- | New runtime memory.
1210
pRuntimeMem :: Field
1211
pRuntimeMem = optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1212

    
1213
-- | Change the instance's OS without reinstalling the instance
1214
pOsNameChange :: Field
1215
pOsNameChange = optionalNEStringField "os_name"
1216

    
1217
-- | Disk index for e.g. grow disk.
1218
pDiskIndex :: Field
1219
pDiskIndex = renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
1220

    
1221
-- | Disk amount to add or grow to.
1222
pDiskChgAmount :: Field
1223
pDiskChgAmount =
1224
  renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
1225

    
1226
-- | Whether the amount parameter is an absolute target or a relative one.
1227
pDiskChgAbsolute :: Field
1228
pDiskChgAbsolute = renameField "DiskChkAbsolute" $ defaultFalse "absolute"
1229

    
1230
-- | Destination group names or UUIDs (defaults to \"all but current group\".
1231
pTargetGroups :: Field
1232
pTargetGroups =
1233
  optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
1234

    
1235
-- | Export mode field.
1236
pExportMode :: Field
1237
pExportMode =
1238
  renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1239

    
1240
-- | Export target_node field, depends on mode.
1241
pExportTargetNode :: Field
1242
pExportTargetNode =
1243
  renameField "ExportTarget" $
1244
  simpleField "target_node" [t| ExportTarget |]
1245

    
1246
-- | Export target node UUID field.
1247
pExportTargetNodeUuid :: Field
1248
pExportTargetNodeUuid =
1249
  renameField "ExportTargetNodeUuid" . optionalField $
1250
  simpleField "target_node_uuid" [t| NonEmptyString |]
1251

    
1252
-- | Whether to remove instance after export.
1253
pRemoveInstance :: Field
1254
pRemoveInstance = defaultFalse "remove_instance"
1255

    
1256
-- | Whether to ignore failures while removing instances.
1257
pIgnoreRemoveFailures :: Field
1258
pIgnoreRemoveFailures = defaultFalse "ignore_remove_failures"
1259

    
1260
-- | Name of X509 key (remote export only).
1261
pX509KeyName :: Field
1262
pX509KeyName = optionalField $ simpleField "x509_key_name" [t| UncheckedList |]
1263

    
1264
-- | Destination X509 CA (remote export only).
1265
pX509DestCA :: Field
1266
pX509DestCA = optionalNEStringField "destination_x509_ca"
1267

    
1268
-- | Search pattern (regular expression). FIXME: this should be
1269
-- compiled at load time?
1270
pTagSearchPattern :: Field
1271
pTagSearchPattern =
1272
  renameField "TagSearchPattern" $ simpleField "pattern" [t| NonEmptyString |]
1273

    
1274
-- | Restricted command name.
1275
pRestrictedCommand :: Field
1276
pRestrictedCommand =
1277
  renameField "RestrictedCommand" $
1278
  simpleField "command" [t| NonEmptyString |]
1279

    
1280
-- | Replace disks mode.
1281
pReplaceDisksMode :: Field
1282
pReplaceDisksMode =
1283
  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1284

    
1285
-- | List of disk indices.
1286
pReplaceDisksList :: Field
1287
pReplaceDisksList =
1288
  renameField "ReplaceDisksList" $ simpleField "disks" [t| [DiskIndex] |]
1289

    
1290
-- | Whether do allow failover in migrations.
1291
pAllowFailover :: Field
1292
pAllowFailover = defaultFalse "allow_failover"
1293

    
1294
-- * Test opcode parameters
1295

    
1296
-- | Duration parameter for 'OpTestDelay'.
1297
pDelayDuration :: Field
1298
pDelayDuration =
1299
  renameField "DelayDuration" $ simpleField "duration" [t| Double |]
1300

    
1301
-- | on_master field for 'OpTestDelay'.
1302
pDelayOnMaster :: Field
1303
pDelayOnMaster = renameField "DelayOnMaster" $ defaultTrue "on_master"
1304

    
1305
-- | on_nodes field for 'OpTestDelay'.
1306
pDelayOnNodes :: Field
1307
pDelayOnNodes =
1308
  renameField "DelayOnNodes" .
1309
  defaultField [| [] |] $
1310
  simpleField "on_nodes" [t| [NonEmptyString] |]
1311

    
1312
-- | on_node_uuids field for 'OpTestDelay'.
1313
pDelayOnNodeUuids :: Field
1314
pDelayOnNodeUuids =
1315
  renameField "DelayOnNodeUuids" . optionalField $
1316
  simpleField "on_node_uuids" [t| [NonEmptyString] |]
1317

    
1318
-- | Repeat parameter for OpTestDelay.
1319
pDelayRepeat :: Field
1320
pDelayRepeat =
1321
  renameField "DelayRepeat" .
1322
  defaultField [| forceNonNeg (0::Int) |] $
1323
  simpleField "repeat" [t| NonNegative Int |]
1324

    
1325
-- | IAllocator test direction.
1326
pIAllocatorDirection :: Field
1327
pIAllocatorDirection =
1328
  renameField "IAllocatorDirection" $
1329
  simpleField "direction" [t| IAllocatorTestDir |]
1330

    
1331
-- | IAllocator test mode.
1332
pIAllocatorMode :: Field
1333
pIAllocatorMode =
1334
  renameField "IAllocatorMode" $
1335
  simpleField "mode" [t| IAllocatorMode |]
1336

    
1337
-- | IAllocator target name (new instance, node to evac, etc.).
1338
pIAllocatorReqName :: Field
1339
pIAllocatorReqName =
1340
  renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
1341

    
1342
-- | Custom OpTestIAllocator nics.
1343
pIAllocatorNics :: Field
1344
pIAllocatorNics =
1345
  renameField "IAllocatorNics" $ simpleField "nics" [t| [UncheckedDict] |]
1346

    
1347
-- | Custom OpTestAllocator disks.
1348
pIAllocatorDisks :: Field
1349
pIAllocatorDisks =
1350
  renameField "IAllocatorDisks" $ simpleField "disks" [t| UncheckedList |]
1351

    
1352
-- | IAllocator memory field.
1353
pIAllocatorMemory :: Field
1354
pIAllocatorMemory =
1355
  renameField "IAllocatorMem" .
1356
  optionalField $
1357
  simpleField "memory" [t| NonNegative Int |]
1358

    
1359
-- | IAllocator vcpus field.
1360
pIAllocatorVCpus :: Field
1361
pIAllocatorVCpus =
1362
  renameField "IAllocatorVCpus" .
1363
  optionalField $
1364
  simpleField "vcpus" [t| NonNegative Int |]
1365

    
1366
-- | IAllocator os field.
1367
pIAllocatorOs :: Field
1368
pIAllocatorOs = renameField "IAllocatorOs" $ optionalNEStringField "os"
1369

    
1370
-- | IAllocator instances field.
1371
pIAllocatorInstances :: Field
1372
pIAllocatorInstances =
1373
  renameField "IAllocatorInstances " .
1374
  optionalField $
1375
  simpleField "instances" [t| [NonEmptyString] |]
1376

    
1377
-- | IAllocator evac mode.
1378
pIAllocatorEvacMode :: Field
1379
pIAllocatorEvacMode =
1380
  renameField "IAllocatorEvacMode" .
1381
  optionalField $
1382
  simpleField "evac_mode" [t| NodeEvacMode |]
1383

    
1384
-- | IAllocator spindle use.
1385
pIAllocatorSpindleUse :: Field
1386
pIAllocatorSpindleUse =
1387
  renameField "IAllocatorSpindleUse" .
1388
  defaultField [| forceNonNeg (1::Int) |] $
1389
  simpleField "spindle_use" [t| NonNegative Int |]
1390

    
1391
-- | IAllocator count field.
1392
pIAllocatorCount :: Field
1393
pIAllocatorCount =
1394
  renameField "IAllocatorCount" .
1395
  defaultField [| forceNonNeg (1::Int) |] $
1396
  simpleField "count" [t| NonNegative Int |]
1397

    
1398
-- | 'OpTestJqueue' notify_waitlock.
1399
pJQueueNotifyWaitLock :: Field
1400
pJQueueNotifyWaitLock = defaultFalse "notify_waitlock"
1401

    
1402
-- | 'OpTestJQueue' notify_exec.
1403
pJQueueNotifyExec :: Field
1404
pJQueueNotifyExec = defaultFalse "notify_exec"
1405

    
1406
-- | 'OpTestJQueue' log_messages.
1407
pJQueueLogMessages :: Field
1408
pJQueueLogMessages =
1409
  defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
1410

    
1411
-- | 'OpTestJQueue' fail attribute.
1412
pJQueueFail :: Field
1413
pJQueueFail =
1414
  renameField "JQueueFail" $ defaultFalse "fail"
1415

    
1416
-- | 'OpTestDummy' result field.
1417
pTestDummyResult :: Field
1418
pTestDummyResult =
1419
  renameField "TestDummyResult" $ simpleField "result" [t| UncheckedValue |]
1420

    
1421
-- | 'OpTestDummy' messages field.
1422
pTestDummyMessages :: Field
1423
pTestDummyMessages =
1424
  renameField "TestDummyMessages" $
1425
  simpleField "messages" [t| UncheckedValue |]
1426

    
1427
-- | 'OpTestDummy' fail field.
1428
pTestDummyFail :: Field
1429
pTestDummyFail =
1430
  renameField "TestDummyFail" $ simpleField "fail" [t| UncheckedValue |]
1431

    
1432
-- | 'OpTestDummy' submit_jobs field.
1433
pTestDummySubmitJobs :: Field
1434
pTestDummySubmitJobs =
1435
  renameField "TestDummySubmitJobs" $
1436
  simpleField "submit_jobs" [t| UncheckedValue |]
1437

    
1438
-- * Network parameters
1439

    
1440
-- | Network name.
1441
pNetworkName :: Field
1442
pNetworkName = simpleField "network_name" [t| NonEmptyString |]
1443

    
1444
-- | Network address (IPv4 subnet). FIXME: no real type for this.
1445
pNetworkAddress4 :: Field
1446
pNetworkAddress4 =
1447
  renameField "NetworkAddress4" $
1448
  simpleField "network" [t| NonEmptyString |]
1449

    
1450
-- | Network gateway (IPv4 address). FIXME: no real type for this.
1451
pNetworkGateway4 :: Field
1452
pNetworkGateway4 =
1453
  renameField "NetworkGateway4" $
1454
  optionalNEStringField "gateway"
1455

    
1456
-- | Network address (IPv6 subnet). FIXME: no real type for this.
1457
pNetworkAddress6 :: Field
1458
pNetworkAddress6 =
1459
  renameField "NetworkAddress6" $
1460
  optionalNEStringField "network6"
1461

    
1462
-- | Network gateway (IPv6 address). FIXME: no real type for this.
1463
pNetworkGateway6 :: Field
1464
pNetworkGateway6 =
1465
  renameField "NetworkGateway6" $
1466
  optionalNEStringField "gateway6"
1467

    
1468
-- | Network specific mac prefix (that overrides the cluster one).
1469
pNetworkMacPrefix :: Field
1470
pNetworkMacPrefix =
1471
  renameField "NetMacPrefix" $
1472
  optionalNEStringField "mac_prefix"
1473

    
1474
-- | Network add reserved IPs.
1475
pNetworkAddRsvdIps :: Field
1476
pNetworkAddRsvdIps =
1477
  renameField "NetworkAddRsvdIps" .
1478
  optionalField $
1479
  simpleField "add_reserved_ips" [t| [NonEmptyString] |]
1480

    
1481
-- | Network remove reserved IPs.
1482
pNetworkRemoveRsvdIps :: Field
1483
pNetworkRemoveRsvdIps =
1484
  renameField "NetworkRemoveRsvdIps" .
1485
  optionalField $
1486
  simpleField "remove_reserved_ips" [t| [NonEmptyString] |]
1487

    
1488
-- | Network mode when connecting to a group.
1489
pNetworkMode :: Field
1490
pNetworkMode = simpleField "network_mode" [t| NICMode |]
1491

    
1492
-- | Network link when connecting to a group.
1493
pNetworkLink :: Field
1494
pNetworkLink = simpleField "network_link" [t| NonEmptyString |]
1495

    
1496
-- * Common opcode parameters
1497

    
1498
-- | Run checks only, don't execute.
1499
pDryRun :: Field
1500
pDryRun = optionalField $ booleanField "dry_run"
1501

    
1502
-- | Debug level.
1503
pDebugLevel :: Field
1504
pDebugLevel = optionalField $ simpleField "debug_level" [t| NonNegative Int |]
1505

    
1506
-- | Opcode priority. Note: python uses a separate constant, we're
1507
-- using the actual value we know it's the default.
1508
pOpPriority :: Field
1509
pOpPriority =
1510
  defaultField [| OpPrioNormal |] $
1511
  simpleField "priority" [t| OpSubmitPriority |]
1512

    
1513
-- | Job dependencies.
1514
pDependencies :: Field
1515
pDependencies =
1516
  optionalNullSerField $ simpleField "depends" [t| [JobDependency] |]
1517

    
1518
-- | Comment field.
1519
pComment :: Field
1520
pComment = optionalNullSerField $ stringField "comment"
1521

    
1522
-- | Reason trail field.
1523
pReason :: Field
1524
pReason = simpleField C.opcodeReason [t| ReasonTrail |]
1525

    
1526
-- * Entire opcode parameter list
1527

    
1528
-- | Old-style query opcode, with locking.
1529
dOldQuery :: [Field]
1530
dOldQuery =
1531
  [ pOutputFields
1532
  , pNames
1533
  , pUseLocking
1534
  ]
1535

    
1536
-- | Old-style query opcode, without locking.
1537
dOldQueryNoLocking :: [Field]
1538
dOldQueryNoLocking =
1539
  [ pOutputFields
1540
  , pNames
1541
  ]