Merge branch 'stable-2.8' into 'master'
[ganeti-local] / src / Ganeti / OpParams.hs
1 {-# LANGUAGE TemplateHaskell #-}
2
3 {-| Implementation of opcodes parameters.
4
5 These are defined in a separate module only due to TemplateHaskell
6 stage restrictions - expressions defined in the current module can't
7 be passed to splices. So we have to either parameters/repeat each
8 parameter definition multiple times, or separate them into this
9 module.
10
11 -}
12
13 {-
14
15 Copyright (C) 2012 Google Inc.
16
17 This program is free software; you can redistribute it and/or modify
18 it under the terms of the GNU General Public License as published by
19 the Free Software Foundation; either version 2 of the License, or
20 (at your option) any later version.
21
22 This program is distributed in the hope that it will be useful, but
23 WITHOUT ANY WARRANTY; without even the implied warranty of
24 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
25 General Public License for more details.
26
27 You should have received a copy of the GNU General Public License
28 along with this program; if not, write to the Free Software
29 Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
30 02110-1301, USA.
31
32 -}
33
34 module Ganeti.OpParams
35   ( TagType(..)
36   , TagObject(..)
37   , tagObjectFrom
38   , tagNameOf
39   , decodeTagObject
40   , encodeTagObject
41   , ReplaceDisksMode(..)
42   , DiskIndex
43   , mkDiskIndex
44   , unDiskIndex
45   , DiskAccess(..)
46   , INicParams(..)
47   , IDiskParams(..)
48   , RecreateDisksInfo(..)
49   , DdmOldChanges(..)
50   , SetParamsMods(..)
51   , ExportTarget(..)
52   , pInstanceName
53   , pInstances
54   , pName
55   , pTagsList
56   , pTagsObject
57   , pOutputFields
58   , pShutdownTimeout
59   , pShutdownTimeout'
60   , pShutdownInstance
61   , pForce
62   , pIgnoreOfflineNodes
63   , pNodeName
64   , pNodeUuid
65   , pNodeNames
66   , pNodeUuids
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   , pMigrationTargetNodeUuid
88   , pMoveTargetNode
89   , pMoveTargetNodeUuid
90   , pStartupPaused
91   , pVerbose
92   , pDebugSimulateErrors
93   , pErrorCodes
94   , pSkipChecks
95   , pIgnoreErrors
96   , pOptGroupName
97   , pDiskParams
98   , pHvState
99   , pDiskState
100   , pIgnoreIpolicy
101   , pAllowRuntimeChgs
102   , pInstDisks
103   , pDiskTemplate
104   , pOptDiskTemplate
105   , pFileDriver
106   , pFileStorageDir
107   , pVgName
108   , pEnabledHypervisors
109   , pHypervisor
110   , pClusterHvParams
111   , pInstHvParams
112   , pClusterBeParams
113   , pInstBeParams
114   , pResetDefaults
115   , pOsHvp
116   , pClusterOsParams
117   , pInstOsParams
118   , pCandidatePoolSize
119   , pUidPool
120   , pAddUids
121   , pRemoveUids
122   , pMaintainNodeHealth
123   , pPreallocWipeDisks
124   , pNicParams
125   , pInstNics
126   , pNdParams
127   , pIpolicy
128   , pDrbdHelper
129   , pDefaultIAllocator
130   , pMasterNetdev
131   , pMasterNetmask
132   , pReservedLvs
133   , pHiddenOs
134   , pBlacklistedOs
135   , pUseExternalMipScript
136   , pQueryFields
137   , pQueryFilter
138   , pOobCommand
139   , pOobTimeout
140   , pIgnoreStatus
141   , pPowerDelay
142   , pPrimaryIp
143   , pSecondaryIp
144   , pReadd
145   , pNodeGroup
146   , pMasterCapable
147   , pVmCapable
148   , pNames
149   , pNodes
150   , pRequiredNodes
151   , pRequiredNodeUuids
152   , pStorageType
153   , pStorageChanges
154   , pMasterCandidate
155   , pOffline
156   , pDrained
157   , pAutoPromote
158   , pPowered
159   , pIallocator
160   , pRemoteNode
161   , pRemoteNodeUuid
162   , pEvacMode
163   , pInstCreateMode
164   , pNoInstall
165   , pInstOs
166   , pPrimaryNode
167   , pPrimaryNodeUuid
168   , pSecondaryNode
169   , pSecondaryNodeUuid
170   , pSourceHandshake
171   , pSourceInstance
172   , pSourceShutdownTimeout
173   , pSourceX509Ca
174   , pSrcNode
175   , pSrcNodeUuid
176   , pSrcPath
177   , pStartInstance
178   , pInstTags
179   , pMultiAllocInstances
180   , pTempOsParams
181   , pTempHvParams
182   , pTempBeParams
183   , pIgnoreFailures
184   , pNewName
185   , pIgnoreSecondaries
186   , pRebootType
187   , pIgnoreDiskSize
188   , pRecreateDisksInfo
189   , pStatic
190   , pInstParamsNicChanges
191   , pInstParamsDiskChanges
192   , pRuntimeMem
193   , pOsNameChange
194   , pDiskIndex
195   , pDiskChgAmount
196   , pDiskChgAbsolute
197   , pTargetGroups
198   , pExportMode
199   , pExportTargetNode
200   , pExportTargetNodeUuid
201   , pRemoveInstance
202   , pIgnoreRemoveFailures
203   , pX509KeyName
204   , pX509DestCA
205   , pTagSearchPattern
206   , pRestrictedCommand
207   , pReplaceDisksMode
208   , pReplaceDisksList
209   , pAllowFailover
210   , pDelayDuration
211   , pDelayOnMaster
212   , pDelayOnNodes
213   , pDelayOnNodeUuids
214   , pDelayRepeat
215   , pIAllocatorDirection
216   , pIAllocatorMode
217   , pIAllocatorReqName
218   , pIAllocatorNics
219   , pIAllocatorDisks
220   , pIAllocatorMemory
221   , pIAllocatorVCpus
222   , pIAllocatorOs
223   , pIAllocatorInstances
224   , pIAllocatorEvacMode
225   , pIAllocatorSpindleUse
226   , pIAllocatorCount
227   , pJQueueNotifyWaitLock
228   , pJQueueNotifyExec
229   , pJQueueLogMessages
230   , pJQueueFail
231   , pTestDummyResult
232   , pTestDummyMessages
233   , pTestDummyFail
234   , pTestDummySubmitJobs
235   , pNetworkName
236   , pNetworkAddress4
237   , pNetworkGateway4
238   , pNetworkAddress6
239   , pNetworkGateway6
240   , pNetworkMacPrefix
241   , pNetworkAddRsvdIps
242   , pNetworkRemoveRsvdIps
243   , pNetworkMode
244   , pNetworkLink
245   , pDryRun
246   , pDebugLevel
247   , pOpPriority
248   , pDependencies
249   , pComment
250   , pReason
251   , pEnabledDiskTemplates
252   , dOldQuery
253   , dOldQueryNoLocking
254   ) where
255
256 import Control.Monad (liftM)
257 import qualified Data.Set as Set
258 import Text.JSON (readJSON, showJSON, JSON, JSValue(..), fromJSString,
259                   JSObject, toJSObject)
260 import qualified Text.JSON
261 import Text.JSON.Pretty (pp_value)
262
263 import Ganeti.BasicTypes
264 import qualified Ganeti.Constants as C
265 import Ganeti.THH
266 import Ganeti.JSON
267 import Ganeti.Types
268 import qualified Ganeti.Query.Language as Qlang
269
270 -- * Helper functions and types
271
272 -- * Type aliases
273
274 -- | Build a boolean field.
275 booleanField :: String -> Field
276 booleanField = flip simpleField [t| Bool |]
277
278 -- | Default a field to 'False'.
279 defaultFalse :: String -> Field
280 defaultFalse = defaultField [| False |] . booleanField
281
282 -- | Default a field to 'True'.
283 defaultTrue :: String -> Field
284 defaultTrue = defaultField [| True |] . booleanField
285
286 -- | An alias for a 'String' field.
287 stringField :: String -> Field
288 stringField = flip simpleField [t| String |]
289
290 -- | An alias for an optional string field.
291 optionalStringField :: String -> Field
292 optionalStringField = optionalField . stringField
293
294 -- | An alias for an optional non-empty string field.
295 optionalNEStringField :: String -> Field
296 optionalNEStringField = optionalField . flip simpleField [t| NonEmptyString |]
297
298 -- | Unchecked value, should be replaced by a better definition.
299 type UncheckedValue = JSValue
300
301 -- | Unchecked dict, should be replaced by a better definition.
302 type UncheckedDict = JSObject JSValue
303
304 -- | Unchecked list, shoild be replaced by a better definition.
305 type UncheckedList = [JSValue]
306
307 -- | Function to force a non-negative value, without returning via a
308 -- monad. This is needed for, and should be used /only/ in the case of
309 -- forcing constants. In case the constant is wrong (< 0), this will
310 -- become a runtime error.
311 forceNonNeg :: (Num a, Ord a, Show a) => a -> NonNegative a
312 forceNonNeg i = case mkNonNegative i of
313                   Ok n -> n
314                   Bad msg -> error msg
315
316 -- ** Tags
317
318 -- | Data type representing what items do the tag operations apply to.
319 $(declareSADT "TagType"
320   [ ("TagTypeInstance", 'C.tagInstance)
321   , ("TagTypeNode",     'C.tagNode)
322   , ("TagTypeGroup",    'C.tagNodegroup)
323   , ("TagTypeCluster",  'C.tagCluster)
324   ])
325 $(makeJSONInstance ''TagType)
326
327 -- | Data type holding a tag object (type and object name).
328 data TagObject = TagInstance String
329                | TagNode     String
330                | TagGroup    String
331                | TagCluster
332                deriving (Show, Eq)
333
334 -- | Tag type for a given tag object.
335 tagTypeOf :: TagObject -> TagType
336 tagTypeOf (TagInstance {}) = TagTypeInstance
337 tagTypeOf (TagNode     {}) = TagTypeNode
338 tagTypeOf (TagGroup    {}) = TagTypeGroup
339 tagTypeOf (TagCluster  {}) = TagTypeCluster
340
341 -- | Gets the potential tag object name.
342 tagNameOf :: TagObject -> Maybe String
343 tagNameOf (TagInstance s) = Just s
344 tagNameOf (TagNode     s) = Just s
345 tagNameOf (TagGroup    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 TagTypeCluster   JSNull      = return TagCluster
355 tagObjectFrom t v =
356   fail $ "Invalid tag type/name combination: " ++ show t ++ "/" ++
357          show (pp_value v)
358
359 -- | Name of the tag \"name\" field.
360 tagNameField :: String
361 tagNameField = "name"
362
363 -- | Custom encoder for 'TagObject' as represented in an opcode.
364 encodeTagObject :: TagObject -> (JSValue, [(String, JSValue)])
365 encodeTagObject t = ( showJSON (tagTypeOf t)
366                     , [(tagNameField, maybe JSNull showJSON (tagNameOf t))] )
367
368 -- | Custom decoder for 'TagObject' as represented in an opcode.
369 decodeTagObject :: (Monad m) => [(String, JSValue)] -> JSValue -> m TagObject
370 decodeTagObject obj kind = do
371   ttype <- fromJVal kind
372   tname <- fromObj obj tagNameField
373   tagObjectFrom ttype tname
374
375 -- ** Disks
376
377 -- | Replace disks type.
378 $(declareSADT "ReplaceDisksMode"
379   [ ("ReplaceOnPrimary",    'C.replaceDiskPri)
380   , ("ReplaceOnSecondary",  'C.replaceDiskSec)
381   , ("ReplaceNewSecondary", 'C.replaceDiskChg)
382   , ("ReplaceAuto",         'C.replaceDiskAuto)
383   ])
384 $(makeJSONInstance ''ReplaceDisksMode)
385
386 -- | Disk index type (embedding constraints on the index value via a
387 -- smart constructor).
388 newtype DiskIndex = DiskIndex { unDiskIndex :: Int }
389   deriving (Show, Eq, Ord)
390
391 -- | Smart constructor for 'DiskIndex'.
392 mkDiskIndex :: (Monad m) => Int -> m DiskIndex
393 mkDiskIndex i | i >= 0 && i < C.maxDisks = return (DiskIndex i)
394               | otherwise = fail $ "Invalid value for disk index '" ++
395                             show i ++ "', required between 0 and " ++
396                             show C.maxDisks
397
398 instance JSON DiskIndex where
399   readJSON v = readJSON v >>= mkDiskIndex
400   showJSON = showJSON . unDiskIndex
401
402 -- ** I* param types
403
404 -- | Type holding disk access modes.
405 $(declareSADT "DiskAccess"
406   [ ("DiskReadOnly",  'C.diskRdonly)
407   , ("DiskReadWrite", 'C.diskRdwr)
408   ])
409 $(makeJSONInstance ''DiskAccess)
410
411 -- | NIC modification definition.
412 $(buildObject "INicParams" "inic"
413   [ optionalField $ simpleField C.inicMac  [t| NonEmptyString |]
414   , optionalField $ simpleField C.inicIp   [t| String         |]
415   , optionalField $ simpleField C.inicMode [t| NonEmptyString |]
416   , optionalField $ simpleField C.inicLink [t| NonEmptyString |]
417   , optionalField $ simpleField C.inicName [t| NonEmptyString |]
418   ])
419
420 -- | Disk modification definition. FIXME: disksize should be VTYPE_UNIT.
421 $(buildObject "IDiskParams" "idisk"
422   [ optionalField $ simpleField C.idiskSize   [t| Int            |]
423   , optionalField $ simpleField C.idiskMode   [t| DiskAccess     |]
424   , optionalField $ simpleField C.idiskAdopt  [t| NonEmptyString |]
425   , optionalField $ simpleField C.idiskVg     [t| NonEmptyString |]
426   , optionalField $ simpleField C.idiskMetavg [t| NonEmptyString |]
427   , optionalField $ simpleField C.idiskName   [t| NonEmptyString |]
428   ])
429
430 -- | Disk changes type for OpInstanceRecreateDisks. This is a bit
431 -- strange, because the type in Python is something like Either
432 -- [DiskIndex] [DiskChanges], but we can't represent the type of an
433 -- empty list in JSON, so we have to add a custom case for the empty
434 -- list.
435 data RecreateDisksInfo
436   = RecreateDisksAll
437   | RecreateDisksIndices (NonEmpty DiskIndex)
438   | RecreateDisksParams (NonEmpty (DiskIndex, IDiskParams))
439     deriving (Eq, Show)
440
441 readRecreateDisks :: JSValue -> Text.JSON.Result RecreateDisksInfo
442 readRecreateDisks (JSArray []) = return RecreateDisksAll
443 readRecreateDisks v =
444   case readJSON v::Text.JSON.Result [DiskIndex] of
445     Text.JSON.Ok indices -> liftM RecreateDisksIndices (mkNonEmpty indices)
446     _ -> case readJSON v::Text.JSON.Result [(DiskIndex, IDiskParams)] of
447            Text.JSON.Ok params -> liftM RecreateDisksParams (mkNonEmpty params)
448            _ -> fail $ "Can't parse disk information as either list of disk"
449                 ++ " indices or list of disk parameters; value received:"
450                 ++ show (pp_value v)
451
452 instance JSON RecreateDisksInfo where
453   readJSON = readRecreateDisks
454   showJSON  RecreateDisksAll            = showJSON ()
455   showJSON (RecreateDisksIndices idx)   = showJSON idx
456   showJSON (RecreateDisksParams params) = showJSON params
457
458 -- | Simple type for old-style ddm changes.
459 data DdmOldChanges = DdmOldIndex (NonNegative Int)
460                    | DdmOldMod DdmSimple
461                      deriving (Eq, Show)
462
463 readDdmOldChanges :: JSValue -> Text.JSON.Result DdmOldChanges
464 readDdmOldChanges v =
465   case readJSON v::Text.JSON.Result (NonNegative Int) of
466     Text.JSON.Ok nn -> return $ DdmOldIndex nn
467     _ -> case readJSON v::Text.JSON.Result DdmSimple of
468            Text.JSON.Ok ddms -> return $ DdmOldMod ddms
469            _ -> fail $ "Can't parse value '" ++ show (pp_value v) ++ "' as"
470                 ++ " either index or modification"
471
472 instance JSON DdmOldChanges where
473   showJSON (DdmOldIndex i) = showJSON i
474   showJSON (DdmOldMod m)   = showJSON m
475   readJSON = readDdmOldChanges
476
477 -- | Instance disk or nic modifications.
478 data SetParamsMods a
479   = SetParamsEmpty
480   | SetParamsDeprecated (NonEmpty (DdmOldChanges, a))
481   | SetParamsNew (NonEmpty (DdmFull, Int, a))
482     deriving (Eq, Show)
483
484 -- | Custom deserialiser for 'SetParamsMods'.
485 readSetParams :: (JSON a) => JSValue -> Text.JSON.Result (SetParamsMods a)
486 readSetParams (JSArray []) = return SetParamsEmpty
487 readSetParams v =
488   case readJSON v::Text.JSON.Result [(DdmOldChanges, JSValue)] of
489     Text.JSON.Ok _ -> liftM SetParamsDeprecated $ readJSON v
490     _ -> liftM SetParamsNew $ readJSON v
491
492 instance (JSON a) => JSON (SetParamsMods a) where
493   showJSON SetParamsEmpty = showJSON ()
494   showJSON (SetParamsDeprecated v) = showJSON v
495   showJSON (SetParamsNew v) = showJSON v
496   readJSON = readSetParams
497
498 -- | Custom type for target_node parameter of OpBackupExport, which
499 -- varies depending on mode. FIXME: this uses an UncheckedList since
500 -- we don't care about individual rows (just like the Python code
501 -- tests). But the proper type could be parsed if we wanted.
502 data ExportTarget = ExportTargetLocal NonEmptyString
503                   | ExportTargetRemote UncheckedList
504                     deriving (Eq, Show)
505
506 -- | Custom reader for 'ExportTarget'.
507 readExportTarget :: JSValue -> Text.JSON.Result ExportTarget
508 readExportTarget (JSString s) = liftM ExportTargetLocal $
509                                 mkNonEmpty (fromJSString s)
510 readExportTarget (JSArray arr) = return $ ExportTargetRemote arr
511 readExportTarget v = fail $ "Invalid value received for 'target_node': " ++
512                      show (pp_value v)
513
514 instance JSON ExportTarget where
515   showJSON (ExportTargetLocal s)  = showJSON s
516   showJSON (ExportTargetRemote l) = showJSON l
517   readJSON = readExportTarget
518
519 -- * Parameters
520
521 -- | A required instance name (for single-instance LUs).
522 pInstanceName :: Field
523 pInstanceName = simpleField "instance_name" [t| String |]
524
525 -- | A list of instances.
526 pInstances :: Field
527 pInstances = defaultField [| [] |] $
528              simpleField "instances" [t| [NonEmptyString] |]
529
530 -- | A generic name.
531 pName :: Field
532 pName = simpleField "name" [t| NonEmptyString |]
533
534 -- | Tags list.
535 pTagsList :: Field
536 pTagsList = simpleField "tags" [t| [String] |]
537
538 -- | Tags object.
539 pTagsObject :: Field
540 pTagsObject =
541   customField 'decodeTagObject 'encodeTagObject [tagNameField] $
542   simpleField "kind" [t| TagObject |]
543
544 -- | Selected output fields.
545 pOutputFields :: Field
546 pOutputFields = simpleField "output_fields" [t| [NonEmptyString] |]
547
548 -- | How long to wait for instance to shut down.
549 pShutdownTimeout :: Field
550 pShutdownTimeout = defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
551                    simpleField "shutdown_timeout" [t| NonNegative Int |]
552
553 -- | Another name for the shutdown timeout, because we like to be
554 -- inconsistent.
555 pShutdownTimeout' :: Field
556 pShutdownTimeout' =
557   renameField "InstShutdownTimeout" .
558   defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
559   simpleField "timeout" [t| NonNegative Int |]
560
561 -- | Whether to shutdown the instance in backup-export.
562 pShutdownInstance :: Field
563 pShutdownInstance = defaultTrue "shutdown"
564
565 -- | Whether to force the operation.
566 pForce :: Field
567 pForce = defaultFalse "force"
568
569 -- | Whether to ignore offline nodes.
570 pIgnoreOfflineNodes :: Field
571 pIgnoreOfflineNodes = defaultFalse "ignore_offline_nodes"
572
573 -- | A required node name (for single-node LUs).
574 pNodeName :: Field
575 pNodeName = simpleField "node_name" [t| NonEmptyString |]
576
577 -- | A node UUID (for single-node LUs).
578 pNodeUuid :: Field
579 pNodeUuid = optionalField $ simpleField "node_uuid" [t| NonEmptyString |]
580
581 -- | List of nodes.
582 pNodeNames :: Field
583 pNodeNames =
584   defaultField [| [] |] $ simpleField "node_names" [t| [NonEmptyString] |]
585
586 -- | List of node UUIDs.
587 pNodeUuids :: Field
588 pNodeUuids =
589   optionalField $ simpleField "node_uuids" [t| [NonEmptyString] |]
590
591 -- | A required node group name (for single-group LUs).
592 pGroupName :: Field
593 pGroupName = simpleField "group_name" [t| NonEmptyString |]
594
595 -- | Migration type (live\/non-live).
596 pMigrationMode :: Field
597 pMigrationMode =
598   renameField "MigrationMode" .
599   optionalField $
600   simpleField "mode" [t| MigrationMode |]
601
602 -- | Obsolete \'live\' migration mode (boolean).
603 pMigrationLive :: Field
604 pMigrationLive =
605   renameField "OldLiveMode" . optionalField $ booleanField "live"
606
607 -- | Migration cleanup parameter.
608 pMigrationCleanup :: Field
609 pMigrationCleanup = renameField "MigrationCleanup" $ defaultFalse "cleanup"
610
611 -- | Whether to force an unknown OS variant.
612 pForceVariant :: Field
613 pForceVariant = defaultFalse "force_variant"
614
615 -- | Whether to wait for the disk to synchronize.
616 pWaitForSync :: Field
617 pWaitForSync = defaultTrue "wait_for_sync"
618
619 -- | Whether to wait for the disk to synchronize (defaults to false).
620 pWaitForSyncFalse :: Field
621 pWaitForSyncFalse = defaultField [| False |] pWaitForSync
622
623 -- | Whether to ignore disk consistency
624 pIgnoreConsistency :: Field
625 pIgnoreConsistency = defaultFalse "ignore_consistency"
626
627 -- | Storage name.
628 pStorageName :: Field
629 pStorageName =
630   renameField "StorageName" $ simpleField "name" [t| NonEmptyString |]
631
632 -- | Whether to use synchronization.
633 pUseLocking :: Field
634 pUseLocking = defaultFalse "use_locking"
635
636 -- | Whether to employ opportunistic locking for nodes, meaning nodes already
637 -- locked by another opcode won't be considered for instance allocation (only
638 -- when an iallocator is used).
639 pOpportunisticLocking :: Field
640 pOpportunisticLocking = defaultFalse "opportunistic_locking"
641
642 -- | Whether to check name.
643 pNameCheck :: Field
644 pNameCheck = defaultTrue "name_check"
645
646 -- | Instance allocation policy.
647 pNodeGroupAllocPolicy :: Field
648 pNodeGroupAllocPolicy = optionalField $
649                         simpleField "alloc_policy" [t| AllocPolicy |]
650
651 -- | Default node parameters for group.
652 pGroupNodeParams :: Field
653 pGroupNodeParams = optionalField $ simpleField "ndparams" [t| UncheckedDict |]
654
655 -- | Resource(s) to query for.
656 pQueryWhat :: Field
657 pQueryWhat = simpleField "what" [t| Qlang.QueryTypeOp |]
658
659 -- | Whether to release locks as soon as possible.
660 pEarlyRelease :: Field
661 pEarlyRelease = defaultFalse "early_release"
662
663 -- | Whether to ensure instance's IP address is inactive.
664 pIpCheck :: Field
665 pIpCheck = defaultTrue "ip_check"
666
667 -- | Check for conflicting IPs.
668 pIpConflictsCheck :: Field
669 pIpConflictsCheck = defaultTrue "conflicts_check"
670
671 -- | Do not remember instance state changes.
672 pNoRemember :: Field
673 pNoRemember = defaultFalse "no_remember"
674
675 -- | Target node for instance migration/failover.
676 pMigrationTargetNode :: Field
677 pMigrationTargetNode = optionalNEStringField "target_node"
678
679 -- | Target node UUID for instance migration/failover.
680 pMigrationTargetNodeUuid :: Field
681 pMigrationTargetNodeUuid = optionalNEStringField "target_node_uuid"
682
683 -- | Target node for instance move (required).
684 pMoveTargetNode :: Field
685 pMoveTargetNode =
686   renameField "MoveTargetNode" $
687   simpleField "target_node" [t| NonEmptyString |]
688
689 -- | Target node UUID for instance move.
690 pMoveTargetNodeUuid :: Field
691 pMoveTargetNodeUuid =
692   renameField "MoveTargetNodeUuid" . optionalField $
693   simpleField "target_node_uuid" [t| NonEmptyString |]
694
695 -- | Pause instance at startup.
696 pStartupPaused :: Field
697 pStartupPaused = defaultFalse "startup_paused"
698
699 -- | Verbose mode.
700 pVerbose :: Field
701 pVerbose = defaultFalse "verbose"
702
703 -- ** Parameters for cluster verification
704
705 -- | Whether to simulate errors (useful for debugging).
706 pDebugSimulateErrors :: Field
707 pDebugSimulateErrors = defaultFalse "debug_simulate_errors"
708
709 -- | Error codes.
710 pErrorCodes :: Field
711 pErrorCodes = defaultFalse "error_codes"
712
713 -- | Which checks to skip.
714 pSkipChecks :: Field
715 pSkipChecks = defaultField [| Set.empty |] $
716               simpleField "skip_checks" [t| Set.Set VerifyOptionalChecks |]
717
718 -- | List of error codes that should be treated as warnings.
719 pIgnoreErrors :: Field
720 pIgnoreErrors = defaultField [| Set.empty |] $
721                 simpleField "ignore_errors" [t| Set.Set CVErrorCode |]
722
723 -- | Optional group name.
724 pOptGroupName :: Field
725 pOptGroupName = renameField "OptGroupName" .
726                 optionalField $ simpleField "group_name" [t| NonEmptyString |]
727
728 -- | Disk templates' parameter defaults.
729 pDiskParams :: Field
730 pDiskParams = optionalField $
731               simpleField "diskparams" [t| GenericContainer DiskTemplate
732                                            UncheckedDict |]
733
734 -- * Parameters for node resource model
735
736 -- | Set hypervisor states.
737 pHvState :: Field
738 pHvState = optionalField $ simpleField "hv_state" [t| UncheckedDict |]
739
740 -- | Set disk states.
741 pDiskState :: Field
742 pDiskState = optionalField $ simpleField "disk_state" [t| UncheckedDict |]
743
744 -- | Whether to ignore ipolicy violations.
745 pIgnoreIpolicy :: Field
746 pIgnoreIpolicy = defaultFalse "ignore_ipolicy"
747
748 -- | Allow runtime changes while migrating.
749 pAllowRuntimeChgs :: Field
750 pAllowRuntimeChgs = defaultTrue "allow_runtime_changes"
751
752 -- | Utility type for OpClusterSetParams.
753 type TestClusterOsListItem = (DdmSimple, NonEmptyString)
754
755 -- | Utility type of OsList.
756 type TestClusterOsList = [TestClusterOsListItem]
757
758 -- Utility type for NIC definitions.
759 --type TestNicDef = INicParams
760
761 -- | List of instance disks.
762 pInstDisks :: Field
763 pInstDisks = renameField "instDisks" $ simpleField "disks" [t| [IDiskParams] |]
764
765 -- | Instance disk template.
766 pDiskTemplate :: Field
767 pDiskTemplate = simpleField "disk_template" [t| DiskTemplate |]
768
769 -- | Instance disk template.
770 pOptDiskTemplate :: Field
771 pOptDiskTemplate =
772   optionalField .
773   renameField "OptDiskTemplate" $
774   simpleField "disk_template" [t| DiskTemplate |]
775
776 -- | File driver.
777 pFileDriver :: Field
778 pFileDriver = optionalField $ simpleField "file_driver" [t| FileDriver |]
779
780 -- | Directory for storing file-backed disks.
781 pFileStorageDir :: Field
782 pFileStorageDir = optionalNEStringField "file_storage_dir"
783
784 -- | Volume group name.
785 pVgName :: Field
786 pVgName = optionalStringField "vg_name"
787
788 -- | List of enabled hypervisors.
789 pEnabledHypervisors :: Field
790 pEnabledHypervisors =
791   optionalField $
792   simpleField "enabled_hypervisors" [t| NonEmpty Hypervisor |]
793
794 -- | List of enabled disk templates.
795 pEnabledDiskTemplates :: Field
796 pEnabledDiskTemplates =
797   optionalField $
798   simpleField "enabled_disk_templates" [t| NonEmpty DiskTemplate |]
799
800 -- | Selected hypervisor for an instance.
801 pHypervisor :: Field
802 pHypervisor =
803   optionalField $
804   simpleField "hypervisor" [t| Hypervisor |]
805
806 -- | Cluster-wide hypervisor parameters, hypervisor-dependent.
807 pClusterHvParams :: Field
808 pClusterHvParams =
809   renameField "ClusterHvParams" .
810   optionalField $
811   simpleField "hvparams" [t| Container UncheckedDict |]
812
813 -- | Instance hypervisor parameters.
814 pInstHvParams :: Field
815 pInstHvParams =
816   renameField "InstHvParams" .
817   defaultField [| toJSObject [] |] $
818   simpleField "hvparams" [t| UncheckedDict |]
819
820 -- | Cluster-wide beparams.
821 pClusterBeParams :: Field
822 pClusterBeParams =
823   renameField "ClusterBeParams" .
824   optionalField $ simpleField "beparams" [t| UncheckedDict |]
825
826 -- | Instance beparams.
827 pInstBeParams :: Field
828 pInstBeParams =
829   renameField "InstBeParams" .
830   defaultField [| toJSObject [] |] $
831   simpleField "beparams" [t| UncheckedDict |]
832
833 -- | Reset instance parameters to default if equal.
834 pResetDefaults :: Field
835 pResetDefaults = defaultFalse "identify_defaults"
836
837 -- | Cluster-wide per-OS hypervisor parameter defaults.
838 pOsHvp :: Field
839 pOsHvp = optionalField $ simpleField "os_hvp" [t| Container UncheckedDict |]
840
841 -- | Cluster-wide OS parameter defaults.
842 pClusterOsParams :: Field
843 pClusterOsParams =
844   renameField "ClusterOsParams" .
845   optionalField $ simpleField "osparams" [t| Container UncheckedDict |]
846
847 -- | Instance OS parameters.
848 pInstOsParams :: Field
849 pInstOsParams =
850   renameField "InstOsParams" . defaultField [| toJSObject [] |] $
851   simpleField "osparams" [t| UncheckedDict |]
852
853 -- | Temporary OS parameters (currently only in reinstall, might be
854 -- added to install as well).
855 pTempOsParams :: Field
856 pTempOsParams =
857   renameField "TempOsParams" .
858   optionalField $ simpleField "osparams" [t| UncheckedDict |]
859
860 -- | Temporary hypervisor parameters, hypervisor-dependent.
861 pTempHvParams :: Field
862 pTempHvParams =
863   renameField "TempHvParams" .
864   defaultField [| toJSObject [] |] $
865   simpleField "hvparams" [t| UncheckedDict |]
866
867 -- | Temporary backend parameters.
868 pTempBeParams :: Field
869 pTempBeParams =
870   renameField "TempBeParams" .
871   defaultField [| toJSObject [] |] $
872   simpleField "beparams" [t| UncheckedDict |]
873
874 -- | Candidate pool size.
875 pCandidatePoolSize :: Field
876 pCandidatePoolSize =
877   optionalField $ simpleField "candidate_pool_size" [t| Positive Int |]
878
879 -- | Set UID pool, must be list of lists describing UID ranges (two
880 -- items, start and end inclusive.
881 pUidPool :: Field
882 pUidPool = optionalField $ simpleField "uid_pool" [t| [[(Int, Int)]] |]
883
884 -- | Extend UID pool, must be list of lists describing UID ranges (two
885 -- items, start and end inclusive.
886 pAddUids :: Field
887 pAddUids = optionalField $ simpleField "add_uids" [t| [[(Int, Int)]] |]
888
889 -- | Shrink UID pool, must be list of lists describing UID ranges (two
890 -- items, start and end inclusive) to be removed.
891 pRemoveUids :: Field
892 pRemoveUids = optionalField $ simpleField "remove_uids" [t| [[(Int, Int)]] |]
893
894 -- | Whether to automatically maintain node health.
895 pMaintainNodeHealth :: Field
896 pMaintainNodeHealth = optionalField $ booleanField "maintain_node_health"
897
898 -- | Whether to wipe disks before allocating them to instances.
899 pPreallocWipeDisks :: Field
900 pPreallocWipeDisks = optionalField $ booleanField "prealloc_wipe_disks"
901
902 -- | Cluster-wide NIC parameter defaults.
903 pNicParams :: Field
904 pNicParams = optionalField $ simpleField "nicparams" [t| INicParams |]
905
906 -- | Instance NIC definitions.
907 pInstNics :: Field
908 pInstNics = simpleField "nics" [t| [INicParams] |]
909
910 -- | Cluster-wide node parameter defaults.
911 pNdParams :: Field
912 pNdParams = optionalField $ simpleField "ndparams" [t| UncheckedDict |]
913
914 -- | Cluster-wide ipolicy specs.
915 pIpolicy :: Field
916 pIpolicy = optionalField $ simpleField "ipolicy" [t| UncheckedDict |]
917
918 -- | DRBD helper program.
919 pDrbdHelper :: Field
920 pDrbdHelper = optionalStringField "drbd_helper"
921
922 -- | Default iallocator for cluster.
923 pDefaultIAllocator :: Field
924 pDefaultIAllocator = optionalStringField "default_iallocator"
925
926 -- | Master network device.
927 pMasterNetdev :: Field
928 pMasterNetdev = optionalStringField "master_netdev"
929
930 -- | Netmask of the master IP.
931 pMasterNetmask :: Field
932 pMasterNetmask =
933   optionalField $ simpleField "master_netmask" [t| NonNegative Int |]
934
935 -- | List of reserved LVs.
936 pReservedLvs :: Field
937 pReservedLvs =
938   optionalField $ simpleField "reserved_lvs" [t| [NonEmptyString] |]
939
940 -- | Modify list of hidden operating systems: each modification must
941 -- have two items, the operation and the OS name; the operation can be
942 -- add or remove.
943 pHiddenOs :: Field
944 pHiddenOs = optionalField $ simpleField "hidden_os" [t| TestClusterOsList |]
945
946 -- | Modify list of blacklisted operating systems: each modification
947 -- must have two items, the operation and the OS name; the operation
948 -- can be add or remove.
949 pBlacklistedOs :: Field
950 pBlacklistedOs =
951   optionalField $ simpleField "blacklisted_os" [t| TestClusterOsList |]
952
953 -- | Whether to use an external master IP address setup script.
954 pUseExternalMipScript :: Field
955 pUseExternalMipScript = optionalField $ booleanField "use_external_mip_script"
956
957 -- | Requested fields.
958 pQueryFields :: Field
959 pQueryFields = simpleField "fields" [t| [NonEmptyString] |]
960
961 -- | Query filter.
962 pQueryFilter :: Field
963 pQueryFilter = simpleField "qfilter" [t| Qlang.Filter String |]
964
965 -- | OOB command to run.
966 pOobCommand :: Field
967 pOobCommand = simpleField "command" [t| OobCommand |]
968
969 -- | Timeout before the OOB helper will be terminated.
970 pOobTimeout :: Field
971 pOobTimeout =
972   defaultField [| C.oobTimeout |] $ simpleField "timeout" [t| Int |]
973
974 -- | Ignores the node offline status for power off.
975 pIgnoreStatus :: Field
976 pIgnoreStatus = defaultFalse "ignore_status"
977
978 -- | Time in seconds to wait between powering on nodes.
979 pPowerDelay :: Field
980 pPowerDelay =
981   -- FIXME: we can't use the proper type "NonNegative Double", since
982   -- the default constant is a plain Double, not a non-negative one.
983   defaultField [| C.oobPowerDelay |] $
984   simpleField "power_delay" [t| Double |]
985
986 -- | Primary IP address.
987 pPrimaryIp :: Field
988 pPrimaryIp = optionalStringField "primary_ip"
989
990 -- | Secondary IP address.
991 pSecondaryIp :: Field
992 pSecondaryIp = optionalNEStringField "secondary_ip"
993
994 -- | Whether node is re-added to cluster.
995 pReadd :: Field
996 pReadd = defaultFalse "readd"
997
998 -- | Initial node group.
999 pNodeGroup :: Field
1000 pNodeGroup = optionalNEStringField "group"
1001
1002 -- | Whether node can become master or master candidate.
1003 pMasterCapable :: Field
1004 pMasterCapable = optionalField $ booleanField "master_capable"
1005
1006 -- | Whether node can host instances.
1007 pVmCapable :: Field
1008 pVmCapable = optionalField $ booleanField "vm_capable"
1009
1010 -- | List of names.
1011 pNames :: Field
1012 pNames = defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
1013
1014 -- | List of node names.
1015 pNodes :: Field
1016 pNodes = defaultField [| [] |] $ simpleField "nodes" [t| [NonEmptyString] |]
1017
1018 -- | Required list of node names.
1019 pRequiredNodes :: Field
1020 pRequiredNodes =
1021   renameField "ReqNodes " $ simpleField "nodes" [t| [NonEmptyString] |]
1022
1023 -- | Required list of node names.
1024 pRequiredNodeUuids :: Field
1025 pRequiredNodeUuids =
1026   renameField "ReqNodeUuids " . optionalField $
1027     simpleField "node_uuids" [t| [NonEmptyString] |]
1028
1029 -- | Storage type.
1030 pStorageType :: Field
1031 pStorageType = simpleField "storage_type" [t| StorageType |]
1032
1033 -- | Storage changes (unchecked).
1034 pStorageChanges :: Field
1035 pStorageChanges = simpleField "changes" [t| UncheckedDict |]
1036
1037 -- | Whether the node should become a master candidate.
1038 pMasterCandidate :: Field
1039 pMasterCandidate = optionalField $ booleanField "master_candidate"
1040
1041 -- | Whether the node should be marked as offline.
1042 pOffline :: Field
1043 pOffline = optionalField $ booleanField "offline"
1044
1045 -- | Whether the node should be marked as drained.
1046 pDrained ::Field
1047 pDrained = optionalField $ booleanField "drained"
1048
1049 -- | Whether node(s) should be promoted to master candidate if necessary.
1050 pAutoPromote :: Field
1051 pAutoPromote = defaultFalse "auto_promote"
1052
1053 -- | Whether the node should be marked as powered
1054 pPowered :: Field
1055 pPowered = optionalField $ booleanField "powered"
1056
1057 -- | Iallocator for deciding the target node for shared-storage
1058 -- instances during migrate and failover.
1059 pIallocator :: Field
1060 pIallocator = optionalNEStringField "iallocator"
1061
1062 -- | New secondary node.
1063 pRemoteNode :: Field
1064 pRemoteNode = optionalNEStringField "remote_node"
1065
1066 -- | New secondary node UUID.
1067 pRemoteNodeUuid :: Field
1068 pRemoteNodeUuid = optionalNEStringField "remote_node_uuid"
1069
1070 -- | Node evacuation mode.
1071 pEvacMode :: Field
1072 pEvacMode = renameField "EvacMode" $ simpleField "mode" [t| NodeEvacMode |]
1073
1074 -- | Instance creation mode.
1075 pInstCreateMode :: Field
1076 pInstCreateMode =
1077   renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
1078
1079 -- | Do not install the OS (will disable automatic start).
1080 pNoInstall :: Field
1081 pNoInstall = optionalField $ booleanField "no_install"
1082
1083 -- | OS type for instance installation.
1084 pInstOs :: Field
1085 pInstOs = optionalNEStringField "os_type"
1086
1087 -- | Primary node for an instance.
1088 pPrimaryNode :: Field
1089 pPrimaryNode = optionalNEStringField "pnode"
1090
1091 -- | Primary node UUID for an instance.
1092 pPrimaryNodeUuid :: Field
1093 pPrimaryNodeUuid = optionalNEStringField "pnode_uuid"
1094
1095 -- | Secondary node for an instance.
1096 pSecondaryNode :: Field
1097 pSecondaryNode = optionalNEStringField "snode"
1098
1099 -- | Secondary node UUID for an instance.
1100 pSecondaryNodeUuid :: Field
1101 pSecondaryNodeUuid = optionalNEStringField "snode_uuid"
1102
1103 -- | Signed handshake from source (remote import only).
1104 pSourceHandshake :: Field
1105 pSourceHandshake =
1106   optionalField $ simpleField "source_handshake" [t| UncheckedList |]
1107
1108 -- | Source instance name (remote import only).
1109 pSourceInstance :: Field
1110 pSourceInstance = optionalNEStringField "source_instance_name"
1111
1112 -- | How long source instance was given to shut down (remote import only).
1113 -- FIXME: non-negative int, whereas the constant is a plain int.
1114 pSourceShutdownTimeout :: Field
1115 pSourceShutdownTimeout =
1116   defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1117   simpleField "source_shutdown_timeout" [t| NonNegative Int |]
1118
1119 -- | Source X509 CA in PEM format (remote import only).
1120 pSourceX509Ca :: Field
1121 pSourceX509Ca = optionalNEStringField "source_x509_ca"
1122
1123 -- | Source node for import.
1124 pSrcNode :: Field
1125 pSrcNode = optionalNEStringField "src_node"
1126
1127 -- | Source node for import.
1128 pSrcNodeUuid :: Field
1129 pSrcNodeUuid = optionalNEStringField "src_node_uuid"
1130
1131 -- | Source directory for import.
1132 pSrcPath :: Field
1133 pSrcPath = optionalNEStringField "src_path"
1134
1135 -- | Whether to start instance after creation.
1136 pStartInstance :: Field
1137 pStartInstance = defaultTrue "start"
1138
1139 -- | Instance tags. FIXME: unify/simplify with pTags, once that
1140 -- migrates to NonEmpty String.
1141 pInstTags :: Field
1142 pInstTags =
1143   renameField "InstTags" .
1144   defaultField [| [] |] $
1145   simpleField "tags" [t| [NonEmptyString] |]
1146
1147 -- | Unchecked list of OpInstanceCreate, used in OpInstanceMultiAlloc.
1148 pMultiAllocInstances :: Field
1149 pMultiAllocInstances =
1150   renameField "InstMultiAlloc" .
1151   defaultField [| [] |] $
1152   simpleField "instances"[t| UncheckedList |]
1153
1154 -- | Ignore failures parameter.
1155 pIgnoreFailures :: Field
1156 pIgnoreFailures = defaultFalse "ignore_failures"
1157
1158 -- | New instance or cluster name.
1159 pNewName :: Field
1160 pNewName = simpleField "new_name" [t| NonEmptyString |]
1161
1162 -- | Whether to start the instance even if secondary disks are failing.
1163 pIgnoreSecondaries :: Field
1164 pIgnoreSecondaries = defaultFalse "ignore_secondaries"
1165
1166 -- | How to reboot the instance.
1167 pRebootType :: Field
1168 pRebootType = simpleField "reboot_type" [t| RebootType |]
1169
1170 -- | Whether to ignore recorded disk size.
1171 pIgnoreDiskSize :: Field
1172 pIgnoreDiskSize = defaultFalse "ignore_size"
1173
1174 -- | Disk list for recreate disks.
1175 pRecreateDisksInfo :: Field
1176 pRecreateDisksInfo =
1177   renameField "RecreateDisksInfo" .
1178   defaultField [| RecreateDisksAll |] $
1179   simpleField "disks" [t| RecreateDisksInfo |]
1180
1181 -- | Whether to only return configuration data without querying nodes.
1182 pStatic :: Field
1183 pStatic = defaultFalse "static"
1184
1185 -- | InstanceSetParams NIC changes.
1186 pInstParamsNicChanges :: Field
1187 pInstParamsNicChanges =
1188   renameField "InstNicChanges" .
1189   defaultField [| SetParamsEmpty |] $
1190   simpleField "nics" [t| SetParamsMods INicParams |]
1191
1192 -- | InstanceSetParams Disk changes.
1193 pInstParamsDiskChanges :: Field
1194 pInstParamsDiskChanges =
1195   renameField "InstDiskChanges" .
1196   defaultField [| SetParamsEmpty |] $
1197   simpleField "disks" [t| SetParamsMods IDiskParams |]
1198
1199 -- | New runtime memory.
1200 pRuntimeMem :: Field
1201 pRuntimeMem = optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1202
1203 -- | Change the instance's OS without reinstalling the instance
1204 pOsNameChange :: Field
1205 pOsNameChange = optionalNEStringField "os_name"
1206
1207 -- | Disk index for e.g. grow disk.
1208 pDiskIndex :: Field
1209 pDiskIndex = renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
1210
1211 -- | Disk amount to add or grow to.
1212 pDiskChgAmount :: Field
1213 pDiskChgAmount =
1214   renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
1215
1216 -- | Whether the amount parameter is an absolute target or a relative one.
1217 pDiskChgAbsolute :: Field
1218 pDiskChgAbsolute = renameField "DiskChkAbsolute" $ defaultFalse "absolute"
1219
1220 -- | Destination group names or UUIDs (defaults to \"all but current group\".
1221 pTargetGroups :: Field
1222 pTargetGroups =
1223   optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
1224
1225 -- | Export mode field.
1226 pExportMode :: Field
1227 pExportMode =
1228   renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1229
1230 -- | Export target_node field, depends on mode.
1231 pExportTargetNode :: Field
1232 pExportTargetNode =
1233   renameField "ExportTarget" $
1234   simpleField "target_node" [t| ExportTarget |]
1235
1236 -- | Export target node UUID field.
1237 pExportTargetNodeUuid :: Field
1238 pExportTargetNodeUuid =
1239   renameField "ExportTargetNodeUuid" . optionalField $
1240   simpleField "target_node_uuid" [t| NonEmptyString |]
1241
1242 -- | Whether to remove instance after export.
1243 pRemoveInstance :: Field
1244 pRemoveInstance = defaultFalse "remove_instance"
1245
1246 -- | Whether to ignore failures while removing instances.
1247 pIgnoreRemoveFailures :: Field
1248 pIgnoreRemoveFailures = defaultFalse "ignore_remove_failures"
1249
1250 -- | Name of X509 key (remote export only).
1251 pX509KeyName :: Field
1252 pX509KeyName = optionalField $ simpleField "x509_key_name" [t| UncheckedList |]
1253
1254 -- | Destination X509 CA (remote export only).
1255 pX509DestCA :: Field
1256 pX509DestCA = optionalNEStringField "destination_x509_ca"
1257
1258 -- | Search pattern (regular expression). FIXME: this should be
1259 -- compiled at load time?
1260 pTagSearchPattern :: Field
1261 pTagSearchPattern =
1262   renameField "TagSearchPattern" $ simpleField "pattern" [t| NonEmptyString |]
1263
1264 -- | Restricted command name.
1265 pRestrictedCommand :: Field
1266 pRestrictedCommand =
1267   renameField "RestrictedCommand" $
1268   simpleField "command" [t| NonEmptyString |]
1269
1270 -- | Replace disks mode.
1271 pReplaceDisksMode :: Field
1272 pReplaceDisksMode =
1273   renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1274
1275 -- | List of disk indices.
1276 pReplaceDisksList :: Field
1277 pReplaceDisksList =
1278   renameField "ReplaceDisksList" $ simpleField "disks" [t| [DiskIndex] |]
1279
1280 -- | Whether do allow failover in migrations.
1281 pAllowFailover :: Field
1282 pAllowFailover = defaultFalse "allow_failover"
1283
1284 -- * Test opcode parameters
1285
1286 -- | Duration parameter for 'OpTestDelay'.
1287 pDelayDuration :: Field
1288 pDelayDuration =
1289   renameField "DelayDuration" $ simpleField "duration" [t| Double |]
1290
1291 -- | on_master field for 'OpTestDelay'.
1292 pDelayOnMaster :: Field
1293 pDelayOnMaster = renameField "DelayOnMaster" $ defaultTrue "on_master"
1294
1295 -- | on_nodes field for 'OpTestDelay'.
1296 pDelayOnNodes :: Field
1297 pDelayOnNodes =
1298   renameField "DelayOnNodes" .
1299   defaultField [| [] |] $
1300   simpleField "on_nodes" [t| [NonEmptyString] |]
1301
1302 -- | on_node_uuids field for 'OpTestDelay'.
1303 pDelayOnNodeUuids :: Field
1304 pDelayOnNodeUuids =
1305   renameField "DelayOnNodeUuids" . optionalField $
1306   simpleField "on_node_uuids" [t| [NonEmptyString] |]
1307
1308 -- | Repeat parameter for OpTestDelay.
1309 pDelayRepeat :: Field
1310 pDelayRepeat =
1311   renameField "DelayRepeat" .
1312   defaultField [| forceNonNeg (0::Int) |] $
1313   simpleField "repeat" [t| NonNegative Int |]
1314
1315 -- | IAllocator test direction.
1316 pIAllocatorDirection :: Field
1317 pIAllocatorDirection =
1318   renameField "IAllocatorDirection" $
1319   simpleField "direction" [t| IAllocatorTestDir |]
1320
1321 -- | IAllocator test mode.
1322 pIAllocatorMode :: Field
1323 pIAllocatorMode =
1324   renameField "IAllocatorMode" $
1325   simpleField "mode" [t| IAllocatorMode |]
1326
1327 -- | IAllocator target name (new instance, node to evac, etc.).
1328 pIAllocatorReqName :: Field
1329 pIAllocatorReqName =
1330   renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
1331
1332 -- | Custom OpTestIAllocator nics.
1333 pIAllocatorNics :: Field
1334 pIAllocatorNics =
1335   renameField "IAllocatorNics" $ simpleField "nics" [t| [UncheckedDict] |]
1336
1337 -- | Custom OpTestAllocator disks.
1338 pIAllocatorDisks :: Field
1339 pIAllocatorDisks =
1340   renameField "IAllocatorDisks" $ simpleField "disks" [t| UncheckedList |]
1341
1342 -- | IAllocator memory field.
1343 pIAllocatorMemory :: Field
1344 pIAllocatorMemory =
1345   renameField "IAllocatorMem" .
1346   optionalField $
1347   simpleField "memory" [t| NonNegative Int |]
1348
1349 -- | IAllocator vcpus field.
1350 pIAllocatorVCpus :: Field
1351 pIAllocatorVCpus =
1352   renameField "IAllocatorVCpus" .
1353   optionalField $
1354   simpleField "vcpus" [t| NonNegative Int |]
1355
1356 -- | IAllocator os field.
1357 pIAllocatorOs :: Field
1358 pIAllocatorOs = renameField "IAllocatorOs" $ optionalNEStringField "os"
1359
1360 -- | IAllocator instances field.
1361 pIAllocatorInstances :: Field
1362 pIAllocatorInstances =
1363   renameField "IAllocatorInstances " .
1364   optionalField $
1365   simpleField "instances" [t| [NonEmptyString] |]
1366
1367 -- | IAllocator evac mode.
1368 pIAllocatorEvacMode :: Field
1369 pIAllocatorEvacMode =
1370   renameField "IAllocatorEvacMode" .
1371   optionalField $
1372   simpleField "evac_mode" [t| NodeEvacMode |]
1373
1374 -- | IAllocator spindle use.
1375 pIAllocatorSpindleUse :: Field
1376 pIAllocatorSpindleUse =
1377   renameField "IAllocatorSpindleUse" .
1378   defaultField [| forceNonNeg (1::Int) |] $
1379   simpleField "spindle_use" [t| NonNegative Int |]
1380
1381 -- | IAllocator count field.
1382 pIAllocatorCount :: Field
1383 pIAllocatorCount =
1384   renameField "IAllocatorCount" .
1385   defaultField [| forceNonNeg (1::Int) |] $
1386   simpleField "count" [t| NonNegative Int |]
1387
1388 -- | 'OpTestJqueue' notify_waitlock.
1389 pJQueueNotifyWaitLock :: Field
1390 pJQueueNotifyWaitLock = defaultFalse "notify_waitlock"
1391
1392 -- | 'OpTestJQueue' notify_exec.
1393 pJQueueNotifyExec :: Field
1394 pJQueueNotifyExec = defaultFalse "notify_exec"
1395
1396 -- | 'OpTestJQueue' log_messages.
1397 pJQueueLogMessages :: Field
1398 pJQueueLogMessages =
1399   defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
1400
1401 -- | 'OpTestJQueue' fail attribute.
1402 pJQueueFail :: Field
1403 pJQueueFail =
1404   renameField "JQueueFail" $ defaultFalse "fail"
1405
1406 -- | 'OpTestDummy' result field.
1407 pTestDummyResult :: Field
1408 pTestDummyResult =
1409   renameField "TestDummyResult" $ simpleField "result" [t| UncheckedValue |]
1410
1411 -- | 'OpTestDummy' messages field.
1412 pTestDummyMessages :: Field
1413 pTestDummyMessages =
1414   renameField "TestDummyMessages" $
1415   simpleField "messages" [t| UncheckedValue |]
1416
1417 -- | 'OpTestDummy' fail field.
1418 pTestDummyFail :: Field
1419 pTestDummyFail =
1420   renameField "TestDummyFail" $ simpleField "fail" [t| UncheckedValue |]
1421
1422 -- | 'OpTestDummy' submit_jobs field.
1423 pTestDummySubmitJobs :: Field
1424 pTestDummySubmitJobs =
1425   renameField "TestDummySubmitJobs" $
1426   simpleField "submit_jobs" [t| UncheckedValue |]
1427
1428 -- * Network parameters
1429
1430 -- | Network name.
1431 pNetworkName :: Field
1432 pNetworkName = simpleField "network_name" [t| NonEmptyString |]
1433
1434 -- | Network address (IPv4 subnet). FIXME: no real type for this.
1435 pNetworkAddress4 :: Field
1436 pNetworkAddress4 =
1437   renameField "NetworkAddress4" $
1438   simpleField "network" [t| NonEmptyString |]
1439
1440 -- | Network gateway (IPv4 address). FIXME: no real type for this.
1441 pNetworkGateway4 :: Field
1442 pNetworkGateway4 =
1443   renameField "NetworkGateway4" $
1444   optionalNEStringField "gateway"
1445
1446 -- | Network address (IPv6 subnet). FIXME: no real type for this.
1447 pNetworkAddress6 :: Field
1448 pNetworkAddress6 =
1449   renameField "NetworkAddress6" $
1450   optionalNEStringField "network6"
1451
1452 -- | Network gateway (IPv6 address). FIXME: no real type for this.
1453 pNetworkGateway6 :: Field
1454 pNetworkGateway6 =
1455   renameField "NetworkGateway6" $
1456   optionalNEStringField "gateway6"
1457
1458 -- | Network specific mac prefix (that overrides the cluster one).
1459 pNetworkMacPrefix :: Field
1460 pNetworkMacPrefix =
1461   renameField "NetMacPrefix" $
1462   optionalNEStringField "mac_prefix"
1463
1464 -- | Network add reserved IPs.
1465 pNetworkAddRsvdIps :: Field
1466 pNetworkAddRsvdIps =
1467   renameField "NetworkAddRsvdIps" .
1468   optionalField $
1469   simpleField "add_reserved_ips" [t| [NonEmptyString] |]
1470
1471 -- | Network remove reserved IPs.
1472 pNetworkRemoveRsvdIps :: Field
1473 pNetworkRemoveRsvdIps =
1474   renameField "NetworkRemoveRsvdIps" .
1475   optionalField $
1476   simpleField "remove_reserved_ips" [t| [NonEmptyString] |]
1477
1478 -- | Network mode when connecting to a group.
1479 pNetworkMode :: Field
1480 pNetworkMode = simpleField "network_mode" [t| NICMode |]
1481
1482 -- | Network link when connecting to a group.
1483 pNetworkLink :: Field
1484 pNetworkLink = simpleField "network_link" [t| NonEmptyString |]
1485
1486 -- * Common opcode parameters
1487
1488 -- | Run checks only, don't execute.
1489 pDryRun :: Field
1490 pDryRun = optionalField $ booleanField "dry_run"
1491
1492 -- | Debug level.
1493 pDebugLevel :: Field
1494 pDebugLevel = optionalField $ simpleField "debug_level" [t| NonNegative Int |]
1495
1496 -- | Opcode priority. Note: python uses a separate constant, we're
1497 -- using the actual value we know it's the default.
1498 pOpPriority :: Field
1499 pOpPriority =
1500   defaultField [| OpPrioNormal |] $
1501   simpleField "priority" [t| OpSubmitPriority |]
1502
1503 -- | Job dependencies.
1504 pDependencies :: Field
1505 pDependencies =
1506   optionalNullSerField $ simpleField "depends" [t| [JobDependency] |]
1507
1508 -- | Comment field.
1509 pComment :: Field
1510 pComment = optionalNullSerField $ stringField "comment"
1511
1512 -- | Reason trail field.
1513 pReason :: Field
1514 pReason = simpleField C.opcodeReason [t| ReasonTrail |]
1515
1516 -- * Entire opcode parameter list
1517
1518 -- | Old-style query opcode, with locking.
1519 dOldQuery :: [Field]
1520 dOldQuery =
1521   [ pOutputFields
1522   , pNames
1523   , pUseLocking
1524   ]
1525
1526 -- | Old-style query opcode, without locking.
1527 dOldQueryNoLocking :: [Field]
1528 dOldQueryNoLocking =
1529   [ pOutputFields
1530   , pNames
1531   ]