Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ d2e0774d

History | View | Annotate | Download (44 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
  , ISnapParams(..)
49
  , RecreateDisksInfo(..)
50
  , DdmOldChanges(..)
51
  , SetParamsMods(..)
52
  , SetSnapParams(..)
53
  , ExportTarget(..)
54
  , pInstanceName
55
  , pInstances
56
  , pName
57
  , pTagsList
58
  , pTagsObject
59
  , pOutputFields
60
  , pShutdownTimeout
61
  , pShutdownTimeout'
62
  , pShutdownInstance
63
  , pForce
64
  , pIgnoreOfflineNodes
65
  , pNodeName
66
  , pNodeNames
67
  , pGroupName
68
  , pMigrationMode
69
  , pMigrationLive
70
  , pMigrationCleanup
71
  , pForceVariant
72
  , pWaitForSync
73
  , pWaitForSyncFalse
74
  , pIgnoreConsistency
75
  , pStorageName
76
  , pUseLocking
77
  , pOpportunisticLocking
78
  , pNameCheck
79
  , pNodeGroupAllocPolicy
80
  , pGroupNodeParams
81
  , pQueryWhat
82
  , pEarlyRelease
83
  , pIpCheck
84
  , pIpConflictsCheck
85
  , pNoRemember
86
  , pMigrationTargetNode
87
  , pMoveTargetNode
88
  , pStartupPaused
89
  , pVerbose
90
  , pDebugSimulateErrors
91
  , pErrorCodes
92
  , pSkipChecks
93
  , pIgnoreErrors
94
  , pOptGroupName
95
  , pDiskParams
96
  , pHvState
97
  , pDiskState
98
  , pIgnoreIpolicy
99
  , pHotplug
100
  , pHotplugIfPossible
101
  , pAllowRuntimeChgs
102
  , pInstDisks
103
  , pInstSnaps
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
  , pStorageType
154
  , pStorageChanges
155
  , pMasterCandidate
156
  , pOffline
157
  , pDrained
158
  , pAutoPromote
159
  , pPowered
160
  , pIallocator
161
  , pRemoteNode
162
  , pEvacMode
163
  , pInstCreateMode
164
  , pNoInstall
165
  , pInstOs
166
  , pPrimaryNode
167
  , pSecondaryNode
168
  , pSourceHandshake
169
  , pSourceInstance
170
  , pSourceShutdownTimeout
171
  , pSourceX509Ca
172
  , pSrcNode
173
  , pSrcPath
174
  , pStartInstance
175
  , pInstTags
176
  , pMultiAllocInstances
177
  , pTempOsParams
178
  , pTempHvParams
179
  , pTempBeParams
180
  , pIgnoreFailures
181
  , pNewName
182
  , pIgnoreSecondaries
183
  , pRebootType
184
  , pIgnoreDiskSize
185
  , pRecreateDisksInfo
186
  , pStatic
187
  , pInstParamsNicChanges
188
  , pInstParamsDiskChanges
189
  , pRuntimeMem
190
  , pOsNameChange
191
  , pDiskIndex
192
  , pDiskChgAmount
193
  , pDiskChgAbsolute
194
  , pTargetGroups
195
  , pExportMode
196
  , pExportTargetNode
197
  , pRemoveInstance
198
  , pIgnoreRemoveFailures
199
  , pX509KeyName
200
  , pX509DestCA
201
  , pTagSearchPattern
202
  , pRestrictedCommand
203
  , pReplaceDisksMode
204
  , pReplaceDisksList
205
  , pAllowFailover
206
  , pDelayDuration
207
  , pDelayOnMaster
208
  , pDelayOnNodes
209
  , pDelayRepeat
210
  , pIAllocatorDirection
211
  , pIAllocatorMode
212
  , pIAllocatorReqName
213
  , pIAllocatorNics
214
  , pIAllocatorDisks
215
  , pIAllocatorMemory
216
  , pIAllocatorVCpus
217
  , pIAllocatorOs
218
  , pIAllocatorInstances
219
  , pIAllocatorEvacMode
220
  , pIAllocatorSpindleUse
221
  , pIAllocatorCount
222
  , pJQueueNotifyWaitLock
223
  , pJQueueNotifyExec
224
  , pJQueueLogMessages
225
  , pJQueueFail
226
  , pTestDummyResult
227
  , pTestDummyMessages
228
  , pTestDummyFail
229
  , pTestDummySubmitJobs
230
  , pNetworkName
231
  , pNetworkAddress4
232
  , pNetworkGateway4
233
  , pNetworkAddress6
234
  , pNetworkGateway6
235
  , pNetworkMacPrefix
236
  , pNetworkAddRsvdIps
237
  , pNetworkRemoveRsvdIps
238
  , pNetworkMode
239
  , pNetworkLink
240
  , pDryRun
241
  , pDebugLevel
242
  , pOpPriority
243
  , pDependencies
244
  , pComment
245
  , pReason
246
  , pEnabledDiskTemplates
247
  , dOldQuery
248
  , dOldQueryNoLocking
249
  ) where
