Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ a82a94e1

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

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

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

    
266
-- * Helper functions and types
267

    
268
-- * Type aliases
269

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

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

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

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

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

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

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

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

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

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

    
312
-- ** Tags
313

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

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

    
332
-- | Tag type for a given tag object.
333
tagTypeOf :: TagObject -> TagType
334
tagTypeOf (TagInstance {}) = TagTypeInstance
335
tagTypeOf (TagNode     {}) = TagTypeNode
336
tagTypeOf (TagGroup    {}) = TagTypeGroup
337
tagTypeOf (TagCluster  {}) = TagTypeCluster
338
tagTypeOf (TagNetwork  {}) = TagTypeNetwork
339

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

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

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

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

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

    
377
-- ** Disks
378

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

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

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

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

    
404
-- ** I* param types
405

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

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

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

    
432
-- | Disk snapshot definition.
433
$(buildObject "ISnapParams" "idisk"
434
  [ simpleField C.idiskSnapshotName [t| NonEmptyString |]])
435

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

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

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

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

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

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

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

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

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

    
504
-- | Instance snapshot params
505
data SetSnapParams a
506
  = SetSnapParamsEmpty
507
  | SetSnapParamsValid (NonEmpty (Int, a))
508
    deriving (Eq, Show)
509

    
510
readSetSnapParams :: (JSON a) => JSValue -> Text.JSON.Result (SetSnapParams a)
511
readSetSnapParams (JSArray []) = return SetSnapParamsEmpty
512
readSetSnapParams v =
513
  case readJSON v::Text.JSON.Result [(Int, JSValue)] of
514
    Text.JSON.Ok _ -> liftM SetSnapParamsValid $ readJSON v
515
    _ -> fail "Cannot parse snapshot params."
516

    
517
instance (JSON a) => JSON (SetSnapParams a) where
518
  showJSON SetSnapParamsEmpty = showJSON ()
519
  showJSON (SetSnapParamsValid v) = showJSON v
520
  readJSON = readSetSnapParams
521

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

    
530
-- | Custom reader for 'ExportTarget'.
531
readExportTarget :: JSValue -> Text.JSON.Result ExportTarget
532
readExportTarget (JSString s) = liftM ExportTargetLocal $
533
                                mkNonEmpty (fromJSString s)
534
readExportTarget (JSArray arr) = return $ ExportTargetRemote arr
535
readExportTarget v = fail $ "Invalid value received for 'target_node': " ++
536
                     show (pp_value v)
537

    
538
instance JSON ExportTarget where
539
  showJSON (ExportTargetLocal s)  = showJSON s
540
  showJSON (ExportTargetRemote l) = showJSON l
541
  readJSON = readExportTarget
542

    
543
-- * Parameters
544

    
545
-- | A required instance name (for single-instance LUs).
546
pInstanceName :: Field
547
pInstanceName = simpleField "instance_name" [t| String |]
548

    
549
-- | A list of instances.
550
pInstances :: Field
551
pInstances = defaultField [| [] |] $
552
             simpleField "instances" [t| [NonEmptyString] |]
553

    
554
-- | A generic name.
555
pName :: Field
556
pName = simpleField "name" [t| NonEmptyString |]
557

    
558
-- | Tags list.
559
pTagsList :: Field
560
pTagsList = simpleField "tags" [t| [String] |]
561

    
562
-- | Tags object.
563
pTagsObject :: Field
564
pTagsObject =
565
  customField 'decodeTagObject 'encodeTagObject [tagNameField] $
566
  simpleField "kind" [t| TagObject |]
567

    
568
-- | Selected output fields.
569
pOutputFields :: Field
570
pOutputFields = simpleField "output_fields" [t| [NonEmptyString] |]
571

    
572
-- | How long to wait for instance to shut down.
573
pShutdownTimeout :: Field
574
pShutdownTimeout = defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
575
                   simpleField "shutdown_timeout" [t| NonNegative Int |]
576

    
577
-- | Another name for the shutdown timeout, because we like to be
578
-- inconsistent.
579
pShutdownTimeout' :: Field
580
pShutdownTimeout' =
581
  renameField "InstShutdownTimeout" .
582
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
583
  simpleField "timeout" [t| NonNegative Int |]
584

    
585
-- | Whether to shutdown the instance in backup-export.
586
pShutdownInstance :: Field
587
pShutdownInstance = defaultTrue "shutdown"
588

    
589
-- | Whether to force the operation.
590
pForce :: Field
591
pForce = defaultFalse "force"
592

    
593
-- | Whether to ignore offline nodes.
594
pIgnoreOfflineNodes :: Field
595
pIgnoreOfflineNodes = defaultFalse "ignore_offline_nodes"
596

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

    
601
-- | List of nodes.
602
pNodeNames :: Field
603
pNodeNames =
604
  defaultField [| [] |] $ simpleField "node_names" [t| [NonEmptyString] |]
