Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ d676dbea

History | View | Annotate | Download (45 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

    
3
{-| Implementation of opcodes parameters.
4

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

    
11
-}
12

    
13
{-
14

    
15
Copyright (C) 2012 Google Inc.
16

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

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

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

    
32
-}
33

    
34
module Ganeti.OpParams
35
  ( TagType(..)
36
  , TagObject(..)
37
  , tagObjectFrom
38
  , tagNameOf
39
  , decodeTagObject
40
  , encodeTagObject
41
  , ReplaceDisksMode(..)
42
  , DiskIndex
43
  , mkDiskIndex
44
  , unDiskIndex
45
  , DiskAccess(..)
46
  , INicParams(..)
47
  , IDiskParams(..)
48
  , RecreateDisksInfo(..)
49
  , DdmOldChanges(..)
50
  , SetParamsMods(..)
51
  , ExportTarget(..)
52
  , pInstanceName
53
  , pInstanceUuid
54
  , pInstances
55
  , pName
56
  , pTagsList
57
  , pTagsObject
58
  , pOutputFields
59
  , pShutdownTimeout
60
  , pShutdownTimeout'
61
  , pShutdownInstance
62
  , pForce
63
  , pIgnoreOfflineNodes
64
  , pNodeName
65
  , pNodeUuid
66
  , pNodeNames
67
  , pNodeUuids
68
  , pGroupName
69
  , pMigrationMode
70
  , pMigrationLive
71
  , pMigrationCleanup
72
  , pForceVariant
73
  , pWaitForSync
74
  , pWaitForSyncFalse
75
  , pIgnoreConsistency
76
  , pStorageName
77
  , pUseLocking
78
  , pOpportunisticLocking
79
  , pNameCheck
80
  , pNodeGroupAllocPolicy
81
  , pGroupNodeParams
82
  , pQueryWhat
83
  , pEarlyRelease
84
  , pIpCheck
85
  , pIpConflictsCheck
86
  , pNoRemember
87
  , pMigrationTargetNode
88
  , pMigrationTargetNodeUuid
89
  , pMoveTargetNode
90
  , pMoveTargetNodeUuid
91
  , pStartupPaused
92
  , pVerbose
93
  , pDebugSimulateErrors
94
  , pErrorCodes
95
  , pSkipChecks
96
  , pIgnoreErrors
97
  , pOptGroupName
98
  , pDiskParams
99
  , pHvState
100
  , pDiskState
101
  , pIgnoreIpolicy
102
  , pAllowRuntimeChgs
103
  , pInstDisks
104
  , pDiskTemplate
105
  , pOptDiskTemplate
106
  , pFileDriver
107
  , pFileStorageDir
108
  , pVgName
109
  , pEnabledHypervisors
110
  , pHypervisor
111
  , pClusterHvParams
112
  , pInstHvParams
113
  , pClusterBeParams
114
  , pInstBeParams
115
  , pResetDefaults
116
  , pOsHvp
117
  , pClusterOsParams
118
  , pInstOsParams
119
  , pCandidatePoolSize
120
  , pUidPool
121
  , pAddUids
122
  , pRemoveUids
123
  , pMaintainNodeHealth
124
  , pModifyEtcHosts
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
  , optionalField $ simpleField C.inicVlan [t| NonEmptyString |]
421
  ])
422

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

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

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

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

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

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

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

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

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

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

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

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

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

    
522
-- * Parameters
523

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
710
-- ** Parameters for cluster verification
711

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

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

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

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

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

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

    
741
-- * Parameters for node resource model
742

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

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

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

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

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

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

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

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

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

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

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

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

    
791
-- | Volume group name.
792
pVgName :: Field
793
pVgName = optionalStringField "vg_name"
794

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

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

    
807
-- | Selected hypervisor for an instance.
808
pHypervisor :: Field
809
pHypervisor =
810
  optionalField $
811
  simpleField "hypervisor" [t| Hypervisor |]
812

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

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

    
827
-- | Cluster-wide beparams.
828
pClusterBeParams :: Field
829
pClusterBeParams =
830
  renameField "ClusterBeParams" .
831
  optionalField $ simpleField "beparams" [t| UncheckedDict |]
832

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

    
840
-- | Reset instance parameters to default if equal.
841
pResetDefaults :: Field
842
pResetDefaults = defaultFalse "identify_defaults"
843

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

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

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

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

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

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

    
881
-- | Candidate pool size.
882
pCandidatePoolSize :: Field
883
pCandidatePoolSize =
884
  optionalField $ simpleField "candidate_pool_size" [t| Positive Int |]
885

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

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

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

    
901
-- | Whether to automatically maintain node health.
902
pMaintainNodeHealth :: Field
903
pMaintainNodeHealth = optionalField $ booleanField "maintain_node_health"
904

    
905
-- | Whether to modify and keep in sync the @/etc/hosts@ files of nodes.
906
pModifyEtcHosts :: Field
907
pModifyEtcHosts = optionalField $ booleanField "modify_etc_hosts"
908

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
1295
-- * Test opcode parameters
1296

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
1439
-- * Network parameters
1440

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

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

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

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

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

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

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

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

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

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

    
1497
-- * Common opcode parameters
1498

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

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

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

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

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

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

    
1527
-- * Entire opcode parameter list
1528

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

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