250

    
251
import Control.Monad (liftM)
252
import qualified Data.Set as Set
253
import Text.JSON (readJSON, showJSON, JSON, JSValue(..), fromJSString,
254
                  JSObject, toJSObject)
255
import qualified Text.JSON
256
import Text.JSON.Pretty (pp_value)
257

    
258
import Ganeti.BasicTypes
259
import qualified Ganeti.Constants as C
260
import Ganeti.THH
261
import Ganeti.JSON
262
import Ganeti.Types
263
import qualified Ganeti.Query.Language as Qlang
264

    
265
-- * Helper functions and types
266

    
267
-- * Type aliases
268

    
269
-- | Build a boolean field.
270
booleanField :: String -> Field
271
booleanField = flip simpleField [t| Bool |]
272

    
273
-- | Default a field to 'False'.
274
defaultFalse :: String -> Field
275
defaultFalse = defaultField [| False |] . booleanField
276

    
277
-- | Default a field to 'True'.
278
defaultTrue :: String -> Field
279
defaultTrue = defaultField [| True |] . booleanField
280

    
281
-- | An alias for a 'String' field.
282
stringField :: String -> Field
283
stringField = flip simpleField [t| String |]
284

    
285
-- | An alias for an optional string field.
286
optionalStringField :: String -> Field
287
optionalStringField = optionalField . stringField
288

    
289
-- | An alias for an optional non-empty string field.
290
optionalNEStringField :: String -> Field
291
optionalNEStringField = optionalField . flip simpleField [t| NonEmptyString |]
292

    
293
-- | Unchecked value, should be replaced by a better definition.
294
type UncheckedValue = JSValue
295

    
296
-- | Unchecked dict, should be replaced by a better definition.
297
type UncheckedDict = JSObject JSValue
298

    
299
-- | Unchecked list, shoild be replaced by a better definition.
300
type UncheckedList = [JSValue]
301

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

    
311
-- ** Tags
312

    
313
-- | Data type representing what items do the tag operations apply to.
314
$(declareSADT "TagType"
315
  [ ("TagTypeInstance", 'C.tagInstance)
316
  , ("TagTypeNode",     'C.tagNode)
317
  , ("TagTypeGroup",    'C.tagNodegroup)
318
  , ("TagTypeCluster",  'C.tagCluster)
319
  ])
320
$(makeJSONInstance ''TagType)
321

    
322
-- | Data type holding a tag object (type and object name).
323
data TagObject = TagInstance String
324
               | TagNode     String
325
               | TagGroup    String
326
               | TagCluster
327
               deriving (Show, Eq)
328

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

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

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

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

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

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

    
370
-- ** Disks
371

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

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

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

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

    
397
-- ** I* param types
398

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

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

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

    
425
-- | Disk snapshot definition.
426
$(buildObject "ISnapParams" "idisk"
427
  [ simpleField C.idiskSnapshotName [t| NonEmptyString |]])
428

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

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

    
451
instance JSON RecreateDisksInfo where
452
  readJSON = readRecreateDisks
453
  showJSON  RecreateDisksAll            = showJSON ()
454
  showJSON (RecreateDisksIndices idx)   = showJSON idx
455
  showJSON (RecreateDisksParams params) = showJSON params
456

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

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

    
471
instance JSON DdmOldChanges where
472
  showJSON (DdmOldIndex i) = showJSON i
473
  showJSON (DdmOldMod m)   = showJSON m
474
  readJSON = readDdmOldChanges
475

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

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

    
491
instance (JSON a) => JSON (SetParamsMods a) where
492
  showJSON SetParamsEmpty = showJSON ()
493
  showJSON (SetParamsDeprecated v) = showJSON v
494
  showJSON (SetParamsNew v) = showJSON v
495
  readJSON = readSetParams
496

    
497
-- | Instance snapshot params
498
data SetSnapParams a
499
  = SetSnapParamsEmpty
500
  | SetSnapParamsValid (NonEmpty (Int, a))
501
    deriving (Eq, Show)
502

    
503
readSetSnapParams :: (JSON a) => JSValue -> Text.JSON.Result (SetSnapParams a)
504
readSetSnapParams (JSArray []) = return SetSnapParamsEmpty
505
readSetSnapParams v =
506
  case readJSON v::Text.JSON.Result [(Int, JSValue)] of
507
    Text.JSON.Ok _ -> liftM SetSnapParamsValid $ readJSON v
508
    _ -> fail "Cannot parse snapshot params."
509

    
510
instance (JSON a) => JSON (SetSnapParams a) where
511
  showJSON SetSnapParamsEmpty = showJSON ()
512
  showJSON (SetSnapParamsValid v) = showJSON v
513
  readJSON = readSetSnapParams
514

    
515
-- | Custom type for target_node parameter of OpBackupExport, which
516
-- varies depending on mode. FIXME: this uses an UncheckedList since
517
-- we don't care about individual rows (just like the Python code
518
-- tests). But the proper type could be parsed if we wanted.
519
data ExportTarget = ExportTargetLocal NonEmptyString
520
                  | ExportTargetRemote UncheckedList
521
                    deriving (Eq, Show)
522

    
523
-- | Custom reader for 'ExportTarget'.
524
readExportTarget :: JSValue -> Text.JSON.Result ExportTarget
525
readExportTarget (JSString s) = liftM ExportTargetLocal $
526
                                mkNonEmpty (fromJSString s)
527
readExportTarget (JSArray arr) = return $ ExportTargetRemote arr
528
readExportTarget v = fail $ "Invalid value received for 'target_node': " ++
529
                     show (pp_value v)
530

    
531
instance JSON ExportTarget where
532
  showJSON (ExportTargetLocal s)  = showJSON s
533
  showJSON (ExportTargetRemote l) = showJSON l
534
  readJSON = readExportTarget
535

    
536
-- * Parameters
537

    
538
-- | A required instance name (for single-instance LUs).
539
pInstanceName :: Field
540
pInstanceName = simpleField "instance_name" [t| String |]
541

    
542
-- | A list of instances.
543
pInstances :: Field
544
pInstances = defaultField [| [] |] $
545
             simpleField "instances" [t| [NonEmptyString] |]
546

    
547
-- | A generic name.
548
pName :: Field
549
pName = simpleField "name" [t| NonEmptyString |]
550

    
551
-- | Tags list.
552
pTagsList :: Field
553
pTagsList = simpleField "tags" [t| [String] |]
554

    
555
-- | Tags object.
556
pTagsObject :: Field
557
pTagsObject =
558
  customField 'decodeTagObject 'encodeTagObject [tagNameField] $
559
  simpleField "kind" [t| TagObject |]
560

    
561
-- | Selected output fields.
562
pOutputFields :: Field
563
pOutputFields = simpleField "output_fields" [t| [NonEmptyString] |]
564

    
565
-- | How long to wait for instance to shut down.
566
pShutdownTimeout :: Field
567
pShutdownTimeout = defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
568
                   simpleField "shutdown_timeout" [t| NonNegative Int |]
569

    
570
-- | Another name for the shutdown timeout, because we like to be
571
-- inconsistent.
572
pShutdownTimeout' :: Field
573
pShutdownTimeout' =
574
  renameField "InstShutdownTimeout" .
575
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
576
  simpleField "timeout" [t| NonNegative Int |]
577

    
578
-- | Whether to shutdown the instance in backup-export.
579
pShutdownInstance :: Field
580
pShutdownInstance = defaultTrue "shutdown"
581

    
582
-- | Whether to force the operation.
583
pForce :: Field
584
pForce = defaultFalse "force"
585

    
586
-- | Whether to ignore offline nodes.
587
pIgnoreOfflineNodes :: Field
588
pIgnoreOfflineNodes = defaultFalse "ignore_offline_nodes"
589

    
590
-- | A required node name (for single-node LUs).
591
pNodeName :: Field
592
pNodeName = simpleField "node_name" [t| NonEmptyString |]
593

    
594
-- | List of nodes.
595
pNodeNames :: Field
596
pNodeNames =
597
  defaultField [| [] |] $ simpleField "node_names" [t| [NonEmptyString] |]
598

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
693
-- | Pause instance at startup.
694
pStartupPaused :: Field
695
pStartupPaused = defaultFalse "startup_paused"
696

    
697
-- | Verbose mode.
698
pVerbose :: Field
699
pVerbose = defaultFalse "verbose"
700

    
701
-- ** Parameters for cluster verification
702

    
703
-- | Whether to simulate errors (useful for debugging).
704
pDebugSimulateErrors :: Field
705
pDebugSimulateErrors = defaultFalse "debug_simulate_errors"
706

    
707
-- | Error codes.
708
pErrorCodes :: Field
709
pErrorCodes = defaultFalse "error_codes"
710

    
711
-- | Which checks to skip.
712
pSkipChecks :: Field
713
pSkipChecks = defaultField [| Set.empty |] $
714
              simpleField "skip_checks" [t| Set.Set VerifyOptionalChecks |]
715

    
716
-- | List of error codes that should be treated as warnings.
717
pIgnoreErrors :: Field
718
pIgnoreErrors = defaultField [| Set.empty |] $
719
                simpleField "ignore_errors" [t| Set.Set CVErrorCode |]
720

    
721
-- | Optional group name.
722
pOptGroupName :: Field
723
pOptGroupName = renameField "OptGroupName" .
724
                optionalField $ simpleField "group_name" [t| NonEmptyString |]
725

    
726
-- | Disk templates' parameter defaults.
727
pDiskParams :: Field
728
pDiskParams = optionalField $
729
              simpleField "diskparams" [t| GenericContainer DiskTemplate
730
                                           UncheckedDict |]
731

    
732
-- | Whether to hotplug device.
733
pHotplug :: Field
734
pHotplug = defaultFalse "hotplug"
735

    
736
pHotplugIfPossible :: Field
737
pHotplugIfPossible = defaultFalse "hotplug_if_possible"
738

    
739
-- * Parameters for node resource model
740

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

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

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

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

    
757
-- | Utility type for OpClusterSetParams.
758
type TestClusterOsListItem = (DdmSimple, NonEmptyString)
759

    
760
-- | Utility type of OsList.
761
type TestClusterOsList = [TestClusterOsListItem]
762

    
763
-- Utility type for NIC definitions.
764
--type TestNicDef = INicParams
765

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

    
770
-- | List of instance snaps.
771
pInstSnaps :: Field
772
pInstSnaps =
773
  renameField "instSnaps" $
774
  simpleField "disks" [t| SetSnapParams ISnapParams |]
775

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
1075
-- | Node evacuation mode.
1076
pEvacMode :: Field
1077
pEvacMode = renameField "EvacMode" $ simpleField "mode" [t| NodeEvacMode |]
1078

    
1079
-- | Instance creation mode.
1080
pInstCreateMode :: Field
1081
pInstCreateMode =
1082
  renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
1083

    
1084
-- | Do not install the OS (will disable automatic start).
1085
pNoInstall :: Field
1086
pNoInstall = optionalField $ booleanField "no_install"
1087

    
1088
-- | OS type for instance installation.
1089
pInstOs :: Field
1090
pInstOs = optionalNEStringField "os_type"
1091

    
1092
-- | Primary node for an instance.
1093
pPrimaryNode :: Field
1094
pPrimaryNode = optionalNEStringField "pnode"
1095

    
1096
-- | Secondary node for an instance.
1097
pSecondaryNode :: Field
1098
pSecondaryNode = optionalNEStringField "snode"
1099

    
1100
-- | Signed handshake from source (remote import only).
1101
pSourceHandshake :: Field
1102
pSourceHandshake =
1103
  optionalField $ simpleField "source_handshake" [t| UncheckedList |]
1104

    
1105
-- | Source instance name (remote import only).
1106
pSourceInstance :: Field
1107
pSourceInstance = optionalNEStringField "source_instance_name"
1108

    
1109
-- | How long source instance was given to shut down (remote import only).
1110
-- FIXME: non-negative int, whereas the constant is a plain int.
1111
pSourceShutdownTimeout :: Field
1112
pSourceShutdownTimeout =
1113
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1114
  simpleField "source_shutdown_timeout" [t| NonNegative Int |]
1115

    
1116
-- | Source X509 CA in PEM format (remote import only).
1117
pSourceX509Ca :: Field
1118
pSourceX509Ca = optionalNEStringField "source_x509_ca"
1119

    
1120
-- | Source node for import.
1121
pSrcNode :: Field
1122
pSrcNode = optionalNEStringField "src_node"
1123

    
1124
-- | Source directory for import.
1125
pSrcPath :: Field
1126
pSrcPath = optionalNEStringField "src_path"
1127

    
1128
-- | Whether to start instance after creation.
1129
pStartInstance :: Field
1130
pStartInstance = defaultTrue "start"
1131

    
1132
-- | Instance tags. FIXME: unify/simplify with pTags, once that
1133
-- migrates to NonEmpty String.
1134
pInstTags :: Field
1135
pInstTags =
1136
  renameField "InstTags" .
1137
  defaultField [| [] |] $
1138
  simpleField "tags" [t| [NonEmptyString] |]
1139

    
1140
-- | Unchecked list of OpInstanceCreate, used in OpInstanceMultiAlloc.
1141
pMultiAllocInstances :: Field
1142
pMultiAllocInstances =
1143
  renameField "InstMultiAlloc" .
1144
  defaultField [| [] |] $
1145
  simpleField "instances"[t| UncheckedList |]
1146

    
1147
-- | Ignore failures parameter.
1148
pIgnoreFailures :: Field
1149
pIgnoreFailures = defaultFalse "ignore_failures"
1150

    
1151
-- | New instance or cluster name.
1152
pNewName :: Field
1153
pNewName = simpleField "new_name" [t| NonEmptyString |]
1154

    
1155
-- | Whether to start the instance even if secondary disks are failing.
1156
pIgnoreSecondaries :: Field
1157
pIgnoreSecondaries = defaultFalse "ignore_secondaries"
1158

    
1159
-- | How to reboot the instance.
1160
pRebootType :: Field
1161
pRebootType = simpleField "reboot_type" [t| RebootType |]
1162

    
1163
-- | Whether to ignore recorded disk size.
1164
pIgnoreDiskSize :: Field
1165
pIgnoreDiskSize = defaultFalse "ignore_size"
1166

    
1167
-- | Disk list for recreate disks.
1168
pRecreateDisksInfo :: Field
1169
pRecreateDisksInfo =
1170
  renameField "RecreateDisksInfo" .
1171
  defaultField [| RecreateDisksAll |] $
1172
  simpleField "disks" [t| RecreateDisksInfo |]
1173

    
1174
-- | Whether to only return configuration data without querying nodes.
1175
pStatic :: Field
1176
pStatic = defaultFalse "static"
1177

    
1178
-- | InstanceSetParams NIC changes.
1179
pInstParamsNicChanges :: Field
1180
pInstParamsNicChanges =
1181
  renameField "InstNicChanges" .
1182
  defaultField [| SetParamsEmpty |] $
1183
  simpleField "nics" [t| SetParamsMods INicParams |]
1184

    
1185
-- | InstanceSetParams Disk changes.
1186
pInstParamsDiskChanges :: Field
1187
pInstParamsDiskChanges =
1188
  renameField "InstDiskChanges" .
1189
  defaultField [| SetParamsEmpty |] $
1190
  simpleField "disks" [t| SetParamsMods IDiskParams |]
1191

    
1192
-- | New runtime memory.
1193
pRuntimeMem :: Field
1194
pRuntimeMem = optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1195

    
1196
-- | Change the instance's OS without reinstalling the instance
1197
pOsNameChange :: Field
1198
pOsNameChange = optionalNEStringField "os_name"
1199

    
1200
-- | Disk index for e.g. grow disk.
1201
pDiskIndex :: Field
1202
pDiskIndex = renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
1203

    
1204
-- | Disk amount to add or grow to.
1205
pDiskChgAmount :: Field
1206
pDiskChgAmount =
1207
  renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
1208

    
1209
-- | Whether the amount parameter is an absolute target or a relative one.
1210
pDiskChgAbsolute :: Field
1211
pDiskChgAbsolute = renameField "DiskChkAbsolute" $ defaultFalse "absolute"
1212

    
1213
-- | Destination group names or UUIDs (defaults to \"all but current group\".
1214
pTargetGroups :: Field
1215
pTargetGroups =
1216
  optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
1217

    
1218
-- | Export mode field.
1219
pExportMode :: Field
1220
pExportMode =
1221
  renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1222

    
1223
-- | Export target_node field, depends on mode.
1224
pExportTargetNode :: Field
1225
pExportTargetNode =
1226
  renameField "ExportTarget" $
1227
  simpleField "target_node" [t| ExportTarget |]
1228

    
1229
-- | Whether to remove instance after export.
1230
pRemoveInstance :: Field
1231
pRemoveInstance = defaultFalse "remove_instance"
1232

    
1233
-- | Whether to ignore failures while removing instances.
1234
pIgnoreRemoveFailures :: Field
1235
pIgnoreRemoveFailures = defaultFalse "ignore_remove_failures"
1236

    
1237
-- | Name of X509 key (remote export only).
1238
pX509KeyName :: Field
1239
pX509KeyName = optionalField $ simpleField "x509_key_name" [t| UncheckedList |]
1240

    
1241
-- | Destination X509 CA (remote export only).
1242
pX509DestCA :: Field
1243
pX509DestCA = optionalNEStringField "destination_x509_ca"
1244

    
1245
-- | Search pattern (regular expression). FIXME: this should be
1246
-- compiled at load time?
1247
pTagSearchPattern :: Field
1248
pTagSearchPattern =
1249
  renameField "TagSearchPattern" $ simpleField "pattern" [t| NonEmptyString |]
1250

    
1251
-- | Restricted command name.
1252
pRestrictedCommand :: Field
1253
pRestrictedCommand =
1254
  renameField "RestrictedCommand" $
1255
  simpleField "command" [t| NonEmptyString |]
1256

    
1257
-- | Replace disks mode.
1258
pReplaceDisksMode :: Field
1259
pReplaceDisksMode =
1260
  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1261

    
1262
-- | List of disk indices.
1263
pReplaceDisksList :: Field
1264
pReplaceDisksList =
1265
  renameField "ReplaceDisksList" $ simpleField "disks" [t| [DiskIndex] |]
1266

    
1267
-- | Whether do allow failover in migrations.
1268
pAllowFailover :: Field
1269
pAllowFailover = defaultFalse "allow_failover"
1270

    
1271
-- * Test opcode parameters
1272

    
1273
-- | Duration parameter for 'OpTestDelay'.
1274
pDelayDuration :: Field
1275
pDelayDuration =
1276
  renameField "DelayDuration" $ simpleField "duration" [t| Double |]
1277

    
1278
-- | on_master field for 'OpTestDelay'.
1279
pDelayOnMaster :: Field
1280
pDelayOnMaster = renameField "DelayOnMaster" $ defaultTrue "on_master"
1281

    
1282
-- | on_nodes field for 'OpTestDelay'.
1283
pDelayOnNodes :: Field
1284
pDelayOnNodes =
1285
  renameField "DelayOnNodes" .
1286
  defaultField [| [] |] $
1287
  simpleField "on_nodes" [t| [NonEmptyString] |]
1288

    
1289
-- | Repeat parameter for OpTestDelay.
1290
pDelayRepeat :: Field
1291
pDelayRepeat =
1292
  renameField "DelayRepeat" .
1293
  defaultField [| forceNonNeg (0::Int) |] $
1294
  simpleField "repeat" [t| NonNegative Int |]
1295

    
1296
-- | IAllocator test direction.
1297
pIAllocatorDirection :: Field
1298
pIAllocatorDirection =
1299
  renameField "IAllocatorDirection" $
1300
  simpleField "direction" [t| IAllocatorTestDir |]
1301

    
1302
-- | IAllocator test mode.
1303
pIAllocatorMode :: Field
1304
pIAllocatorMode =
1305
  renameField "IAllocatorMode" $
1306
  simpleField "mode" [t| IAllocatorMode |]
1307

    
1308
-- | IAllocator target name (new instance, node to evac, etc.).
1309
pIAllocatorReqName :: Field
1310
pIAllocatorReqName =
1311
  renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
1312

    
1313
-- | Custom OpTestIAllocator nics.
1314
pIAllocatorNics :: Field
1315
pIAllocatorNics =
1316
  renameField "IAllocatorNics" $ simpleField "nics" [t| [UncheckedDict] |]
1317

    
1318
-- | Custom OpTestAllocator disks.
1319
pIAllocatorDisks :: Field
1320
pIAllocatorDisks =
1321
  renameField "IAllocatorDisks" $ simpleField "disks" [t| UncheckedList |]
1322

    
1323
-- | IAllocator memory field.
1324
pIAllocatorMemory :: Field
1325
pIAllocatorMemory =
1326
  renameField "IAllocatorMem" .
1327
  optionalField $
1328
  simpleField "memory" [t| NonNegative Int |]
1329

    
1330
-- | IAllocator vcpus field.
1331
pIAllocatorVCpus :: Field
1332
pIAllocatorVCpus =
1333
  renameField "IAllocatorVCpus" .
1334
  optionalField $
1335
  simpleField "vcpus" [t| NonNegative Int |]
1336

    
1337
-- | IAllocator os field.
1338
pIAllocatorOs :: Field
1339
pIAllocatorOs = renameField "IAllocatorOs" $ optionalNEStringField "os"
1340

    
1341
-- | IAllocator instances field.
1342
pIAllocatorInstances :: Field
1343
pIAllocatorInstances =
1344
  renameField "IAllocatorInstances " .
1345
  optionalField $
1346
  simpleField "instances" [t| [NonEmptyString] |]
1347

    
1348
-- | IAllocator evac mode.
1349
pIAllocatorEvacMode :: Field
1350
pIAllocatorEvacMode =
1351
  renameField "IAllocatorEvacMode" .
1352
  optionalField $
1353
  simpleField "evac_mode" [t| NodeEvacMode |]
1354

    
1355
-- | IAllocator spindle use.
1356
pIAllocatorSpindleUse :: Field
1357
pIAllocatorSpindleUse =
1358
  renameField "IAllocatorSpindleUse" .
1359
  defaultField [| forceNonNeg (1::Int) |] $
1360
  simpleField "spindle_use" [t| NonNegative Int |]
1361

    
1362
-- | IAllocator count field.
1363
pIAllocatorCount :: Field
1364
pIAllocatorCount =
1365
  renameField "IAllocatorCount" .
1366
  defaultField [| forceNonNeg (1::Int) |] $
1367
  simpleField "count" [t| NonNegative Int |]
1368

    
1369
-- | 'OpTestJqueue' notify_waitlock.
1370
pJQueueNotifyWaitLock :: Field
1371
pJQueueNotifyWaitLock = defaultFalse "notify_waitlock"
1372

    
1373
-- | 'OpTestJQueue' notify_exec.
1374
pJQueueNotifyExec :: Field
1375
pJQueueNotifyExec = defaultFalse "notify_exec"
1376

    
1377
-- | 'OpTestJQueue' log_messages.
1378
pJQueueLogMessages :: Field
1379
pJQueueLogMessages =
1380
  defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
1381

    
1382
-- | 'OpTestJQueue' fail attribute.
1383
pJQueueFail :: Field
1384
pJQueueFail =
1385
  renameField "JQueueFail" $ defaultFalse "fail"
1386

    
1387
-- | 'OpTestDummy' result field.
1388
pTestDummyResult :: Field
1389
pTestDummyResult =
1390
  renameField "TestDummyResult" $ simpleField "result" [t| UncheckedValue |]
1391

    
1392
-- | 'OpTestDummy' messages field.
1393
pTestDummyMessages :: Field
1394
pTestDummyMessages =
1395
  renameField "TestDummyMessages" $
1396
  simpleField "messages" [t| UncheckedValue |]
1397

    
1398
-- | 'OpTestDummy' fail field.
1399
pTestDummyFail :: Field
1400
pTestDummyFail =
1401
  renameField "TestDummyFail" $ simpleField "fail" [t| UncheckedValue |]
1402

    
1403
-- | 'OpTestDummy' submit_jobs field.
1404
pTestDummySubmitJobs :: Field
1405
pTestDummySubmitJobs =
1406
  renameField "TestDummySubmitJobs" $
1407
  simpleField "submit_jobs" [t| UncheckedValue |]
1408

    
1409
-- * Network parameters
1410

    
1411
-- | Network name.
1412
pNetworkName :: Field
1413
pNetworkName = simpleField "network_name" [t| NonEmptyString |]
1414

    
1415
-- | Network address (IPv4 subnet). FIXME: no real type for this.
1416
pNetworkAddress4 :: Field
1417
pNetworkAddress4 =
1418
  renameField "NetworkAddress4" $
1419
  simpleField "network" [t| NonEmptyString |]
1420

    
1421
-- | Network gateway (IPv4 address). FIXME: no real type for this.
1422
pNetworkGateway4 :: Field
1423
pNetworkGateway4 =
1424
  renameField "NetworkGateway4" $
1425
  optionalNEStringField "gateway"
1426

    
1427
-- | Network address (IPv6 subnet). FIXME: no real type for this.
1428
pNetworkAddress6 :: Field
1429
pNetworkAddress6 =
1430
  renameField "NetworkAddress6" $
1431
  optionalNEStringField "network6"
1432

    
1433
-- | Network gateway (IPv6 address). FIXME: no real type for this.
1434
pNetworkGateway6 :: Field
1435
pNetworkGateway6 =
1436
  renameField "NetworkGateway6" $
1437
  optionalNEStringField "gateway6"
1438

    
1439
-- | Network specific mac prefix (that overrides the cluster one).
1440
pNetworkMacPrefix :: Field
1441
pNetworkMacPrefix =
1442
  renameField "NetMacPrefix" $
1443
  optionalNEStringField "mac_prefix"
1444

    
1445
-- | Network add reserved IPs.
1446
pNetworkAddRsvdIps :: Field
1447
pNetworkAddRsvdIps =
1448
  renameField "NetworkAddRsvdIps" .
1449
  optionalField $
1450
  simpleField "add_reserved_ips" [t| [NonEmptyString] |]
1451

    
1452
-- | Network remove reserved IPs.
1453
pNetworkRemoveRsvdIps :: Field
1454
pNetworkRemoveRsvdIps =
1455
  renameField "NetworkRemoveRsvdIps" .
1456
  optionalField $
1457
  simpleField "remove_reserved_ips" [t| [NonEmptyString] |]
1458

    
1459
-- | Network mode when connecting to a group.
1460
pNetworkMode :: Field
1461
pNetworkMode = simpleField "network_mode" [t| NICMode |]
1462

    
1463
-- | Network link when connecting to a group.
1464
pNetworkLink :: Field
1465
pNetworkLink = simpleField "network_link" [t| NonEmptyString |]
1466

    
1467
-- * Common opcode parameters
1468

    
1469
-- | Run checks only, don't execute.
1470
pDryRun :: Field
1471
pDryRun = optionalField $ booleanField "dry_run"
1472

    
1473
-- | Debug level.
1474
pDebugLevel :: Field
1475
pDebugLevel = optionalField $ simpleField "debug_level" [t| NonNegative Int |]
1476

    
1477
-- | Opcode priority. Note: python uses a separate constant, we're
1478
-- using the actual value we know it's the default.
1479
pOpPriority :: Field
1480
pOpPriority =
1481
  defaultField [| OpPrioNormal |] $
1482
  simpleField "priority" [t| OpSubmitPriority |]
1483

    
1484
-- | Job dependencies.
1485
pDependencies :: Field
1486
pDependencies =
1487
  optionalNullSerField $ simpleField "depends" [t| [JobDependency] |]
1488

    
1489
-- | Comment field.
1490
pComment :: Field
1491
pComment = optionalNullSerField $ stringField "comment"
1492

    
1493
-- | Reason trail field.
1494
pReason :: Field
1495
pReason = simpleField C.opcodeReason [t| ReasonTrail |]
1496

    
1497
-- * Entire opcode parameter list
1498

    
1499
-- | Old-style query opcode, with locking.
1500
dOldQuery :: [Field]
1501
dOldQuery =
1502
  [ pOutputFields
1503
  , pNames
1504
  , pUseLocking
1505
  ]
1506

    
1507
-- | Old-style query opcode, without locking.
1508
dOldQueryNoLocking :: [Field]
1509
dOldQueryNoLocking =
1510
  [ pOutputFields
1511
  , pNames
1512
  ]