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