module Ganeti.Constants where
import Control.Arrow ((***),(&&&))
import Data.List ((\\))
import Data.Map (Map)
import qualified Data.Map as Map (empty, fromList, keys, insert)
import Data.Monoid
import qualified AutoConf
import Ganeti.ConstantUtils (PythonChar(..), FrozenSet, Protocol(..),
buildVersion)
import qualified Ganeti.ConstantUtils as ConstantUtils
import qualified Ganeti.HTools.Types as Types
import Ganeti.HTools.Types (AutoRepairResult(..), AutoRepairType(..))
import Ganeti.Logging (SyslogUsage(..))
import qualified Ganeti.Logging as Logging (syslogUsageToRaw)
import qualified Ganeti.Runtime as Runtime
import Ganeti.Runtime (GanetiDaemon(..), MiscGroup(..), GanetiGroup(..),
ExtraLogReason(..))
import Ganeti.THH (PyValueEx(..))
import Ganeti.Types
import qualified Ganeti.Types as Types
import Ganeti.Confd.Types (ConfdRequestType(..), ConfdReqField(..),
ConfdReplyStatus(..), ConfdNodeRole(..),
ConfdErrorType(..))
import qualified Ganeti.Confd.Types as Types
import qualified Ganeti.HTools.Tags.Constants as Tags
htoolsProgs :: [String]
htoolsProgs = AutoConf.htoolsProgs
drbdBarriers :: String
drbdBarriers = AutoConf.drbdBarriers
drbdNoMetaFlush :: Bool
drbdNoMetaFlush = AutoConf.drbdNoMetaFlush
lvmStripecount :: Int
lvmStripecount = AutoConf.lvmStripecount
hasGnuLn :: Bool
hasGnuLn = AutoConf.hasGnuLn
exportDir :: String
exportDir = AutoConf.exportDir
backupDir :: String
backupDir = AutoConf.backupDir
osSearchPath :: [String]
osSearchPath = AutoConf.osSearchPath
esSearchPath :: [String]
esSearchPath = AutoConf.esSearchPath
sshConfigDir :: String
sshConfigDir = AutoConf.sshConfigDir
xenConfigDir :: String
xenConfigDir = AutoConf.xenConfigDir
sysconfdir :: String
sysconfdir = AutoConf.sysconfdir
toolsdir :: String
toolsdir = AutoConf.toolsdir
localstatedir :: String
localstatedir = AutoConf.localstatedir
pkglibdir :: String
pkglibdir = AutoConf.pkglibdir
sharedir :: String
sharedir = AutoConf.sharedir
manPages :: Map String Int
manPages = Map.fromList AutoConf.manPages
versionedsharedir :: String
versionedsharedir = AutoConf.versionedsharedir
gntScripts :: [String]
gntScripts = AutoConf.gntScripts
releaseVersion :: String
releaseVersion = AutoConf.packageVersion
versionMajor :: Int
versionMajor = AutoConf.versionMajor
versionMinor :: Int
versionMinor = AutoConf.versionMinor
versionRevision :: Int
versionRevision = AutoConf.versionRevision
dirVersion :: String
dirVersion = AutoConf.dirVersion
osApiV10 :: Int
osApiV10 = 10
osApiV15 :: Int
osApiV15 = 15
osApiV20 :: Int
osApiV20 = 20
osApiVersions :: FrozenSet Int
osApiVersions = ConstantUtils.mkSet [osApiV10, osApiV15, osApiV20]
exportVersion :: Int
exportVersion = 0
rapiVersion :: Int
rapiVersion = 2
configMajor :: Int
configMajor = AutoConf.versionMajor
configMinor :: Int
configMinor = AutoConf.versionMinor
configRevision :: Int
configRevision = 0
configVersion :: Int
configVersion = buildVersion configMajor configMinor configRevision
protocolVersion :: Int
protocolVersion = buildVersion configMajor configMinor configRevision
daemonsGroup :: String
daemonsGroup = Runtime.daemonGroup (ExtraGroup DaemonsGroup)
adminGroup :: String
adminGroup = Runtime.daemonGroup (ExtraGroup AdminGroup)
masterdUser :: String
masterdUser = Runtime.daemonUser GanetiMasterd
masterdGroup :: String
masterdGroup = Runtime.daemonGroup (DaemonGroup GanetiMasterd)
metadUser :: String
metadUser = Runtime.daemonUser GanetiMetad
metadGroup :: String
metadGroup = Runtime.daemonGroup (DaemonGroup GanetiMetad)
rapiUser :: String
rapiUser = Runtime.daemonUser GanetiRapi
rapiGroup :: String
rapiGroup = Runtime.daemonGroup (DaemonGroup GanetiRapi)
confdUser :: String
confdUser = Runtime.daemonUser GanetiConfd
confdGroup :: String
confdGroup = Runtime.daemonGroup (DaemonGroup GanetiConfd)
wconfdUser :: String
wconfdUser = Runtime.daemonUser GanetiWConfd
wconfdGroup :: String
wconfdGroup = Runtime.daemonGroup (DaemonGroup GanetiWConfd)
kvmdUser :: String
kvmdUser = Runtime.daemonUser GanetiKvmd
kvmdGroup :: String
kvmdGroup = Runtime.daemonGroup (DaemonGroup GanetiKvmd)
luxidUser :: String
luxidUser = Runtime.daemonUser GanetiLuxid
luxidGroup :: String
luxidGroup = Runtime.daemonGroup (DaemonGroup GanetiLuxid)
nodedUser :: String
nodedUser = Runtime.daemonUser GanetiNoded
nodedGroup :: String
nodedGroup = Runtime.daemonGroup (DaemonGroup GanetiNoded)
mondUser :: String
mondUser = Runtime.daemonUser GanetiMond
mondGroup :: String
mondGroup = Runtime.daemonGroup (DaemonGroup GanetiMond)
sshLoginUser :: String
sshLoginUser = AutoConf.sshLoginUser
sshConsoleUser :: String
sshConsoleUser = AutoConf.sshConsoleUser
cpuPinningSep :: String
cpuPinningSep = ":"
cpuPinningAll :: String
cpuPinningAll = "all"
cpuPinningAllVal :: Int
cpuPinningAllVal = 1
cpuPinningOff :: [Int]
cpuPinningOff = [cpuPinningAllVal]
cpuPinningAllXen :: String
cpuPinningAllXen = "0-63"
ddCmd :: String
ddCmd = "dd"
ddBlockSize :: Int
ddBlockSize = 1024^2
maxWipeChunk :: Int
maxWipeChunk = 1024
minWipeChunkPercent :: Int
minWipeChunkPercent = 10
runDirsMode :: Int
runDirsMode = 0o775
secureDirMode :: Int
secureDirMode = 0o700
secureFileMode :: Int
secureFileMode = 0o600
adoptableBlockdevRoot :: String
adoptableBlockdevRoot = "/dev/disk/"
enableMond :: Bool
enableMond = AutoConf.enableMond
enableMetad :: Bool
enableMetad = AutoConf.enableMetad
enableRestrictedCommands :: Bool
enableRestrictedCommands = AutoConf.enableRestrictedCommands
ssh :: String
ssh = "ssh"
scp :: String
scp = "scp"
confd :: String
confd = Runtime.daemonName GanetiConfd
masterd :: String
masterd = Runtime.daemonName GanetiMasterd
metad :: String
metad = Runtime.daemonName GanetiMetad
mond :: String
mond = Runtime.daemonName GanetiMond
maintd :: String
maintd = Runtime.daemonName GanetiMaintd
noded :: String
noded = Runtime.daemonName GanetiNoded
wconfd :: String
wconfd = Runtime.daemonName GanetiWConfd
luxid :: String
luxid = Runtime.daemonName GanetiLuxid
rapi :: String
rapi = Runtime.daemonName GanetiRapi
kvmd :: String
kvmd = Runtime.daemonName GanetiKvmd
daemonsMaster :: FrozenSet String
daemonsMaster = ConstantUtils.mkSet [wconfd, luxid, rapi]
daemons :: FrozenSet String
daemons =
ConstantUtils.mkSet
$ map Runtime.daemonName [minBound .. maxBound]
defaultConfdPort :: Int
defaultConfdPort = 1814
defaultMondPort :: Int
defaultMondPort = 1815
defaultMaintdPort :: Int
defaultMaintdPort = 1816
defaultMetadPort :: Int
defaultMetadPort = 80
defaultNodedPort :: Int
defaultNodedPort = 1811
defaultRapiPort :: Int
defaultRapiPort = 5080
daemonsPorts :: Map String (Protocol, Int)
daemonsPorts =
Map.fromList
[ (confd, (Udp, defaultConfdPort))
, (metad, (Tcp, defaultMetadPort))
, (mond, (Tcp, defaultMondPort))
, (maintd, (Tcp, defaultMaintdPort))
, (noded, (Tcp, defaultNodedPort))
, (rapi, (Tcp, defaultRapiPort))
, (ssh, (Tcp, 22))
]
firstDrbdPort :: Int
firstDrbdPort = 11000
lastDrbdPort :: Int
lastDrbdPort = 14999
daemonsLogbase :: Map String String
daemonsLogbase =
Map.fromList
[ (Runtime.daemonName d, Runtime.daemonLogBase d) | d <- [minBound..] ]
daemonsExtraLogbase :: Map String (Map String String)
daemonsExtraLogbase =
Map.fromList $
map (Runtime.daemonName *** id)
[ (GanetiMond, Map.fromList
[ ("access", Runtime.daemonsExtraLogbase GanetiMond AccessLog)
, ("error", Runtime.daemonsExtraLogbase GanetiMond ErrorLog)
])
]
extraLogreasonAccess :: String
extraLogreasonAccess = Runtime.daemonsExtraLogbase GanetiMond AccessLog
extraLogreasonError :: String
extraLogreasonError = Runtime.daemonsExtraLogbase GanetiMond ErrorLog
devConsole :: String
devConsole = ConstantUtils.devConsole
procMounts :: String
procMounts = "/proc/mounts"
luxiEom :: PythonChar
luxiEom = PythonChar '\x03'
luxiOverride :: String
luxiOverride = "FORCE_LUXI_SOCKET"
luxiOverrideMaster :: String
luxiOverrideMaster = "master"
luxiOverrideQuery :: String
luxiOverrideQuery = "query"
luxiVersion :: Int
luxiVersion = configVersion
syslogUsage :: String
syslogUsage = AutoConf.syslogUsage
syslogNo :: String
syslogNo = Logging.syslogUsageToRaw SyslogNo
syslogYes :: String
syslogYes = Logging.syslogUsageToRaw SyslogYes
syslogOnly :: String
syslogOnly = Logging.syslogUsageToRaw SyslogOnly
syslogSocket :: String
syslogSocket = "/dev/log"
exportConfFile :: String
exportConfFile = "config.ini"
xenBootloader :: String
xenBootloader = AutoConf.xenBootloader
xenCmdXl :: String
xenCmdXl = "xl"
xenCmdXm :: String
xenCmdXm = "xm"
xenInitrd :: String
xenInitrd = AutoConf.xenInitrd
xenKernel :: String
xenKernel = AutoConf.xenKernel
xlSocatCmd :: String
xlSocatCmd = "socat -b524288 - TCP:%s:%d #"
xlMigrationPidfile :: String
xlMigrationPidfile = "socat.pid"
knownXenCommands :: FrozenSet String
knownXenCommands = ConstantUtils.mkSet [xenCmdXl, xenCmdXm]
kvmPath :: String
kvmPath = AutoConf.kvmPath
kvmKernel :: String
kvmKernel = AutoConf.kvmKernel
socatEscapeCode :: String
socatEscapeCode = "0x1d"
socatPath :: String
socatPath = AutoConf.socatPath
socatUseCompress :: Bool
socatUseCompress = AutoConf.socatUseCompress
socatUseEscape :: Bool
socatUseEscape = AutoConf.socatUseEscape
lxcDevicesDefault :: String
lxcDevicesDefault =
"c 1:3 rw"
++ ",c 1:5 rw"
++ ",c 1:7 rw"
++ ",c 1:8 rw"
++ ",c 1:9 rw"
++ ",c 1:10 rw"
++ ",c 5:0 rw"
++ ",c 5:1 rw"
++ ",c 5:2 rw"
++ ",c 136:* rw"
lxcDropCapabilitiesDefault :: String
lxcDropCapabilitiesDefault =
"mac_override"
++ ",sys_boot"
++ ",sys_module"
++ ",sys_time"
++ ",sys_admin"
lxcStateRunning :: String
lxcStateRunning = "RUNNING"
consMessage :: String
consMessage = "msg"
consSpice :: String
consSpice = "spice"
consSsh :: String
consSsh = "ssh"
consVnc :: String
consVnc = "vnc"
consAll :: FrozenSet String
consAll = ConstantUtils.mkSet [consMessage, consSpice, consSsh, consVnc]
rsaKeyBits :: Int
rsaKeyBits = 2048
opensslCiphers :: String
opensslCiphers = "HIGH:-DES:-3DES:-EXPORT:-DH"
x509CertCn :: String
x509CertCn = "ganeti.example.com"
x509CertDefaultValidity :: Int
x509CertDefaultValidity = 365 * 5
x509CertSignatureHeader :: String
x509CertSignatureHeader = "X-Ganeti-Signature"
x509CertSignDigest :: String
x509CertSignDigest = "SHA1"
iemExport :: String
iemExport = "export"
iemImport :: String
iemImport = "import"
iecGzip :: String
iecGzip = "gzip"
iecGzipFast :: String
iecGzipFast = "gzip-fast"
iecGzipSlow :: String
iecGzipSlow = "gzip-slow"
iecLzop :: String
iecLzop = "lzop"
iecNone :: String
iecNone = "none"
iecAll :: [String]
iecAll = [iecGzip, iecGzipFast, iecGzipSlow, iecLzop, iecNone]
iecDefaultTools :: [String]
iecDefaultTools = [iecGzip, iecGzipFast, iecGzipSlow]
iecCompressionUtilities :: Map String String
iecCompressionUtilities =
Map.fromList
[ (iecGzipFast, iecGzip)
, (iecGzipSlow, iecGzip)
]
ieCustomSize :: String
ieCustomSize = "fd"
ieioFile :: String
ieioFile = "file"
ieioRawDisk :: String
ieioRawDisk = "raw"
ieioScript :: String
ieioScript = "script"
valueDefault :: String
valueDefault = "default"
valueAuto :: String
valueAuto = "auto"
valueGenerate :: String
valueGenerate = "generate"
valueNone :: String
valueNone = "none"
valueTrue :: String
valueTrue = "true"
valueFalse :: String
valueFalse = "false"
hooksNameCfgupdate :: String
hooksNameCfgupdate = "config-update"
hooksNameWatcher :: String
hooksNameWatcher = "watcher"
hooksPath :: String
hooksPath = "/sbin:/bin:/usr/sbin:/usr/bin"
hooksPhasePost :: String
hooksPhasePost = "post"
hooksPhasePre :: String
hooksPhasePre = "pre"
hooksVersion :: Int
hooksVersion = 2
htypeCluster :: String
htypeCluster = "CLUSTER"
htypeGroup :: String
htypeGroup = "GROUP"
htypeInstance :: String
htypeInstance = "INSTANCE"
htypeNetwork :: String
htypeNetwork = "NETWORK"
htypeNode :: String
htypeNode = "NODE"
hkrSkip :: Int
hkrSkip = 0
hkrFail :: Int
hkrFail = 1
hkrSuccess :: Int
hkrSuccess = 2
stBlock :: String
stBlock = Types.storageTypeToRaw StorageBlock
stDiskless :: String
stDiskless = Types.storageTypeToRaw StorageDiskless
stExt :: String
stExt = Types.storageTypeToRaw StorageExt
stFile :: String
stFile = Types.storageTypeToRaw StorageFile
stSharedFile :: String
stSharedFile = Types.storageTypeToRaw StorageSharedFile
stGluster :: String
stGluster = Types.storageTypeToRaw StorageGluster
stLvmPv :: String
stLvmPv = Types.storageTypeToRaw StorageLvmPv
stLvmVg :: String
stLvmVg = Types.storageTypeToRaw StorageLvmVg
stRados :: String
stRados = Types.storageTypeToRaw StorageRados
storageTypes :: FrozenSet String
storageTypes = ConstantUtils.mkSet $ map Types.storageTypeToRaw [minBound..]
stsReport :: FrozenSet String
stsReport = ConstantUtils.mkSet [stFile, stLvmPv, stLvmVg]
stsReportNodeStorage :: FrozenSet String
stsReportNodeStorage = ConstantUtils.union stsReport $
ConstantUtils.mkSet [ stSharedFile
, stGluster
]
sfNode :: String
sfNode = "node"
sfType :: String
sfType = "type"
sfAllocatable :: String
sfAllocatable = Types.storageFieldToRaw SFAllocatable
sfFree :: String
sfFree = Types.storageFieldToRaw SFFree
sfName :: String
sfName = Types.storageFieldToRaw SFName
sfSize :: String
sfSize = Types.storageFieldToRaw SFSize
sfUsed :: String
sfUsed = Types.storageFieldToRaw SFUsed
validStorageFields :: FrozenSet String
validStorageFields =
ConstantUtils.mkSet $ map Types.storageFieldToRaw [minBound..] ++
[sfNode, sfType]
modifiableStorageFields :: Map String (FrozenSet String)
modifiableStorageFields =
Map.fromList [(Types.storageTypeToRaw StorageLvmPv,
ConstantUtils.mkSet [sfAllocatable])]
soFixConsistency :: String
soFixConsistency = "fix-consistency"
validStorageOperations :: Map String (FrozenSet String)
validStorageOperations =
Map.fromList [(Types.storageTypeToRaw StorageLvmVg,
ConstantUtils.mkSet [soFixConsistency])]
vfDev :: String
vfDev = "dev"
vfInstance :: String
vfInstance = "instance"
vfName :: String
vfName = "name"
vfNode :: String
vfNode = "node"
vfPhys :: String
vfPhys = "phys"
vfSize :: String
vfSize = "size"
vfVg :: String
vfVg = "vg"
ldsFaulty :: Int
ldsFaulty = Types.localDiskStatusToRaw DiskStatusFaulty
ldsOkay :: Int
ldsOkay = Types.localDiskStatusToRaw DiskStatusOk
ldsUnknown :: Int
ldsUnknown = Types.localDiskStatusToRaw DiskStatusUnknown
ldsSync :: Int
ldsSync = Types.localDiskStatusToRaw DiskStatusSync
ldsNames :: Map Int String
ldsNames =
Map.fromList [ (Types.localDiskStatusToRaw ds,
localDiskStatusName ds) | ds <- [minBound..] ]
dtDiskless :: String
dtDiskless = Types.diskTemplateToRaw DTDiskless
dtFile :: String
dtFile = Types.diskTemplateToRaw DTFile
dtSharedFile :: String
dtSharedFile = Types.diskTemplateToRaw DTSharedFile
dtPlain :: String
dtPlain = Types.diskTemplateToRaw DTPlain
dtBlock :: String
dtBlock = Types.diskTemplateToRaw DTBlock
dtDrbd8 :: String
dtDrbd8 = Types.diskTemplateToRaw DTDrbd8
dtRbd :: String
dtRbd = Types.diskTemplateToRaw DTRbd
dtExt :: String
dtExt = Types.diskTemplateToRaw DTExt
dtGluster :: String
dtGluster = Types.diskTemplateToRaw DTGluster
dtMixed :: String
dtMixed = "mixed"
diskTemplatePreference :: [String]
diskTemplatePreference =
map Types.diskTemplateToRaw
[DTBlock, DTDiskless, DTDrbd8, DTExt, DTFile,
DTPlain, DTRbd, DTSharedFile, DTGluster]
diskTemplates :: FrozenSet String
diskTemplates = ConstantUtils.mkSet $ map Types.diskTemplateToRaw [minBound..]
defaultEnabledDiskTemplates :: [String]
defaultEnabledDiskTemplates = map Types.diskTemplateToRaw [DTDrbd8, DTPlain]
mapDiskTemplateStorageType :: Map String String
mapDiskTemplateStorageType =
Map.fromList $
map ( Types.diskTemplateToRaw
&&& Types.storageTypeToRaw . diskTemplateToStorageType)
[minBound..maxBound]
dtsIntMirror :: FrozenSet String
dtsIntMirror = ConstantUtils.mkSet [dtDrbd8]
dtsExtMirror :: FrozenSet String
dtsExtMirror =
ConstantUtils.mkSet $
map Types.diskTemplateToRaw
[DTDiskless, DTBlock, DTExt, DTSharedFile, DTRbd, DTGluster]
dtsNotLvm :: FrozenSet String
dtsNotLvm =
ConstantUtils.mkSet $
map Types.diskTemplateToRaw
[DTSharedFile, DTDiskless, DTBlock, DTExt, DTFile, DTRbd, DTGluster]
dtsGrowable :: FrozenSet String
dtsGrowable =
ConstantUtils.mkSet $
map Types.diskTemplateToRaw
[DTSharedFile, DTDrbd8, DTPlain, DTExt, DTFile, DTRbd, DTGluster]
dtsMayAdopt :: FrozenSet String
dtsMayAdopt =
ConstantUtils.mkSet $ map Types.diskTemplateToRaw [DTBlock, DTPlain]
dtsMustAdopt :: FrozenSet String
dtsMustAdopt = ConstantUtils.mkSet [Types.diskTemplateToRaw DTBlock]
dtsMirrored :: FrozenSet String
dtsMirrored = dtsIntMirror `ConstantUtils.union` dtsExtMirror
dtsFilebased :: FrozenSet String
dtsFilebased =
ConstantUtils.mkSet $ map Types.diskTemplateToRaw
[DTSharedFile, DTFile, DTGluster]
dtsInstanceDependentPath :: FrozenSet String
dtsInstanceDependentPath =
ConstantUtils.mkSet $ map Types.diskTemplateToRaw
[DTSharedFile, DTFile]
dtsCopyable :: FrozenSet String
dtsCopyable =
ConstantUtils.mkSet $ map Types.diskTemplateToRaw [DTPlain, DTFile]
dtsSnapshotCapable :: FrozenSet String
dtsSnapshotCapable =
ConstantUtils.mkSet $ map Types.diskTemplateToRaw [DTPlain, DTDrbd8, DTExt]
dtsExclStorage :: FrozenSet String
dtsExclStorage = ConstantUtils.mkSet $ map Types.diskTemplateToRaw [DTPlain]
dtsNoFreeSpaceCheck :: FrozenSet String
dtsNoFreeSpaceCheck =
ConstantUtils.mkSet $
map Types.diskTemplateToRaw [DTExt, DTSharedFile, DTFile, DTRbd, DTGluster]
dtsBlock :: FrozenSet String
dtsBlock =
ConstantUtils.mkSet $
map Types.diskTemplateToRaw [DTPlain, DTDrbd8, DTBlock, DTRbd, DTExt]
dtsLvm :: FrozenSet String
dtsLvm = diskTemplates `ConstantUtils.difference` dtsNotLvm
dtsHaveAccess :: FrozenSet String
dtsHaveAccess = ConstantUtils.mkSet $
map Types.diskTemplateToRaw [DTRbd, DTGluster, DTExt]
dtsNotConvertibleFrom :: FrozenSet String
dtsNotConvertibleFrom =
ConstantUtils.mkSet $
map Types.diskTemplateToRaw [DTDiskless]
dtsNotConvertibleTo :: FrozenSet String
dtsNotConvertibleTo =
ConstantUtils.mkSet $
map Types.diskTemplateToRaw [DTDiskless, DTBlock]
drbdHmacAlg :: String
drbdHmacAlg = "md5"
drbdDefaultNetProtocol :: String
drbdDefaultNetProtocol = "C"
drbdMigrationNetProtocol :: String
drbdMigrationNetProtocol = "C"
drbdStatusFile :: String
drbdStatusFile = "/proc/drbd"
drbdSecretLength :: Int
drbdSecretLength = 20
drbdMetaSize :: Int
drbdMetaSize = 128
drbdBDiskBarriers :: String
drbdBDiskBarriers = "b"
drbdBDiskDrain :: String
drbdBDiskDrain = "d"
drbdBDiskFlush :: String
drbdBDiskFlush = "f"
drbdBNone :: String
drbdBNone = "n"
drbdValidBarrierOpt :: FrozenSet (FrozenSet String)
drbdValidBarrierOpt =
ConstantUtils.mkSet
[ ConstantUtils.mkSet [drbdBNone]
, ConstantUtils.mkSet [drbdBDiskBarriers]
, ConstantUtils.mkSet [drbdBDiskDrain]
, ConstantUtils.mkSet [drbdBDiskFlush]
, ConstantUtils.mkSet [drbdBDiskDrain, drbdBDiskFlush]
, ConstantUtils.mkSet [drbdBDiskBarriers, drbdBDiskDrain]
, ConstantUtils.mkSet [drbdBDiskBarriers, drbdBDiskFlush]
, ConstantUtils.mkSet [drbdBDiskBarriers, drbdBDiskFlush, drbdBDiskDrain]
]
rbdCmd :: String
rbdCmd = "rbd"
fdBlktap :: String
fdBlktap = Types.fileDriverToRaw FileBlktap
fdBlktap2 :: String
fdBlktap2 = Types.fileDriverToRaw FileBlktap2
fdLoop :: String
fdLoop = Types.fileDriverToRaw FileLoop
fdDefault :: String
fdDefault = fdLoop
fileDriver :: FrozenSet String
fileDriver =
ConstantUtils.mkSet $
map Types.fileDriverToRaw [minBound..]
dtsDrbd :: FrozenSet String
dtsDrbd = ConstantUtils.mkSet [Types.diskTemplateToRaw DTDrbd8]
diskRdonly :: String
diskRdonly = Types.diskModeToRaw DiskRdOnly
diskRdwr :: String
diskRdwr = Types.diskModeToRaw DiskRdWr
diskAccessSet :: FrozenSet String
diskAccessSet = ConstantUtils.mkSet $ map Types.diskModeToRaw [minBound..]
replaceDiskAuto :: String
replaceDiskAuto = Types.replaceDisksModeToRaw ReplaceAuto
replaceDiskChg :: String
replaceDiskChg = Types.replaceDisksModeToRaw ReplaceNewSecondary
replaceDiskPri :: String
replaceDiskPri = Types.replaceDisksModeToRaw ReplaceOnPrimary
replaceDiskSec :: String
replaceDiskSec = Types.replaceDisksModeToRaw ReplaceOnSecondary
replaceModes :: FrozenSet String
replaceModes =
ConstantUtils.mkSet $ map Types.replaceDisksModeToRaw [minBound..]
exportModeLocal :: String
exportModeLocal = Types.exportModeToRaw ExportModeLocal
exportModeRemote :: String
exportModeRemote = Types.exportModeToRaw ExportModeRemote
exportModes :: FrozenSet String
exportModes = ConstantUtils.mkSet $ map Types.exportModeToRaw [minBound..]
instanceCreate :: String
instanceCreate = Types.instCreateModeToRaw InstCreate
instanceImport :: String
instanceImport = Types.instCreateModeToRaw InstImport
instanceRemoteImport :: String
instanceRemoteImport = Types.instCreateModeToRaw InstRemoteImport
instanceCreateModes :: FrozenSet String
instanceCreateModes =
ConstantUtils.mkSet $ map Types.instCreateModeToRaw [minBound..]
rieHandshake :: String
rieHandshake = "Hi, I'm Ganeti"
rieVersion :: Int
rieVersion = 0
rieCertValidity :: Int
rieCertValidity = 24 * 60 * 60
rieConnectAttemptTimeout :: Int
rieConnectAttemptTimeout = 20
rieConnectRetries :: Int
rieConnectRetries = 10
rieConnectTimeout :: Int
rieConnectTimeout = 180
childLingerTimeout :: Double
childLingerTimeout = 5.0
inisectBep :: String
inisectBep = "backend"
inisectExp :: String
inisectExp = "export"
inisectHyp :: String
inisectHyp = "hypervisor"
inisectIns :: String
inisectIns = "instance"
inisectOsp :: String
inisectOsp = "os"
inisectOspPrivate :: String
inisectOspPrivate = "os_private"
ddmAdd :: String
ddmAdd = Types.ddmFullToRaw DdmFullAdd
ddmAttach :: String
ddmAttach = Types.ddmFullToRaw DdmFullAttach
ddmModify :: String
ddmModify = Types.ddmFullToRaw DdmFullModify
ddmRemove :: String
ddmRemove = Types.ddmFullToRaw DdmFullRemove
ddmDetach :: String
ddmDetach = Types.ddmFullToRaw DdmFullDetach
ddmsValues :: FrozenSet String
ddmsValues = ConstantUtils.mkSet [ddmAdd, ddmAttach, ddmRemove, ddmDetach]
ddmsValuesWithModify :: FrozenSet String
ddmsValuesWithModify = ConstantUtils.mkSet $ map Types.ddmFullToRaw [minBound..]
exitSuccess :: Int
exitSuccess = 0
exitFailure :: Int
exitFailure = ConstantUtils.exitFailure
exitNotcluster :: Int
exitNotcluster = 5
exitNotmaster :: Int
exitNotmaster = 11
exitNodesetupError :: Int
exitNodesetupError = 12
exitConfirmation :: Int
exitConfirmation = 13
exitUnknownField :: Int
exitUnknownField = 14
tagCluster :: String
tagCluster = Types.tagKindToRaw TagKindCluster
tagInstance :: String
tagInstance = Types.tagKindToRaw TagKindInstance
tagNetwork :: String
tagNetwork = Types.tagKindToRaw TagKindNetwork
tagNode :: String
tagNode = Types.tagKindToRaw TagKindNode
tagNodegroup :: String
tagNodegroup = Types.tagKindToRaw TagKindGroup
validTagTypes :: FrozenSet String
validTagTypes = ConstantUtils.mkSet $ map Types.tagKindToRaw [minBound..]
maxTagLen :: Int
maxTagLen = 128
maxTagsPerObj :: Int
maxTagsPerObj = 4096
defaultBridge :: String
defaultBridge = AutoConf.defaultBridge
defaultOvs :: String
defaultOvs = "switch1"
classicDrbdSyncSpeed :: Int
classicDrbdSyncSpeed = 60 * 1024
ip4AddressAny :: String
ip4AddressAny = "0.0.0.0"
ip4AddressLocalhost :: String
ip4AddressLocalhost = "127.0.0.1"
ip6AddressAny :: String
ip6AddressAny = "::"
ip6AddressLocalhost :: String
ip6AddressLocalhost = "::1"
ip4Version :: Int
ip4Version = 4
ip6Version :: Int
ip6Version = 6
validIpVersions :: FrozenSet Int
validIpVersions = ConstantUtils.mkSet [ip4Version, ip6Version]
tcpPingTimeout :: Int
tcpPingTimeout = 10
defaultVg :: String
defaultVg = AutoConf.defaultVg
defaultDrbdHelper :: String
defaultDrbdHelper = "/bin/true"
minVgSize :: Int
minVgSize = 20480
defaultMacPrefix :: String
defaultMacPrefix = "aa:00:00"
defaultShutdownTimeout :: Int
defaultShutdownTimeout = 120
nodeMaxClockSkew :: Int
nodeMaxClockSkew = 150
diskTransferConnectTimeout :: Int
diskTransferConnectTimeout = 60
diskSeparator :: String
diskSeparator = AutoConf.diskSeparator
ipCommandPath :: String
ipCommandPath = AutoConf.ipPath
jobIdsKey :: String
jobIdsKey = "jobs"
runpartsErr :: Int
runpartsErr = 2
runpartsRun :: Int
runpartsRun = 1
runpartsSkip :: Int
runpartsSkip = 0
runpartsStatus :: [Int]
runpartsStatus = [runpartsErr, runpartsRun, runpartsSkip]
rpcEncodingNone :: Int
rpcEncodingNone = 0
rpcEncodingZlibBase64 :: Int
rpcEncodingZlibBase64 = 1
rpcTmoUrgent :: Int
rpcTmoUrgent = Types.rpcTimeoutToRaw Urgent
rpcTmoFast :: Int
rpcTmoFast = Types.rpcTimeoutToRaw Fast
rpcTmoNormal :: Int
rpcTmoNormal = Types.rpcTimeoutToRaw Normal
rpcTmoSlow :: Int
rpcTmoSlow = Types.rpcTimeoutToRaw Slow
rpcTmo_4hrs :: Int
rpcTmo_4hrs = Types.rpcTimeoutToRaw FourHours
rpcTmo_1day :: Int
rpcTmo_1day = Types.rpcTimeoutToRaw OneDay
rpcConnectTimeout :: Int
rpcConnectTimeout = 5
osScriptCreate :: String
osScriptCreate = "create"
osScriptCreateUntrusted :: String
osScriptCreateUntrusted = "create_untrusted"
osScriptExport :: String
osScriptExport = "export"
osScriptImport :: String
osScriptImport = "import"
osScriptRename :: String
osScriptRename = "rename"
osScriptVerify :: String
osScriptVerify = "verify"
osScripts :: [String]
osScripts = [osScriptCreate, osScriptCreateUntrusted, osScriptExport,
osScriptImport, osScriptRename, osScriptVerify]
osApiFile :: String
osApiFile = "ganeti_api_version"
osVariantsFile :: String
osVariantsFile = "variants.list"
osParametersFile :: String
osParametersFile = "parameters.list"
osValidateParameters :: String
osValidateParameters = "parameters"
osValidateCalls :: FrozenSet String
osValidateCalls = ConstantUtils.mkSet [osValidateParameters]
esActionAttach :: String
esActionAttach = "attach"
esActionCreate :: String
esActionCreate = "create"
esActionDetach :: String
esActionDetach = "detach"
esActionGrow :: String
esActionGrow = "grow"
esActionRemove :: String
esActionRemove = "remove"
esActionSetinfo :: String
esActionSetinfo = "setinfo"
esActionVerify :: String
esActionVerify = "verify"
esActionSnapshot :: String
esActionSnapshot = "snapshot"
esActionOpen :: String
esActionOpen = "open"
esActionClose :: String
esActionClose = "close"
esScriptCreate :: String
esScriptCreate = esActionCreate
esScriptRemove :: String
esScriptRemove = esActionRemove
esScriptGrow :: String
esScriptGrow = esActionGrow
esScriptAttach :: String
esScriptAttach = esActionAttach
esScriptDetach :: String
esScriptDetach = esActionDetach
esScriptSetinfo :: String
esScriptSetinfo = esActionSetinfo
esScriptVerify :: String
esScriptVerify = esActionVerify
esScriptSnapshot :: String
esScriptSnapshot = esActionSnapshot
esScriptOpen :: String
esScriptOpen = esActionOpen
esScriptClose :: String
esScriptClose = esActionClose
esScripts :: FrozenSet String
esScripts =
ConstantUtils.mkSet [esScriptAttach,
esScriptCreate,
esScriptDetach,
esScriptGrow,
esScriptRemove,
esScriptSetinfo,
esScriptVerify,
esScriptSnapshot,
esScriptOpen,
esScriptClose]
esParametersFile :: String
esParametersFile = "parameters.list"
instanceRebootSoft :: String
instanceRebootSoft = Types.rebootTypeToRaw RebootSoft
instanceRebootHard :: String
instanceRebootHard = Types.rebootTypeToRaw RebootHard
instanceRebootFull :: String
instanceRebootFull = Types.rebootTypeToRaw RebootFull
rebootTypes :: FrozenSet String
rebootTypes = ConstantUtils.mkSet $ map Types.rebootTypeToRaw [minBound..]
instanceRebootAllowed :: String
instanceRebootAllowed = "reboot"
instanceRebootExit :: String
instanceRebootExit = "exit"
rebootBehaviors :: [String]
rebootBehaviors = [instanceRebootAllowed, instanceRebootExit]
vtypeBool :: VType
vtypeBool = VTypeBool
vtypeInt :: VType
vtypeInt = VTypeInt
vtypeFloat :: VType
vtypeFloat = VTypeFloat
vtypeMaybeString :: VType
vtypeMaybeString = VTypeMaybeString
vtypeSize :: VType
vtypeSize = VTypeSize
vtypeString :: VType
vtypeString = VTypeString
enforceableTypes :: FrozenSet VType
enforceableTypes = ConstantUtils.mkSet [minBound..]
ifaceNoIpVersionSpecified :: Int
ifaceNoIpVersionSpecified = 0
validSerialSpeeds :: [Int]
validSerialSpeeds =
[75,
110,
300,
600,
1200,
1800,
2400,
4800,
9600,
14400,
19200,
28800,
38400,
57600,
115200,
230400,
345600,
460800]
hvAcpi :: String
hvAcpi = "acpi"
hvBlockdevPrefix :: String
hvBlockdevPrefix = "blockdev_prefix"
hvBootloaderArgs :: String
hvBootloaderArgs = "bootloader_args"
hvBootloaderPath :: String
hvBootloaderPath = "bootloader_path"
hvBootOrder :: String
hvBootOrder = "boot_order"
hvCdromImagePath :: String
hvCdromImagePath = "cdrom_image_path"
hvCpuCap :: String
hvCpuCap = "cpu_cap"
hvCpuCores :: String
hvCpuCores = "cpu_cores"
hvCpuMask :: String
hvCpuMask = "cpu_mask"
hvCpuSockets :: String
hvCpuSockets = "cpu_sockets"
hvCpuThreads :: String
hvCpuThreads = "cpu_threads"
hvCpuType :: String
hvCpuType = "cpu_type"
hvCpuWeight :: String
hvCpuWeight = "cpu_weight"
hvDeviceModel :: String
hvDeviceModel = "device_model"
hvDiskCache :: String
hvDiskCache = "disk_cache"
hvDiskType :: String
hvDiskType = "disk_type"
hvInitrdPath :: String
hvInitrdPath = "initrd_path"
hvInitScript :: String
hvInitScript = "init_script"
hvKernelArgs :: String
hvKernelArgs = "kernel_args"
hvKernelPath :: String
hvKernelPath = "kernel_path"
hvKeymap :: String
hvKeymap = "keymap"
hvKvmCdrom2ImagePath :: String
hvKvmCdrom2ImagePath = "cdrom2_image_path"
hvKvmCdromDiskType :: String
hvKvmCdromDiskType = "cdrom_disk_type"
hvKvmExtra :: String
hvKvmExtra = "kvm_extra"
hvKvmFlag :: String
hvKvmFlag = "kvm_flag"
hvKvmFloppyImagePath :: String
hvKvmFloppyImagePath = "floppy_image_path"
hvKvmMachineVersion :: String
hvKvmMachineVersion = "machine_version"
hvKvmMigrationCaps :: String
hvKvmMigrationCaps = "migration_caps"
hvKvmPath :: String
hvKvmPath = "kvm_path"
hvKvmDiskAio :: String
hvKvmDiskAio = "disk_aio"
hvKvmScsiControllerType :: String
hvKvmScsiControllerType = "scsi_controller_type"
hvKvmPciReservations :: String
hvKvmPciReservations = "kvm_pci_reservations"
hvKvmSpiceAudioCompr :: String
hvKvmSpiceAudioCompr = "spice_playback_compression"
hvKvmSpiceBind :: String
hvKvmSpiceBind = "spice_bind"
hvKvmSpiceIpVersion :: String
hvKvmSpiceIpVersion = "spice_ip_version"
hvKvmSpiceJpegImgCompr :: String
hvKvmSpiceJpegImgCompr = "spice_jpeg_wan_compression"
hvKvmSpiceLosslessImgCompr :: String
hvKvmSpiceLosslessImgCompr = "spice_image_compression"
hvKvmSpicePasswordFile :: String
hvKvmSpicePasswordFile = "spice_password_file"
hvKvmSpiceStreamingVideoDetection :: String
hvKvmSpiceStreamingVideoDetection = "spice_streaming_video"
hvKvmSpiceTlsCiphers :: String
hvKvmSpiceTlsCiphers = "spice_tls_ciphers"
hvKvmSpiceUseTls :: String
hvKvmSpiceUseTls = "spice_use_tls"
hvKvmSpiceUseVdagent :: String
hvKvmSpiceUseVdagent = "spice_use_vdagent"
hvKvmSpiceZlibGlzImgCompr :: String
hvKvmSpiceZlibGlzImgCompr = "spice_zlib_glz_wan_compression"
hvKvmUseChroot :: String
hvKvmUseChroot = "use_chroot"
hvKvmUserShutdown :: String
hvKvmUserShutdown = "user_shutdown"
hvLxcStartupTimeout :: String
hvLxcStartupTimeout = "startup_timeout"
hvLxcExtraCgroups :: String
hvLxcExtraCgroups = "extra_cgroups"
hvLxcDevices :: String
hvLxcDevices = "devices"
hvLxcDropCapabilities :: String
hvLxcDropCapabilities = "drop_capabilities"
hvLxcExtraConfig :: String
hvLxcExtraConfig = "extra_config"
hvLxcNumTtys :: String
hvLxcNumTtys = "num_ttys"
hvMemPath :: String
hvMemPath = "mem_path"
hvMigrationBandwidth :: String
hvMigrationBandwidth = "migration_bandwidth"
hvMigrationDowntime :: String
hvMigrationDowntime = "migration_downtime"
hvMigrationMode :: String
hvMigrationMode = "migration_mode"
hvMigrationPort :: String
hvMigrationPort = "migration_port"
hvNicType :: String
hvNicType = "nic_type"
hvPae :: String
hvPae = "pae"
hvPassthrough :: String
hvPassthrough = "pci_pass"
hvRebootBehavior :: String
hvRebootBehavior = "reboot_behavior"
hvRootPath :: String
hvRootPath = "root_path"
hvSecurityDomain :: String
hvSecurityDomain = "security_domain"
hvSecurityModel :: String
hvSecurityModel = "security_model"
hvSerialConsole :: String
hvSerialConsole = "serial_console"
hvSerialSpeed :: String
hvSerialSpeed = "serial_speed"
hvSoundhw :: String
hvSoundhw = "soundhw"
hvUsbDevices :: String
hvUsbDevices = "usb_devices"
hvUsbMouse :: String
hvUsbMouse = "usb_mouse"
hvUseBootloader :: String
hvUseBootloader = "use_bootloader"
hvUseLocaltime :: String
hvUseLocaltime = "use_localtime"
hvVga :: String
hvVga = "vga"
hvVhostNet :: String
hvVhostNet = "vhost_net"
hvVirtioNetQueues :: String
hvVirtioNetQueues = "virtio_net_queues"
hvVifScript :: String
hvVifScript = "vif_script"
hvVifType :: String
hvVifType = "vif_type"
hvViridian :: String
hvViridian = "viridian"
hvVncBindAddress :: String
hvVncBindAddress = "vnc_bind_address"
hvVncPasswordFile :: String
hvVncPasswordFile = "vnc_password_file"
hvVncTls :: String
hvVncTls = "vnc_tls"
hvVncX509 :: String
hvVncX509 = "vnc_x509_path"
hvVncX509Verify :: String
hvVncX509Verify = "vnc_x509_verify"
hvVnetHdr :: String
hvVnetHdr = "vnet_hdr"
hvXenCmd :: String
hvXenCmd = "xen_cmd"
hvXenCpuid :: String
hvXenCpuid = "cpuid"
hvsParameterTitles :: Map String String
hvsParameterTitles =
Map.fromList
[(hvAcpi, "ACPI"),
(hvBootOrder, "Boot_order"),
(hvCdromImagePath, "CDROM_image_path"),
(hvCpuType, "cpu_type"),
(hvDiskType, "Disk_type"),
(hvInitrdPath, "Initrd_path"),
(hvKernelPath, "Kernel_path"),
(hvNicType, "NIC_type"),
(hvPae, "PAE"),
(hvPassthrough, "pci_pass"),
(hvVncBindAddress, "VNC_bind_address")]
hvsParameters :: FrozenSet String
hvsParameters = ConstantUtils.mkSet $ Map.keys hvsParameterTypes
hvsParameterTypes :: Map String VType
hvsParameterTypes = Map.fromList
[ (hvAcpi, VTypeBool)
, (hvBlockdevPrefix, VTypeString)
, (hvBootloaderArgs, VTypeString)
, (hvBootloaderPath, VTypeString)
, (hvBootOrder, VTypeString)
, (hvCdromImagePath, VTypeString)
, (hvCpuCap, VTypeInt)
, (hvCpuCores, VTypeInt)
, (hvCpuMask, VTypeString)
, (hvCpuSockets, VTypeInt)
, (hvCpuThreads, VTypeInt)
, (hvCpuType, VTypeString)
, (hvCpuWeight, VTypeInt)
, (hvDeviceModel, VTypeString)
, (hvDiskCache, VTypeString)
, (hvDiskType, VTypeString)
, (hvInitrdPath, VTypeString)
, (hvInitScript, VTypeString)
, (hvKernelArgs, VTypeString)
, (hvKernelPath, VTypeString)
, (hvKeymap, VTypeString)
, (hvKvmCdrom2ImagePath, VTypeString)
, (hvKvmCdromDiskType, VTypeString)
, (hvKvmExtra, VTypeString)
, (hvKvmFlag, VTypeString)
, (hvKvmFloppyImagePath, VTypeString)
, (hvKvmMachineVersion, VTypeString)
, (hvKvmMigrationCaps, VTypeString)
, (hvKvmPath, VTypeString)
, (hvKvmDiskAio, VTypeString)
, (hvKvmScsiControllerType, VTypeString)
, (hvKvmPciReservations, VTypeInt)
, (hvKvmSpiceAudioCompr, VTypeBool)
, (hvKvmSpiceBind, VTypeString)
, (hvKvmSpiceIpVersion, VTypeInt)
, (hvKvmSpiceJpegImgCompr, VTypeString)
, (hvKvmSpiceLosslessImgCompr, VTypeString)
, (hvKvmSpicePasswordFile, VTypeString)
, (hvKvmSpiceStreamingVideoDetection, VTypeString)
, (hvKvmSpiceTlsCiphers, VTypeString)
, (hvKvmSpiceUseTls, VTypeBool)
, (hvKvmSpiceUseVdagent, VTypeBool)
, (hvKvmSpiceZlibGlzImgCompr, VTypeString)
, (hvKvmUseChroot, VTypeBool)
, (hvKvmUserShutdown, VTypeBool)
, (hvLxcDevices, VTypeString)
, (hvLxcDropCapabilities, VTypeString)
, (hvLxcExtraCgroups, VTypeString)
, (hvLxcExtraConfig, VTypeString)
, (hvLxcNumTtys, VTypeInt)
, (hvLxcStartupTimeout, VTypeInt)
, (hvMemPath, VTypeString)
, (hvMigrationBandwidth, VTypeInt)
, (hvMigrationDowntime, VTypeInt)
, (hvMigrationMode, VTypeString)
, (hvMigrationPort, VTypeInt)
, (hvNicType, VTypeString)
, (hvPae, VTypeBool)
, (hvPassthrough, VTypeString)
, (hvRebootBehavior, VTypeString)
, (hvRootPath, VTypeMaybeString)
, (hvSecurityDomain, VTypeString)
, (hvSecurityModel, VTypeString)
, (hvSerialConsole, VTypeBool)
, (hvSerialSpeed, VTypeInt)
, (hvSoundhw, VTypeString)
, (hvUsbDevices, VTypeString)
, (hvUsbMouse, VTypeString)
, (hvUseBootloader, VTypeBool)
, (hvUseLocaltime, VTypeBool)
, (hvVga, VTypeString)
, (hvVhostNet, VTypeBool)
, (hvVirtioNetQueues, VTypeInt)
, (hvVifScript, VTypeString)
, (hvVifType, VTypeString)
, (hvViridian, VTypeBool)
, (hvVncBindAddress, VTypeString)
, (hvVncPasswordFile, VTypeString)
, (hvVncTls, VTypeBool)
, (hvVncX509, VTypeString)
, (hvVncX509Verify, VTypeBool)
, (hvVnetHdr, VTypeBool)
, (hvXenCmd, VTypeString)
, (hvXenCpuid, VTypeString)
]
hvMigrationActive :: String
hvMigrationActive = "active"
hvMigrationCancelled :: String
hvMigrationCancelled = "cancelled"
hvMigrationCompleted :: String
hvMigrationCompleted = "completed"
hvMigrationFailed :: String
hvMigrationFailed = "failed"
hvMigrationValidStatuses :: FrozenSet String
hvMigrationValidStatuses =
ConstantUtils.mkSet [hvMigrationActive,
hvMigrationCancelled,
hvMigrationCompleted,
hvMigrationFailed]
hvMigrationFailedStatuses :: FrozenSet String
hvMigrationFailedStatuses =
ConstantUtils.mkSet [hvMigrationFailed, hvMigrationCancelled]
hvKvmMigrationValidStatuses :: FrozenSet String
hvKvmMigrationValidStatuses = hvMigrationValidStatuses
hvNodeinfoKeyVersion :: String
hvNodeinfoKeyVersion = "hv_version"
hvstCpuNode :: String
hvstCpuNode = "cpu_node"
hvstCpuTotal :: String
hvstCpuTotal = "cpu_total"
hvstMemoryHv :: String
hvstMemoryHv = "mem_hv"
hvstMemoryNode :: String
hvstMemoryNode = "mem_node"
hvstMemoryTotal :: String
hvstMemoryTotal = "mem_total"
hvstsParameters :: FrozenSet String
hvstsParameters =
ConstantUtils.mkSet [hvstCpuNode,
hvstCpuTotal,
hvstMemoryHv,
hvstMemoryNode,
hvstMemoryTotal]
hvstDefaults :: Map String Int
hvstDefaults =
Map.fromList
[ (hvstCpuNode , ConstantUtils.hvstDefaultCpuNode )
, (hvstCpuTotal , ConstantUtils.hvstDefaultCpuTotal )
, (hvstMemoryHv , ConstantUtils.hvstDefaultMemoryHv )
, (hvstMemoryTotal, ConstantUtils.hvstDefaultMemoryTotal)
, (hvstMemoryNode , ConstantUtils.hvstDefaultMemoryNode )
]
hvstsParameterTypes :: Map String VType
hvstsParameterTypes =
Map.fromList [(hvstMemoryTotal, VTypeInt),
(hvstMemoryNode, VTypeInt),
(hvstMemoryHv, VTypeInt),
(hvstCpuTotal, VTypeInt),
(hvstCpuNode, VTypeInt)]
dsDiskOverhead :: String
dsDiskOverhead = "disk_overhead"
dsDiskReserved :: String
dsDiskReserved = "disk_reserved"
dsDiskTotal :: String
dsDiskTotal = "disk_total"
dsDefaults :: Map String Int
dsDefaults =
Map.fromList
[(dsDiskTotal, 0),
(dsDiskReserved, 0),
(dsDiskOverhead, 0)]
dssParameterTypes :: Map String VType
dssParameterTypes =
Map.fromList [(dsDiskTotal, VTypeInt),
(dsDiskReserved, VTypeInt),
(dsDiskOverhead, VTypeInt)]
dssParameters :: FrozenSet String
dssParameters =
ConstantUtils.mkSet [dsDiskTotal, dsDiskReserved, dsDiskOverhead]
dsValidTypes :: FrozenSet String
dsValidTypes = ConstantUtils.mkSet [Types.diskTemplateToRaw DTPlain]
beAlwaysFailover :: String
beAlwaysFailover = "always_failover"
beAutoBalance :: String
beAutoBalance = "auto_balance"
beMaxmem :: String
beMaxmem = "maxmem"
beMemory :: String
beMemory = "memory"
beMinmem :: String
beMinmem = "minmem"
beSpindleUse :: String
beSpindleUse = "spindle_use"
beVcpus :: String
beVcpus = "vcpus"
besParameterTypes :: Map String VType
besParameterTypes =
Map.fromList [(beAlwaysFailover, VTypeBool),
(beAutoBalance, VTypeBool),
(beMaxmem, VTypeSize),
(beMinmem, VTypeSize),
(beSpindleUse, VTypeInt),
(beVcpus, VTypeInt)]
besParameterTitles :: Map String String
besParameterTitles =
Map.fromList [(beAutoBalance, "Auto_balance"),
(beMinmem, "ConfigMinMem"),
(beVcpus, "ConfigVCPUs"),
(beMaxmem, "ConfigMaxMem")]
besParameterCompat :: Map String VType
besParameterCompat = Map.insert beMemory VTypeSize besParameterTypes
besParameters :: FrozenSet String
besParameters =
ConstantUtils.mkSet [beAlwaysFailover,
beAutoBalance,
beMaxmem,
beMinmem,
beSpindleUse,
beVcpus]
ispecMemSize :: String
ispecMemSize = ConstantUtils.ispecMemSize
ispecCpuCount :: String
ispecCpuCount = ConstantUtils.ispecCpuCount
ispecDiskCount :: String
ispecDiskCount = ConstantUtils.ispecDiskCount
ispecDiskSize :: String
ispecDiskSize = ConstantUtils.ispecDiskSize
ispecNicCount :: String
ispecNicCount = ConstantUtils.ispecNicCount
ispecSpindleUse :: String
ispecSpindleUse = ConstantUtils.ispecSpindleUse
ispecsParameterTypes :: Map String VType
ispecsParameterTypes =
Map.fromList
[(ConstantUtils.ispecDiskSize, VTypeInt),
(ConstantUtils.ispecCpuCount, VTypeInt),
(ConstantUtils.ispecSpindleUse, VTypeInt),
(ConstantUtils.ispecMemSize, VTypeInt),
(ConstantUtils.ispecNicCount, VTypeInt),
(ConstantUtils.ispecDiskCount, VTypeInt)]
ispecsParameters :: FrozenSet String
ispecsParameters =
ConstantUtils.mkSet [ConstantUtils.ispecCpuCount,
ConstantUtils.ispecDiskCount,
ConstantUtils.ispecDiskSize,
ConstantUtils.ispecMemSize,
ConstantUtils.ispecNicCount,
ConstantUtils.ispecSpindleUse]
ispecsMinmax :: String
ispecsMinmax = ConstantUtils.ispecsMinmax
ispecsMax :: String
ispecsMax = "max"
ispecsMin :: String
ispecsMin = "min"
ispecsStd :: String
ispecsStd = ConstantUtils.ispecsStd
ipolicyDts :: String
ipolicyDts = ConstantUtils.ipolicyDts
ipolicyVcpuRatio :: String
ipolicyVcpuRatio = ConstantUtils.ipolicyVcpuRatio
ipolicySpindleRatio :: String
ipolicySpindleRatio = ConstantUtils.ipolicySpindleRatio
ipolicyMemoryRatio :: String
ipolicyMemoryRatio = ConstantUtils.ipolicyMemoryRatio
ispecsMinmaxKeys :: FrozenSet String
ispecsMinmaxKeys = ConstantUtils.mkSet [ispecsMax, ispecsMin]
ipolicyParameters :: FrozenSet String
ipolicyParameters =
ConstantUtils.mkSet [ConstantUtils.ipolicyVcpuRatio,
ConstantUtils.ipolicySpindleRatio,
ConstantUtils.ipolicyMemoryRatio]
ipolicyAllKeys :: FrozenSet String
ipolicyAllKeys =
ConstantUtils.union ipolicyParameters $
ConstantUtils.mkSet [ConstantUtils.ipolicyDts,
ConstantUtils.ispecsMinmax,
ispecsStd]
ndExclusiveStorage :: String
ndExclusiveStorage = "exclusive_storage"
ndOobProgram :: String
ndOobProgram = "oob_program"
ndSpindleCount :: String
ndSpindleCount = "spindle_count"
ndOvs :: String
ndOvs = "ovs"
ndOvsLink :: String
ndOvsLink = "ovs_link"
ndOvsName :: String
ndOvsName = "ovs_name"
ndSshPort :: String
ndSshPort = "ssh_port"
ndCpuSpeed :: String
ndCpuSpeed = "cpu_speed"
ndsParameterTypes :: Map String VType
ndsParameterTypes =
Map.fromList
[(ndExclusiveStorage, VTypeBool),
(ndOobProgram, VTypeString),
(ndOvs, VTypeBool),
(ndOvsLink, VTypeMaybeString),
(ndOvsName, VTypeMaybeString),
(ndSpindleCount, VTypeInt),
(ndSshPort, VTypeInt),
(ndCpuSpeed, VTypeFloat)]
ndsParameters :: FrozenSet String
ndsParameters = ConstantUtils.mkSet (Map.keys ndsParameterTypes)
ndsParameterTitles :: Map String String
ndsParameterTitles =
Map.fromList
[(ndExclusiveStorage, "ExclusiveStorage"),
(ndOobProgram, "OutOfBandProgram"),
(ndOvs, "OpenvSwitch"),
(ndOvsLink, "OpenvSwitchLink"),
(ndOvsName, "OpenvSwitchName"),
(ndSpindleCount, "SpindleCount")]
ldpAccess :: String
ldpAccess = "access"
ldpBarriers :: String
ldpBarriers = "disabled-barriers"
ldpDefaultMetavg :: String
ldpDefaultMetavg = "default-metavg"
ldpDelayTarget :: String
ldpDelayTarget = "c-delay-target"
ldpDiskCustom :: String
ldpDiskCustom = "disk-custom"
ldpDynamicResync :: String
ldpDynamicResync = "dynamic-resync"
ldpFillTarget :: String
ldpFillTarget = "c-fill-target"
ldpMaxRate :: String
ldpMaxRate = "c-max-rate"
ldpMinRate :: String
ldpMinRate = "c-min-rate"
ldpNetCustom :: String
ldpNetCustom = "net-custom"
ldpNoMetaFlush :: String
ldpNoMetaFlush = "disable-meta-flush"
ldpPlanAhead :: String
ldpPlanAhead = "c-plan-ahead"
ldpPool :: String
ldpPool = "pool"
ldpProtocol :: String
ldpProtocol = "protocol"
ldpResyncRate :: String
ldpResyncRate = "resync-rate"
ldpStripes :: String
ldpStripes = "stripes"
diskLdTypes :: Map String VType
diskLdTypes =
Map.fromList
[(ldpAccess, VTypeString),
(ldpResyncRate, VTypeInt),
(ldpStripes, VTypeInt),
(ldpBarriers, VTypeString),
(ldpNoMetaFlush, VTypeBool),
(ldpDefaultMetavg, VTypeString),
(ldpDiskCustom, VTypeString),
(ldpNetCustom, VTypeString),
(ldpProtocol, VTypeString),
(ldpDynamicResync, VTypeBool),
(ldpPlanAhead, VTypeInt),
(ldpFillTarget, VTypeInt),
(ldpDelayTarget, VTypeInt),
(ldpMaxRate, VTypeInt),
(ldpMinRate, VTypeInt),
(ldpPool, VTypeString)]
diskLdParameters :: FrozenSet String
diskLdParameters = ConstantUtils.mkSet (Map.keys diskLdTypes)
drbdResyncRate :: String
drbdResyncRate = "resync-rate"
drbdDataStripes :: String
drbdDataStripes = "data-stripes"
drbdMetaStripes :: String
drbdMetaStripes = "meta-stripes"
drbdDiskBarriers :: String
drbdDiskBarriers = "disk-barriers"
drbdMetaBarriers :: String
drbdMetaBarriers = "meta-barriers"
drbdDefaultMetavg :: String
drbdDefaultMetavg = "metavg"
drbdDiskCustom :: String
drbdDiskCustom = "disk-custom"
drbdNetCustom :: String
drbdNetCustom = "net-custom"
drbdProtocol :: String
drbdProtocol = "protocol"
drbdDynamicResync :: String
drbdDynamicResync = "dynamic-resync"
drbdPlanAhead :: String
drbdPlanAhead = "c-plan-ahead"
drbdFillTarget :: String
drbdFillTarget = "c-fill-target"
drbdDelayTarget :: String
drbdDelayTarget = "c-delay-target"
drbdMaxRate :: String
drbdMaxRate = "c-max-rate"
drbdMinRate :: String
drbdMinRate = "c-min-rate"
lvStripes :: String
lvStripes = "stripes"
rbdAccess :: String
rbdAccess = "access"
rbdPool :: String
rbdPool = "pool"
diskDtTypes :: Map String VType
diskDtTypes =
Map.fromList [(drbdResyncRate, VTypeInt),
(drbdDataStripes, VTypeInt),
(drbdMetaStripes, VTypeInt),
(drbdDiskBarriers, VTypeString),
(drbdMetaBarriers, VTypeBool),
(drbdDefaultMetavg, VTypeString),
(drbdDiskCustom, VTypeString),
(drbdNetCustom, VTypeString),
(drbdProtocol, VTypeString),
(drbdDynamicResync, VTypeBool),
(drbdPlanAhead, VTypeInt),
(drbdFillTarget, VTypeInt),
(drbdDelayTarget, VTypeInt),
(drbdMaxRate, VTypeInt),
(drbdMinRate, VTypeInt),
(lvStripes, VTypeInt),
(rbdAccess, VTypeString),
(rbdPool, VTypeString),
(glusterHost, VTypeString),
(glusterVolume, VTypeString),
(glusterPort, VTypeInt)
]
diskDtParameters :: FrozenSet String
diskDtParameters = ConstantUtils.mkSet (Map.keys diskDtTypes)
ddpLocalIp :: String
ddpLocalIp = "local-ip"
ddpRemoteIp :: String
ddpRemoteIp = "remote-ip"
ddpPort :: String
ddpPort = "port"
ddpLocalMinor :: String
ddpLocalMinor = "local-minor"
ddpRemoteMinor :: String
ddpRemoteMinor = "remote-minor"
oobPowerOn :: String
oobPowerOn = Types.oobCommandToRaw OobPowerOn
oobPowerOff :: String
oobPowerOff = Types.oobCommandToRaw OobPowerOff
oobPowerCycle :: String
oobPowerCycle = Types.oobCommandToRaw OobPowerCycle
oobPowerStatus :: String
oobPowerStatus = Types.oobCommandToRaw OobPowerStatus
oobHealth :: String
oobHealth = Types.oobCommandToRaw OobHealth
oobCommands :: FrozenSet String
oobCommands = ConstantUtils.mkSet $ map Types.oobCommandToRaw [minBound..]
oobPowerStatusPowered :: String
oobPowerStatusPowered = "powered"
oobTimeout :: Int
oobTimeout = 60
oobPowerDelay :: Double
oobPowerDelay = 2.0
oobStatusCritical :: String
oobStatusCritical = Types.oobStatusToRaw OobStatusCritical
oobStatusOk :: String
oobStatusOk = Types.oobStatusToRaw OobStatusOk
oobStatusUnknown :: String
oobStatusUnknown = Types.oobStatusToRaw OobStatusUnknown
oobStatusWarning :: String
oobStatusWarning = Types.oobStatusToRaw OobStatusWarning
oobStatuses :: FrozenSet String
oobStatuses = ConstantUtils.mkSet $ map Types.oobStatusToRaw [minBound..]
ppDefault :: String
ppDefault = "default"
nicLink :: String
nicLink = "link"
nicMode :: String
nicMode = "mode"
nicVlan :: String
nicVlan = "vlan"
nicsParameterTypes :: Map String VType
nicsParameterTypes =
Map.fromList [(nicMode, vtypeString),
(nicLink, vtypeString),
(nicVlan, vtypeString)]
nicsParameters :: FrozenSet String
nicsParameters = ConstantUtils.mkSet (Map.keys nicsParameterTypes)
nicModeBridged :: String
nicModeBridged = Types.nICModeToRaw NMBridged
nicModeRouted :: String
nicModeRouted = Types.nICModeToRaw NMRouted
nicModeOvs :: String
nicModeOvs = Types.nICModeToRaw NMOvs
nicIpPool :: String
nicIpPool = Types.nICModeToRaw NMPool
nicValidModes :: FrozenSet String
nicValidModes = ConstantUtils.mkSet $ map Types.nICModeToRaw [minBound..]
releaseAction :: String
releaseAction = "release"
reserveAction :: String
reserveAction = "reserve"
idiskAdopt :: String
idiskAdopt = "adopt"
idiskMetavg :: String
idiskMetavg = "metavg"
idiskMode :: String
idiskMode = "mode"
idiskName :: String
idiskName = "name"
idiskSize :: String
idiskSize = "size"
idiskSpindles :: String
idiskSpindles = "spindles"
idiskVg :: String
idiskVg = "vg"
idiskProvider :: String
idiskProvider = "provider"
idiskAccess :: String
idiskAccess = "access"
idiskType :: String
idiskType = "dev_type"
idiskParamsTypes :: Map String VType
idiskParamsTypes =
Map.fromList [ (idiskSize, VTypeSize)
, (idiskSpindles, VTypeInt)
, (idiskMode, VTypeString)
, (idiskAdopt, VTypeString)
, (idiskVg, VTypeString)
, (idiskMetavg, VTypeString)
, (idiskProvider, VTypeString)
, (idiskAccess, VTypeString)
, (idiskName, VTypeMaybeString)
, (idiskType, VTypeString)
]
idiskParams :: FrozenSet String
idiskParams = ConstantUtils.mkSet (Map.keys idiskParamsTypes)
modifiableIdiskParamsTypes :: Map String VType
modifiableIdiskParamsTypes =
Map.fromList [(idiskMode, VTypeString),
(idiskName, VTypeString)]
modifiableIdiskParams :: FrozenSet String
modifiableIdiskParams =
ConstantUtils.mkSet (Map.keys modifiableIdiskParamsTypes)
inicBridge :: String
inicBridge = "bridge"
inicIp :: String
inicIp = "ip"
inicLink :: String
inicLink = "link"
inicMac :: String
inicMac = "mac"
inicMode :: String
inicMode = "mode"
inicName :: String
inicName = "name"
inicNetwork :: String
inicNetwork = "network"
inicVlan :: String
inicVlan = "vlan"
inicParamsTypes :: Map String VType
inicParamsTypes =
Map.fromList [(inicBridge, VTypeMaybeString),
(inicIp, VTypeMaybeString),
(inicLink, VTypeString),
(inicMac, VTypeString),
(inicMode, VTypeString),
(inicName, VTypeMaybeString),
(inicNetwork, VTypeMaybeString),
(inicVlan, VTypeMaybeString)]
inicParams :: FrozenSet String
inicParams = ConstantUtils.mkSet (Map.keys inicParamsTypes)
htXenPvm :: String
htXenPvm = Types.hypervisorToRaw XenPvm
htFake :: String
htFake = Types.hypervisorToRaw Fake
htXenHvm :: String
htXenHvm = Types.hypervisorToRaw XenHvm
htKvm :: String
htKvm = Types.hypervisorToRaw Kvm
htChroot :: String
htChroot = Types.hypervisorToRaw Chroot
htLxc :: String
htLxc = Types.hypervisorToRaw Lxc
hyperTypes :: FrozenSet String
hyperTypes = ConstantUtils.mkSet $ map Types.hypervisorToRaw [minBound..]
htsReqPort :: FrozenSet String
htsReqPort = ConstantUtils.mkSet [htXenHvm, htKvm]
vncBasePort :: Int
vncBasePort = 5900
vncDefaultBindAddress :: String
vncDefaultBindAddress = ip4AddressAny
qemuPciSlots :: Int
qemuPciSlots = 32
qemuDefaultPciReservations :: Int
qemuDefaultPciReservations = 12
htNicE1000 :: String
htNicE1000 = "e1000"
htNicI82551 :: String
htNicI82551 = "i82551"
htNicI8259er :: String
htNicI8259er = "i82559er"
htNicI85557b :: String
htNicI85557b = "i82557b"
htNicNe2kIsa :: String
htNicNe2kIsa = "ne2k_isa"
htNicNe2kPci :: String
htNicNe2kPci = "ne2k_pci"
htNicParavirtual :: String
htNicParavirtual = "paravirtual"
htNicPcnet :: String
htNicPcnet = "pcnet"
htNicRtl8139 :: String
htNicRtl8139 = "rtl8139"
htHvmValidNicTypes :: FrozenSet String
htHvmValidNicTypes =
ConstantUtils.mkSet [htNicE1000,
htNicNe2kIsa,
htNicNe2kPci,
htNicParavirtual,
htNicRtl8139]
htKvmValidNicTypes :: FrozenSet String
htKvmValidNicTypes =
ConstantUtils.mkSet [htNicE1000,
htNicI82551,
htNicI8259er,
htNicI85557b,
htNicNe2kIsa,
htNicNe2kPci,
htNicParavirtual,
htNicPcnet,
htNicRtl8139]
htHvmVifIoemu :: String
htHvmVifIoemu = "ioemu"
htHvmVifVif :: String
htHvmVifVif = "vif"
htHvmValidVifTypes :: FrozenSet String
htHvmValidVifTypes = ConstantUtils.mkSet [htHvmVifIoemu, htHvmVifVif]
htDiskIde :: String
htDiskIde = "ide"
htDiskIoemu :: String
htDiskIoemu = "ioemu"
htDiskMtd :: String
htDiskMtd = "mtd"
htDiskParavirtual :: String
htDiskParavirtual = "paravirtual"
htDiskPflash :: String
htDiskPflash = "pflash"
htDiskScsi :: String
htDiskScsi = "scsi"
htDiskSd :: String
htDiskSd = "sd"
htDiskScsiGeneric :: String
htDiskScsiGeneric = "scsi-generic"
htDiskScsiBlock :: String
htDiskScsiBlock = "scsi-block"
htDiskScsiCd :: String
htDiskScsiCd = "scsi-cd"
htDiskScsiHd :: String
htDiskScsiHd = "scsi-hd"
htScsiDeviceTypes :: FrozenSet String
htScsiDeviceTypes =
ConstantUtils.mkSet [htDiskScsiGeneric,
htDiskScsiBlock,
htDiskScsiCd,
htDiskScsiHd]
htHvmValidDiskTypes :: FrozenSet String
htHvmValidDiskTypes = ConstantUtils.mkSet [htDiskIoemu, htDiskParavirtual]
htKvmValidDiskTypes :: FrozenSet String
htKvmValidDiskTypes =
ConstantUtils.mkSet [htDiskIde,
htDiskMtd,
htDiskParavirtual,
htDiskPflash,
htDiskScsi,
htDiskSd,
htDiskScsiGeneric,
htDiskScsiBlock,
htDiskScsiHd,
htDiskScsiCd]
htScsiControllerLsi :: String
htScsiControllerLsi = "lsi"
htScsiControllerVirtio :: String
htScsiControllerVirtio = "virtio-scsi-pci"
htScsiControllerMegasas :: String
htScsiControllerMegasas = "megasas"
htKvmValidScsiControllerTypes :: FrozenSet String
htKvmValidScsiControllerTypes =
ConstantUtils.mkSet [htScsiControllerLsi,
htScsiControllerVirtio,
htScsiControllerMegasas]
htCacheDefault :: String
htCacheDefault = "default"
htCacheNone :: String
htCacheNone = "none"
htCacheWback :: String
htCacheWback = "writeback"
htCacheWthrough :: String
htCacheWthrough = "writethrough"
htValidCacheTypes :: FrozenSet String
htValidCacheTypes =
ConstantUtils.mkSet [htCacheDefault,
htCacheNone,
htCacheWback,
htCacheWthrough]
htKvmAioThreads :: String
htKvmAioThreads = "threads"
htKvmAioNative :: String
htKvmAioNative = "native"
htKvmValidAioTypes :: FrozenSet String
htKvmValidAioTypes =
ConstantUtils.mkSet [htKvmAioThreads,
htKvmAioNative]
htMouseMouse :: String
htMouseMouse = "mouse"
htMouseTablet :: String
htMouseTablet = "tablet"
htKvmValidMouseTypes :: FrozenSet String
htKvmValidMouseTypes = ConstantUtils.mkSet [htMouseMouse, htMouseTablet]
htBoCdrom :: String
htBoCdrom = "cdrom"
htBoDisk :: String
htBoDisk = "disk"
htBoFloppy :: String
htBoFloppy = "floppy"
htBoNetwork :: String
htBoNetwork = "network"
htKvmValidBoTypes :: FrozenSet String
htKvmValidBoTypes =
ConstantUtils.mkSet [htBoCdrom, htBoDisk, htBoFloppy, htBoNetwork]
htKvmSpiceLosslessImgComprAutoGlz :: String
htKvmSpiceLosslessImgComprAutoGlz = "auto_glz"
htKvmSpiceLosslessImgComprAutoLz :: String
htKvmSpiceLosslessImgComprAutoLz = "auto_lz"
htKvmSpiceLosslessImgComprGlz :: String
htKvmSpiceLosslessImgComprGlz = "glz"
htKvmSpiceLosslessImgComprLz :: String
htKvmSpiceLosslessImgComprLz = "lz"
htKvmSpiceLosslessImgComprOff :: String
htKvmSpiceLosslessImgComprOff = "off"
htKvmSpiceLosslessImgComprQuic :: String
htKvmSpiceLosslessImgComprQuic = "quic"
htKvmSpiceValidLosslessImgComprOptions :: FrozenSet String
htKvmSpiceValidLosslessImgComprOptions =
ConstantUtils.mkSet [htKvmSpiceLosslessImgComprAutoGlz,
htKvmSpiceLosslessImgComprAutoLz,
htKvmSpiceLosslessImgComprGlz,
htKvmSpiceLosslessImgComprLz,
htKvmSpiceLosslessImgComprOff,
htKvmSpiceLosslessImgComprQuic]
htKvmSpiceLossyImgComprAlways :: String
htKvmSpiceLossyImgComprAlways = "always"
htKvmSpiceLossyImgComprAuto :: String
htKvmSpiceLossyImgComprAuto = "auto"
htKvmSpiceLossyImgComprNever :: String
htKvmSpiceLossyImgComprNever = "never"
htKvmSpiceValidLossyImgComprOptions :: FrozenSet String
htKvmSpiceValidLossyImgComprOptions =
ConstantUtils.mkSet [htKvmSpiceLossyImgComprAlways,
htKvmSpiceLossyImgComprAuto,
htKvmSpiceLossyImgComprNever]
htKvmSpiceVideoStreamDetectionAll :: String
htKvmSpiceVideoStreamDetectionAll = "all"
htKvmSpiceVideoStreamDetectionFilter :: String
htKvmSpiceVideoStreamDetectionFilter = "filter"
htKvmSpiceVideoStreamDetectionOff :: String
htKvmSpiceVideoStreamDetectionOff = "off"
htKvmSpiceValidVideoStreamDetectionOptions :: FrozenSet String
htKvmSpiceValidVideoStreamDetectionOptions =
ConstantUtils.mkSet [htKvmSpiceVideoStreamDetectionAll,
htKvmSpiceVideoStreamDetectionFilter,
htKvmSpiceVideoStreamDetectionOff]
htSmNone :: String
htSmNone = "none"
htSmPool :: String
htSmPool = "pool"
htSmUser :: String
htSmUser = "user"
htKvmValidSmTypes :: FrozenSet String
htKvmValidSmTypes = ConstantUtils.mkSet [htSmNone, htSmPool, htSmUser]
htKvmDisabled :: String
htKvmDisabled = "disabled"
htKvmEnabled :: String
htKvmEnabled = "enabled"
htKvmFlagValues :: FrozenSet String
htKvmFlagValues = ConstantUtils.mkSet [htKvmDisabled, htKvmEnabled]
htMigrationLive :: String
htMigrationLive = Types.migrationModeToRaw MigrationLive
htMigrationNonlive :: String
htMigrationNonlive = Types.migrationModeToRaw MigrationNonLive
htMigrationModes :: FrozenSet String
htMigrationModes =
ConstantUtils.mkSet $ map Types.migrationModeToRaw [minBound..]
verifyNplusoneMem :: String
verifyNplusoneMem = Types.verifyOptionalChecksToRaw VerifyNPlusOneMem
verifyOptionalChecks :: FrozenSet String
verifyOptionalChecks =
ConstantUtils.mkSet $ map Types.verifyOptionalChecksToRaw [minBound..]
cvTcluster :: String
cvTcluster = "cluster"
cvTgroup :: String
cvTgroup = "group"
cvTnode :: String
cvTnode = "node"
cvTinstance :: String
cvTinstance = "instance"
cvWarning :: String
cvWarning = "WARNING"
cvError :: String
cvError = "ERROR"
cvEclustercert :: (String, String, String)
cvEclustercert =
("cluster",
Types.cVErrorCodeToRaw CvECLUSTERCERT,
"Cluster certificate files verification failure")
cvEclusterclientcert :: (String, String, String)
cvEclusterclientcert =
("cluster",
Types.cVErrorCodeToRaw CvECLUSTERCLIENTCERT,
"Cluster client certificate files verification failure")
cvEclustercfg :: (String, String, String)
cvEclustercfg =
("cluster",
Types.cVErrorCodeToRaw CvECLUSTERCFG,
"Cluster configuration verification failure")
cvEclusterdanglinginst :: (String, String, String)
cvEclusterdanglinginst =
("node",
Types.cVErrorCodeToRaw CvECLUSTERDANGLINGINST,
"Some instances have a non-existing primary node")
cvEclusterdanglingnodes :: (String, String, String)
cvEclusterdanglingnodes =
("node",
Types.cVErrorCodeToRaw CvECLUSTERDANGLINGNODES,
"Some nodes belong to non-existing groups")
cvEclusterfilecheck :: (String, String, String)
cvEclusterfilecheck =
("cluster",
Types.cVErrorCodeToRaw CvECLUSTERFILECHECK,
"Cluster configuration verification failure")
cvEgroupdifferentpvsize :: (String, String, String)
cvEgroupdifferentpvsize =
("group",
Types.cVErrorCodeToRaw CvEGROUPDIFFERENTPVSIZE,
"PVs in the group have different sizes")
cvEinstancebadnode :: (String, String, String)
cvEinstancebadnode =
("instance",
Types.cVErrorCodeToRaw CvEINSTANCEBADNODE,
"Instance marked as running lives on an offline node")
cvEinstancedown :: (String, String, String)
cvEinstancedown =
("instance",
Types.cVErrorCodeToRaw CvEINSTANCEDOWN,
"Instance not running on its primary node")
cvEinstancefaultydisk :: (String, String, String)
cvEinstancefaultydisk =
("instance",
Types.cVErrorCodeToRaw CvEINSTANCEFAULTYDISK,
"Impossible to retrieve status for a disk")
cvEinstancelayout :: (String, String, String)
cvEinstancelayout =
("instance",
Types.cVErrorCodeToRaw CvEINSTANCELAYOUT,
"Instance has multiple secondary nodes")
cvEinstancemissingcfgparameter :: (String, String, String)
cvEinstancemissingcfgparameter =
("instance",
Types.cVErrorCodeToRaw CvEINSTANCEMISSINGCFGPARAMETER,
"A configuration parameter for an instance is missing")
cvEinstancemissingdisk :: (String, String, String)
cvEinstancemissingdisk =
("instance",
Types.cVErrorCodeToRaw CvEINSTANCEMISSINGDISK,
"Missing volume on an instance")
cvEinstancepolicy :: (String, String, String)
cvEinstancepolicy =
("instance",
Types.cVErrorCodeToRaw CvEINSTANCEPOLICY,
"Instance does not meet policy")
cvEinstancesplitgroups :: (String, String, String)
cvEinstancesplitgroups =
("instance",
Types.cVErrorCodeToRaw CvEINSTANCESPLITGROUPS,
"Instance with primary and secondary nodes in different groups")
cvEinstanceunsuitablenode :: (String, String, String)
cvEinstanceunsuitablenode =
("instance",
Types.cVErrorCodeToRaw CvEINSTANCEUNSUITABLENODE,
"Instance running on nodes that are not suitable for it")
cvEinstancewrongnode :: (String, String, String)
cvEinstancewrongnode =
("instance",
Types.cVErrorCodeToRaw CvEINSTANCEWRONGNODE,
"Instance running on the wrong node")
cvEnodedrbd :: (String, String, String)
cvEnodedrbd =
("node",
Types.cVErrorCodeToRaw CvENODEDRBD,
"Error parsing the DRBD status file")
cvEnodedrbdhelper :: (String, String, String)
cvEnodedrbdhelper =
("node",
Types.cVErrorCodeToRaw CvENODEDRBDHELPER,
"Error caused by the DRBD helper")
cvEnodedrbdversion :: (String, String, String)
cvEnodedrbdversion =
("node",
Types.cVErrorCodeToRaw CvENODEDRBDVERSION,
"DRBD version mismatch within a node group")
cvEnodefilecheck :: (String, String, String)
cvEnodefilecheck =
("node",
Types.cVErrorCodeToRaw CvENODEFILECHECK,
"Error retrieving the checksum of the node files")
cvEnodefilestoragepaths :: (String, String, String)
cvEnodefilestoragepaths =
("node",
Types.cVErrorCodeToRaw CvENODEFILESTORAGEPATHS,
"Detected bad file storage paths")
cvEnodefilestoragepathunusable :: (String, String, String)
cvEnodefilestoragepathunusable =
("node",
Types.cVErrorCodeToRaw CvENODEFILESTORAGEPATHUNUSABLE,
"File storage path unusable")
cvEnodehooks :: (String, String, String)
cvEnodehooks =
("node",
Types.cVErrorCodeToRaw CvENODEHOOKS,
"Communication failure in hooks execution")
cvEnodehv :: (String, String, String)
cvEnodehv =
("node",
Types.cVErrorCodeToRaw CvENODEHV,
"Hypervisor parameters verification failure")
cvEnodelvm :: (String, String, String)
cvEnodelvm =
("node",
Types.cVErrorCodeToRaw CvENODELVM,
"LVM-related node error")
cvEnoden1 :: (String, String, String)
cvEnoden1 =
("node",
Types.cVErrorCodeToRaw CvENODEN1,
"Not enough memory to accommodate instance failovers")
cvEextags :: (String, String, String)
cvEextags =
("node",
Types.cVErrorCodeToRaw CvEEXTAGS,
"Instances with same exclusion tag on the same node")
cvEnodenet :: (String, String, String)
cvEnodenet =
("node",
Types.cVErrorCodeToRaw CvENODENET,
"Network-related node error")
cvEnodeoobpath :: (String, String, String)
cvEnodeoobpath =
("node",
Types.cVErrorCodeToRaw CvENODEOOBPATH,
"Invalid Out Of Band path")
cvEnodeorphaninstance :: (String, String, String)
cvEnodeorphaninstance =
("node",
Types.cVErrorCodeToRaw CvENODEORPHANINSTANCE,
"Unknown intance running on a node")
cvEnodeorphanlv :: (String, String, String)
cvEnodeorphanlv =
("node",
Types.cVErrorCodeToRaw CvENODEORPHANLV,
"Unknown LVM logical volume")
cvEnodeos :: (String, String, String)
cvEnodeos =
("node",
Types.cVErrorCodeToRaw CvENODEOS,
"OS-related node error")
cvEnoderpc :: (String, String, String)
cvEnoderpc =
("node",
Types.cVErrorCodeToRaw CvENODERPC,
"Error during connection to the primary node of an instance")
cvEnodesetup :: (String, String, String)
cvEnodesetup =
("node",
Types.cVErrorCodeToRaw CvENODESETUP,
"Node setup error")
cvEnodesharedfilestoragepathunusable :: (String, String, String)
cvEnodesharedfilestoragepathunusable =
("node",
Types.cVErrorCodeToRaw CvENODESHAREDFILESTORAGEPATHUNUSABLE,
"Shared file storage path unusable")
cvEnodeglusterstoragepathunusable :: (String, String, String)
cvEnodeglusterstoragepathunusable =
("node",
Types.cVErrorCodeToRaw CvENODEGLUSTERSTORAGEPATHUNUSABLE,
"Gluster storage path unusable")
cvEnodessh :: (String, String, String)
cvEnodessh =
("node",
Types.cVErrorCodeToRaw CvENODESSH,
"SSH-related node error")
cvEnodetime :: (String, String, String)
cvEnodetime =
("node",
Types.cVErrorCodeToRaw CvENODETIME,
"Node returned invalid time")
cvEnodeuserscripts :: (String, String, String)
cvEnodeuserscripts =
("node",
Types.cVErrorCodeToRaw CvENODEUSERSCRIPTS,
"User scripts not present or not executable")
cvEnodeversion :: (String, String, String)
cvEnodeversion =
("node",
Types.cVErrorCodeToRaw CvENODEVERSION,
"Protocol version mismatch or Ganeti version mismatch")
cvAllEcodes :: FrozenSet (String, String, String)
cvAllEcodes =
ConstantUtils.mkSet
[cvEclustercert,
cvEclustercfg,
cvEclusterdanglinginst,
cvEclusterdanglingnodes,
cvEclusterfilecheck,
cvEgroupdifferentpvsize,
cvEinstancebadnode,
cvEinstancedown,
cvEinstancefaultydisk,
cvEinstancelayout,
cvEinstancemissingcfgparameter,
cvEinstancemissingdisk,
cvEinstancepolicy,
cvEinstancesplitgroups,
cvEinstanceunsuitablenode,
cvEinstancewrongnode,
cvEnodedrbd,
cvEnodedrbdhelper,
cvEnodedrbdversion,
cvEnodefilecheck,
cvEnodefilestoragepaths,
cvEnodefilestoragepathunusable,
cvEnodehooks,
cvEnodehv,
cvEnodelvm,
cvEnoden1,
cvEnodenet,
cvEnodeoobpath,
cvEnodeorphaninstance,
cvEnodeorphanlv,
cvEnodeos,
cvEnoderpc,
cvEnodesetup,
cvEnodesharedfilestoragepathunusable,
cvEnodeglusterstoragepathunusable,
cvEnodessh,
cvEnodetime,
cvEnodeuserscripts,
cvEnodeversion]
cvAllEcodesStrings :: FrozenSet String
cvAllEcodesStrings =
ConstantUtils.mkSet $ map Types.cVErrorCodeToRaw [minBound..]
nvBridges :: String
nvBridges = "bridges"
nvClientCert :: String
nvClientCert = "client-cert"
nvDrbdhelper :: String
nvDrbdhelper = "drbd-helper"
nvDrbdversion :: String
nvDrbdversion = "drbd-version"
nvDrbdlist :: String
nvDrbdlist = "drbd-list"
nvExclusivepvs :: String
nvExclusivepvs = "exclusive-pvs"
nvFilelist :: String
nvFilelist = "filelist"
nvAcceptedStoragePaths :: String
nvAcceptedStoragePaths = "allowed-file-storage-paths"
nvFileStoragePath :: String
nvFileStoragePath = "file-storage-path"
nvSharedFileStoragePath :: String
nvSharedFileStoragePath = "shared-file-storage-path"
nvGlusterStoragePath :: String
nvGlusterStoragePath = "gluster-storage-path"
nvHvinfo :: String
nvHvinfo = "hvinfo"
nvHvparams :: String
nvHvparams = "hvparms"
nvHypervisor :: String
nvHypervisor = "hypervisor"
nvInstancelist :: String
nvInstancelist = "instancelist"
nvLvlist :: String
nvLvlist = "lvlist"
nvMasterip :: String
nvMasterip = "master-ip"
nvNodelist :: String
nvNodelist = "nodelist"
nvNodenettest :: String
nvNodenettest = "node-net-test"
nvNodesetup :: String
nvNodesetup = "nodesetup"
nvOobPaths :: String
nvOobPaths = "oob-paths"
nvOslist :: String
nvOslist = "oslist"
nvPvlist :: String
nvPvlist = "pvlist"
nvTime :: String
nvTime = "time"
nvUserscripts :: String
nvUserscripts = "user-scripts"
nvVersion :: String
nvVersion = "version"
nvVglist :: String
nvVglist = "vglist"
nvNonvmnodes :: String
nvNonvmnodes = "nonvmnodes"
nvSshSetup :: String
nvSshSetup = "ssh-setup"
nvSshClutter :: String
nvSshClutter = "ssh-clutter"
inststAdmindown :: String
inststAdmindown = Types.instanceStatusToRaw StatusDown
inststAdminoffline :: String
inststAdminoffline = Types.instanceStatusToRaw StatusOffline
inststErrordown :: String
inststErrordown = Types.instanceStatusToRaw ErrorDown
inststErrorup :: String
inststErrorup = Types.instanceStatusToRaw ErrorUp
inststNodedown :: String
inststNodedown = Types.instanceStatusToRaw NodeDown
inststNodeoffline :: String
inststNodeoffline = Types.instanceStatusToRaw NodeOffline
inststRunning :: String
inststRunning = Types.instanceStatusToRaw Running
inststUserdown :: String
inststUserdown = Types.instanceStatusToRaw UserDown
inststWrongnode :: String
inststWrongnode = Types.instanceStatusToRaw WrongNode
inststAll :: FrozenSet String
inststAll = ConstantUtils.mkSet $ map Types.instanceStatusToRaw [minBound..]
adminstDown :: String
adminstDown = Types.adminStateToRaw AdminDown
adminstOffline :: String
adminstOffline = Types.adminStateToRaw AdminOffline
adminstUp :: String
adminstUp = Types.adminStateToRaw AdminUp
adminstAll :: FrozenSet String
adminstAll = ConstantUtils.mkSet $ map Types.adminStateToRaw [minBound..]
adminSource :: AdminStateSource
adminSource = AdminSource
userSource :: AdminStateSource
userSource = UserSource
adminStateSources :: FrozenSet AdminStateSource
adminStateSources = ConstantUtils.mkSet [minBound..]
nrDrained :: String
nrDrained = Types.nodeRoleToRaw NRDrained
nrMaster :: String
nrMaster = Types.nodeRoleToRaw NRMaster
nrMcandidate :: String
nrMcandidate = Types.nodeRoleToRaw NRCandidate
nrOffline :: String
nrOffline = Types.nodeRoleToRaw NROffline
nrRegular :: String
nrRegular = Types.nodeRoleToRaw NRRegular
nrAll :: FrozenSet String
nrAll = ConstantUtils.mkSet $ map Types.nodeRoleToRaw [minBound..]
sslCertExpirationError :: Int
sslCertExpirationError = 7
sslCertExpirationWarn :: Int
sslCertExpirationWarn = 30
iallocatorVersion :: Int
iallocatorVersion = 2
iallocatorDirIn :: String
iallocatorDirIn = Types.iAllocatorTestDirToRaw IAllocatorDirIn
iallocatorDirOut :: String
iallocatorDirOut = Types.iAllocatorTestDirToRaw IAllocatorDirOut
validIallocatorDirections :: FrozenSet String
validIallocatorDirections =
ConstantUtils.mkSet $ map Types.iAllocatorTestDirToRaw [minBound..]
iallocatorModeAlloc :: String
iallocatorModeAlloc = Types.iAllocatorModeToRaw IAllocatorAlloc
iallocatorModeAllocateSecondary :: String
iallocatorModeAllocateSecondary =
Types.iAllocatorModeToRaw IAllocatorAllocateSecondary
iallocatorModeChgGroup :: String
iallocatorModeChgGroup = Types.iAllocatorModeToRaw IAllocatorChangeGroup
iallocatorModeMultiAlloc :: String
iallocatorModeMultiAlloc = Types.iAllocatorModeToRaw IAllocatorMultiAlloc
iallocatorModeNodeEvac :: String
iallocatorModeNodeEvac = Types.iAllocatorModeToRaw IAllocatorNodeEvac
iallocatorModeReloc :: String
iallocatorModeReloc = Types.iAllocatorModeToRaw IAllocatorReloc
validIallocatorModes :: FrozenSet String
validIallocatorModes =
ConstantUtils.mkSet $ map Types.iAllocatorModeToRaw [minBound..]
iallocatorSearchPath :: [String]
iallocatorSearchPath = AutoConf.iallocatorSearchPath
defaultIallocatorShortcut :: String
defaultIallocatorShortcut = "."
defaultOpportunisticRetryInterval :: Int
defaultOpportunisticRetryInterval = 30
nodeEvacPri :: String
nodeEvacPri = Types.evacModeToRaw ChangePrimary
nodeEvacSec :: String
nodeEvacSec = Types.evacModeToRaw ChangeSecondary
nodeEvacAll :: String
nodeEvacAll = Types.evacModeToRaw ChangeAll
nodeEvacModes :: FrozenSet String
nodeEvacModes = ConstantUtils.mkSet $ map Types.evacModeToRaw [minBound..]
jobQueueVersion :: Int
jobQueueVersion = 1
jobQueueSizeHardLimit :: Int
jobQueueSizeHardLimit = 5000
jobQueueFilesPerms :: Int
jobQueueFilesPerms = 0o640
jobNotchanged :: String
jobNotchanged = "nochange"
jobStatusQueued :: String
jobStatusQueued = Types.jobStatusToRaw JOB_STATUS_QUEUED
jobStatusWaiting :: String
jobStatusWaiting = Types.jobStatusToRaw JOB_STATUS_WAITING
jobStatusCanceling :: String
jobStatusCanceling = Types.jobStatusToRaw JOB_STATUS_CANCELING
jobStatusRunning :: String
jobStatusRunning = Types.jobStatusToRaw JOB_STATUS_RUNNING
jobStatusCanceled :: String
jobStatusCanceled = Types.jobStatusToRaw JOB_STATUS_CANCELED
jobStatusSuccess :: String
jobStatusSuccess = Types.jobStatusToRaw JOB_STATUS_SUCCESS
jobStatusError :: String
jobStatusError = Types.jobStatusToRaw JOB_STATUS_ERROR
jobsPending :: FrozenSet String
jobsPending =
ConstantUtils.mkSet [jobStatusQueued, jobStatusWaiting, jobStatusCanceling]
jobsFinalized :: FrozenSet String
jobsFinalized =
ConstantUtils.mkSet $ map Types.finalizedJobStatusToRaw [minBound..]
jobStatusAll :: FrozenSet String
jobStatusAll = ConstantUtils.mkSet $ map Types.jobStatusToRaw [minBound..]
opStatusCanceling :: String
opStatusCanceling = "canceling"
opStatusQueued :: String
opStatusQueued = "queued"
opStatusRunning :: String
opStatusRunning = "running"
opStatusWaiting :: String
opStatusWaiting = "waiting"
opStatusCanceled :: String
opStatusCanceled = "canceled"
opStatusError :: String
opStatusError = "error"
opStatusSuccess :: String
opStatusSuccess = "success"
opsFinalized :: FrozenSet String
opsFinalized =
ConstantUtils.mkSet [opStatusCanceled, opStatusError, opStatusSuccess]
opPrioLowest :: Int
opPrioLowest = 19
opPrioHighest :: Int
opPrioHighest = 20
opPrioLow :: Int
opPrioLow = Types.opSubmitPriorityToRaw OpPrioLow
opPrioNormal :: Int
opPrioNormal = Types.opSubmitPriorityToRaw OpPrioNormal
opPrioHigh :: Int
opPrioHigh = Types.opSubmitPriorityToRaw OpPrioHigh
opPrioSubmitValid :: FrozenSet Int
opPrioSubmitValid = ConstantUtils.mkSet [opPrioLow, opPrioNormal, opPrioHigh]
opPrioDefault :: Int
opPrioDefault = opPrioNormal
locksAppend :: String
locksAppend = "append"
locksReplace :: String
locksReplace = "replace"
lockAttemptsMaxwait :: Double
lockAttemptsMaxwait = 75.0
lockAttemptsMinwait :: Double
lockAttemptsMinwait = 5.0
lockAttemptsTimeout :: Int
lockAttemptsTimeout = (10 * 3600) `div` (opPrioDefault opPrioHighest)
elogMessage :: String
elogMessage = Types.eLogTypeToRaw ELogMessage
elogRemoteImport :: String
elogRemoteImport = Types.eLogTypeToRaw ELogRemoteImport
elogJqueueTest :: String
elogJqueueTest = Types.eLogTypeToRaw ELogJqueueTest
elogDelayTest :: String
elogDelayTest = Types.eLogTypeToRaw ELogDelayTest
etcHostsAdd :: String
etcHostsAdd = "add"
etcHostsRemove :: String
etcHostsRemove = "remove"
jqtMsgprefix :: String
jqtMsgprefix = "TESTMSG="
jqtExec :: String
jqtExec = "exec"
jqtExpandnames :: String
jqtExpandnames = "expandnames"
jqtLogmsg :: String
jqtLogmsg = "logmsg"
jqtStartmsg :: String
jqtStartmsg = "startmsg"
jqtAll :: FrozenSet String
jqtAll = ConstantUtils.mkSet [jqtExec, jqtExpandnames, jqtLogmsg, jqtStartmsg]
qrCluster :: String
qrCluster = "cluster"
qrExport :: String
qrExport = "export"
qrExtstorage :: String
qrExtstorage = "extstorage"
qrGroup :: String
qrGroup = "group"
qrInstance :: String
qrInstance = "instance"
qrJob :: String
qrJob = "job"
qrLock :: String
qrLock = "lock"
qrNetwork :: String
qrNetwork = "network"
qrFilter :: String
qrFilter = "filter"
qrNode :: String
qrNode = "node"
qrOs :: String
qrOs = "os"
qrViaOp :: FrozenSet String
qrViaOp =
ConstantUtils.mkSet [qrCluster,
qrOs,
qrExtstorage]
qrViaLuxi :: FrozenSet String
qrViaLuxi = ConstantUtils.mkSet [qrGroup,
qrExport,
qrInstance,
qrJob,
qrLock,
qrNetwork,
qrNode,
qrFilter]
qrViaRapi :: FrozenSet String
qrViaRapi = qrViaLuxi
qrViaRapiPut :: FrozenSet String
qrViaRapiPut = ConstantUtils.mkSet [qrLock, qrJob, qrFilter]
qftBool :: String
qftBool = "bool"
qftNumber :: String
qftNumber = "number"
qftNumberFloat :: String
qftNumberFloat = "float"
qftOther :: String
qftOther = "other"
qftText :: String
qftText = "text"
qftTimestamp :: String
qftTimestamp = "timestamp"
qftUnit :: String
qftUnit = "unit"
qftUnknown :: String
qftUnknown = "unknown"
qftAll :: FrozenSet String
qftAll =
ConstantUtils.mkSet [qftBool,
qftNumber,
qftNumberFloat,
qftOther,
qftText,
qftTimestamp,
qftUnit,
qftUnknown]
rsNodata :: Int
rsNodata = 2
rsNormal :: Int
rsNormal = 0
rsOffline :: Int
rsOffline = 4
rsUnavail :: Int
rsUnavail = 3
rsUnknown :: Int
rsUnknown = 1
rsAll :: FrozenSet Int
rsAll =
ConstantUtils.mkSet [rsNodata,
rsNormal,
rsOffline,
rsUnavail,
rsUnknown]
rssDescription :: Map Int (String, String)
rssDescription =
Map.fromList [(rsUnknown, ("(unknown)", "??")),
(rsNodata, ("(nodata)", "?")),
(rsOffline, ("(offline)", "*")),
(rsUnavail, ("(unavail)", "-"))]
maxDisks :: Int
maxDisks = Types.maxDisks
maxNics :: Int
maxNics = Types.maxNics
ssconfFileprefix :: String
ssconfFileprefix = "ssconf_"
ssClusterName :: String
ssClusterName = "cluster_name"
ssClusterTags :: String
ssClusterTags = "cluster_tags"
ssFileStorageDir :: String
ssFileStorageDir = "file_storage_dir"
ssSharedFileStorageDir :: String
ssSharedFileStorageDir = "shared_file_storage_dir"
ssGlusterStorageDir :: String
ssGlusterStorageDir = "gluster_storage_dir"
ssMasterCandidates :: String
ssMasterCandidates = "master_candidates"
ssMasterCandidatesIps :: String
ssMasterCandidatesIps = "master_candidates_ips"
ssMasterCandidatesCerts :: String
ssMasterCandidatesCerts = "master_candidates_certs"
ssMasterIp :: String
ssMasterIp = "master_ip"
ssMasterNetdev :: String
ssMasterNetdev = "master_netdev"
ssMasterNetmask :: String
ssMasterNetmask = "master_netmask"
ssMasterNode :: String
ssMasterNode = "master_node"
ssNodeList :: String
ssNodeList = "node_list"
ssNodePrimaryIps :: String
ssNodePrimaryIps = "node_primary_ips"
ssNodeSecondaryIps :: String
ssNodeSecondaryIps = "node_secondary_ips"
ssNodeVmCapable :: String
ssNodeVmCapable = "node_vm_capable"
ssOfflineNodes :: String
ssOfflineNodes = "offline_nodes"
ssOnlineNodes :: String
ssOnlineNodes = "online_nodes"
ssPrimaryIpFamily :: String
ssPrimaryIpFamily = "primary_ip_family"
ssInstanceList :: String
ssInstanceList = "instance_list"
ssReleaseVersion :: String
ssReleaseVersion = "release_version"
ssHypervisorList :: String
ssHypervisorList = "hypervisor_list"
ssMaintainNodeHealth :: String
ssMaintainNodeHealth = "maintain_node_health"
ssUidPool :: String
ssUidPool = "uid_pool"
ssNodegroups :: String
ssNodegroups = "nodegroups"
ssNetworks :: String
ssNetworks = "networks"
ssHvparamsPref :: String
ssHvparamsPref = "hvparams_"
ssHvparamsXenChroot :: String
ssHvparamsXenChroot = ssHvparamsPref ++ htChroot
ssHvparamsXenFake :: String
ssHvparamsXenFake = ssHvparamsPref ++ htFake
ssHvparamsXenHvm :: String
ssHvparamsXenHvm = ssHvparamsPref ++ htXenHvm
ssHvparamsXenKvm :: String
ssHvparamsXenKvm = ssHvparamsPref ++ htKvm
ssHvparamsXenLxc :: String
ssHvparamsXenLxc = ssHvparamsPref ++ htLxc
ssHvparamsXenPvm :: String
ssHvparamsXenPvm = ssHvparamsPref ++ htXenPvm
validSsHvparamsKeys :: FrozenSet String
validSsHvparamsKeys =
ConstantUtils.mkSet [ssHvparamsXenChroot,
ssHvparamsXenLxc,
ssHvparamsXenFake,
ssHvparamsXenHvm,
ssHvparamsXenKvm,
ssHvparamsXenPvm]
ssFilePerms :: Int
ssFilePerms = 0o444
ssEnabledUserShutdown :: String
ssEnabledUserShutdown = "enabled_user_shutdown"
ssSshPorts :: String
ssSshPorts = "ssh_ports"
validSsKeys :: FrozenSet String
validSsKeys = ConstantUtils.mkSet
[ ssClusterName
, ssClusterTags
, ssFileStorageDir
, ssSharedFileStorageDir
, ssGlusterStorageDir
, ssMasterCandidates
, ssMasterCandidatesIps
, ssMasterCandidatesCerts
, ssMasterIp
, ssMasterNetdev
, ssMasterNetmask
, ssMasterNode
, ssNodeList
, ssNodePrimaryIps
, ssNodeSecondaryIps
, ssNodeVmCapable
, ssOfflineNodes
, ssOnlineNodes
, ssPrimaryIpFamily
, ssInstanceList
, ssReleaseVersion
, ssHypervisorList
, ssMaintainNodeHealth
, ssUidPool
, ssNodegroups
, ssNetworks
, ssEnabledUserShutdown
, ssSshPorts
]
<>
validSsHvparamsKeys
defaultEnabledHypervisor :: String
defaultEnabledHypervisor = htXenPvm
hvcDefaults :: Map Hypervisor (Map String PyValueEx)
hvcDefaults =
Map.fromList
[ (XenPvm, Map.fromList
[ (hvUseBootloader, PyValueEx False)
, (hvBootloaderPath, PyValueEx xenBootloader)
, (hvBootloaderArgs, PyValueEx "")
, (hvKernelPath, PyValueEx xenKernel)
, (hvInitrdPath, PyValueEx "")
, (hvRootPath, PyValueEx "/dev/xvda1")
, (hvKernelArgs, PyValueEx "ro")
, (hvMigrationPort, PyValueEx (8002 :: Int))
, (hvMigrationMode, PyValueEx htMigrationLive)
, (hvBlockdevPrefix, PyValueEx "sd")
, (hvRebootBehavior, PyValueEx instanceRebootAllowed)
, (hvCpuMask, PyValueEx cpuPinningAll)
, (hvCpuCap, PyValueEx (0 :: Int))
, (hvCpuWeight, PyValueEx (256 :: Int))
, (hvVifScript, PyValueEx "")
, (hvXenCmd, PyValueEx xenCmdXm)
, (hvXenCpuid, PyValueEx "")
, (hvSoundhw, PyValueEx "")
])
, (XenHvm, Map.fromList
[ (hvBootOrder, PyValueEx "cd")
, (hvCdromImagePath, PyValueEx "")
, (hvNicType, PyValueEx htNicRtl8139)
, (hvDiskType, PyValueEx htDiskParavirtual)
, (hvVncBindAddress, PyValueEx ip4AddressAny)
, (hvAcpi, PyValueEx True)
, (hvPae, PyValueEx True)
, (hvKernelPath, PyValueEx "/usr/lib/xen/boot/hvmloader")
, (hvDeviceModel, PyValueEx "/usr/lib/xen/bin/qemu-dm")
, (hvMigrationPort, PyValueEx (8002 :: Int))
, (hvMigrationMode, PyValueEx htMigrationNonlive)
, (hvUseLocaltime, PyValueEx False)
, (hvBlockdevPrefix, PyValueEx "hd")
, (hvPassthrough, PyValueEx "")
, (hvRebootBehavior, PyValueEx instanceRebootAllowed)
, (hvCpuMask, PyValueEx cpuPinningAll)
, (hvCpuCap, PyValueEx (0 :: Int))
, (hvCpuWeight, PyValueEx (256 :: Int))
, (hvVifType, PyValueEx htHvmVifIoemu)
, (hvVifScript, PyValueEx "")
, (hvViridian, PyValueEx False)
, (hvXenCmd, PyValueEx xenCmdXm)
, (hvXenCpuid, PyValueEx "")
, (hvSoundhw, PyValueEx "")
])
, (Kvm, Map.fromList
[ (hvKvmPath, PyValueEx kvmPath)
, (hvKernelPath, PyValueEx kvmKernel)
, (hvInitrdPath, PyValueEx "")
, (hvKernelArgs, PyValueEx "ro")
, (hvRootPath, PyValueEx "/dev/vda1")
, (hvAcpi, PyValueEx True)
, (hvSerialConsole, PyValueEx True)
, (hvSerialSpeed, PyValueEx (38400 :: Int))
, (hvVncBindAddress, PyValueEx "")
, (hvVncTls, PyValueEx False)
, (hvVncX509, PyValueEx "")
, (hvVncX509Verify, PyValueEx False)
, (hvVncPasswordFile, PyValueEx "")
, (hvKvmScsiControllerType, PyValueEx htScsiControllerLsi)
, (hvKvmPciReservations, PyValueEx qemuDefaultPciReservations)
, (hvKvmSpiceBind, PyValueEx "")
, (hvKvmSpiceIpVersion, PyValueEx ifaceNoIpVersionSpecified)
, (hvKvmSpicePasswordFile, PyValueEx "")
, (hvKvmSpiceLosslessImgCompr, PyValueEx "")
, (hvKvmSpiceJpegImgCompr, PyValueEx "")
, (hvKvmSpiceZlibGlzImgCompr, PyValueEx "")
, (hvKvmSpiceStreamingVideoDetection, PyValueEx "")
, (hvKvmSpiceAudioCompr, PyValueEx True)
, (hvKvmSpiceUseTls, PyValueEx False)
, (hvKvmSpiceTlsCiphers, PyValueEx opensslCiphers)
, (hvKvmSpiceUseVdagent, PyValueEx True)
, (hvKvmFloppyImagePath, PyValueEx "")
, (hvCdromImagePath, PyValueEx "")
, (hvKvmCdrom2ImagePath, PyValueEx "")
, (hvBootOrder, PyValueEx htBoDisk)
, (hvNicType, PyValueEx htNicParavirtual)
, (hvDiskType, PyValueEx htDiskParavirtual)
, (hvKvmCdromDiskType, PyValueEx "")
, (hvKvmDiskAio, PyValueEx htKvmAioThreads)
, (hvUsbMouse, PyValueEx "")
, (hvKeymap, PyValueEx "")
, (hvMigrationPort, PyValueEx (8102 :: Int))
, (hvMigrationBandwidth, PyValueEx (32 :: Int))
, (hvMigrationDowntime, PyValueEx (30 :: Int))
, (hvMigrationMode, PyValueEx htMigrationLive)
, (hvUseLocaltime, PyValueEx False)
, (hvDiskCache, PyValueEx htCacheDefault)
, (hvSecurityModel, PyValueEx htSmNone)
, (hvSecurityDomain, PyValueEx "")
, (hvKvmFlag, PyValueEx "")
, (hvVhostNet, PyValueEx False)
, (hvVirtioNetQueues, PyValueEx (1 :: Int))
, (hvKvmUseChroot, PyValueEx False)
, (hvKvmUserShutdown, PyValueEx False)
, (hvMemPath, PyValueEx "")
, (hvRebootBehavior, PyValueEx instanceRebootAllowed)
, (hvCpuMask, PyValueEx cpuPinningAll)
, (hvCpuType, PyValueEx "")
, (hvCpuCores, PyValueEx (0 :: Int))
, (hvCpuThreads, PyValueEx (0 :: Int))
, (hvCpuSockets, PyValueEx (0 :: Int))
, (hvSoundhw, PyValueEx "")
, (hvUsbDevices, PyValueEx "")
, (hvVga, PyValueEx "")
, (hvKvmExtra, PyValueEx "")
, (hvKvmMachineVersion, PyValueEx "")
, (hvKvmMigrationCaps, PyValueEx "")
, (hvVnetHdr, PyValueEx True)])
, (Fake, Map.fromList [(hvMigrationMode, PyValueEx htMigrationLive)])
, (Chroot, Map.fromList [(hvInitScript, PyValueEx "/ganeti-chroot")])
, (Lxc, Map.fromList
[ (hvCpuMask, PyValueEx "")
, (hvLxcDevices, PyValueEx lxcDevicesDefault)
, (hvLxcDropCapabilities, PyValueEx lxcDropCapabilitiesDefault)
, (hvLxcExtraCgroups, PyValueEx "")
, (hvLxcExtraConfig, PyValueEx "")
, (hvLxcNumTtys, PyValueEx (6 :: Int))
, (hvLxcStartupTimeout, PyValueEx (30 :: Int))
])
]
hvcGlobals :: FrozenSet String
hvcGlobals =
ConstantUtils.mkSet [hvMigrationBandwidth,
hvMigrationMode,
hvMigrationPort,
hvXenCmd]
becDefaults :: Map String PyValueEx
becDefaults =
Map.fromList
[ (beMinmem, PyValueEx (128 :: Int))
, (beMaxmem, PyValueEx (128 :: Int))
, (beVcpus, PyValueEx (1 :: Int))
, (beAutoBalance, PyValueEx True)
, (beAlwaysFailover, PyValueEx False)
, (beSpindleUse, PyValueEx (1 :: Int))
]
ndcDefaults :: Map String PyValueEx
ndcDefaults =
Map.fromList
[ (ndOobProgram, PyValueEx "")
, (ndSpindleCount, PyValueEx (1 :: Int))
, (ndExclusiveStorage, PyValueEx False)
, (ndOvs, PyValueEx False)
, (ndOvsName, PyValueEx defaultOvs)
, (ndOvsLink, PyValueEx "")
, (ndSshPort, PyValueEx (22 :: Int))
, (ndCpuSpeed, PyValueEx (1 :: Double))
]
ndcGlobals :: FrozenSet String
ndcGlobals = ConstantUtils.mkSet [ndExclusiveStorage]
defaultDelayTarget :: Int
defaultDelayTarget = 1
defaultDiskCustom :: String
defaultDiskCustom = ""
defaultDiskResync :: Bool
defaultDiskResync = False
defaultFillTarget :: Int
defaultFillTarget = 0
defaultMinRate :: Int
defaultMinRate = 4 * 1024
defaultNetCustom :: String
defaultNetCustom = ""
defaultPlanAhead :: Int
defaultPlanAhead = 20
defaultRbdPool :: String
defaultRbdPool = "rbd"
diskLdDefaults :: Map DiskTemplate (Map String PyValueEx)
diskLdDefaults =
Map.fromList
[ (DTBlock, Map.empty)
, (DTDrbd8, Map.fromList
[ (ldpBarriers, PyValueEx drbdBarriers)
, (ldpDefaultMetavg, PyValueEx defaultVg)
, (ldpDelayTarget, PyValueEx defaultDelayTarget)
, (ldpDiskCustom, PyValueEx defaultDiskCustom)
, (ldpDynamicResync, PyValueEx defaultDiskResync)
, (ldpFillTarget, PyValueEx defaultFillTarget)
, (ldpMaxRate, PyValueEx classicDrbdSyncSpeed)
, (ldpMinRate, PyValueEx defaultMinRate)
, (ldpNetCustom, PyValueEx defaultNetCustom)
, (ldpNoMetaFlush, PyValueEx drbdNoMetaFlush)
, (ldpPlanAhead, PyValueEx defaultPlanAhead)
, (ldpProtocol, PyValueEx drbdDefaultNetProtocol)
, (ldpResyncRate, PyValueEx classicDrbdSyncSpeed)
])
, (DTExt, Map.fromList
[ (ldpAccess, PyValueEx diskKernelspace)
])
, (DTFile, Map.empty)
, (DTPlain, Map.fromList [(ldpStripes, PyValueEx lvmStripecount)])
, (DTRbd, Map.fromList
[ (ldpPool, PyValueEx defaultRbdPool)
, (ldpAccess, PyValueEx diskKernelspace)
])
, (DTSharedFile, Map.empty)
, (DTGluster, Map.fromList
[ (rbdAccess, PyValueEx diskKernelspace)
, (glusterHost, PyValueEx glusterHostDefault)
, (glusterVolume, PyValueEx glusterVolumeDefault)
, (glusterPort, PyValueEx glusterPortDefault)
])
]
diskDtDefaults :: Map DiskTemplate (Map String PyValueEx)
diskDtDefaults =
Map.fromList
[ (DTBlock, Map.empty)
, (DTDiskless, Map.empty)
, (DTDrbd8, Map.fromList
[ (drbdDataStripes, PyValueEx lvmStripecount)
, (drbdDefaultMetavg, PyValueEx defaultVg)
, (drbdDelayTarget, PyValueEx defaultDelayTarget)
, (drbdDiskBarriers, PyValueEx drbdBarriers)
, (drbdDiskCustom, PyValueEx defaultDiskCustom)
, (drbdDynamicResync, PyValueEx defaultDiskResync)
, (drbdFillTarget, PyValueEx defaultFillTarget)
, (drbdMaxRate, PyValueEx classicDrbdSyncSpeed)
, (drbdMetaBarriers, PyValueEx drbdNoMetaFlush)
, (drbdMetaStripes, PyValueEx lvmStripecount)
, (drbdMinRate, PyValueEx defaultMinRate)
, (drbdNetCustom, PyValueEx defaultNetCustom)
, (drbdPlanAhead, PyValueEx defaultPlanAhead)
, (drbdProtocol, PyValueEx drbdDefaultNetProtocol)
, (drbdResyncRate, PyValueEx classicDrbdSyncSpeed)
])
, (DTExt, Map.fromList
[ (rbdAccess, PyValueEx diskKernelspace)
])
, (DTFile, Map.empty)
, (DTPlain, Map.fromList [(lvStripes, PyValueEx lvmStripecount)])
, (DTRbd, Map.fromList
[ (rbdPool, PyValueEx defaultRbdPool)
, (rbdAccess, PyValueEx diskKernelspace)
])
, (DTSharedFile, Map.empty)
, (DTGluster, Map.fromList
[ (rbdAccess, PyValueEx diskKernelspace)
, (glusterHost, PyValueEx glusterHostDefault)
, (glusterVolume, PyValueEx glusterVolumeDefault)
, (glusterPort, PyValueEx glusterPortDefault)
])
]
niccDefaults :: Map String PyValueEx
niccDefaults =
Map.fromList
[ (nicMode, PyValueEx nicModeBridged)
, (nicLink, PyValueEx defaultBridge)
, (nicVlan, PyValueEx "")
]
ispecsMinmaxDefaults :: Map String (Map String Int)
ispecsMinmaxDefaults =
Map.fromList
[(ispecsMin,
Map.fromList
[(ConstantUtils.ispecMemSize, Types.iSpecMemorySize Types.defMinISpec),
(ConstantUtils.ispecCpuCount, Types.iSpecCpuCount Types.defMinISpec),
(ConstantUtils.ispecDiskCount, Types.iSpecDiskCount Types.defMinISpec),
(ConstantUtils.ispecDiskSize, Types.iSpecDiskSize Types.defMinISpec),
(ConstantUtils.ispecNicCount, Types.iSpecNicCount Types.defMinISpec),
(ConstantUtils.ispecSpindleUse, Types.iSpecSpindleUse Types.defMinISpec)]),
(ispecsMax,
Map.fromList
[(ConstantUtils.ispecMemSize, Types.iSpecMemorySize Types.defMaxISpec),
(ConstantUtils.ispecCpuCount, Types.iSpecCpuCount Types.defMaxISpec),
(ConstantUtils.ispecDiskCount, Types.iSpecDiskCount Types.defMaxISpec),
(ConstantUtils.ispecDiskSize, Types.iSpecDiskSize Types.defMaxISpec),
(ConstantUtils.ispecNicCount, Types.iSpecNicCount Types.defMaxISpec),
(ConstantUtils.ispecSpindleUse, Types.iSpecSpindleUse Types.defMaxISpec)])]
ipolicyDefaults :: Map String PyValueEx
ipolicyDefaults =
Map.fromList
[ (ispecsMinmax, PyValueEx [ispecsMinmaxDefaults])
, (ispecsStd, PyValueEx (Map.fromList
[ (ispecMemSize, 128)
, (ispecCpuCount, 1)
, (ispecDiskCount, 1)
, (ispecDiskSize, 1024)
, (ispecNicCount, 1)
, (ispecSpindleUse, 1)
] :: Map String Int))
, (ipolicyDts, PyValueEx (ConstantUtils.toList diskTemplates))
, (ipolicyVcpuRatio, PyValueEx ConstantUtils.ipolicyDefaultsVcpuRatio)
, (ipolicySpindleRatio, PyValueEx ConstantUtils.ipolicyDefaultsSpindleRatio)
, (ipolicyMemoryRatio, PyValueEx ConstantUtils.ipolicyDefaultsMemoryRatio)
]
masterPoolSizeDefault :: Int
masterPoolSizeDefault = 10
partMargin :: Double
partMargin = 0.01
partReserved :: Double
partReserved = 0.02
luxidJobqueuePollInterval :: Int
luxidJobqueuePollInterval = 307
luxidMaximalRunningJobsDefault :: Int
luxidMaximalRunningJobsDefault = 20
luxidMaximalTrackedJobsDefault :: Int
luxidMaximalTrackedJobsDefault = 25
luxidRetryForkCount :: Int
luxidRetryForkCount = 5
luxidRetryForkStepUS :: Int
luxidRetryForkStepUS = 500000
luxidJobDeathDetectionRetries :: Int
luxidJobDeathDetectionRetries = 3
luxidJobDeathDelay :: Int
luxidJobDeathDelay = 100000
wconfdDeathdetectionIntervall :: Int
wconfdDeathdetectionIntervall = 311
wconfdDefCtmo :: Int
wconfdDefCtmo = 10
wconfdDefRwto :: Int
wconfdDefRwto = 60
wconfLivelockPrefix :: String
wconfLivelockPrefix = "wconf-daemon"
confdProtocolVersion :: Int
confdProtocolVersion = ConstantUtils.confdProtocolVersion
confdReqPing :: Int
confdReqPing = Types.confdRequestTypeToRaw ReqPing
confdReqNodeRoleByname :: Int
confdReqNodeRoleByname = Types.confdRequestTypeToRaw ReqNodeRoleByName
confdReqNodePipByInstanceIp :: Int
confdReqNodePipByInstanceIp = Types.confdRequestTypeToRaw ReqNodePipByInstPip
confdReqClusterMaster :: Int
confdReqClusterMaster = Types.confdRequestTypeToRaw ReqClusterMaster
confdReqNodePipList :: Int
confdReqNodePipList = Types.confdRequestTypeToRaw ReqNodePipList
confdReqMcPipList :: Int
confdReqMcPipList = Types.confdRequestTypeToRaw ReqMcPipList
confdReqInstancesIpsList :: Int
confdReqInstancesIpsList = Types.confdRequestTypeToRaw ReqInstIpsList
confdReqNodeDrbd :: Int
confdReqNodeDrbd = Types.confdRequestTypeToRaw ReqNodeDrbd
confdReqNodeInstances :: Int
confdReqNodeInstances = Types.confdRequestTypeToRaw ReqNodeInstances
confdReqInstanceDisks :: Int
confdReqInstanceDisks = Types.confdRequestTypeToRaw ReqInstanceDisks
confdReqConfigQuery :: Int
confdReqConfigQuery = Types.confdRequestTypeToRaw ReqConfigQuery
confdReqDataCollectors :: Int
confdReqDataCollectors = Types.confdRequestTypeToRaw ReqDataCollectors
confdReqs :: FrozenSet Int
confdReqs =
ConstantUtils.mkSet .
map Types.confdRequestTypeToRaw $
[minBound..] \\ [ReqNodeInstances]
confdReqfieldName :: Int
confdReqfieldName = Types.confdReqFieldToRaw ReqFieldName
confdReqfieldIp :: Int
confdReqfieldIp = Types.confdReqFieldToRaw ReqFieldIp
confdReqfieldMnodePip :: Int
confdReqfieldMnodePip = Types.confdReqFieldToRaw ReqFieldMNodePip
confdReplStatusOk :: Int
confdReplStatusOk = Types.confdReplyStatusToRaw ReplyStatusOk
confdReplStatusError :: Int
confdReplStatusError = Types.confdReplyStatusToRaw ReplyStatusError
confdReplStatusNotimplemented :: Int
confdReplStatusNotimplemented = Types.confdReplyStatusToRaw ReplyStatusNotImpl
confdReplStatuses :: FrozenSet Int
confdReplStatuses =
ConstantUtils.mkSet $ map Types.confdReplyStatusToRaw [minBound..]
confdNodeRoleMaster :: Int
confdNodeRoleMaster = Types.confdNodeRoleToRaw NodeRoleMaster
confdNodeRoleCandidate :: Int
confdNodeRoleCandidate = Types.confdNodeRoleToRaw NodeRoleCandidate
confdNodeRoleOffline :: Int
confdNodeRoleOffline = Types.confdNodeRoleToRaw NodeRoleOffline
confdNodeRoleDrained :: Int
confdNodeRoleDrained = Types.confdNodeRoleToRaw NodeRoleDrained
confdNodeRoleRegular :: Int
confdNodeRoleRegular = Types.confdNodeRoleToRaw NodeRoleRegular
confdErrorUnknownEntry :: Int
confdErrorUnknownEntry = Types.confdErrorTypeToRaw ConfdErrorUnknownEntry
confdErrorInternal :: Int
confdErrorInternal = Types.confdErrorTypeToRaw ConfdErrorInternal
confdErrorArgument :: Int
confdErrorArgument = Types.confdErrorTypeToRaw ConfdErrorArgument
confdReqqLink :: String
confdReqqLink = ConstantUtils.confdReqqLink
confdReqqIp :: String
confdReqqIp = ConstantUtils.confdReqqIp
confdReqqIplist :: String
confdReqqIplist = ConstantUtils.confdReqqIplist
confdReqqFields :: String
confdReqqFields = ConstantUtils.confdReqqFields
confdMaxClockSkew :: Int
confdMaxClockSkew = 2 * nodeMaxClockSkew
confdConfigReloadTimeout :: Int
confdConfigReloadTimeout = 17
confdConfigReloadRatelimit :: Int
confdConfigReloadRatelimit = 250000
confdMagicFourcc :: String
confdMagicFourcc = "plj0"
confdDefaultReqCoverage :: Int
confdDefaultReqCoverage = 6
confdClientExpireTimeout :: Int
confdClientExpireTimeout = 10
maxUdpDataSize :: Int
maxUdpDataSize = 61440
uidpoolUidMin :: Int
uidpoolUidMin = 0
uidpoolUidMax :: Integer
uidpoolUidMax = 2 ^ 32 1
pgrep :: String
pgrep = "pgrep"
initialNodeGroupName :: String
initialNodeGroupName = "default"
allocPolicyLastResort :: String
allocPolicyLastResort = Types.allocPolicyToRaw AllocLastResort
allocPolicyPreferred :: String
allocPolicyPreferred = Types.allocPolicyToRaw AllocPreferred
allocPolicyUnallocable :: String
allocPolicyUnallocable = Types.allocPolicyToRaw AllocUnallocable
validAllocPolicies :: [String]
validAllocPolicies = map Types.allocPolicyToRaw [minBound..]
blockdevDriverManual :: String
blockdevDriverManual = Types.blockDriverToRaw BlockDrvManual
qemuimgPath :: String
qemuimgPath = AutoConf.qemuimgPath
iallocHail :: String
iallocHail = "hail"
fakeOpMasterTurndown :: String
fakeOpMasterTurndown = "OP_CLUSTER_IP_TURNDOWN"
fakeOpMasterTurnup :: String
fakeOpMasterTurnup = "OP_CLUSTER_IP_TURNUP"
cryptoTypeSslDigest :: String
cryptoTypeSslDigest = "ssl"
cryptoTypeSsh :: String
cryptoTypeSsh = "ssh"
cryptoTypes :: FrozenSet String
cryptoTypes = ConstantUtils.mkSet [cryptoTypeSslDigest]
cryptoActionGet :: String
cryptoActionGet = "get"
cryptoActionCreate :: String
cryptoActionCreate = "create"
cryptoActionDelete :: String
cryptoActionDelete = "delete"
cryptoActions :: FrozenSet String
cryptoActions =
ConstantUtils.mkSet [ cryptoActionCreate
, cryptoActionGet
, cryptoActionDelete]
cryptoBootstrap :: String
cryptoBootstrap = "bootstrap"
cryptoOptionCertFile :: String
cryptoOptionCertFile = "cert_file"
cryptoOptionSerialNo :: String
cryptoOptionSerialNo = "serial_no"
sshkDsa :: String
sshkDsa = Types.sshKeyTypeToRaw DSA
sshkEcdsa :: String
sshkEcdsa = Types.sshKeyTypeToRaw ECDSA
sshkRsa :: String
sshkRsa = Types.sshKeyTypeToRaw RSA
sshkAll :: FrozenSet String
sshkAll = ConstantUtils.mkSet [sshkRsa, sshkDsa, sshkEcdsa]
sshakDss :: String
sshakDss = "ssh-dss"
sshakRsa :: String
sshakRsa = "ssh-rsa"
sshakAll :: FrozenSet String
sshakAll = ConstantUtils.mkSet [sshakDss, sshakRsa]
sshDefaultKeyType :: String
sshDefaultKeyType = sshkRsa
sshDefaultKeyBits :: Int
sshDefaultKeyBits = 2048
sshsClusterName :: String
sshsClusterName = "cluster_name"
sshsSshHostKey :: String
sshsSshHostKey = "ssh_host_key"
sshsSshRootKey :: String
sshsSshRootKey = "ssh_root_key"
sshsSshAuthorizedKeys :: String
sshsSshAuthorizedKeys = "authorized_keys"
sshsSshPublicKeys :: String
sshsSshPublicKeys = "public_keys"
sshsNodeDaemonCertificate :: String
sshsNodeDaemonCertificate = "node_daemon_certificate"
sshsSshKeyType :: String
sshsSshKeyType = "ssh_key_type"
sshsSshKeyBits :: String
sshsSshKeyBits = "ssh_key_bits"
sshsMaxRetries :: Integer
sshsMaxRetries = 3
sshsAdd :: String
sshsAdd = "add"
sshsReplaceOrAdd :: String
sshsReplaceOrAdd = "replace_or_add"
sshsRemove :: String
sshsRemove = "remove"
sshsOverride :: String
sshsOverride = "override"
sshsClear :: String
sshsClear = "clear"
sshsGenerate :: String
sshsGenerate = "generate"
sshsSuffix :: String
sshsSuffix = "suffix"
sshsMasterSuffix :: String
sshsMasterSuffix = "_master_tmp"
sshsActions :: FrozenSet String
sshsActions = ConstantUtils.mkSet [ sshsAdd
, sshsRemove
, sshsOverride
, sshsClear
, sshsReplaceOrAdd]
sshHostDsaPriv :: String
sshHostDsaPriv = sshConfigDir ++ "/ssh_host_dsa_key"
sshHostDsaPub :: String
sshHostDsaPub = sshHostDsaPriv ++ ".pub"
sshHostEcdsaPriv :: String
sshHostEcdsaPriv = sshConfigDir ++ "/ssh_host_ecdsa_key"
sshHostEcdsaPub :: String
sshHostEcdsaPub = sshHostEcdsaPriv ++ ".pub"
sshHostRsaPriv :: String
sshHostRsaPriv = sshConfigDir ++ "/ssh_host_rsa_key"
sshHostRsaPub :: String
sshHostRsaPub = sshHostRsaPriv ++ ".pub"
sshDaemonKeyfiles :: Map String (String, String)
sshDaemonKeyfiles =
Map.fromList [ (sshkRsa, (sshHostRsaPriv, sshHostRsaPub))
, (sshkDsa, (sshHostDsaPriv, sshHostDsaPub))
, (sshkEcdsa, (sshHostEcdsaPriv, sshHostEcdsaPub))
]
ndsClusterName :: String
ndsClusterName = "cluster_name"
ndsNodeDaemonCertificate :: String
ndsNodeDaemonCertificate = "node_daemon_certificate"
ndsSsconf :: String
ndsSsconf = "ssconf"
ndsHmac :: String
ndsHmac = "hmac_key"
ndsStartNodeDaemon :: String
ndsStartNodeDaemon = "start_node_daemon"
ndsNodeName :: String
ndsNodeName = "node_name"
ndsAction :: String
ndsAction = "action"
vClusterEtcHosts :: String
vClusterEtcHosts = "/etc/hosts"
vClusterVirtPathPrefix :: String
vClusterVirtPathPrefix = "/###-VIRTUAL-PATH-###,"
vClusterRootdirEnvname :: String
vClusterRootdirEnvname = "GANETI_ROOTDIR"
vClusterHostnameEnvname :: String
vClusterHostnameEnvname = "GANETI_HOSTNAME"
vClusterVpathWhitelist :: FrozenSet String
vClusterVpathWhitelist = ConstantUtils.mkSet [ vClusterEtcHosts ]
opcodeReasonSrcClient :: String
opcodeReasonSrcClient = "gnt:client"
_opcodeReasonSrcDaemon :: String
_opcodeReasonSrcDaemon = "gnt:daemon"
_opcodeReasonSrcMasterd :: String
_opcodeReasonSrcMasterd = _opcodeReasonSrcDaemon ++ ":masterd"
opcodeReasonSrcNoded :: String
opcodeReasonSrcNoded = _opcodeReasonSrcDaemon ++ ":noded"
opcodeReasonSrcMaintd :: String
opcodeReasonSrcMaintd = _opcodeReasonSrcDaemon ++ ":maintd"
opcodeReasonSrcOpcode :: String
opcodeReasonSrcOpcode = "gnt:opcode"
opcodeReasonSrcPickup :: String
opcodeReasonSrcPickup = _opcodeReasonSrcMasterd ++ ":pickup"
opcodeReasonSrcWatcher :: String
opcodeReasonSrcWatcher = "gnt:watcher"
opcodeReasonSrcRlib2 :: String
opcodeReasonSrcRlib2 = "gnt:library:rlib2"
opcodeReasonSrcUser :: String
opcodeReasonSrcUser = "gnt:user"
opcodeReasonSources :: FrozenSet String
opcodeReasonSources =
ConstantUtils.mkSet [opcodeReasonSrcClient,
opcodeReasonSrcNoded,
opcodeReasonSrcOpcode,
opcodeReasonSrcPickup,
opcodeReasonSrcWatcher,
opcodeReasonSrcRlib2,
opcodeReasonSrcUser]
randomUuidFile :: String
randomUuidFile = ConstantUtils.randomUuidFile
autoRepairFailover :: String
autoRepairFailover = Types.autoRepairTypeToRaw ArFailover
autoRepairFixStorage :: String
autoRepairFixStorage = Types.autoRepairTypeToRaw ArFixStorage
autoRepairMigrate :: String
autoRepairMigrate = Types.autoRepairTypeToRaw ArMigrate
autoRepairReinstall :: String
autoRepairReinstall = Types.autoRepairTypeToRaw ArReinstall
autoRepairAllTypes :: FrozenSet String
autoRepairAllTypes =
ConstantUtils.mkSet [autoRepairFailover,
autoRepairFixStorage,
autoRepairMigrate,
autoRepairReinstall]
autoRepairEnoperm :: String
autoRepairEnoperm = Types.autoRepairResultToRaw ArEnoperm
autoRepairFailure :: String
autoRepairFailure = Types.autoRepairResultToRaw ArFailure
autoRepairSuccess :: String
autoRepairSuccess = Types.autoRepairResultToRaw ArSuccess
autoRepairAllResults :: FrozenSet String
autoRepairAllResults =
ConstantUtils.mkSet [autoRepairEnoperm, autoRepairFailure, autoRepairSuccess]
builtinDataCollectorVersion :: String
builtinDataCollectorVersion = "B"
opcodeReason :: String
opcodeReason = "reason"
opcodeSequential :: String
opcodeSequential = "sequential"
diskstatsFile :: String
diskstatsFile = "/proc/diskstats"
statFile :: String
statFile = "/proc/stat"
cpuavgloadBufferSize :: Int
cpuavgloadBufferSize = 150
cpuavgloadWindowSize :: Int
cpuavgloadWindowSize = 600
xentopCommand :: String
xentopCommand = "xentop"
xentopAverageThreshold :: Int
xentopAverageThreshold = 100
mondTimeInterval :: Int
mondTimeInterval = 5
mondConfigTimeInterval :: Int
mondConfigTimeInterval = 15
mondLatestApiVersion :: Int
mondLatestApiVersion = 1
mondDefaultCategory :: String
mondDefaultCategory = "default"
maintdDefaultRoundDelay :: Int
maintdDefaultRoundDelay = 300
diskUserspace :: String
diskUserspace = Types.diskAccessModeToRaw DiskUserspace
diskKernelspace :: String
diskKernelspace = Types.diskAccessModeToRaw DiskKernelspace
diskValidAccessModes :: FrozenSet String
diskValidAccessModes =
ConstantUtils.mkSet $ map Types.diskAccessModeToRaw [minBound..]
upgradeQueueDrainTimeout :: Int
upgradeQueueDrainTimeout = 36 * 60 * 60
upgradeQueuePollInterval :: Int
upgradeQueuePollInterval = 10
hotplugActionAdd :: String
hotplugActionAdd = Types.hotplugActionToRaw HAAdd
hotplugActionRemove :: String
hotplugActionRemove = Types.hotplugActionToRaw HARemove
hotplugActionModify :: String
hotplugActionModify = Types.hotplugActionToRaw HAMod
hotplugAllActions :: FrozenSet String
hotplugAllActions =
ConstantUtils.mkSet $ map Types.hotplugActionToRaw [minBound..]
hotplugTargetNic :: String
hotplugTargetNic = Types.hotplugTargetToRaw HTNic
hotplugTargetDisk :: String
hotplugTargetDisk = Types.hotplugTargetToRaw HTDisk
hotplugAllTargets :: FrozenSet String
hotplugAllTargets =
ConstantUtils.mkSet $ map Types.hotplugTargetToRaw [minBound..]
diskRemoveRetryTimeout :: Int
diskRemoveRetryTimeout = 30
diskRemoveRetryInterval :: Int
diskRemoveRetryInterval = 3
uuidRegex :: String
uuidRegex = "^[a-f0-9]{8}-[a-f0-9]{4}-[a-f0-9]{4}-[a-f0-9]{4}-[a-f0-9]{12}$"
luxiSocketPerms :: Int
luxiSocketPerms = 0o660
luxiKeyMethod :: String
luxiKeyMethod = "method"
luxiKeyArgs :: String
luxiKeyArgs = "args"
luxiKeySuccess :: String
luxiKeySuccess = "success"
luxiKeyResult :: String
luxiKeyResult = "result"
luxiKeyVersion :: String
luxiKeyVersion = "version"
luxiReqSubmitJob :: String
luxiReqSubmitJob = "SubmitJob"
luxiReqSubmitJobToDrainedQueue :: String
luxiReqSubmitJobToDrainedQueue = "SubmitJobToDrainedQueue"
luxiReqSubmitManyJobs :: String
luxiReqSubmitManyJobs = "SubmitManyJobs"
luxiReqWaitForJobChange :: String
luxiReqWaitForJobChange = "WaitForJobChange"
luxiReqPickupJob :: String
luxiReqPickupJob = "PickupJob"
luxiReqCancelJob :: String
luxiReqCancelJob = "CancelJob"
luxiReqArchiveJob :: String
luxiReqArchiveJob = "ArchiveJob"
luxiReqChangeJobPriority :: String
luxiReqChangeJobPriority = "ChangeJobPriority"
luxiReqAutoArchiveJobs :: String
luxiReqAutoArchiveJobs = "AutoArchiveJobs"
luxiReqQuery :: String
luxiReqQuery = "Query"
luxiReqQueryFields :: String
luxiReqQueryFields = "QueryFields"
luxiReqQueryJobs :: String
luxiReqQueryJobs = "QueryJobs"
luxiReqQueryFilters :: String
luxiReqQueryFilters = "QueryFilters"
luxiReqReplaceFilter :: String
luxiReqReplaceFilter = "ReplaceFilter"
luxiReqDeleteFilter :: String
luxiReqDeleteFilter = "DeleteFilter"
luxiReqQueryInstances :: String
luxiReqQueryInstances = "QueryInstances"
luxiReqQueryNodes :: String
luxiReqQueryNodes = "QueryNodes"
luxiReqQueryGroups :: String
luxiReqQueryGroups = "QueryGroups"
luxiReqQueryNetworks :: String
luxiReqQueryNetworks = "QueryNetworks"
luxiReqQueryExports :: String
luxiReqQueryExports = "QueryExports"
luxiReqQueryConfigValues :: String
luxiReqQueryConfigValues = "QueryConfigValues"
luxiReqQueryClusterInfo :: String
luxiReqQueryClusterInfo = "QueryClusterInfo"
luxiReqQueryTags :: String
luxiReqQueryTags = "QueryTags"
luxiReqSetDrainFlag :: String
luxiReqSetDrainFlag = "SetDrainFlag"
luxiReqSetWatcherPause :: String
luxiReqSetWatcherPause = "SetWatcherPause"
luxiReqAll :: FrozenSet String
luxiReqAll =
ConstantUtils.mkSet
[ luxiReqArchiveJob
, luxiReqAutoArchiveJobs
, luxiReqCancelJob
, luxiReqChangeJobPriority
, luxiReqQuery
, luxiReqQueryClusterInfo
, luxiReqQueryConfigValues
, luxiReqQueryExports
, luxiReqQueryFields
, luxiReqQueryGroups
, luxiReqQueryInstances
, luxiReqQueryJobs
, luxiReqQueryNodes
, luxiReqQueryNetworks
, luxiReqQueryTags
, luxiReqSetDrainFlag
, luxiReqSetWatcherPause
, luxiReqSubmitJob
, luxiReqSubmitJobToDrainedQueue
, luxiReqSubmitManyJobs
, luxiReqWaitForJobChange
, luxiReqPickupJob
, luxiReqQueryFilters
, luxiReqReplaceFilter
, luxiReqDeleteFilter
]
luxiDefCtmo :: Int
luxiDefCtmo = 30
luxiDefRwto :: Int
luxiDefRwto = 180
luxiWfjcTimeout :: Int
luxiWfjcTimeout = (luxiDefRwto 1) `div` 2
luxiLivelockPrefix :: String
luxiLivelockPrefix = "luxi-daemon"
luxiCancelJobTimeout :: Int
luxiCancelJobTimeout = (luxiDefRwto 1) `div` 4
masterVotingRetries :: Int
masterVotingRetries = 6
masterVotingRetryIntervall :: Int
masterVotingRetryIntervall = 10
qlangOpAnd :: String
qlangOpAnd = "&"
qlangOpOr :: String
qlangOpOr = "|"
qlangOpNot :: String
qlangOpNot = "!"
qlangOpTrue :: String
qlangOpTrue = "?"
qlangOpContains :: String
qlangOpContains = "=[]"
qlangOpEqual :: String
qlangOpEqual = "=="
qlangOpEqualLegacy :: String
qlangOpEqualLegacy = "="
qlangOpGe :: String
qlangOpGe = ">="
qlangOpGt :: String
qlangOpGt = ">"
qlangOpLe :: String
qlangOpLe = "<="
qlangOpLt :: String
qlangOpLt = "<"
qlangOpNotEqual :: String
qlangOpNotEqual = "!="
qlangOpRegexp :: String
qlangOpRegexp = "=~"
qlangFilterDetectionChars :: FrozenSet String
qlangFilterDetectionChars =
ConstantUtils.mkSet ["!", " ", "\"", "\'",
")", "(", "\x0b", "\n",
"\r", "\x0c", "/", "<",
"\t", ">", "=", "\\", "~"]
qlangGlobDetectionChars :: FrozenSet String
qlangGlobDetectionChars = ConstantUtils.mkSet ["*", "?"]
errorsEcodeEnviron :: String
errorsEcodeEnviron = "environment_error"
errorsEcodeExists :: String
errorsEcodeExists = "already_exists"
errorsEcodeFault :: String
errorsEcodeFault = "internal_error"
errorsEcodeInval :: String
errorsEcodeInval = "wrong_input"
errorsEcodeNoent :: String
errorsEcodeNoent = "unknown_entity"
errorsEcodeNores :: String
errorsEcodeNores = "insufficient_resources"
errorsEcodeNotunique :: String
errorsEcodeNotunique = "resource_not_unique"
errorsEcodeResolver :: String
errorsEcodeResolver = "resolver_error"
errorsEcodeState :: String
errorsEcodeState = "wrong_state"
errorsEcodeTempNores :: String
errorsEcodeTempNores = "temp_insufficient_resources"
errorsEcodeAll :: FrozenSet String
errorsEcodeAll =
ConstantUtils.mkSet [ errorsEcodeNores
, errorsEcodeExists
, errorsEcodeState
, errorsEcodeNotunique
, errorsEcodeTempNores
, errorsEcodeNoent
, errorsEcodeFault
, errorsEcodeResolver
, errorsEcodeInval
, errorsEcodeEnviron
]
jstoreJobsPerArchiveDirectory :: Int
jstoreJobsPerArchiveDirectory = 10000
glusterHost :: String
glusterHost = "host"
glusterHostDefault :: String
glusterHostDefault = "127.0.0.1"
glusterVolume :: String
glusterVolume = "volume"
glusterVolumeDefault :: String
glusterVolumeDefault = "gv0"
glusterPort :: String
glusterPort = "port"
glusterPortDefault :: Int
glusterPortDefault = 24007
instanceCommunicationDoc :: String
instanceCommunicationDoc =
"Enable or disable the communication mechanism for an instance"
instanceCommunicationMacPrefix :: String
instanceCommunicationMacPrefix = "52:54:00"
instanceCommunicationNetwork4 :: String
instanceCommunicationNetwork4 = "169.254.0.0/16"
instanceCommunicationNetwork6 :: String
instanceCommunicationNetwork6 = "fe80::/10"
instanceCommunicationNetworkLink :: String
instanceCommunicationNetworkLink = "communication_rt"
instanceCommunicationNetworkMode :: String
instanceCommunicationNetworkMode = nicModeRouted
instanceCommunicationNicPrefix :: String
instanceCommunicationNicPrefix = "ganeti:communication:"
privateParametersBlacklist :: [String]
privateParametersBlacklist = [ "osparams_private"
, "osparams_secret"
, "osparams_private_cluster"
]
debugModeConfidentialityWarning :: String
debugModeConfidentialityWarning =
"ALERT: %s started in debug mode.\n\
\ Private and secret parameters WILL be logged!\n"
redacted :: String
redacted = Types.redacted
statSize :: String
statSize = "size"
helperVmStartup :: Int
helperVmStartup = 5 * 60
helperVmShutdown :: Int
helperVmShutdown = 2 * 60 * 60
zeroingTimeoutPerMib :: Double
zeroingTimeoutPerMib = 1.0 / (100.0 / 5.0)
ipv4NetworkMinSize :: Int
ipv4NetworkMinSize = 30
ipv4NetworkMaxSize :: Int
ipv4NetworkMaxSize = 30
dataCollectorCPULoad :: String
dataCollectorCPULoad = "cpu-avg-load"
dataCollectorXenCpuLoad :: String
dataCollectorXenCpuLoad = "xen-cpu-avg-load"
dataCollectorDiskStats :: String
dataCollectorDiskStats = "diskstats"
dataCollectorDrbd :: String
dataCollectorDrbd = "drbd"
dataCollectorLv :: String
dataCollectorLv = "lv"
dataCollectorKvmRSS :: String
dataCollectorKvmRSS = "kvm-inst-rss"
dataCollectorInstStatus :: String
dataCollectorInstStatus = "inst-status-xen"
dataCollectorDiagnose :: String
dataCollectorDiagnose = "diagnose"
dataCollectorParameterInterval :: String
dataCollectorParameterInterval = "interval"
dataCollectorNames :: FrozenSet String
dataCollectorNames =
ConstantUtils.mkSet [ dataCollectorCPULoad
, dataCollectorDiskStats
, dataCollectorDrbd
, dataCollectorLv
, dataCollectorInstStatus
, dataCollectorXenCpuLoad
, dataCollectorKvmRSS
, dataCollectorDiagnose
]
dataCollectorStateActive :: String
dataCollectorStateActive = "active"
dataCollectorsEnabledName :: String
dataCollectorsEnabledName = "enabled_data_collectors"
dataCollectorsIntervalName :: String
dataCollectorsIntervalName = "data_collector_interval"
dataCollectorDiagnoseDirectory :: String
dataCollectorDiagnoseDirectory = sysconfdir ++ "/ganeti/node-diagnose-commands"
exTagsPrefix :: String
exTagsPrefix = Tags.exTagsPrefix
maintdPrefix :: String
maintdPrefix = "maintd:"
maintdSuccessTagPrefix :: String
maintdSuccessTagPrefix = maintdPrefix ++ "repairready:"
maintdFailureTagPrefix :: String
maintdFailureTagPrefix = maintdPrefix ++ "repairfailed:"