module Ganeti.OpParams
( TagType(..)
, TagObject(..)
, tagObjectFrom
, tagNameOf
, decodeTagObject
, encodeTagObject
, ReplaceDisksMode(..)
, DiskIndex
, mkDiskIndex
, unDiskIndex
, DiskAccess(..)
, INicParams(..)
, IDiskParams(..)
, RecreateDisksInfo(..)
, DdmOldChanges(..)
, SetParamsMods(..)
, ExportTarget(..)
, pInstanceName
, pInstanceUuid
, pInstances
, pName
, pTagsList
, pTagsObject
, pOutputFields
, pShutdownTimeout
, pShutdownTimeout'
, pShutdownInstance
, pForce
, pIgnoreOfflineNodes
, pNodeName
, pNodeUuid
, pNodeNames
, pNodeUuids
, pGroupName
, pMigrationMode
, pMigrationLive
, pMigrationCleanup
, pForceVariant
, pWaitForSync
, pWaitForSyncFalse
, pIgnoreConsistency
, pStorageName
, pUseLocking
, pOpportunisticLocking
, pNameCheck
, pNodeGroupAllocPolicy
, pGroupNodeParams
, pQueryWhat
, pEarlyRelease
, pIpCheck
, pIpConflictsCheck
, pNoRemember
, pMigrationTargetNode
, pMigrationTargetNodeUuid
, pMoveTargetNode
, pMoveTargetNodeUuid
, pStartupPaused
, pVerbose
, pDebugSimulateErrors
, pErrorCodes
, pSkipChecks
, pIgnoreErrors
, pOptGroupName
, pDiskParams
, pHvState
, pDiskState
, pIgnoreIpolicy
, pAllowRuntimeChgs
, pInstDisks
, pDiskTemplate
, pOptDiskTemplate
, pFileDriver
, pFileStorageDir
, pGlobalFileStorageDir
, pGlobalSharedFileStorageDir
, pVgName
, pEnabledHypervisors
, pHypervisor
, pClusterHvParams
, pInstHvParams
, pClusterBeParams
, pInstBeParams
, pResetDefaults
, pOsHvp
, pClusterOsParams
, pInstOsParams
, pCandidatePoolSize
, pUidPool
, pAddUids
, pRemoveUids
, pMaintainNodeHealth
, pModifyEtcHosts
, pPreallocWipeDisks
, pNicParams
, pInstNics
, pNdParams
, pIpolicy
, pDrbdHelper
, pDefaultIAllocator
, pMasterNetdev
, pMasterNetmask
, pReservedLvs
, pHiddenOs
, pBlacklistedOs
, pUseExternalMipScript
, pQueryFields
, pQueryFilter
, pOobCommand
, pOobTimeout
, pIgnoreStatus
, pPowerDelay
, pPrimaryIp
, pSecondaryIp
, pReadd
, pNodeGroup
, pMasterCapable
, pVmCapable
, pNames
, pNodes
, pRequiredNodes
, pRequiredNodeUuids
, pStorageType
, pStorageChanges
, pMasterCandidate
, pOffline
, pDrained
, pAutoPromote
, pPowered
, pIallocator
, pRemoteNode
, pRemoteNodeUuid
, pEvacMode
, pInstCreateMode
, pNoInstall
, pInstOs
, pPrimaryNode
, pPrimaryNodeUuid
, pSecondaryNode
, pSecondaryNodeUuid
, pSourceHandshake
, pSourceInstance
, pSourceShutdownTimeout
, pSourceX509Ca
, pSrcNode
, pSrcNodeUuid
, pSrcPath
, pStartInstance
, pInstTags
, pMultiAllocInstances
, pTempOsParams
, pTempHvParams
, pTempBeParams
, pIgnoreFailures
, pNewName
, pIgnoreSecondaries
, pRebootType
, pIgnoreDiskSize
, pRecreateDisksInfo
, pStatic
, pInstParamsNicChanges
, pInstParamsDiskChanges
, pRuntimeMem
, pOsNameChange
, pDiskIndex
, pDiskChgAmount
, pDiskChgAbsolute
, pTargetGroups
, pExportMode
, pExportTargetNode
, pExportTargetNodeUuid
, pRemoveInstance
, pIgnoreRemoveFailures
, pX509KeyName
, pX509DestCA
, pTagSearchPattern
, pRestrictedCommand
, pReplaceDisksMode
, pReplaceDisksList
, pAllowFailover
, pDelayDuration
, pDelayOnMaster
, pDelayOnNodes
, pDelayOnNodeUuids
, pDelayRepeat
, pIAllocatorDirection
, pIAllocatorMode
, pIAllocatorReqName
, pIAllocatorNics
, pIAllocatorDisks
, pIAllocatorMemory
, pIAllocatorVCpus
, pIAllocatorOs
, pIAllocatorInstances
, pIAllocatorEvacMode
, pIAllocatorSpindleUse
, pIAllocatorCount
, pJQueueNotifyWaitLock
, pJQueueNotifyExec
, pJQueueLogMessages
, pJQueueFail
, pTestDummyResult
, pTestDummyMessages
, pTestDummyFail
, pTestDummySubmitJobs
, pNetworkName
, pNetworkAddress4
, pNetworkGateway4
, pNetworkAddress6
, pNetworkGateway6
, pNetworkMacPrefix
, pNetworkAddRsvdIps
, pNetworkRemoveRsvdIps
, pNetworkMode
, pNetworkLink
, pDryRun
, pDebugLevel
, pOpPriority
, pDependencies
, pComment
, pReason
, pEnabledDiskTemplates
, dOldQuery
, dOldQueryNoLocking
) where
import Control.Monad (liftM)
import qualified Data.Set as Set
import Text.JSON (readJSON, showJSON, JSON, JSValue(..), fromJSString,
JSObject, toJSObject)
import qualified Text.JSON
import Text.JSON.Pretty (pp_value)
import Ganeti.BasicTypes
import qualified Ganeti.Constants as C
import Ganeti.THH
import Ganeti.JSON
import Ganeti.Types
import qualified Ganeti.Query.Language as Qlang
booleanField :: String -> Field
booleanField = flip simpleField [t| Bool |]
defaultFalse :: String -> Field
defaultFalse = defaultField [| False |] . booleanField
defaultTrue :: String -> Field
defaultTrue = defaultField [| True |] . booleanField
stringField :: String -> Field
stringField = flip simpleField [t| String |]
optionalStringField :: String -> Field
optionalStringField = optionalField . stringField
optionalNEStringField :: String -> Field
optionalNEStringField = optionalField . flip simpleField [t| NonEmptyString |]
type UncheckedValue = JSValue
type UncheckedDict = JSObject JSValue
type UncheckedList = [JSValue]
forceNonNeg :: (Num a, Ord a, Show a) => a -> NonNegative a
forceNonNeg i = case mkNonNegative i of
Ok n -> n
Bad msg -> error msg
$(declareSADT "TagType"
[ ("TagTypeInstance", 'C.tagInstance)
, ("TagTypeNode", 'C.tagNode)
, ("TagTypeGroup", 'C.tagNodegroup)
, ("TagTypeCluster", 'C.tagCluster)
, ("TagTypeNetwork", 'C.tagNetwork)
])
$(makeJSONInstance ''TagType)
data TagObject = TagInstance String
| TagNode String
| TagGroup String
| TagNetwork String
| TagCluster
deriving (Show, Eq)
tagTypeOf :: TagObject -> TagType
tagTypeOf (TagInstance {}) = TagTypeInstance
tagTypeOf (TagNode {}) = TagTypeNode
tagTypeOf (TagGroup {}) = TagTypeGroup
tagTypeOf (TagCluster {}) = TagTypeCluster
tagTypeOf (TagNetwork {}) = TagTypeNetwork
tagNameOf :: TagObject -> Maybe String
tagNameOf (TagInstance s) = Just s
tagNameOf (TagNode s) = Just s
tagNameOf (TagGroup s) = Just s
tagNameOf (TagNetwork s) = Just s
tagNameOf TagCluster = Nothing
tagObjectFrom :: (Monad m) => TagType -> JSValue -> m TagObject
tagObjectFrom TagTypeInstance (JSString s) =
return . TagInstance $ fromJSString s
tagObjectFrom TagTypeNode (JSString s) = return . TagNode $ fromJSString s
tagObjectFrom TagTypeGroup (JSString s) = return . TagGroup $ fromJSString s
tagObjectFrom TagTypeNetwork (JSString s) =
return . TagNetwork $ fromJSString s
tagObjectFrom TagTypeCluster JSNull = return TagCluster
tagObjectFrom t v =
fail $ "Invalid tag type/name combination: " ++ show t ++ "/" ++
show (pp_value v)
tagNameField :: String
tagNameField = "name"
encodeTagObject :: TagObject -> (JSValue, [(String, JSValue)])
encodeTagObject t = ( showJSON (tagTypeOf t)
, [(tagNameField, maybe JSNull showJSON (tagNameOf t))] )
decodeTagObject :: (Monad m) => [(String, JSValue)] -> JSValue -> m TagObject
decodeTagObject obj kind = do
ttype <- fromJVal kind
tname <- fromObj obj tagNameField
tagObjectFrom ttype tname
$(declareSADT "ReplaceDisksMode"
[ ("ReplaceOnPrimary", 'C.replaceDiskPri)
, ("ReplaceOnSecondary", 'C.replaceDiskSec)
, ("ReplaceNewSecondary", 'C.replaceDiskChg)
, ("ReplaceAuto", 'C.replaceDiskAuto)
])
$(makeJSONInstance ''ReplaceDisksMode)
newtype DiskIndex = DiskIndex { unDiskIndex :: Int }
deriving (Show, Eq, Ord)
mkDiskIndex :: (Monad m) => Int -> m DiskIndex
mkDiskIndex i | i >= 0 && i < C.maxDisks = return (DiskIndex i)
| otherwise = fail $ "Invalid value for disk index '" ++
show i ++ "', required between 0 and " ++
show C.maxDisks
instance JSON DiskIndex where
readJSON v = readJSON v >>= mkDiskIndex
showJSON = showJSON . unDiskIndex
$(declareSADT "DiskAccess"
[ ("DiskReadOnly", 'C.diskRdonly)
, ("DiskReadWrite", 'C.diskRdwr)
])
$(makeJSONInstance ''DiskAccess)
$(buildObject "INicParams" "inic"
[ optionalField $ simpleField C.inicMac [t| NonEmptyString |]
, optionalField $ simpleField C.inicIp [t| String |]
, optionalField $ simpleField C.inicMode [t| NonEmptyString |]
, optionalField $ simpleField C.inicLink [t| NonEmptyString |]
, optionalField $ simpleField C.inicName [t| NonEmptyString |]
])
$(buildObject "IDiskParams" "idisk"
[ optionalField $ simpleField C.idiskSize [t| Int |]
, optionalField $ simpleField C.idiskMode [t| DiskAccess |]
, optionalField $ simpleField C.idiskAdopt [t| NonEmptyString |]
, optionalField $ simpleField C.idiskVg [t| NonEmptyString |]
, optionalField $ simpleField C.idiskMetavg [t| NonEmptyString |]
, optionalField $ simpleField C.idiskName [t| NonEmptyString |]
])
data RecreateDisksInfo
= RecreateDisksAll
| RecreateDisksIndices (NonEmpty DiskIndex)
| RecreateDisksParams (NonEmpty (DiskIndex, IDiskParams))
deriving (Eq, Show)
readRecreateDisks :: JSValue -> Text.JSON.Result RecreateDisksInfo
readRecreateDisks (JSArray []) = return RecreateDisksAll
readRecreateDisks v =
case readJSON v::Text.JSON.Result [DiskIndex] of
Text.JSON.Ok indices -> liftM RecreateDisksIndices (mkNonEmpty indices)
_ -> case readJSON v::Text.JSON.Result [(DiskIndex, IDiskParams)] of
Text.JSON.Ok params -> liftM RecreateDisksParams (mkNonEmpty params)
_ -> fail $ "Can't parse disk information as either list of disk"
++ " indices or list of disk parameters; value received:"
++ show (pp_value v)
instance JSON RecreateDisksInfo where
readJSON = readRecreateDisks
showJSON RecreateDisksAll = showJSON ()
showJSON (RecreateDisksIndices idx) = showJSON idx
showJSON (RecreateDisksParams params) = showJSON params
data DdmOldChanges = DdmOldIndex (NonNegative Int)
| DdmOldMod DdmSimple
deriving (Eq, Show)
readDdmOldChanges :: JSValue -> Text.JSON.Result DdmOldChanges
readDdmOldChanges v =
case readJSON v::Text.JSON.Result (NonNegative Int) of
Text.JSON.Ok nn -> return $ DdmOldIndex nn
_ -> case readJSON v::Text.JSON.Result DdmSimple of
Text.JSON.Ok ddms -> return $ DdmOldMod ddms
_ -> fail $ "Can't parse value '" ++ show (pp_value v) ++ "' as"
++ " either index or modification"
instance JSON DdmOldChanges where
showJSON (DdmOldIndex i) = showJSON i
showJSON (DdmOldMod m) = showJSON m
readJSON = readDdmOldChanges
data SetParamsMods a
= SetParamsEmpty
| SetParamsDeprecated (NonEmpty (DdmOldChanges, a))
| SetParamsNew (NonEmpty (DdmFull, Int, a))
deriving (Eq, Show)
readSetParams :: (JSON a) => JSValue -> Text.JSON.Result (SetParamsMods a)
readSetParams (JSArray []) = return SetParamsEmpty
readSetParams v =
case readJSON v::Text.JSON.Result [(DdmOldChanges, JSValue)] of
Text.JSON.Ok _ -> liftM SetParamsDeprecated $ readJSON v
_ -> liftM SetParamsNew $ readJSON v
instance (JSON a) => JSON (SetParamsMods a) where
showJSON SetParamsEmpty = showJSON ()
showJSON (SetParamsDeprecated v) = showJSON v
showJSON (SetParamsNew v) = showJSON v
readJSON = readSetParams
data ExportTarget = ExportTargetLocal NonEmptyString
| ExportTargetRemote UncheckedList
deriving (Eq, Show)
readExportTarget :: JSValue -> Text.JSON.Result ExportTarget
readExportTarget (JSString s) = liftM ExportTargetLocal $
mkNonEmpty (fromJSString s)
readExportTarget (JSArray arr) = return $ ExportTargetRemote arr
readExportTarget v = fail $ "Invalid value received for 'target_node': " ++
show (pp_value v)
instance JSON ExportTarget where
showJSON (ExportTargetLocal s) = showJSON s
showJSON (ExportTargetRemote l) = showJSON l
readJSON = readExportTarget
pInstanceName :: Field
pInstanceName = simpleField "instance_name" [t| String |]
pInstanceUuid :: Field
pInstanceUuid = optionalField $ simpleField "instance_uuid" [t| String |]
pInstances :: Field
pInstances = defaultField [| [] |] $
simpleField "instances" [t| [NonEmptyString] |]
pName :: Field
pName = simpleField "name" [t| NonEmptyString |]
pTagsList :: Field
pTagsList = simpleField "tags" [t| [String] |]
pTagsObject :: Field
pTagsObject =
customField 'decodeTagObject 'encodeTagObject [tagNameField] $
simpleField "kind" [t| TagObject |]
pOutputFields :: Field
pOutputFields = simpleField "output_fields" [t| [NonEmptyString] |]
pShutdownTimeout :: Field
pShutdownTimeout = defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
simpleField "shutdown_timeout" [t| NonNegative Int |]
pShutdownTimeout' :: Field
pShutdownTimeout' =
renameField "InstShutdownTimeout" .
defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
simpleField "timeout" [t| NonNegative Int |]
pShutdownInstance :: Field
pShutdownInstance = defaultTrue "shutdown"
pForce :: Field
pForce = defaultFalse "force"
pIgnoreOfflineNodes :: Field
pIgnoreOfflineNodes = defaultFalse "ignore_offline_nodes"
pNodeName :: Field
pNodeName = simpleField "node_name" [t| NonEmptyString |]
pNodeUuid :: Field
pNodeUuid = optionalField $ simpleField "node_uuid" [t| NonEmptyString |]
pNodeNames :: Field
pNodeNames =
defaultField [| [] |] $ simpleField "node_names" [t| [NonEmptyString] |]
pNodeUuids :: Field
pNodeUuids =
optionalField $ simpleField "node_uuids" [t| [NonEmptyString] |]
pGroupName :: Field
pGroupName = simpleField "group_name" [t| NonEmptyString |]
pMigrationMode :: Field
pMigrationMode =
renameField "MigrationMode" .
optionalField $
simpleField "mode" [t| MigrationMode |]
pMigrationLive :: Field
pMigrationLive =
renameField "OldLiveMode" . optionalField $ booleanField "live"
pMigrationCleanup :: Field
pMigrationCleanup = renameField "MigrationCleanup" $ defaultFalse "cleanup"
pForceVariant :: Field
pForceVariant = defaultFalse "force_variant"
pWaitForSync :: Field
pWaitForSync = defaultTrue "wait_for_sync"
pWaitForSyncFalse :: Field
pWaitForSyncFalse = defaultField [| False |] pWaitForSync
pIgnoreConsistency :: Field
pIgnoreConsistency = defaultFalse "ignore_consistency"
pStorageName :: Field
pStorageName =
renameField "StorageName" $ simpleField "name" [t| NonEmptyString |]
pUseLocking :: Field
pUseLocking = defaultFalse "use_locking"
pOpportunisticLocking :: Field
pOpportunisticLocking = defaultFalse "opportunistic_locking"
pNameCheck :: Field
pNameCheck = defaultTrue "name_check"
pNodeGroupAllocPolicy :: Field
pNodeGroupAllocPolicy = optionalField $
simpleField "alloc_policy" [t| AllocPolicy |]
pGroupNodeParams :: Field
pGroupNodeParams = optionalField $ simpleField "ndparams" [t| UncheckedDict |]
pQueryWhat :: Field
pQueryWhat = simpleField "what" [t| Qlang.QueryTypeOp |]
pEarlyRelease :: Field
pEarlyRelease = defaultFalse "early_release"
pIpCheck :: Field
pIpCheck = defaultTrue "ip_check"
pIpConflictsCheck :: Field
pIpConflictsCheck = defaultTrue "conflicts_check"
pNoRemember :: Field
pNoRemember = defaultFalse "no_remember"
pMigrationTargetNode :: Field
pMigrationTargetNode = optionalNEStringField "target_node"
pMigrationTargetNodeUuid :: Field
pMigrationTargetNodeUuid = optionalNEStringField "target_node_uuid"
pMoveTargetNode :: Field
pMoveTargetNode =
renameField "MoveTargetNode" $
simpleField "target_node" [t| NonEmptyString |]
pMoveTargetNodeUuid :: Field
pMoveTargetNodeUuid =
renameField "MoveTargetNodeUuid" . optionalField $
simpleField "target_node_uuid" [t| NonEmptyString |]
pStartupPaused :: Field
pStartupPaused = defaultFalse "startup_paused"
pVerbose :: Field
pVerbose = defaultFalse "verbose"
pDebugSimulateErrors :: Field
pDebugSimulateErrors = defaultFalse "debug_simulate_errors"
pErrorCodes :: Field
pErrorCodes = defaultFalse "error_codes"
pSkipChecks :: Field
pSkipChecks = defaultField [| Set.empty |] $
simpleField "skip_checks" [t| Set.Set VerifyOptionalChecks |]
pIgnoreErrors :: Field
pIgnoreErrors = defaultField [| Set.empty |] $
simpleField "ignore_errors" [t| Set.Set CVErrorCode |]
pOptGroupName :: Field
pOptGroupName = renameField "OptGroupName" .
optionalField $ simpleField "group_name" [t| NonEmptyString |]
pDiskParams :: Field
pDiskParams = optionalField $
simpleField "diskparams" [t| GenericContainer DiskTemplate
UncheckedDict |]
pHvState :: Field
pHvState = optionalField $ simpleField "hv_state" [t| UncheckedDict |]
pDiskState :: Field
pDiskState = optionalField $ simpleField "disk_state" [t| UncheckedDict |]
pIgnoreIpolicy :: Field
pIgnoreIpolicy = defaultFalse "ignore_ipolicy"
pAllowRuntimeChgs :: Field
pAllowRuntimeChgs = defaultTrue "allow_runtime_changes"
type TestClusterOsListItem = (DdmSimple, NonEmptyString)
type TestClusterOsList = [TestClusterOsListItem]
pInstDisks :: Field
pInstDisks = renameField "instDisks" $ simpleField "disks" [t| [IDiskParams] |]
pDiskTemplate :: Field
pDiskTemplate = simpleField "disk_template" [t| DiskTemplate |]
pOptDiskTemplate :: Field
pOptDiskTemplate =
optionalField .
renameField "OptDiskTemplate" $
simpleField "disk_template" [t| DiskTemplate |]
pFileDriver :: Field
pFileDriver = optionalField $ simpleField "file_driver" [t| FileDriver |]
pFileStorageDir :: Field
pFileStorageDir = optionalNEStringField "file_storage_dir"
pGlobalFileStorageDir :: Field
pGlobalFileStorageDir = optionalNEStringField "file_storage_dir"
pGlobalSharedFileStorageDir :: Field
pGlobalSharedFileStorageDir = optionalNEStringField "shared_file_storage_dir"
pVgName :: Field
pVgName = optionalStringField "vg_name"
pEnabledHypervisors :: Field
pEnabledHypervisors =
optionalField $
simpleField "enabled_hypervisors" [t| NonEmpty Hypervisor |]
pEnabledDiskTemplates :: Field
pEnabledDiskTemplates =
optionalField $
simpleField "enabled_disk_templates" [t| NonEmpty DiskTemplate |]
pHypervisor :: Field
pHypervisor =
optionalField $
simpleField "hypervisor" [t| Hypervisor |]
pClusterHvParams :: Field
pClusterHvParams =
renameField "ClusterHvParams" .
optionalField $
simpleField "hvparams" [t| Container UncheckedDict |]
pInstHvParams :: Field
pInstHvParams =
renameField "InstHvParams" .
defaultField [| toJSObject [] |] $
simpleField "hvparams" [t| UncheckedDict |]
pClusterBeParams :: Field
pClusterBeParams =
renameField "ClusterBeParams" .
optionalField $ simpleField "beparams" [t| UncheckedDict |]
pInstBeParams :: Field
pInstBeParams =
renameField "InstBeParams" .
defaultField [| toJSObject [] |] $
simpleField "beparams" [t| UncheckedDict |]
pResetDefaults :: Field
pResetDefaults = defaultFalse "identify_defaults"
pOsHvp :: Field
pOsHvp = optionalField $ simpleField "os_hvp" [t| Container UncheckedDict |]
pClusterOsParams :: Field
pClusterOsParams =
renameField "ClusterOsParams" .
optionalField $ simpleField "osparams" [t| Container UncheckedDict |]
pInstOsParams :: Field
pInstOsParams =
renameField "InstOsParams" . defaultField [| toJSObject [] |] $
simpleField "osparams" [t| UncheckedDict |]
pTempOsParams :: Field
pTempOsParams =
renameField "TempOsParams" .
optionalField $ simpleField "osparams" [t| UncheckedDict |]
pTempHvParams :: Field
pTempHvParams =
renameField "TempHvParams" .
defaultField [| toJSObject [] |] $
simpleField "hvparams" [t| UncheckedDict |]
pTempBeParams :: Field
pTempBeParams =
renameField "TempBeParams" .
defaultField [| toJSObject [] |] $
simpleField "beparams" [t| UncheckedDict |]
pCandidatePoolSize :: Field
pCandidatePoolSize =
optionalField $ simpleField "candidate_pool_size" [t| Positive Int |]
pUidPool :: Field
pUidPool = optionalField $ simpleField "uid_pool" [t| [[(Int, Int)]] |]
pAddUids :: Field
pAddUids = optionalField $ simpleField "add_uids" [t| [[(Int, Int)]] |]
pRemoveUids :: Field
pRemoveUids = optionalField $ simpleField "remove_uids" [t| [[(Int, Int)]] |]
pMaintainNodeHealth :: Field
pMaintainNodeHealth = optionalField $ booleanField "maintain_node_health"
pModifyEtcHosts :: Field
pModifyEtcHosts = optionalField $ booleanField "modify_etc_hosts"
pPreallocWipeDisks :: Field
pPreallocWipeDisks = optionalField $ booleanField "prealloc_wipe_disks"
pNicParams :: Field
pNicParams = optionalField $ simpleField "nicparams" [t| INicParams |]
pInstNics :: Field
pInstNics = simpleField "nics" [t| [INicParams] |]
pNdParams :: Field
pNdParams = optionalField $ simpleField "ndparams" [t| UncheckedDict |]
pIpolicy :: Field
pIpolicy = optionalField $ simpleField "ipolicy" [t| UncheckedDict |]
pDrbdHelper :: Field
pDrbdHelper = optionalStringField "drbd_helper"
pDefaultIAllocator :: Field
pDefaultIAllocator = optionalStringField "default_iallocator"
pMasterNetdev :: Field
pMasterNetdev = optionalStringField "master_netdev"
pMasterNetmask :: Field
pMasterNetmask =
optionalField $ simpleField "master_netmask" [t| NonNegative Int |]
pReservedLvs :: Field
pReservedLvs =
optionalField $ simpleField "reserved_lvs" [t| [NonEmptyString] |]
pHiddenOs :: Field
pHiddenOs = optionalField $ simpleField "hidden_os" [t| TestClusterOsList |]
pBlacklistedOs :: Field
pBlacklistedOs =
optionalField $ simpleField "blacklisted_os" [t| TestClusterOsList |]
pUseExternalMipScript :: Field
pUseExternalMipScript = optionalField $ booleanField "use_external_mip_script"
pQueryFields :: Field
pQueryFields = simpleField "fields" [t| [NonEmptyString] |]
pQueryFilter :: Field
pQueryFilter = simpleField "qfilter" [t| Qlang.Filter String |]
pOobCommand :: Field
pOobCommand = simpleField "command" [t| OobCommand |]
pOobTimeout :: Field
pOobTimeout =
defaultField [| C.oobTimeout |] $ simpleField "timeout" [t| Int |]
pIgnoreStatus :: Field
pIgnoreStatus = defaultFalse "ignore_status"
pPowerDelay :: Field
pPowerDelay =
defaultField [| C.oobPowerDelay |] $
simpleField "power_delay" [t| Double |]
pPrimaryIp :: Field
pPrimaryIp = optionalStringField "primary_ip"
pSecondaryIp :: Field
pSecondaryIp = optionalNEStringField "secondary_ip"
pReadd :: Field
pReadd = defaultFalse "readd"
pNodeGroup :: Field
pNodeGroup = optionalNEStringField "group"
pMasterCapable :: Field
pMasterCapable = optionalField $ booleanField "master_capable"
pVmCapable :: Field
pVmCapable = optionalField $ booleanField "vm_capable"
pNames :: Field
pNames = defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
pNodes :: Field
pNodes = defaultField [| [] |] $ simpleField "nodes" [t| [NonEmptyString] |]
pRequiredNodes :: Field
pRequiredNodes =
renameField "ReqNodes " $ simpleField "nodes" [t| [NonEmptyString] |]
pRequiredNodeUuids :: Field
pRequiredNodeUuids =
renameField "ReqNodeUuids " . optionalField $
simpleField "node_uuids" [t| [NonEmptyString] |]
pStorageType :: Field
pStorageType = simpleField "storage_type" [t| StorageType |]
pStorageChanges :: Field
pStorageChanges = simpleField "changes" [t| UncheckedDict |]
pMasterCandidate :: Field
pMasterCandidate = optionalField $ booleanField "master_candidate"
pOffline :: Field
pOffline = optionalField $ booleanField "offline"
pDrained ::Field
pDrained = optionalField $ booleanField "drained"
pAutoPromote :: Field
pAutoPromote = defaultFalse "auto_promote"
pPowered :: Field
pPowered = optionalField $ booleanField "powered"
pIallocator :: Field
pIallocator = optionalNEStringField "iallocator"
pRemoteNode :: Field
pRemoteNode = optionalNEStringField "remote_node"
pRemoteNodeUuid :: Field
pRemoteNodeUuid = optionalNEStringField "remote_node_uuid"
pEvacMode :: Field
pEvacMode = renameField "EvacMode" $ simpleField "mode" [t| NodeEvacMode |]
pInstCreateMode :: Field
pInstCreateMode =
renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
pNoInstall :: Field
pNoInstall = optionalField $ booleanField "no_install"
pInstOs :: Field
pInstOs = optionalNEStringField "os_type"
pPrimaryNode :: Field
pPrimaryNode = optionalNEStringField "pnode"
pPrimaryNodeUuid :: Field
pPrimaryNodeUuid = optionalNEStringField "pnode_uuid"
pSecondaryNode :: Field
pSecondaryNode = optionalNEStringField "snode"
pSecondaryNodeUuid :: Field
pSecondaryNodeUuid = optionalNEStringField "snode_uuid"
pSourceHandshake :: Field
pSourceHandshake =
optionalField $ simpleField "source_handshake" [t| UncheckedList |]
pSourceInstance :: Field
pSourceInstance = optionalNEStringField "source_instance_name"
pSourceShutdownTimeout :: Field
pSourceShutdownTimeout =
defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
simpleField "source_shutdown_timeout" [t| NonNegative Int |]
pSourceX509Ca :: Field
pSourceX509Ca = optionalNEStringField "source_x509_ca"
pSrcNode :: Field
pSrcNode = optionalNEStringField "src_node"
pSrcNodeUuid :: Field
pSrcNodeUuid = optionalNEStringField "src_node_uuid"
pSrcPath :: Field
pSrcPath = optionalNEStringField "src_path"
pStartInstance :: Field
pStartInstance = defaultTrue "start"
pInstTags :: Field
pInstTags =
renameField "InstTags" .
defaultField [| [] |] $
simpleField "tags" [t| [NonEmptyString] |]
pMultiAllocInstances :: Field
pMultiAllocInstances =
renameField "InstMultiAlloc" .
defaultField [| [] |] $
simpleField "instances"[t| UncheckedList |]
pIgnoreFailures :: Field
pIgnoreFailures = defaultFalse "ignore_failures"
pNewName :: Field
pNewName = simpleField "new_name" [t| NonEmptyString |]
pIgnoreSecondaries :: Field
pIgnoreSecondaries = defaultFalse "ignore_secondaries"
pRebootType :: Field
pRebootType = simpleField "reboot_type" [t| RebootType |]
pIgnoreDiskSize :: Field
pIgnoreDiskSize = defaultFalse "ignore_size"
pRecreateDisksInfo :: Field
pRecreateDisksInfo =
renameField "RecreateDisksInfo" .
defaultField [| RecreateDisksAll |] $
simpleField "disks" [t| RecreateDisksInfo |]
pStatic :: Field
pStatic = defaultFalse "static"
pInstParamsNicChanges :: Field
pInstParamsNicChanges =
renameField "InstNicChanges" .
defaultField [| SetParamsEmpty |] $
simpleField "nics" [t| SetParamsMods INicParams |]
pInstParamsDiskChanges :: Field
pInstParamsDiskChanges =
renameField "InstDiskChanges" .
defaultField [| SetParamsEmpty |] $
simpleField "disks" [t| SetParamsMods IDiskParams |]
pRuntimeMem :: Field
pRuntimeMem = optionalField $ simpleField "runtime_mem" [t| Positive Int |]
pOsNameChange :: Field
pOsNameChange = optionalNEStringField "os_name"
pDiskIndex :: Field
pDiskIndex = renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
pDiskChgAmount :: Field
pDiskChgAmount =
renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
pDiskChgAbsolute :: Field
pDiskChgAbsolute = renameField "DiskChkAbsolute" $ defaultFalse "absolute"
pTargetGroups :: Field
pTargetGroups =
optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
pExportMode :: Field
pExportMode =
renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
pExportTargetNode :: Field
pExportTargetNode =
renameField "ExportTarget" $
simpleField "target_node" [t| ExportTarget |]
pExportTargetNodeUuid :: Field
pExportTargetNodeUuid =
renameField "ExportTargetNodeUuid" . optionalField $
simpleField "target_node_uuid" [t| NonEmptyString |]
pRemoveInstance :: Field
pRemoveInstance = defaultFalse "remove_instance"
pIgnoreRemoveFailures :: Field
pIgnoreRemoveFailures = defaultFalse "ignore_remove_failures"
pX509KeyName :: Field
pX509KeyName = optionalField $ simpleField "x509_key_name" [t| UncheckedList |]
pX509DestCA :: Field
pX509DestCA = optionalNEStringField "destination_x509_ca"
pTagSearchPattern :: Field
pTagSearchPattern =
renameField "TagSearchPattern" $ simpleField "pattern" [t| NonEmptyString |]
pRestrictedCommand :: Field
pRestrictedCommand =
renameField "RestrictedCommand" $
simpleField "command" [t| NonEmptyString |]
pReplaceDisksMode :: Field
pReplaceDisksMode =
renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
pReplaceDisksList :: Field
pReplaceDisksList =
renameField "ReplaceDisksList" $ simpleField "disks" [t| [DiskIndex] |]
pAllowFailover :: Field
pAllowFailover = defaultFalse "allow_failover"
pDelayDuration :: Field
pDelayDuration =
renameField "DelayDuration" $ simpleField "duration" [t| Double |]
pDelayOnMaster :: Field
pDelayOnMaster = renameField "DelayOnMaster" $ defaultTrue "on_master"
pDelayOnNodes :: Field
pDelayOnNodes =
renameField "DelayOnNodes" .
defaultField [| [] |] $
simpleField "on_nodes" [t| [NonEmptyString] |]
pDelayOnNodeUuids :: Field
pDelayOnNodeUuids =
renameField "DelayOnNodeUuids" . optionalField $
simpleField "on_node_uuids" [t| [NonEmptyString] |]
pDelayRepeat :: Field
pDelayRepeat =
renameField "DelayRepeat" .
defaultField [| forceNonNeg (0::Int) |] $
simpleField "repeat" [t| NonNegative Int |]
pIAllocatorDirection :: Field
pIAllocatorDirection =
renameField "IAllocatorDirection" $
simpleField "direction" [t| IAllocatorTestDir |]
pIAllocatorMode :: Field
pIAllocatorMode =
renameField "IAllocatorMode" $
simpleField "mode" [t| IAllocatorMode |]
pIAllocatorReqName :: Field
pIAllocatorReqName =
renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
pIAllocatorNics :: Field
pIAllocatorNics =
renameField "IAllocatorNics" $ simpleField "nics" [t| [UncheckedDict] |]
pIAllocatorDisks :: Field
pIAllocatorDisks =
renameField "IAllocatorDisks" $ simpleField "disks" [t| UncheckedList |]
pIAllocatorMemory :: Field
pIAllocatorMemory =
renameField "IAllocatorMem" .
optionalField $
simpleField "memory" [t| NonNegative Int |]
pIAllocatorVCpus :: Field
pIAllocatorVCpus =
renameField "IAllocatorVCpus" .
optionalField $
simpleField "vcpus" [t| NonNegative Int |]
pIAllocatorOs :: Field
pIAllocatorOs = renameField "IAllocatorOs" $ optionalNEStringField "os"
pIAllocatorInstances :: Field
pIAllocatorInstances =
renameField "IAllocatorInstances " .
optionalField $
simpleField "instances" [t| [NonEmptyString] |]
pIAllocatorEvacMode :: Field
pIAllocatorEvacMode =
renameField "IAllocatorEvacMode" .
optionalField $
simpleField "evac_mode" [t| NodeEvacMode |]
pIAllocatorSpindleUse :: Field
pIAllocatorSpindleUse =
renameField "IAllocatorSpindleUse" .
defaultField [| forceNonNeg (1::Int) |] $
simpleField "spindle_use" [t| NonNegative Int |]
pIAllocatorCount :: Field
pIAllocatorCount =
renameField "IAllocatorCount" .
defaultField [| forceNonNeg (1::Int) |] $
simpleField "count" [t| NonNegative Int |]
pJQueueNotifyWaitLock :: Field
pJQueueNotifyWaitLock = defaultFalse "notify_waitlock"
pJQueueNotifyExec :: Field
pJQueueNotifyExec = defaultFalse "notify_exec"
pJQueueLogMessages :: Field
pJQueueLogMessages =
defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
pJQueueFail :: Field
pJQueueFail =
renameField "JQueueFail" $ defaultFalse "fail"
pTestDummyResult :: Field
pTestDummyResult =
renameField "TestDummyResult" $ simpleField "result" [t| UncheckedValue |]
pTestDummyMessages :: Field
pTestDummyMessages =
renameField "TestDummyMessages" $
simpleField "messages" [t| UncheckedValue |]
pTestDummyFail :: Field
pTestDummyFail =
renameField "TestDummyFail" $ simpleField "fail" [t| UncheckedValue |]
pTestDummySubmitJobs :: Field
pTestDummySubmitJobs =
renameField "TestDummySubmitJobs" $
simpleField "submit_jobs" [t| UncheckedValue |]
pNetworkName :: Field
pNetworkName = simpleField "network_name" [t| NonEmptyString |]
pNetworkAddress4 :: Field
pNetworkAddress4 =
renameField "NetworkAddress4" $
simpleField "network" [t| NonEmptyString |]
pNetworkGateway4 :: Field
pNetworkGateway4 =
renameField "NetworkGateway4" $
optionalNEStringField "gateway"
pNetworkAddress6 :: Field
pNetworkAddress6 =
renameField "NetworkAddress6" $
optionalNEStringField "network6"
pNetworkGateway6 :: Field
pNetworkGateway6 =
renameField "NetworkGateway6" $
optionalNEStringField "gateway6"
pNetworkMacPrefix :: Field
pNetworkMacPrefix =
renameField "NetMacPrefix" $
optionalNEStringField "mac_prefix"
pNetworkAddRsvdIps :: Field
pNetworkAddRsvdIps =
renameField "NetworkAddRsvdIps" .
optionalField $
simpleField "add_reserved_ips" [t| [NonEmptyString] |]
pNetworkRemoveRsvdIps :: Field
pNetworkRemoveRsvdIps =
renameField "NetworkRemoveRsvdIps" .
optionalField $
simpleField "remove_reserved_ips" [t| [NonEmptyString] |]
pNetworkMode :: Field
pNetworkMode = simpleField "network_mode" [t| NICMode |]
pNetworkLink :: Field
pNetworkLink = simpleField "network_link" [t| NonEmptyString |]
pDryRun :: Field
pDryRun = optionalField $ booleanField "dry_run"
pDebugLevel :: Field
pDebugLevel = optionalField $ simpleField "debug_level" [t| NonNegative Int |]
pOpPriority :: Field
pOpPriority =
defaultField [| OpPrioNormal |] $
simpleField "priority" [t| OpSubmitPriority |]
pDependencies :: Field
pDependencies =
optionalNullSerField $ simpleField "depends" [t| [JobDependency] |]
pComment :: Field
pComment = optionalNullSerField $ stringField "comment"
pReason :: Field
pReason = simpleField C.opcodeReason [t| ReasonTrail |]
dOldQuery :: [Field]
dOldQuery =
[ pOutputFields
, pNames
, pUseLocking
]
dOldQueryNoLocking :: [Field]
dOldQueryNoLocking =
[ pOutputFields
, pNames
]