605

    
606
-- | A required node group name (for single-group LUs).
607
pGroupName :: Field
608
pGroupName = simpleField "group_name" [t| NonEmptyString |]
609

    
610
-- | Migration type (live\/non-live).
611
pMigrationMode :: Field
612
pMigrationMode =
613
  renameField "MigrationMode" .
614
  optionalField $
615
  simpleField "mode" [t| MigrationMode |]
616

    
617
-- | Obsolete \'live\' migration mode (boolean).
618
pMigrationLive :: Field
619
pMigrationLive =
620
  renameField "OldLiveMode" . optionalField $ booleanField "live"
621

    
622
-- | Migration cleanup parameter.
623
pMigrationCleanup :: Field
624
pMigrationCleanup = renameField "MigrationCleanup" $ defaultFalse "cleanup"
625

    
626
-- | Whether to force an unknown OS variant.
627
pForceVariant :: Field
628
pForceVariant = defaultFalse "force_variant"
629

    
630
-- | Whether to wait for the disk to synchronize.
631
pWaitForSync :: Field
632
pWaitForSync = defaultTrue "wait_for_sync"
633

    
634
-- | Whether to wait for the disk to synchronize (defaults to false).
635
pWaitForSyncFalse :: Field
636
pWaitForSyncFalse = defaultField [| False |] pWaitForSync
637

    
638
-- | Whether to ignore disk consistency
639
pIgnoreConsistency :: Field
640
pIgnoreConsistency = defaultFalse "ignore_consistency"
641

    
642
-- | Storage name.
643
pStorageName :: Field
644
pStorageName =
645
  renameField "StorageName" $ simpleField "name" [t| NonEmptyString |]
646

    
647
-- | Whether to use synchronization.
648
pUseLocking :: Field
649
pUseLocking = defaultFalse "use_locking"
650

    
651
-- | Whether to employ opportunistic locking for nodes, meaning nodes already
652
-- locked by another opcode won't be considered for instance allocation (only
653
-- when an iallocator is used).
654
pOpportunisticLocking :: Field
655
pOpportunisticLocking = defaultFalse "opportunistic_locking"
656

    
657
-- | Whether to check name.
658
pNameCheck :: Field
659
pNameCheck = defaultTrue "name_check"
660

    
661
-- | Instance allocation policy.
662
pNodeGroupAllocPolicy :: Field
663
pNodeGroupAllocPolicy = optionalField $
664
                        simpleField "alloc_policy" [t| AllocPolicy |]
665

    
666
-- | Default node parameters for group.
667
pGroupNodeParams :: Field
668
pGroupNodeParams = optionalField $ simpleField "ndparams" [t| UncheckedDict |]
669

    
670
-- | Resource(s) to query for.
671
pQueryWhat :: Field
672
pQueryWhat = simpleField "what" [t| Qlang.QueryTypeOp |]
673

    
674
-- | Whether to release locks as soon as possible.
675
pEarlyRelease :: Field
676
pEarlyRelease = defaultFalse "early_release"
677

    
678
-- | Whether to ensure instance's IP address is inactive.
679
pIpCheck :: Field
680
pIpCheck = defaultTrue "ip_check"
681

    
682
-- | Check for conflicting IPs.
683
pIpConflictsCheck :: Field
684
pIpConflictsCheck = defaultTrue "conflicts_check"
685

    
686
-- | Do not remember instance state changes.
687
pNoRemember :: Field
688
pNoRemember = defaultFalse "no_remember"
689

    
690
-- | Target node for instance migration/failover.
691
pMigrationTargetNode :: Field
692
pMigrationTargetNode = optionalNEStringField "target_node"
693

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

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

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

    
708
-- ** Parameters for cluster verification
709

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

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

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

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

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

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

    
739
-- | Whether to hotplug device.
740
pHotplug :: Field
741
pHotplug = defaultFalse "hotplug"
742

    
743
pHotplugIfPossible :: Field
744
pHotplugIfPossible = defaultFalse "hotplug_if_possible"
745

    
746
-- | Whether to remove disks.
747
pKeepDisks :: Field
748
pKeepDisks = defaultFalse "keep_disks"
749

    
750
-- * Parameters for node resource model
751

    
752
-- | Set hypervisor states.
753
pHvState :: Field
754
pHvState = optionalField $ simpleField "hv_state" [t| UncheckedDict |]
755

    
756
-- | Set disk states.
757
pDiskState :: Field
758
pDiskState = optionalField $ simpleField "disk_state" [t| UncheckedDict |]
759

    
760
-- | Whether to ignore ipolicy violations.
761
pIgnoreIpolicy :: Field
762
pIgnoreIpolicy = defaultFalse "ignore_ipolicy"
763

    
764
-- | Allow runtime changes while migrating.
765
pAllowRuntimeChgs :: Field
766
pAllowRuntimeChgs = defaultTrue "allow_runtime_changes"
767

    
768
-- | Utility type for OpClusterSetParams.
769
type TestClusterOsListItem = (DdmSimple, NonEmptyString)
770

    
771
-- | Utility type of OsList.
772
type TestClusterOsList = [TestClusterOsListItem]
773

    
774
-- Utility type for NIC definitions.
775
--type TestNicDef = INicParams
776

    
777
-- | List of instance disks.
778
pInstDisks :: Field
779
pInstDisks = renameField "instDisks" $ simpleField "disks" [t| [IDiskParams] |]
780

    
781
-- | List of instance snaps.
782
pInstSnaps :: Field
783
pInstSnaps =
784
  renameField "instSnaps" $
785
  simpleField "disks" [t| SetSnapParams ISnapParams |]
786

    
787
-- | Instance disk template.
788
pDiskTemplate :: Field
789
pDiskTemplate = simpleField "disk_template" [t| DiskTemplate |]
790

    
791
-- | Instance disk template.
792
pOptDiskTemplate :: Field
793
pOptDiskTemplate =
794
  optionalField .
795
  renameField "OptDiskTemplate" $
796
  simpleField "disk_template" [t| DiskTemplate |]
797

    
798
-- | File driver.
799
pFileDriver :: Field
800
pFileDriver = optionalField $ simpleField "file_driver" [t| FileDriver |]
801

    
802
-- | Directory for storing file-backed disks.
803
pFileStorageDir :: Field
804
pFileStorageDir = optionalNEStringField "file_storage_dir"
805

    
806
-- | Volume group name.
807
pVgName :: Field
808
pVgName = optionalStringField "vg_name"
809

    
810
-- | List of enabled hypervisors.
811
pEnabledHypervisors :: Field
812
pEnabledHypervisors =
813
  optionalField $
814
  simpleField "enabled_hypervisors" [t| NonEmpty Hypervisor |]
815

    
816
-- | List of enabled disk templates.
817
pEnabledDiskTemplates :: Field
818
pEnabledDiskTemplates =
819
  optionalField $
820
  simpleField "enabled_disk_templates" [t| NonEmpty DiskTemplate |]
821

    
822
-- | Selected hypervisor for an instance.
823
pHypervisor :: Field
824
pHypervisor =
825
  optionalField $
826
  simpleField "hypervisor" [t| Hypervisor |]
827

    
828
-- | Cluster-wide hypervisor parameters, hypervisor-dependent.
829
pClusterHvParams :: Field
830
pClusterHvParams =
831
  renameField "ClusterHvParams" .
832
  optionalField $
833
  simpleField "hvparams" [t| Container UncheckedDict |]
834

    
835
-- | Instance hypervisor parameters.
836
pInstHvParams :: Field
837
pInstHvParams =
838
  renameField "InstHvParams" .
839
  defaultField [| toJSObject [] |] $
840
  simpleField "hvparams" [t| UncheckedDict |]
841

    
842
-- | Cluster-wide beparams.
843
pClusterBeParams :: Field
844
pClusterBeParams =
845
  renameField "ClusterBeParams" .
846
  optionalField $ simpleField "beparams" [t| UncheckedDict |]
847

    
848
-- | Instance beparams.
849
pInstBeParams :: Field
850
pInstBeParams =
851
  renameField "InstBeParams" .
852
  defaultField [| toJSObject [] |] $
853
  simpleField "beparams" [t| UncheckedDict |]
854

    
855
-- | Reset instance parameters to default if equal.
856
pResetDefaults :: Field
857
pResetDefaults = defaultFalse "identify_defaults"
858

    
859
-- | Cluster-wide per-OS hypervisor parameter defaults.
860
pOsHvp :: Field
861
pOsHvp = optionalField $ simpleField "os_hvp" [t| Container UncheckedDict |]
862

    
863
-- | Cluster-wide OS parameter defaults.
864
pClusterOsParams :: Field
865
pClusterOsParams =
866
  renameField "ClusterOsParams" .
867
  optionalField $ simpleField "osparams" [t| Container UncheckedDict |]
868

    
869
-- | Instance OS parameters.
870
pInstOsParams :: Field
871
pInstOsParams =
872
  renameField "InstOsParams" . defaultField [| toJSObject [] |] $
873
  simpleField "osparams" [t| UncheckedDict |]
874

    
875
-- | Temporary OS parameters (currently only in reinstall, might be
876
-- added to install as well).
877
pTempOsParams :: Field
878
pTempOsParams =
879
  renameField "TempOsParams" .
880
  optionalField $ simpleField "osparams" [t| UncheckedDict |]
881

    
882
-- | Temporary hypervisor parameters, hypervisor-dependent.
883
pTempHvParams :: Field
884
pTempHvParams =
885
  renameField "TempHvParams" .
886
  defaultField [| toJSObject [] |] $
887
  simpleField "hvparams" [t| UncheckedDict |]
888

    
889
-- | Temporary backend parameters.
890
pTempBeParams :: Field
891
pTempBeParams =
892
  renameField "TempBeParams" .
893
  defaultField [| toJSObject [] |] $
894
  simpleField "beparams" [t| UncheckedDict |]
895

    
896
-- | Candidate pool size.
897
pCandidatePoolSize :: Field
898
pCandidatePoolSize =
899
  optionalField $ simpleField "candidate_pool_size" [t| Positive Int |]
900

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

    
906
-- | Extend UID pool, must be list of lists describing UID ranges (two
907
-- items, start and end inclusive.
908
pAddUids :: Field
909
pAddUids = optionalField $ simpleField "add_uids" [t| [[(Int, Int)]] |]
910

    
911
-- | Shrink UID pool, must be list of lists describing UID ranges (two
912
-- items, start and end inclusive) to be removed.
913
pRemoveUids :: Field
914
pRemoveUids = optionalField $ simpleField "remove_uids" [t| [[(Int, Int)]] |]
915

    
916
-- | Whether to automatically maintain node health.
917
pMaintainNodeHealth :: Field
918
pMaintainNodeHealth = optionalField $ booleanField "maintain_node_health"
919

    
920
-- | Whether to modify and keep in sync the @/etc/hosts@ files of nodes.
921
pModifyEtcHosts :: Field
922
pModifyEtcHosts = optionalField $ booleanField "modify_etc_hosts"
923

    
924
-- | Whether to wipe disks before allocating them to instances.
925
pPreallocWipeDisks :: Field
926
pPreallocWipeDisks = optionalField $ booleanField "prealloc_wipe_disks"
927

    
928
-- | Cluster-wide NIC parameter defaults.
929
pNicParams :: Field
930
pNicParams = optionalField $ simpleField "nicparams" [t| INicParams |]
931

    
932
-- | Instance NIC definitions.
933
pInstNics :: Field
934
pInstNics = simpleField "nics" [t| [INicParams] |]
935

    
936
-- | Cluster-wide node parameter defaults.
937
pNdParams :: Field
938
pNdParams = optionalField $ simpleField "ndparams" [t| UncheckedDict |]
939

    
940
-- | Cluster-wide ipolicy specs.
941
pIpolicy :: Field
942
pIpolicy = optionalField $ simpleField "ipolicy" [t| UncheckedDict |]
943

    
944
-- | DRBD helper program.
945
pDrbdHelper :: Field
946
pDrbdHelper = optionalStringField "drbd_helper"
947

    
948
-- | Default iallocator for cluster.
949
pDefaultIAllocator :: Field
950
pDefaultIAllocator = optionalStringField "default_iallocator"
951

    
952
-- | Master network device.
953
pMasterNetdev :: Field
954
pMasterNetdev = optionalStringField "master_netdev"
955

    
956
-- | Netmask of the master IP.
957
pMasterNetmask :: Field
958
pMasterNetmask =
959
  optionalField $ simpleField "master_netmask" [t| NonNegative Int |]
960

    
961
-- | List of reserved LVs.
962
pReservedLvs :: Field
963
pReservedLvs =
964
  optionalField $ simpleField "reserved_lvs" [t| [NonEmptyString] |]
965

    
966
-- | Modify list of hidden operating systems: each modification must
967
-- have two items, the operation and the OS name; the operation can be
968
-- add or remove.
969
pHiddenOs :: Field
970
pHiddenOs = optionalField $ simpleField "hidden_os" [t| TestClusterOsList |]
971

    
972
-- | Modify list of blacklisted operating systems: each modification
973
-- must have two items, the operation and the OS name; the operation
974
-- can be add or remove.
975
pBlacklistedOs :: Field
976
pBlacklistedOs =
977
  optionalField $ simpleField "blacklisted_os" [t| TestClusterOsList |]
978

    
979
-- | Whether to use an external master IP address setup script.
980
pUseExternalMipScript :: Field
981
pUseExternalMipScript = optionalField $ booleanField "use_external_mip_script"
982

    
983
-- | Requested fields.
984
pQueryFields :: Field
985
pQueryFields = simpleField "fields" [t| [NonEmptyString] |]
986

    
987
-- | Query filter.
988
pQueryFilter :: Field
989
pQueryFilter = simpleField "qfilter" [t| Qlang.Filter String |]
990

    
991
-- | OOB command to run.
992
pOobCommand :: Field
993
pOobCommand = simpleField "command" [t| OobCommand |]
994

    
995
-- | Timeout before the OOB helper will be terminated.
996
pOobTimeout :: Field
997
pOobTimeout =
998
  defaultField [| C.oobTimeout |] $ simpleField "timeout" [t| Int |]
999

    
1000
-- | Ignores the node offline status for power off.
1001
pIgnoreStatus :: Field
1002
pIgnoreStatus = defaultFalse "ignore_status"
1003

    
1004
-- | Time in seconds to wait between powering on nodes.
1005
pPowerDelay :: Field
1006
pPowerDelay =
1007
  -- FIXME: we can't use the proper type "NonNegative Double", since
1008
  -- the default constant is a plain Double, not a non-negative one.
1009
  defaultField [| C.oobPowerDelay |] $
1010
  simpleField "power_delay" [t| Double |]
1011

    
1012
-- | Primary IP address.
1013
pPrimaryIp :: Field
1014
pPrimaryIp = optionalStringField "primary_ip"
1015

    
1016
-- | Secondary IP address.
1017
pSecondaryIp :: Field
1018
pSecondaryIp = optionalNEStringField "secondary_ip"
1019

    
1020
-- | Whether node is re-added to cluster.
1021
pReadd :: Field
1022
pReadd = defaultFalse "readd"
1023

    
1024
-- | Initial node group.
1025
pNodeGroup :: Field
1026
pNodeGroup = optionalNEStringField "group"
1027

    
1028
-- | Whether node can become master or master candidate.
1029
pMasterCapable :: Field
1030
pMasterCapable = optionalField $ booleanField "master_capable"
1031

    
1032
-- | Whether node can host instances.
1033
pVmCapable :: Field
1034
pVmCapable = optionalField $ booleanField "vm_capable"
1035

    
1036
-- | List of names.
1037
pNames :: Field
1038
pNames = defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
1039

    
1040
-- | List of node names.
1041
pNodes :: Field
1042
pNodes = defaultField [| [] |] $ simpleField "nodes" [t| [NonEmptyString] |]
1043

    
1044
-- | Required list of node names.
1045
pRequiredNodes :: Field
1046
pRequiredNodes =
1047
  renameField "ReqNodes " $ simpleField "nodes" [t| [NonEmptyString] |]
1048

    
1049
-- | Storage type.
1050
pStorageType :: Field
1051
pStorageType = simpleField "storage_type" [t| StorageType |]
1052

    
1053
-- | Storage changes (unchecked).
1054
pStorageChanges :: Field
1055
pStorageChanges = simpleField "changes" [t| UncheckedDict |]
1056

    
1057
-- | Whether the node should become a master candidate.
1058
pMasterCandidate :: Field
1059
pMasterCandidate = optionalField $ booleanField "master_candidate"
1060

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

    
1065
-- | Whether the node should be marked as drained.
1066
pDrained ::Field
1067
pDrained = optionalField $ booleanField "drained"
1068

    
1069
-- | Whether node(s) should be promoted to master candidate if necessary.
1070
pAutoPromote :: Field
1071
pAutoPromote = defaultFalse "auto_promote"
1072

    
1073
-- | Whether the node should be marked as powered
1074
pPowered :: Field
1075
pPowered = optionalField $ booleanField "powered"
1076

    
1077
-- | Iallocator for deciding the target node for shared-storage
1078
-- instances during migrate and failover.
1079
pIallocator :: Field
1080
pIallocator = optionalNEStringField "iallocator"
1081

    
1082
-- | New secondary node.
1083
pRemoteNode :: Field
1084
pRemoteNode = optionalNEStringField "remote_node"
1085

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

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

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

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

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

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

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

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

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

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

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

    
1135
-- | Source directory for import.
1136
pSrcPath :: Field
1137
pSrcPath = optionalNEStringField "src_path"
1138

    
1139
-- | Whether to start instance after creation.
1140
pStartInstance :: Field
1141
pStartInstance = defaultTrue "start"
1142

    
1143
-- | Instance tags. FIXME: unify/simplify with pTags, once that
1144
-- migrates to NonEmpty String.
1145
pInstTags :: Field
1146
pInstTags =
1147
  renameField "InstTags" .
1148
  defaultField [| [] |] $
1149
  simpleField "tags" [t| [NonEmptyString] |]
1150

    
1151
-- | Unchecked list of OpInstanceCreate, used in OpInstanceMultiAlloc.
1152
pMultiAllocInstances :: Field
1153
pMultiAllocInstances =
1154
  renameField "InstMultiAlloc" .
1155
  defaultField [| [] |] $
1156
  simpleField "instances"[t| UncheckedList |]
1157

    
1158
-- | Ignore failures parameter.
1159
pIgnoreFailures :: Field
1160
pIgnoreFailures = defaultFalse "ignore_failures"
1161

    
1162
-- | New instance or cluster name.
1163
pNewName :: Field
1164
pNewName = simpleField "new_name" [t| NonEmptyString |]
1165

    
1166
-- | Whether to start the instance even if secondary disks are failing.
1167
pIgnoreSecondaries :: Field
1168
pIgnoreSecondaries = defaultFalse "ignore_secondaries"
1169

    
1170
-- | How to reboot the instance.
1171
pRebootType :: Field
1172
pRebootType = simpleField "reboot_type" [t| RebootType |]
1173

    
1174
-- | Whether to ignore recorded disk size.
1175
pIgnoreDiskSize :: Field
1176
pIgnoreDiskSize = defaultFalse "ignore_size"
1177

    
1178
-- | Disk list for recreate disks.
1179
pRecreateDisksInfo :: Field
1180
pRecreateDisksInfo =
1181
  renameField "RecreateDisksInfo" .
1182
  defaultField [| RecreateDisksAll |] $
1183
  simpleField "disks" [t| RecreateDisksInfo |]
1184

    
1185
-- | Whether to only return configuration data without querying nodes.
1186
pStatic :: Field
1187
pStatic = defaultFalse "static"
1188

    
1189
-- | InstanceSetParams NIC changes.
1190
pInstParamsNicChanges :: Field
1191
pInstParamsNicChanges =
1192
  renameField "InstNicChanges" .
1193
  defaultField [| SetParamsEmpty |] $
1194
  simpleField "nics" [t| SetParamsMods INicParams |]
1195

    
1196
-- | InstanceSetParams Disk changes.
1197
pInstParamsDiskChanges :: Field
1198
pInstParamsDiskChanges =
1199
  renameField "InstDiskChanges" .
1200
  defaultField [| SetParamsEmpty |] $
1201
  simpleField "disks" [t| SetParamsMods IDiskParams |]
1202

    
1203
-- | New runtime memory.
1204
pRuntimeMem :: Field
1205
pRuntimeMem = optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1206

    
1207
-- | Change the instance's OS without reinstalling the instance
1208
pOsNameChange :: Field
1209
pOsNameChange = optionalNEStringField "os_name"
1210

    
1211
-- | Disk index for e.g. grow disk.
1212
pDiskIndex :: Field
1213
pDiskIndex = renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
1214

    
1215
-- | Disk amount to add or grow to.
1216
pDiskChgAmount :: Field
1217
pDiskChgAmount =
1218
  renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
1219

    
1220
-- | Whether the amount parameter is an absolute target or a relative one.
1221
pDiskChgAbsolute :: Field
1222
pDiskChgAbsolute = renameField "DiskChkAbsolute" $ defaultFalse "absolute"
1223

    
1224
-- | Destination group names or UUIDs (defaults to \"all but current group\".
1225
pTargetGroups :: Field
1226
pTargetGroups =
1227
  optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
1228

    
1229
-- | Export mode field.
1230
pExportMode :: Field
1231
pExportMode =
1232
  renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1233

    
1234
-- | Export target_node field, depends on mode.
1235
pExportTargetNode :: Field
1236
pExportTargetNode =
1237
  renameField "ExportTarget" $
1238
  simpleField "target_node" [t| ExportTarget |]
1239

    
1240
-- | Whether to remove instance after export.
1241
pRemoveInstance :: Field
1242
pRemoveInstance = defaultFalse "remove_instance"
1243

    
1244
-- | Whether to ignore failures while removing instances.
1245
pIgnoreRemoveFailures :: Field
1246
pIgnoreRemoveFailures = defaultFalse "ignore_remove_failures"
1247

    
1248
-- | Name of X509 key (remote export only).
1249
pX509KeyName :: Field
1250
pX509KeyName = optionalField $ simpleField "x509_key_name" [t| UncheckedList |]
1251

    
1252
-- | Destination X509 CA (remote export only).
1253
pX509DestCA :: Field
1254
pX509DestCA = optionalNEStringField "destination_x509_ca"
1255

    
1256
-- | Search pattern (regular expression). FIXME: this should be
1257
-- compiled at load time?
1258
pTagSearchPattern :: Field
1259
pTagSearchPattern =
1260
  renameField "TagSearchPattern" $ simpleField "pattern" [t| NonEmptyString |]
1261

    
1262
-- | Restricted command name.
1263
pRestrictedCommand :: Field
1264
pRestrictedCommand =
1265
  renameField "RestrictedCommand" $
1266
  simpleField "command" [t| NonEmptyString |]
1267

    
1268
-- | Replace disks mode.
1269
pReplaceDisksMode :: Field
1270
pReplaceDisksMode =
1271
  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1272

    
1273
-- | List of disk indices.
1274
pReplaceDisksList :: Field
1275
pReplaceDisksList =
1276
  renameField "ReplaceDisksList" $ simpleField "disks" [t| [DiskIndex] |]
1277

    
1278
-- | Whether do allow failover in migrations.
1279
pAllowFailover :: Field
1280
pAllowFailover = defaultFalse "allow_failover"
1281

    
1282
-- * Test opcode parameters
1283

    
1284
-- | Duration parameter for 'OpTestDelay'.
1285
pDelayDuration :: Field
1286
pDelayDuration =
1287
  renameField "DelayDuration" $ simpleField "duration" [t| Double |]
1288

    
1289
-- | on_master field for 'OpTestDelay'.
1290
pDelayOnMaster :: Field
1291
pDelayOnMaster = renameField "DelayOnMaster" $ defaultTrue "on_master"
1292

    
1293
-- | on_nodes field for 'OpTestDelay'.
1294
pDelayOnNodes :: Field
1295
pDelayOnNodes =
1296
  renameField "DelayOnNodes" .
1297
  defaultField [| [] |] $
1298
  simpleField "on_nodes" [t| [NonEmptyString] |]
1299

    
1300
-- | Repeat parameter for OpTestDelay.
1301
pDelayRepeat :: Field
1302
pDelayRepeat =
1303
  renameField "DelayRepeat" .
1304
  defaultField [| forceNonNeg (0::Int) |] $
1305
  simpleField "repeat" [t| NonNegative Int |]
1306

    
1307
-- | IAllocator test direction.
1308
pIAllocatorDirection :: Field
1309
pIAllocatorDirection =
1310
  renameField "IAllocatorDirection" $
1311
  simpleField "direction" [t| IAllocatorTestDir |]
1312

    
1313
-- | IAllocator test mode.
1314
pIAllocatorMode :: Field
1315
pIAllocatorMode =
1316
  renameField "IAllocatorMode" $
1317
  simpleField "mode" [t| IAllocatorMode |]
1318

    
1319
-- | IAllocator target name (new instance, node to evac, etc.).
1320
pIAllocatorReqName :: Field
1321
pIAllocatorReqName =
1322
  renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
1323

    
1324
-- | Custom OpTestIAllocator nics.
1325
pIAllocatorNics :: Field
1326
pIAllocatorNics =
1327
  renameField "IAllocatorNics" $ simpleField "nics" [t| [UncheckedDict] |]
1328

    
1329
-- | Custom OpTestAllocator disks.
1330
pIAllocatorDisks :: Field
1331
pIAllocatorDisks =
1332
  renameField "IAllocatorDisks" $ simpleField "disks" [t| UncheckedList |]
1333

    
1334
-- | IAllocator memory field.
1335
pIAllocatorMemory :: Field
1336
pIAllocatorMemory =
1337
  renameField "IAllocatorMem" .
1338
  optionalField $
1339
  simpleField "memory" [t| NonNegative Int |]
1340

    
1341
-- | IAllocator vcpus field.
1342
pIAllocatorVCpus :: Field
1343
pIAllocatorVCpus =
1344
  renameField "IAllocatorVCpus" .
1345
  optionalField $
1346
  simpleField "vcpus" [t| NonNegative Int |]
1347

    
1348
-- | IAllocator os field.
1349
pIAllocatorOs :: Field
1350
pIAllocatorOs = renameField "IAllocatorOs" $ optionalNEStringField "os"
1351

    
1352
-- | IAllocator instances field.
1353
pIAllocatorInstances :: Field
1354
pIAllocatorInstances =
1355
  renameField "IAllocatorInstances " .
1356
  optionalField $
1357
  simpleField "instances" [t| [NonEmptyString] |]
1358

    
1359
-- | IAllocator evac mode.
1360
pIAllocatorEvacMode :: Field
1361
pIAllocatorEvacMode =
1362
  renameField "IAllocatorEvacMode" .
1363
  optionalField $
1364
  simpleField "evac_mode" [t| NodeEvacMode |]
1365

    
1366
-- | IAllocator spindle use.
1367
pIAllocatorSpindleUse :: Field
1368
pIAllocatorSpindleUse =
1369
  renameField "IAllocatorSpindleUse" .
1370
  defaultField [| forceNonNeg (1::Int) |] $
1371
  simpleField "spindle_use" [t| NonNegative Int |]
1372

    
1373
-- | IAllocator count field.
1374
pIAllocatorCount :: Field
1375
pIAllocatorCount =
1376
  renameField "IAllocatorCount" .
1377
  defaultField [| forceNonNeg (1::Int) |] $
1378
  simpleField "count" [t| NonNegative Int |]
1379

    
1380
-- | 'OpTestJqueue' notify_waitlock.
1381
pJQueueNotifyWaitLock :: Field
1382
pJQueueNotifyWaitLock = defaultFalse "notify_waitlock"
1383

    
1384
-- | 'OpTestJQueue' notify_exec.
1385
pJQueueNotifyExec :: Field
1386
pJQueueNotifyExec = defaultFalse "notify_exec"
1387

    
1388
-- | 'OpTestJQueue' log_messages.
1389
pJQueueLogMessages :: Field
1390
pJQueueLogMessages =
1391
  defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
1392

    
1393
-- | 'OpTestJQueue' fail attribute.
1394
pJQueueFail :: Field
1395
pJQueueFail =
1396
  renameField "JQueueFail" $ defaultFalse "fail"
1397

    
1398
-- | 'OpTestDummy' result field.
1399
pTestDummyResult :: Field
1400
pTestDummyResult =
1401
  renameField "TestDummyResult" $ simpleField "result" [t| UncheckedValue |]
1402

    
1403
-- | 'OpTestDummy' messages field.
1404
pTestDummyMessages :: Field
1405
pTestDummyMessages =
1406
  renameField "TestDummyMessages" $
1407
  simpleField "messages" [t| UncheckedValue |]
1408

    
1409
-- | 'OpTestDummy' fail field.
1410
pTestDummyFail :: Field
1411
pTestDummyFail =
1412
  renameField "TestDummyFail" $ simpleField "fail" [t| UncheckedValue |]
1413

    
1414
-- | 'OpTestDummy' submit_jobs field.
1415
pTestDummySubmitJobs :: Field
1416
pTestDummySubmitJobs =
1417
  renameField "TestDummySubmitJobs" $
1418
  simpleField "submit_jobs" [t| UncheckedValue |]
1419

    
1420
-- * Network parameters
1421

    
1422
-- | Network name.
1423
pNetworkName :: Field
1424
pNetworkName = simpleField "network_name" [t| NonEmptyString |]
1425

    
1426
-- | Network address (IPv4 subnet). FIXME: no real type for this.
1427
pNetworkAddress4 :: Field
1428
pNetworkAddress4 =
1429
  renameField "NetworkAddress4" $
1430
  simpleField "network" [t| NonEmptyString |]
1431

    
1432
-- | Network gateway (IPv4 address). FIXME: no real type for this.
1433
pNetworkGateway4 :: Field
1434
pNetworkGateway4 =
1435
  renameField "NetworkGateway4" $
1436
  optionalNEStringField "gateway"
1437

    
1438
-- | Network address (IPv6 subnet). FIXME: no real type for this.
1439
pNetworkAddress6 :: Field
1440
pNetworkAddress6 =
1441
  renameField "NetworkAddress6" $
1442
  optionalNEStringField "network6"
1443

    
1444
-- | Network gateway (IPv6 address). FIXME: no real type for this.
1445
pNetworkGateway6 :: Field
1446
pNetworkGateway6 =
1447
  renameField "NetworkGateway6" $
1448
  optionalNEStringField "gateway6"
1449

    
1450
-- | Network specific mac prefix (that overrides the cluster one).
1451
pNetworkMacPrefix :: Field
1452
pNetworkMacPrefix =
1453
  renameField "NetMacPrefix" $
1454
  optionalNEStringField "mac_prefix"
1455

    
1456
-- | Network add reserved IPs.
1457
pNetworkAddRsvdIps :: Field
1458
pNetworkAddRsvdIps =
1459
  renameField "NetworkAddRsvdIps" .
1460
  optionalField $
1461
  simpleField "add_reserved_ips" [t| [NonEmptyString] |]
1462

    
1463
-- | Network remove reserved IPs.
1464
pNetworkRemoveRsvdIps :: Field
1465
pNetworkRemoveRsvdIps =
1466
  renameField "NetworkRemoveRsvdIps" .
1467
  optionalField $
1468
  simpleField "remove_reserved_ips" [t| [NonEmptyString] |]
1469

    
1470
-- | Network mode when connecting to a group.
1471
pNetworkMode :: Field
1472
pNetworkMode = simpleField "network_mode" [t| NICMode |]
1473

    
1474
-- | Network link when connecting to a group.
1475
pNetworkLink :: Field
1476
pNetworkLink = simpleField "network_link" [t| NonEmptyString |]
1477

    
1478
-- * Common opcode parameters
1479

    
1480
-- | Run checks only, don't execute.
1481
pDryRun :: Field
1482
pDryRun = optionalField $ booleanField "dry_run"
1483

    
1484
-- | Debug level.
1485
pDebugLevel :: Field
1486
pDebugLevel = optionalField $ simpleField "debug_level" [t| NonNegative Int |]
1487

    
1488
-- | Opcode priority. Note: python uses a separate constant, we're
1489
-- using the actual value we know it's the default.
1490
pOpPriority :: Field
1491
pOpPriority =
1492
  defaultField [| OpPrioNormal |] $
1493
  simpleField "priority" [t| OpSubmitPriority |]
1494

    
1495
-- | Job dependencies.
1496
pDependencies :: Field
1497
pDependencies =
1498
  optionalNullSerField $ simpleField "depends" [t| [JobDependency] |]
1499

    
1500
-- | Comment field.
1501
pComment :: Field
1502
pComment = optionalNullSerField $ stringField "comment"
1503

    
1504
-- | Reason trail field.
1505
pReason :: Field
1506
pReason = simpleField C.opcodeReason [t| ReasonTrail |]
1507

    
1508
-- * Entire opcode parameter list
1509

    
1510
-- | Old-style query opcode, with locking.
1511
dOldQuery :: [Field]
1512
dOldQuery =
1513
  [ pOutputFields
1514
  , pNames
1515
  , pUseLocking
1516
  ]
1517

    
1518
-- | Old-style query opcode, without locking.
1519
dOldQueryNoLocking :: [Field]
1520
dOldQueryNoLocking =
1521
  [ pOutputFields
1522
  , pNames
1523
  ]