Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Constants.hs @ a15072d7

History | View | Annotate | Download (123.4 kB)

1
{-# OPTIONS -fno-warn-type-defaults #-}
2
{-| Constants contains the Haskell constants
3

    
4
The constants in this module are used in Haskell and are also
5
converted to Python.
6

    
7
Do not write any definitions in this file other than constants.  Do
8
not even write helper functions.  The definitions in this module are
9
automatically stripped to build the Makefile.am target
10
'ListConstants.hs'.  If there are helper functions in this module,
11
they will also be dragged and it will cause compilation to fail.
12
Therefore, all helper functions should go to a separate module and
13
imported.
14

    
15
-}
16

    
17
{-
18

    
19
Copyright (C) 2013, 2014 Google Inc.
20

    
21
This program is free software; you can redistribute it and/or modify
22
it under the terms of the GNU General Public License as published by
23
the Free Software Foundation; either version 2 of the License, or
24
(at your option) any later version.
25

    
26
This program is distributed in the hope that it will be useful, but
27
WITHOUT ANY WARRANTY; without even the implied warranty of
28
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
29
General Public License for more details.
30

    
31
You should have received a copy of the GNU General Public License
32
along with this program; if not, write to the Free Software
33
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
34
02110-1301, USA.
35

    
36
-}
37
module Ganeti.Constants where
38

    
39
import Control.Arrow ((***))
40
import Data.List ((\\))
41
import Data.Map (Map)
42
import qualified Data.Map as Map (empty, fromList, keys, insert)
43

    
44
import qualified AutoConf
45
import Ganeti.ConstantUtils (PythonChar(..), FrozenSet, Protocol(..),
46
                             buildVersion)
47
import qualified Ganeti.ConstantUtils as ConstantUtils
48
import Ganeti.HTools.Types (AutoRepairResult(..), AutoRepairType(..))
49
import qualified Ganeti.HTools.Types as Types
50
import Ganeti.Logging (SyslogUsage(..))
51
import qualified Ganeti.Logging as Logging (syslogUsageToRaw)
52
import qualified Ganeti.Runtime as Runtime
53
import Ganeti.Runtime (GanetiDaemon(..), MiscGroup(..), GanetiGroup(..),
54
                       ExtraLogReason(..))
55
import Ganeti.THH (PyValueEx(..))
56
import Ganeti.Types
57
import qualified Ganeti.Types as Types
58
import Ganeti.Confd.Types (ConfdRequestType(..), ConfdReqField(..),
59
                           ConfdReplyStatus(..), ConfdNodeRole(..),
60
                           ConfdErrorType(..))
61
import qualified Ganeti.Confd.Types as Types
62

    
63
{-# ANN module "HLint: ignore Use camelCase" #-}
64

    
65
-- * 'autoconf' constants for Python only ('autotools/build-bash-completion')
66

    
67
htoolsProgs :: [String]
68
htoolsProgs = AutoConf.htoolsProgs
69

    
70
-- * 'autoconf' constants for Python only ('lib/constants.py')
71

    
72
drbdBarriers :: String
73
drbdBarriers = AutoConf.drbdBarriers
74

    
75
drbdNoMetaFlush :: Bool
76
drbdNoMetaFlush = AutoConf.drbdNoMetaFlush
77

    
78
lvmStripecount :: Int
79
lvmStripecount = AutoConf.lvmStripecount
80

    
81
hasGnuLn :: Bool
82
hasGnuLn = AutoConf.hasGnuLn
83

    
84
-- * 'autoconf' constants for Python only ('lib/pathutils.py')
85

    
86
-- ** Build-time constants
87

    
88
exportDir :: String
89
exportDir = AutoConf.exportDir
90

    
91
osSearchPath :: [String]
92
osSearchPath = AutoConf.osSearchPath
93

    
94
esSearchPath :: [String]
95
esSearchPath = AutoConf.esSearchPath
96

    
97
sshConfigDir :: String
98
sshConfigDir = AutoConf.sshConfigDir
99

    
100
xenConfigDir :: String
101
xenConfigDir = AutoConf.xenConfigDir
102

    
103
sysconfdir :: String
104
sysconfdir = AutoConf.sysconfdir
105

    
106
toolsdir :: String
107
toolsdir = AutoConf.toolsdir
108

    
109
localstatedir :: String
110
localstatedir = AutoConf.localstatedir
111

    
112
-- ** Paths which don't change for a virtual cluster
113

    
114
pkglibdir :: String
115
pkglibdir = AutoConf.pkglibdir
116

    
117
sharedir :: String
118
sharedir = AutoConf.sharedir
119

    
120
-- * 'autoconf' constants for Python only ('lib/build/sphinx_ext.py')
121

    
122
manPages :: Map String Int
123
manPages = Map.fromList AutoConf.manPages
124

    
125
-- * 'autoconf' constants for QA cluster only ('qa/qa_cluster.py')
126

    
127
versionedsharedir :: String
128
versionedsharedir = AutoConf.versionedsharedir
129

    
130
-- * 'autoconf' constants for Python only ('tests/py/docs_unittest.py')
131

    
132
gntScripts :: [String]
133
gntScripts = AutoConf.gntScripts
134

    
135
-- * Various versions
136

    
137
releaseVersion :: String
138
releaseVersion = AutoConf.packageVersion
139

    
140
versionMajor :: Int
141
versionMajor = AutoConf.versionMajor
142

    
143
versionMinor :: Int
144
versionMinor = AutoConf.versionMinor
145

    
146
versionRevision :: Int
147
versionRevision = AutoConf.versionRevision
148

    
149
dirVersion :: String
150
dirVersion = AutoConf.dirVersion
151

    
152
osApiV10 :: Int
153
osApiV10 = 10
154

    
155
osApiV15 :: Int
156
osApiV15 = 15
157

    
158
osApiV20 :: Int
159
osApiV20 = 20
160

    
161
osApiVersions :: FrozenSet Int
162
osApiVersions = ConstantUtils.mkSet [osApiV10, osApiV15, osApiV20]
163

    
164
exportVersion :: Int
165
exportVersion = 0
166

    
167
rapiVersion :: Int
168
rapiVersion = 2
169

    
170
configMajor :: Int
171
configMajor = AutoConf.versionMajor
172

    
173
configMinor :: Int
174
configMinor = AutoConf.versionMinor
175

    
176
-- | The configuration is supposed to remain stable across
177
-- revisions. Therefore, the revision number is cleared to '0'.
178
configRevision :: Int
179
configRevision = 0
180

    
181
configVersion :: Int
182
configVersion = buildVersion configMajor configMinor configRevision
183

    
184
-- | Similarly to the configuration (see 'configRevision'), the
185
-- protocols are supposed to remain stable across revisions.
186
protocolVersion :: Int
187
protocolVersion = buildVersion configMajor configMinor configRevision
188

    
189
-- * User separation
190

    
191
daemonsGroup :: String
192
daemonsGroup = Runtime.daemonGroup (ExtraGroup DaemonsGroup)
193

    
194
adminGroup :: String
195
adminGroup = Runtime.daemonGroup (ExtraGroup AdminGroup)
196

    
197
masterdUser :: String
198
masterdUser = Runtime.daemonUser GanetiMasterd
199

    
200
masterdGroup :: String
201
masterdGroup = Runtime.daemonGroup (DaemonGroup GanetiMasterd)
202

    
203
metadUser :: String
204
metadUser = Runtime.daemonUser GanetiMetad
205

    
206
metadGroup :: String
207
metadGroup = Runtime.daemonGroup (DaemonGroup GanetiMetad)
208

    
209
rapiUser :: String
210
rapiUser = Runtime.daemonUser GanetiRapi
211

    
212
rapiGroup :: String
213
rapiGroup = Runtime.daemonGroup (DaemonGroup GanetiRapi)
214

    
215
confdUser :: String
216
confdUser = Runtime.daemonUser GanetiConfd
217

    
218
confdGroup :: String
219
confdGroup = Runtime.daemonGroup (DaemonGroup GanetiConfd)
220

    
221
wconfdUser :: String
222
wconfdUser = Runtime.daemonUser GanetiWConfd
223

    
224
wconfdGroup :: String
225
wconfdGroup = Runtime.daemonGroup (DaemonGroup GanetiWConfd)
226

    
227
kvmdUser :: String
228
kvmdUser = Runtime.daemonUser GanetiKvmd
229

    
230
kvmdGroup :: String
231
kvmdGroup = Runtime.daemonGroup (DaemonGroup GanetiKvmd)
232

    
233
luxidUser :: String
234
luxidUser = Runtime.daemonUser GanetiLuxid
235

    
236
luxidGroup :: String
237
luxidGroup = Runtime.daemonGroup (DaemonGroup GanetiLuxid)
238

    
239
nodedUser :: String
240
nodedUser = Runtime.daemonUser GanetiNoded
241

    
242
nodedGroup :: String
243
nodedGroup = Runtime.daemonGroup (DaemonGroup GanetiNoded)
244

    
245
mondUser :: String
246
mondUser = Runtime.daemonUser GanetiMond
247

    
248
mondGroup :: String
249
mondGroup = Runtime.daemonGroup (DaemonGroup GanetiMond)
250

    
251
sshLoginUser :: String
252
sshLoginUser = AutoConf.sshLoginUser
253

    
254
sshConsoleUser :: String
255
sshConsoleUser = AutoConf.sshConsoleUser
256

    
257
-- * Cpu pinning separators and constants
258

    
259
cpuPinningSep :: String
260
cpuPinningSep = ":"
261

    
262
cpuPinningAll :: String
263
cpuPinningAll = "all"
264

    
265
-- | Internal representation of "all"
266
cpuPinningAllVal :: Int
267
cpuPinningAllVal = -1
268

    
269
-- | One "all" entry in a CPU list means CPU pinning is off
270
cpuPinningOff :: [Int]
271
cpuPinningOff = [cpuPinningAllVal]
272

    
273
-- | A Xen-specific implementation detail is that there is no way to
274
-- actually say "use any cpu for pinning" in a Xen configuration file,
275
-- as opposed to the command line, where you can say
276
-- @
277
-- xm vcpu-pin <domain> <vcpu> all
278
-- @
279
--
280
-- The workaround used in Xen is "0-63" (see source code function
281
-- "xm_vcpu_pin" in @<xen-source>/tools/python/xen/xm/main.py@).
282
--
283
-- To support future changes, the following constant is treated as a
284
-- blackbox string that simply means "use any cpu for pinning under
285
-- xen".
286
cpuPinningAllXen :: String
287
cpuPinningAllXen = "0-63"
288

    
289
-- | A KVM-specific implementation detail - the following value is
290
-- used to set CPU affinity to all processors (--0 through --31), per
291
-- taskset man page.
292
--
293
-- FIXME: This only works for machines with up to 32 CPU cores
294
cpuPinningAllKvm :: Int
295
cpuPinningAllKvm = 0xFFFFFFFF
296

    
297
-- * Wipe
298

    
299
ddCmd :: String
300
ddCmd = "dd"
301

    
302
-- | 1GB
303
maxWipeChunk :: Int
304
maxWipeChunk = 1024
305

    
306
minWipeChunkPercent :: Int
307
minWipeChunkPercent = 10
308

    
309
-- * Directories
310

    
311
runDirsMode :: Int
312
runDirsMode = 0o775
313

    
314
secureDirMode :: Int
315
secureDirMode = 0o700
316

    
317
secureFileMode :: Int
318
secureFileMode = 0o600
319

    
320
adoptableBlockdevRoot :: String
321
adoptableBlockdevRoot = "/dev/disk/"
322

    
323
-- * 'autoconf' enable/disable
324

    
325
enableConfd :: Bool
326
enableConfd = AutoConf.enableConfd
327

    
328
enableMond :: Bool
329
enableMond = AutoConf.enableMond
330

    
331
enableRestrictedCommands :: Bool
332
enableRestrictedCommands = AutoConf.enableRestrictedCommands
333

    
334
-- * SSH constants
335

    
336
ssh :: String
337
ssh = "ssh"
338

    
339
scp :: String
340
scp = "scp"
341

    
342
-- * Daemons
343

    
344
confd :: String
345
confd = Runtime.daemonName GanetiConfd
346

    
347
masterd :: String
348
masterd = Runtime.daemonName GanetiMasterd
349

    
350
metad :: String
351
metad = Runtime.daemonName GanetiMetad
352

    
353
mond :: String
354
mond = Runtime.daemonName GanetiMond
355

    
356
noded :: String
357
noded = Runtime.daemonName GanetiNoded
358

    
359
wconfd :: String
360
wconfd = Runtime.daemonName GanetiWConfd
361

    
362
luxid :: String
363
luxid = Runtime.daemonName GanetiLuxid
364

    
365
rapi :: String
366
rapi = Runtime.daemonName GanetiRapi
367

    
368
kvmd :: String
369
kvmd = Runtime.daemonName GanetiKvmd
370

    
371
daemons :: FrozenSet String
372
daemons =
373
  ConstantUtils.mkSet [confd,
374
                       luxid,
375
                       masterd,
376
                       mond,
377
                       noded,
378
                       rapi]
379

    
380
defaultConfdPort :: Int
381
defaultConfdPort = 1814
382

    
383
defaultMondPort :: Int
384
defaultMondPort = 1815
385

    
386
defaultMetadPort :: Int
387
defaultMetadPort = 8080
388

    
389
defaultNodedPort :: Int
390
defaultNodedPort = 1811
391

    
392
defaultRapiPort :: Int
393
defaultRapiPort = 5080
394

    
395
daemonsPorts :: Map String (Protocol, Int)
396
daemonsPorts =
397
  Map.fromList
398
  [ (confd, (Udp, defaultConfdPort))
399
  , (metad, (Tcp, defaultMetadPort))
400
  , (mond, (Tcp, defaultMondPort))
401
  , (noded, (Tcp, defaultNodedPort))
402
  , (rapi, (Tcp, defaultRapiPort))
403
  , (ssh, (Tcp, 22))
404
  ]
405

    
406
firstDrbdPort :: Int
407
firstDrbdPort = 11000
408

    
409
lastDrbdPort :: Int
410
lastDrbdPort = 14999
411

    
412
daemonsLogbase :: Map String String
413
daemonsLogbase =
414
  Map.fromList
415
  [ (Runtime.daemonName d, Runtime.daemonLogBase d) | d <- [minBound..] ]
416

    
417
daemonsExtraLogbase :: Map String (Map String String)
418
daemonsExtraLogbase =
419
  Map.fromList $
420
  map (Runtime.daemonName *** id)
421
  [ (GanetiMond, Map.fromList
422
                 [ ("access", Runtime.daemonsExtraLogbase GanetiMond AccessLog)
423
                 , ("error", Runtime.daemonsExtraLogbase GanetiMond ErrorLog)
424
                 ])
425
  ]
426

    
427
extraLogreasonAccess :: String
428
extraLogreasonAccess = Runtime.daemonsExtraLogbase GanetiMond AccessLog
429

    
430
extraLogreasonError :: String
431
extraLogreasonError = Runtime.daemonsExtraLogbase GanetiMond ErrorLog
432

    
433
devConsole :: String
434
devConsole = ConstantUtils.devConsole
435

    
436
procMounts :: String
437
procMounts = "/proc/mounts"
438

    
439
-- * Luxi (Local UniX Interface) related constants
440

    
441
luxiEom :: PythonChar
442
luxiEom = PythonChar '\x03'
443

    
444
-- | Environment variable for the luxi override socket
445
luxiOverride :: String
446
luxiOverride = "FORCE_LUXI_SOCKET"
447

    
448
luxiOverrideMaster :: String
449
luxiOverrideMaster = "master"
450

    
451
luxiOverrideQuery :: String
452
luxiOverrideQuery = "query"
453

    
454
luxiVersion :: Int
455
luxiVersion = configVersion
456

    
457
-- * Syslog
458

    
459
syslogUsage :: String
460
syslogUsage = AutoConf.syslogUsage
461

    
462
syslogNo :: String
463
syslogNo = Logging.syslogUsageToRaw SyslogNo
464

    
465
syslogYes :: String
466
syslogYes = Logging.syslogUsageToRaw SyslogYes
467

    
468
syslogOnly :: String
469
syslogOnly = Logging.syslogUsageToRaw SyslogOnly
470

    
471
syslogSocket :: String
472
syslogSocket = "/dev/log"
473

    
474
exportConfFile :: String
475
exportConfFile = "config.ini"
476

    
477
-- * Xen
478

    
479
xenBootloader :: String
480
xenBootloader = AutoConf.xenBootloader
481

    
482
xenCmdXl :: String
483
xenCmdXl = "xl"
484

    
485
xenCmdXm :: String
486
xenCmdXm = "xm"
487

    
488
xenInitrd :: String
489
xenInitrd = AutoConf.xenInitrd
490

    
491
xenKernel :: String
492
xenKernel = AutoConf.xenKernel
493

    
494
-- FIXME: perhaps rename to 'validXenCommands' for consistency with
495
-- other constants
496
knownXenCommands :: FrozenSet String
497
knownXenCommands = ConstantUtils.mkSet [xenCmdXl, xenCmdXm]
498

    
499
-- * KVM and socat
500

    
501
kvmPath :: String
502
kvmPath = AutoConf.kvmPath
503

    
504
kvmKernel :: String
505
kvmKernel = AutoConf.kvmKernel
506

    
507
socatEscapeCode :: String
508
socatEscapeCode = "0x1d"
509

    
510
socatPath :: String
511
socatPath = AutoConf.socatPath
512

    
513
socatUseCompress :: Bool
514
socatUseCompress = AutoConf.socatUseCompress
515

    
516
socatUseEscape :: Bool
517
socatUseEscape = AutoConf.socatUseEscape
518

    
519
-- * Console types
520

    
521
-- | Display a message for console access
522
consMessage :: String
523
consMessage = "msg"
524

    
525
-- | Console as SPICE server
526
consSpice :: String
527
consSpice = "spice"
528

    
529
-- | Console as SSH command
530
consSsh :: String
531
consSsh = "ssh"
532

    
533
-- | Console as VNC server
534
consVnc :: String
535
consVnc = "vnc"
536

    
537
consAll :: FrozenSet String
538
consAll = ConstantUtils.mkSet [consMessage, consSpice, consSsh, consVnc]
539

    
540
-- | RSA key bit length
541
--
542
-- For RSA keys more bits are better, but they also make operations
543
-- more expensive. NIST SP 800-131 recommends a minimum of 2048 bits
544
-- from the year 2010 on.
545
rsaKeyBits :: Int
546
rsaKeyBits = 2048
547

    
548
-- | Ciphers allowed for SSL connections.
549
--
550
-- For the format, see ciphers(1). A better way to disable ciphers
551
-- would be to use the exclamation mark (!), but socat versions below
552
-- 1.5 can't parse exclamation marks in options properly. When
553
-- modifying the ciphers, ensure not to accidentially add something
554
-- after it's been removed. Use the "openssl" utility to check the
555
-- allowed ciphers, e.g.  "openssl ciphers -v HIGH:-DES".
556
opensslCiphers :: String
557
opensslCiphers = "HIGH:-DES:-3DES:-EXPORT:-ADH"
558

    
559
-- * X509
560

    
561
-- | commonName (CN) used in certificates
562
x509CertCn :: String
563
x509CertCn = "ganeti.example.com"
564

    
565
-- | Default validity of certificates in days
566
x509CertDefaultValidity :: Int
567
x509CertDefaultValidity = 365 * 5
568

    
569
x509CertSignatureHeader :: String
570
x509CertSignatureHeader = "X-Ganeti-Signature"
571

    
572
-- | Digest used to sign certificates ("openssl x509" uses SHA1 by default)
573
x509CertSignDigest :: String
574
x509CertSignDigest = "SHA1"
575

    
576
-- * Import/export daemon mode
577

    
578
iemExport :: String
579
iemExport = "export"
580

    
581
iemImport :: String
582
iemImport = "import"
583

    
584
-- * Import/export transport compression
585

    
586
iecGzip :: String
587
iecGzip = "gzip"
588

    
589
iecNone :: String
590
iecNone = "none"
591

    
592
iecAll :: [String]
593
iecAll = [iecGzip, iecNone]
594

    
595
ieCustomSize :: String
596
ieCustomSize = "fd"
597

    
598
-- * Import/export I/O
599

    
600
-- | Direct file I/O, equivalent to a shell's I/O redirection using
601
-- '<' or '>'
602
ieioFile :: String
603
ieioFile = "file"
604

    
605
-- | Raw block device I/O using "dd"
606
ieioRawDisk :: String
607
ieioRawDisk = "raw"
608

    
609
-- | OS definition import/export script
610
ieioScript :: String
611
ieioScript = "script"
612

    
613
-- * Values
614

    
615
valueDefault :: String
616
valueDefault = "default"
617

    
618
valueAuto :: String
619
valueAuto = "auto"
620

    
621
valueGenerate :: String
622
valueGenerate = "generate"
623

    
624
valueNone :: String
625
valueNone = "none"
626

    
627
valueTrue :: String
628
valueTrue = "true"
629

    
630
valueFalse :: String
631
valueFalse = "false"
632

    
633
-- * Hooks
634

    
635
hooksNameCfgupdate :: String
636
hooksNameCfgupdate = "config-update"
637

    
638
hooksNameWatcher :: String
639
hooksNameWatcher = "watcher"
640

    
641
hooksPath :: String
642
hooksPath = "/sbin:/bin:/usr/sbin:/usr/bin"
643

    
644
hooksPhasePost :: String
645
hooksPhasePost = "post"
646

    
647
hooksPhasePre :: String
648
hooksPhasePre = "pre"
649

    
650
hooksVersion :: Int
651
hooksVersion = 2
652

    
653
-- * Hooks subject type (what object type does the LU deal with)
654

    
655
htypeCluster :: String
656
htypeCluster = "CLUSTER"
657

    
658
htypeGroup :: String
659
htypeGroup = "GROUP"
660

    
661
htypeInstance :: String
662
htypeInstance = "INSTANCE"
663

    
664
htypeNetwork :: String
665
htypeNetwork = "NETWORK"
666

    
667
htypeNode :: String
668
htypeNode = "NODE"
669

    
670
-- * Hkr
671

    
672
hkrSkip :: Int
673
hkrSkip = 0
674

    
675
hkrFail :: Int
676
hkrFail = 1
677

    
678
hkrSuccess :: Int
679
hkrSuccess = 2
680

    
681
-- * Storage types
682

    
683
stBlock :: String
684
stBlock = Types.storageTypeToRaw StorageBlock
685

    
686
stDiskless :: String
687
stDiskless = Types.storageTypeToRaw StorageDiskless
688

    
689
stExt :: String
690
stExt = Types.storageTypeToRaw StorageExt
691

    
692
stFile :: String
693
stFile = Types.storageTypeToRaw StorageFile
694

    
695
stSharedFile :: String
696
stSharedFile = Types.storageTypeToRaw StorageSharedFile
697

    
698
stLvmPv :: String
699
stLvmPv = Types.storageTypeToRaw StorageLvmPv
700

    
701
stLvmVg :: String
702
stLvmVg = Types.storageTypeToRaw StorageLvmVg
703

    
704
stRados :: String
705
stRados = Types.storageTypeToRaw StorageRados
706

    
707
storageTypes :: FrozenSet String
708
storageTypes = ConstantUtils.mkSet $ map Types.storageTypeToRaw [minBound..]
709

    
710
-- | The set of storage types for which full storage reporting is available
711
stsReport :: FrozenSet String
712
stsReport = ConstantUtils.mkSet [stFile, stLvmPv, stLvmVg]
713

    
714
-- | The set of storage types for which node storage reporting is available
715
-- | (as used by LUQueryNodeStorage)
716
stsReportNodeStorage :: FrozenSet String
717
stsReportNodeStorage = ConstantUtils.union stsReport $
718
                                           ConstantUtils.mkSet [stSharedFile]
719

    
720
-- * Storage fields
721
-- ** First two are valid in LU context only, not passed to backend
722

    
723
sfNode :: String
724
sfNode = "node"
725

    
726
sfType :: String
727
sfType = "type"
728

    
729
-- ** and the rest are valid in backend
730

    
731
sfAllocatable :: String
732
sfAllocatable = Types.storageFieldToRaw SFAllocatable
733

    
734
sfFree :: String
735
sfFree = Types.storageFieldToRaw SFFree
736

    
737
sfName :: String
738
sfName = Types.storageFieldToRaw SFName
739

    
740
sfSize :: String
741
sfSize = Types.storageFieldToRaw SFSize
742

    
743
sfUsed :: String
744
sfUsed = Types.storageFieldToRaw SFUsed
745

    
746
validStorageFields :: FrozenSet String
747
validStorageFields =
748
  ConstantUtils.mkSet $ map Types.storageFieldToRaw [minBound..] ++
749
                        [sfNode, sfType]
750

    
751
modifiableStorageFields :: Map String (FrozenSet String)
752
modifiableStorageFields =
753
  Map.fromList [(Types.storageTypeToRaw StorageLvmPv,
754
                 ConstantUtils.mkSet [sfAllocatable])]
755

    
756
-- * Storage operations
757

    
758
soFixConsistency :: String
759
soFixConsistency = "fix-consistency"
760

    
761
validStorageOperations :: Map String (FrozenSet String)
762
validStorageOperations =
763
  Map.fromList [(Types.storageTypeToRaw StorageLvmVg,
764
                 ConstantUtils.mkSet [soFixConsistency])]
765

    
766
-- * Volume fields
767

    
768
vfDev :: String
769
vfDev = "dev"
770

    
771
vfInstance :: String
772
vfInstance = "instance"
773

    
774
vfName :: String
775
vfName = "name"
776

    
777
vfNode :: String
778
vfNode = "node"
779

    
780
vfPhys :: String
781
vfPhys = "phys"
782

    
783
vfSize :: String
784
vfSize = "size"
785

    
786
vfVg :: String
787
vfVg = "vg"
788

    
789
-- * Local disk status
790

    
791
ldsFaulty :: Int
792
ldsFaulty = Types.localDiskStatusToRaw DiskStatusFaulty
793

    
794
ldsOkay :: Int
795
ldsOkay = Types.localDiskStatusToRaw DiskStatusOk
796

    
797
ldsUnknown :: Int
798
ldsUnknown = Types.localDiskStatusToRaw DiskStatusUnknown
799

    
800
ldsNames :: Map Int String
801
ldsNames =
802
  Map.fromList [ (Types.localDiskStatusToRaw ds,
803
                  localDiskStatusName ds) | ds <- [minBound..] ]
804

    
805
-- * Disk template types
806

    
807
dtDiskless :: String
808
dtDiskless = Types.diskTemplateToRaw DTDiskless
809

    
810
dtFile :: String
811
dtFile = Types.diskTemplateToRaw DTFile
812

    
813
dtSharedFile :: String
814
dtSharedFile = Types.diskTemplateToRaw DTSharedFile
815

    
816
dtPlain :: String
817
dtPlain = Types.diskTemplateToRaw DTPlain
818

    
819
dtBlock :: String
820
dtBlock = Types.diskTemplateToRaw DTBlock
821

    
822
dtDrbd8 :: String
823
dtDrbd8 = Types.diskTemplateToRaw DTDrbd8
824

    
825
dtRbd :: String
826
dtRbd = Types.diskTemplateToRaw DTRbd
827

    
828
dtExt :: String
829
dtExt = Types.diskTemplateToRaw DTExt
830

    
831
dtGluster :: String
832
dtGluster = Types.diskTemplateToRaw DTGluster
833

    
834
-- | This is used to order determine the default disk template when
835
-- the list of enabled disk templates is inferred from the current
836
-- state of the cluster.  This only happens on an upgrade from a
837
-- version of Ganeti that did not support the 'enabled_disk_templates'
838
-- so far.
839
diskTemplatePreference :: [String]
840
diskTemplatePreference =
841
  map Types.diskTemplateToRaw
842
  [DTBlock, DTDiskless, DTDrbd8, DTExt, DTFile,
843
   DTPlain, DTRbd, DTSharedFile, DTGluster]
844

    
845
diskTemplates :: FrozenSet String
846
diskTemplates = ConstantUtils.mkSet $ map Types.diskTemplateToRaw [minBound..]
847

    
848
-- | Disk templates that are enabled by default
849
defaultEnabledDiskTemplates :: [String]
850
defaultEnabledDiskTemplates = map Types.diskTemplateToRaw [DTDrbd8, DTPlain]
851

    
852
-- | Mapping of disk templates to storage types
853
mapDiskTemplateStorageType :: Map String String
854
mapDiskTemplateStorageType =
855
  Map.fromList $
856
  map (Types.diskTemplateToRaw *** Types.storageTypeToRaw)
857
  [(DTBlock, StorageBlock),
858
   (DTDrbd8, StorageLvmVg),
859
   (DTExt, StorageExt),
860
   (DTSharedFile, StorageSharedFile),
861
   (DTFile, StorageFile),
862
   (DTDiskless, StorageDiskless),
863
   (DTPlain, StorageLvmVg),
864
   (DTRbd, StorageRados),
865
   (DTGluster, StorageSharedFile)]
866

    
867
-- | The set of network-mirrored disk templates
868
dtsIntMirror :: FrozenSet String
869
dtsIntMirror = ConstantUtils.mkSet [dtDrbd8]
870

    
871
-- | 'DTDiskless' is 'trivially' externally mirrored
872
dtsExtMirror :: FrozenSet String
873
dtsExtMirror =
874
  ConstantUtils.mkSet $
875
  map Types.diskTemplateToRaw
876
  [DTDiskless, DTBlock, DTExt, DTSharedFile, DTRbd, DTGluster]
877

    
878
-- | The set of non-lvm-based disk templates
879
dtsNotLvm :: FrozenSet String
880
dtsNotLvm =
881
  ConstantUtils.mkSet $
882
  map Types.diskTemplateToRaw
883
  [DTSharedFile, DTDiskless, DTBlock, DTExt, DTFile, DTRbd, DTGluster]
884

    
885
-- | The set of disk templates which can be grown
886
dtsGrowable :: FrozenSet String
887
dtsGrowable =
888
  ConstantUtils.mkSet $
889
  map Types.diskTemplateToRaw
890
  [DTSharedFile, DTDrbd8, DTPlain, DTExt, DTFile, DTRbd, DTGluster]
891

    
892
-- | The set of disk templates that allow adoption
893
dtsMayAdopt :: FrozenSet String
894
dtsMayAdopt =
895
  ConstantUtils.mkSet $ map Types.diskTemplateToRaw [DTBlock, DTPlain]
896

    
897
-- | The set of disk templates that *must* use adoption
898
dtsMustAdopt :: FrozenSet String
899
dtsMustAdopt = ConstantUtils.mkSet [Types.diskTemplateToRaw DTBlock]
900

    
901
-- | The set of disk templates that allow migrations
902
dtsMirrored :: FrozenSet String
903
dtsMirrored = dtsIntMirror `ConstantUtils.union` dtsExtMirror
904

    
905
-- | The set of file based disk templates
906
dtsFilebased :: FrozenSet String
907
dtsFilebased =
908
  ConstantUtils.mkSet $ map Types.diskTemplateToRaw
909
  [DTSharedFile, DTFile, DTGluster]
910

    
911
-- | The set of disk templates that can be moved by copying
912
--
913
-- Note: a requirement is that they're not accessed externally or
914
-- shared between nodes; in particular, sharedfile is not suitable.
915
dtsCopyable :: FrozenSet String
916
dtsCopyable =
917
  ConstantUtils.mkSet $ map Types.diskTemplateToRaw [DTPlain, DTFile]
918

    
919
-- | The set of disk templates that are supported by exclusive_storage
920
dtsExclStorage :: FrozenSet String
921
dtsExclStorage = ConstantUtils.mkSet $ map Types.diskTemplateToRaw [DTPlain]
922

    
923
-- | Templates for which we don't perform checks on free space
924
dtsNoFreeSpaceCheck :: FrozenSet String
925
dtsNoFreeSpaceCheck =
926
  ConstantUtils.mkSet $
927
  map Types.diskTemplateToRaw [DTExt, DTSharedFile, DTFile, DTRbd, DTGluster]
928

    
929
dtsBlock :: FrozenSet String
930
dtsBlock =
931
  ConstantUtils.mkSet $
932
  map Types.diskTemplateToRaw [DTPlain, DTDrbd8, DTBlock, DTRbd, DTExt]
933

    
934
-- | The set of lvm-based disk templates
935
dtsLvm :: FrozenSet String
936
dtsLvm = diskTemplates `ConstantUtils.difference` dtsNotLvm
937

    
938
-- | The set of lvm-based disk templates
939
dtsHaveAccess :: FrozenSet String
940
dtsHaveAccess = ConstantUtils.mkSet $
941
  map Types.diskTemplateToRaw [DTRbd, DTGluster]
942

    
943
-- * Drbd
944

    
945
drbdHmacAlg :: String
946
drbdHmacAlg = "md5"
947

    
948
drbdDefaultNetProtocol :: String
949
drbdDefaultNetProtocol = "C"
950

    
951
drbdMigrationNetProtocol :: String
952
drbdMigrationNetProtocol = "C"
953

    
954
drbdStatusFile :: String
955
drbdStatusFile = "/proc/drbd"
956

    
957
-- | Size of DRBD meta block device
958
drbdMetaSize :: Int
959
drbdMetaSize = 128
960

    
961
-- * Drbd barrier types
962

    
963
drbdBDiskBarriers :: String
964
drbdBDiskBarriers = "b"
965

    
966
drbdBDiskDrain :: String
967
drbdBDiskDrain = "d"
968

    
969
drbdBDiskFlush :: String
970
drbdBDiskFlush = "f"
971

    
972
drbdBNone :: String
973
drbdBNone = "n"
974

    
975
-- | Valid barrier combinations: "n" or any non-null subset of "bfd"
976
drbdValidBarrierOpt :: FrozenSet (FrozenSet String)
977
drbdValidBarrierOpt =
978
  ConstantUtils.mkSet
979
  [ ConstantUtils.mkSet [drbdBNone]
980
  , ConstantUtils.mkSet [drbdBDiskBarriers]
981
  , ConstantUtils.mkSet [drbdBDiskDrain]
982
  , ConstantUtils.mkSet [drbdBDiskFlush]
983
  , ConstantUtils.mkSet [drbdBDiskDrain, drbdBDiskFlush]
984
  , ConstantUtils.mkSet [drbdBDiskBarriers, drbdBDiskDrain]
985
  , ConstantUtils.mkSet [drbdBDiskBarriers, drbdBDiskFlush]
986
  , ConstantUtils.mkSet [drbdBDiskBarriers, drbdBDiskFlush, drbdBDiskDrain]
987
  ]
988

    
989
-- | Rbd tool command
990
rbdCmd :: String
991
rbdCmd = "rbd"
992

    
993
-- * File backend driver
994

    
995
fdBlktap :: String
996
fdBlktap = Types.fileDriverToRaw FileBlktap
997

    
998
fdBlktap2 :: String
999
fdBlktap2 = Types.fileDriverToRaw FileBlktap2
1000

    
1001
fdLoop :: String
1002
fdLoop = Types.fileDriverToRaw FileLoop
1003

    
1004
fdDefault :: String
1005
fdDefault = fdLoop
1006

    
1007
fileDriver :: FrozenSet String
1008
fileDriver =
1009
  ConstantUtils.mkSet $
1010
  map Types.fileDriverToRaw [minBound..]
1011

    
1012
-- | The set of drbd-like disk types
1013
dtsDrbd :: FrozenSet String
1014
dtsDrbd = ConstantUtils.mkSet [Types.diskTemplateToRaw DTDrbd8]
1015

    
1016
-- * Disk access mode
1017

    
1018
diskRdonly :: String
1019
diskRdonly = Types.diskModeToRaw DiskRdOnly
1020

    
1021
diskRdwr :: String
1022
diskRdwr = Types.diskModeToRaw DiskRdWr
1023

    
1024
diskAccessSet :: FrozenSet String
1025
diskAccessSet = ConstantUtils.mkSet $ map Types.diskModeToRaw [minBound..]
1026

    
1027
-- * Disk replacement mode
1028

    
1029
replaceDiskAuto :: String
1030
replaceDiskAuto = Types.replaceDisksModeToRaw ReplaceAuto
1031

    
1032
replaceDiskChg :: String
1033
replaceDiskChg = Types.replaceDisksModeToRaw ReplaceNewSecondary
1034

    
1035
replaceDiskPri :: String
1036
replaceDiskPri = Types.replaceDisksModeToRaw ReplaceOnPrimary
1037

    
1038
replaceDiskSec :: String
1039
replaceDiskSec = Types.replaceDisksModeToRaw ReplaceOnSecondary
1040

    
1041
replaceModes :: FrozenSet String
1042
replaceModes =
1043
  ConstantUtils.mkSet $ map Types.replaceDisksModeToRaw [minBound..]
1044

    
1045
-- * Instance export mode
1046

    
1047
exportModeLocal :: String
1048
exportModeLocal = Types.exportModeToRaw ExportModeLocal
1049

    
1050
exportModeRemote :: String
1051
exportModeRemote = Types.exportModeToRaw ExportModeRemote
1052

    
1053
exportModes :: FrozenSet String
1054
exportModes = ConstantUtils.mkSet $ map Types.exportModeToRaw [minBound..]
1055

    
1056
-- * Instance creation modes
1057

    
1058
instanceCreate :: String
1059
instanceCreate = Types.instCreateModeToRaw InstCreate
1060

    
1061
instanceImport :: String
1062
instanceImport = Types.instCreateModeToRaw InstImport
1063

    
1064
instanceRemoteImport :: String
1065
instanceRemoteImport = Types.instCreateModeToRaw InstRemoteImport
1066

    
1067
instanceCreateModes :: FrozenSet String
1068
instanceCreateModes =
1069
  ConstantUtils.mkSet $ map Types.instCreateModeToRaw [minBound..]
1070

    
1071
-- * Remote import/export handshake message and version
1072

    
1073
rieHandshake :: String
1074
rieHandshake = "Hi, I'm Ganeti"
1075

    
1076
rieVersion :: Int
1077
rieVersion = 0
1078

    
1079
-- | Remote import/export certificate validity (seconds)
1080
rieCertValidity :: Int
1081
rieCertValidity = 24 * 60 * 60
1082

    
1083
-- | Export only: how long to wait per connection attempt (seconds)
1084
rieConnectAttemptTimeout :: Int
1085
rieConnectAttemptTimeout = 20
1086

    
1087
-- | Export only: number of attempts to connect
1088
rieConnectRetries :: Int
1089
rieConnectRetries = 10
1090

    
1091
-- | Overall timeout for establishing connection
1092
rieConnectTimeout :: Int
1093
rieConnectTimeout = 180
1094

    
1095
-- | Give child process up to 5 seconds to exit after sending a signal
1096
childLingerTimeout :: Double
1097
childLingerTimeout = 5.0
1098

    
1099
-- * Import/export config options
1100

    
1101
inisectBep :: String
1102
inisectBep = "backend"
1103

    
1104
inisectExp :: String
1105
inisectExp = "export"
1106

    
1107
inisectHyp :: String
1108
inisectHyp = "hypervisor"
1109

    
1110
inisectIns :: String
1111
inisectIns = "instance"
1112

    
1113
inisectOsp :: String
1114
inisectOsp = "os"
1115

    
1116
inisectOspPrivate :: String
1117
inisectOspPrivate = "os_private"
1118

    
1119
-- * Dynamic device modification
1120

    
1121
ddmAdd :: String
1122
ddmAdd = Types.ddmFullToRaw DdmFullAdd
1123

    
1124
ddmModify :: String
1125
ddmModify = Types.ddmFullToRaw DdmFullModify
1126

    
1127
ddmRemove :: String
1128
ddmRemove = Types.ddmFullToRaw DdmFullRemove
1129

    
1130
ddmsValues :: FrozenSet String
1131
ddmsValues = ConstantUtils.mkSet [ddmAdd, ddmRemove]
1132

    
1133
ddmsValuesWithModify :: FrozenSet String
1134
ddmsValuesWithModify = ConstantUtils.mkSet $ map Types.ddmFullToRaw [minBound..]
1135

    
1136
-- * Common exit codes
1137

    
1138
exitSuccess :: Int
1139
exitSuccess = 0
1140

    
1141
exitFailure :: Int
1142
exitFailure = ConstantUtils.exitFailure
1143

    
1144
exitNotcluster :: Int
1145
exitNotcluster = 5
1146

    
1147
exitNotmaster :: Int
1148
exitNotmaster = 11
1149

    
1150
exitNodesetupError :: Int
1151
exitNodesetupError = 12
1152

    
1153
-- | Need user confirmation
1154
exitConfirmation :: Int
1155
exitConfirmation = 13
1156

    
1157
-- | Exit code for query operations with unknown fields
1158
exitUnknownField :: Int
1159
exitUnknownField = 14
1160

    
1161
-- * Tags
1162

    
1163
tagCluster :: String
1164
tagCluster = Types.tagKindToRaw TagKindCluster
1165

    
1166
tagInstance :: String
1167
tagInstance = Types.tagKindToRaw TagKindInstance
1168

    
1169
tagNetwork :: String
1170
tagNetwork = Types.tagKindToRaw TagKindNetwork
1171

    
1172
tagNode :: String
1173
tagNode = Types.tagKindToRaw TagKindNode
1174

    
1175
tagNodegroup :: String
1176
tagNodegroup = Types.tagKindToRaw TagKindGroup
1177

    
1178
validTagTypes :: FrozenSet String
1179
validTagTypes = ConstantUtils.mkSet $ map Types.tagKindToRaw [minBound..]
1180

    
1181
maxTagLen :: Int
1182
maxTagLen = 128
1183

    
1184
maxTagsPerObj :: Int
1185
maxTagsPerObj = 4096
1186

    
1187
-- * Others
1188

    
1189
defaultBridge :: String
1190
defaultBridge = "xen-br0"
1191

    
1192
defaultOvs :: String
1193
defaultOvs = "switch1"
1194

    
1195
-- | 60 MiB/s, expressed in KiB/s
1196
classicDrbdSyncSpeed :: Int
1197
classicDrbdSyncSpeed = 60 * 1024
1198

    
1199
ip4AddressAny :: String
1200
ip4AddressAny = "0.0.0.0"
1201

    
1202
ip4AddressLocalhost :: String
1203
ip4AddressLocalhost = "127.0.0.1"
1204

    
1205
ip6AddressAny :: String
1206
ip6AddressAny = "::"
1207

    
1208
ip6AddressLocalhost :: String
1209
ip6AddressLocalhost = "::1"
1210

    
1211
ip4Version :: Int
1212
ip4Version = 4
1213

    
1214
ip6Version :: Int
1215
ip6Version = 6
1216

    
1217
validIpVersions :: FrozenSet Int
1218
validIpVersions = ConstantUtils.mkSet [ip4Version, ip6Version]
1219

    
1220
tcpPingTimeout :: Int
1221
tcpPingTimeout = 10
1222

    
1223
defaultVg :: String
1224
defaultVg = "xenvg"
1225

    
1226
defaultDrbdHelper :: String
1227
defaultDrbdHelper = "/bin/true"
1228

    
1229
minVgSize :: Int
1230
minVgSize = 20480
1231

    
1232
defaultMacPrefix :: String
1233
defaultMacPrefix = "aa:00:00"
1234

    
1235
-- | Default maximum instance wait time (seconds)
1236
defaultShutdownTimeout :: Int
1237
defaultShutdownTimeout = 120
1238

    
1239
-- | Node clock skew (seconds)
1240
nodeMaxClockSkew :: Int
1241
nodeMaxClockSkew = 150
1242

    
1243
-- | Time for an intra-cluster disk transfer to wait for a connection
1244
diskTransferConnectTimeout :: Int
1245
diskTransferConnectTimeout = 60
1246

    
1247
-- | Disk index separator
1248
diskSeparator :: String
1249
diskSeparator = AutoConf.diskSeparator
1250

    
1251
ipCommandPath :: String
1252
ipCommandPath = AutoConf.ipPath
1253

    
1254
-- | Key for job IDs in opcode result
1255
jobIdsKey :: String
1256
jobIdsKey = "jobs"
1257

    
1258
-- * Runparts results
1259

    
1260
runpartsErr :: Int
1261
runpartsErr = 2
1262

    
1263
runpartsRun :: Int
1264
runpartsRun = 1
1265

    
1266
runpartsSkip :: Int
1267
runpartsSkip = 0
1268

    
1269
runpartsStatus :: [Int]
1270
runpartsStatus = [runpartsErr, runpartsRun, runpartsSkip]
1271

    
1272
-- * RPC
1273

    
1274
rpcEncodingNone :: Int
1275
rpcEncodingNone = 0
1276

    
1277
rpcEncodingZlibBase64 :: Int
1278
rpcEncodingZlibBase64 = 1
1279

    
1280
-- * Timeout table
1281
--
1282
-- Various time constants for the timeout table
1283

    
1284
rpcTmoUrgent :: Int
1285
rpcTmoUrgent = Types.rpcTimeoutToRaw Urgent
1286

    
1287
rpcTmoFast :: Int
1288
rpcTmoFast = Types.rpcTimeoutToRaw Fast
1289

    
1290
rpcTmoNormal :: Int
1291
rpcTmoNormal = Types.rpcTimeoutToRaw Normal
1292

    
1293
rpcTmoSlow :: Int
1294
rpcTmoSlow = Types.rpcTimeoutToRaw Slow
1295

    
1296
-- | 'rpcTmo_4hrs' contains an underscore to circumvent a limitation
1297
-- in the 'Ganeti.THH.deCamelCase' function and generate the correct
1298
-- Python name.
1299
rpcTmo_4hrs :: Int
1300
rpcTmo_4hrs = Types.rpcTimeoutToRaw FourHours
1301

    
1302
-- | 'rpcTmo_1day' contains an underscore to circumvent a limitation
1303
-- in the 'Ganeti.THH.deCamelCase' function and generate the correct
1304
-- Python name.
1305
rpcTmo_1day :: Int
1306
rpcTmo_1day = Types.rpcTimeoutToRaw OneDay
1307

    
1308
-- | Timeout for connecting to nodes (seconds)
1309
rpcConnectTimeout :: Int
1310
rpcConnectTimeout = 5
1311

    
1312
-- OS
1313

    
1314
osScriptCreate :: String
1315
osScriptCreate = "create"
1316

    
1317
osScriptExport :: String
1318
osScriptExport = "export"
1319

    
1320
osScriptImport :: String
1321
osScriptImport = "import"
1322

    
1323
osScriptRename :: String
1324
osScriptRename = "rename"
1325

    
1326
osScriptVerify :: String
1327
osScriptVerify = "verify"
1328

    
1329
osScripts :: [String]
1330
osScripts = [osScriptCreate, osScriptExport, osScriptImport, osScriptRename,
1331
             osScriptVerify]
1332

    
1333
osApiFile :: String
1334
osApiFile = "ganeti_api_version"
1335

    
1336
osVariantsFile :: String
1337
osVariantsFile = "variants.list"
1338

    
1339
osParametersFile :: String
1340
osParametersFile = "parameters.list"
1341

    
1342
osValidateParameters :: String
1343
osValidateParameters = "parameters"
1344

    
1345
osValidateCalls :: FrozenSet String
1346
osValidateCalls = ConstantUtils.mkSet [osValidateParameters]
1347

    
1348
-- | External Storage (ES) related constants
1349

    
1350
esActionAttach :: String
1351
esActionAttach = "attach"
1352

    
1353
esActionCreate :: String
1354
esActionCreate = "create"
1355

    
1356
esActionDetach :: String
1357
esActionDetach = "detach"
1358

    
1359
esActionGrow :: String
1360
esActionGrow = "grow"
1361

    
1362
esActionRemove :: String
1363
esActionRemove = "remove"
1364

    
1365
esActionSetinfo :: String
1366
esActionSetinfo = "setinfo"
1367

    
1368
esActionVerify :: String
1369
esActionVerify = "verify"
1370

    
1371
esScriptCreate :: String
1372
esScriptCreate = esActionCreate
1373

    
1374
esScriptRemove :: String
1375
esScriptRemove = esActionRemove
1376

    
1377
esScriptGrow :: String
1378
esScriptGrow = esActionGrow
1379

    
1380
esScriptAttach :: String
1381
esScriptAttach = esActionAttach
1382

    
1383
esScriptDetach :: String
1384
esScriptDetach = esActionDetach
1385

    
1386
esScriptSetinfo :: String
1387
esScriptSetinfo = esActionSetinfo
1388

    
1389
esScriptVerify :: String
1390
esScriptVerify = esActionVerify
1391

    
1392
esScripts :: FrozenSet String
1393
esScripts =
1394
  ConstantUtils.mkSet [esScriptAttach,
1395
                       esScriptCreate,
1396
                       esScriptDetach,
1397
                       esScriptGrow,
1398
                       esScriptRemove,
1399
                       esScriptSetinfo,
1400
                       esScriptVerify]
1401

    
1402
esParametersFile :: String
1403
esParametersFile = "parameters.list"
1404

    
1405
-- * Reboot types
1406

    
1407
instanceRebootSoft :: String
1408
instanceRebootSoft = Types.rebootTypeToRaw RebootSoft
1409

    
1410
instanceRebootHard :: String
1411
instanceRebootHard = Types.rebootTypeToRaw RebootHard
1412

    
1413
instanceRebootFull :: String
1414
instanceRebootFull = Types.rebootTypeToRaw RebootFull
1415

    
1416
rebootTypes :: FrozenSet String
1417
rebootTypes = ConstantUtils.mkSet $ map Types.rebootTypeToRaw [minBound..]
1418

    
1419
-- * Instance reboot behaviors
1420

    
1421
instanceRebootAllowed :: String
1422
instanceRebootAllowed = "reboot"
1423

    
1424
instanceRebootExit :: String
1425
instanceRebootExit = "exit"
1426

    
1427
rebootBehaviors :: [String]
1428
rebootBehaviors = [instanceRebootAllowed, instanceRebootExit]
1429

    
1430
-- * VTypes
1431

    
1432
vtypeBool :: VType
1433
vtypeBool = VTypeBool
1434

    
1435
vtypeInt :: VType
1436
vtypeInt = VTypeInt
1437

    
1438
vtypeMaybeString :: VType
1439
vtypeMaybeString = VTypeMaybeString
1440

    
1441
-- | Size in MiBs
1442
vtypeSize :: VType
1443
vtypeSize = VTypeSize
1444

    
1445
vtypeString :: VType
1446
vtypeString = VTypeString
1447

    
1448
enforceableTypes :: FrozenSet VType
1449
enforceableTypes = ConstantUtils.mkSet [minBound..]
1450

    
1451
-- | Constant representing that the user does not specify any IP version
1452
ifaceNoIpVersionSpecified :: Int
1453
ifaceNoIpVersionSpecified = 0
1454

    
1455
validSerialSpeeds :: [Int]
1456
validSerialSpeeds =
1457
  [75,
1458
   110,
1459
   300,
1460
   600,
1461
   1200,
1462
   1800,
1463
   2400,
1464
   4800,
1465
   9600,
1466
   14400,
1467
   19200,
1468
   28800,
1469
   38400,
1470
   57600,
1471
   115200,
1472
   230400,
1473
   345600,
1474
   460800]
1475

    
1476
-- * HV parameter names (global namespace)
1477

    
1478
hvAcpi :: String
1479
hvAcpi = "acpi"
1480

    
1481
hvBlockdevPrefix :: String
1482
hvBlockdevPrefix = "blockdev_prefix"
1483

    
1484
hvBootloaderArgs :: String
1485
hvBootloaderArgs = "bootloader_args"
1486

    
1487
hvBootloaderPath :: String
1488
hvBootloaderPath = "bootloader_path"
1489

    
1490
hvBootOrder :: String
1491
hvBootOrder = "boot_order"
1492

    
1493
hvCdromImagePath :: String
1494
hvCdromImagePath = "cdrom_image_path"
1495

    
1496
hvCpuCap :: String
1497
hvCpuCap = "cpu_cap"
1498

    
1499
hvCpuCores :: String
1500
hvCpuCores = "cpu_cores"
1501

    
1502
hvCpuMask :: String
1503
hvCpuMask = "cpu_mask"
1504

    
1505
hvCpuSockets :: String
1506
hvCpuSockets = "cpu_sockets"
1507

    
1508
hvCpuThreads :: String
1509
hvCpuThreads = "cpu_threads"
1510

    
1511
hvCpuType :: String
1512
hvCpuType = "cpu_type"
1513

    
1514
hvCpuWeight :: String
1515
hvCpuWeight = "cpu_weight"
1516

    
1517
hvDeviceModel :: String
1518
hvDeviceModel = "device_model"
1519

    
1520
hvDiskCache :: String
1521
hvDiskCache = "disk_cache"
1522

    
1523
hvDiskType :: String
1524
hvDiskType = "disk_type"
1525

    
1526
hvInitrdPath :: String
1527
hvInitrdPath = "initrd_path"
1528

    
1529
hvInitScript :: String
1530
hvInitScript = "init_script"
1531

    
1532
hvKernelArgs :: String
1533
hvKernelArgs = "kernel_args"
1534

    
1535
hvKernelPath :: String
1536
hvKernelPath = "kernel_path"
1537

    
1538
hvKeymap :: String
1539
hvKeymap = "keymap"
1540

    
1541
hvKvmCdrom2ImagePath :: String
1542
hvKvmCdrom2ImagePath = "cdrom2_image_path"
1543

    
1544
hvKvmCdromDiskType :: String
1545
hvKvmCdromDiskType = "cdrom_disk_type"
1546

    
1547
hvKvmExtra :: String
1548
hvKvmExtra = "kvm_extra"
1549

    
1550
hvKvmFlag :: String
1551
hvKvmFlag = "kvm_flag"
1552

    
1553
hvKvmFloppyImagePath :: String
1554
hvKvmFloppyImagePath = "floppy_image_path"
1555

    
1556
hvKvmMachineVersion :: String
1557
hvKvmMachineVersion = "machine_version"
1558

    
1559
hvKvmPath :: String
1560
hvKvmPath = "kvm_path"
1561

    
1562
hvKvmSpiceAudioCompr :: String
1563
hvKvmSpiceAudioCompr = "spice_playback_compression"
1564

    
1565
hvKvmSpiceBind :: String
1566
hvKvmSpiceBind = "spice_bind"
1567

    
1568
hvKvmSpiceIpVersion :: String
1569
hvKvmSpiceIpVersion = "spice_ip_version"
1570

    
1571
hvKvmSpiceJpegImgCompr :: String
1572
hvKvmSpiceJpegImgCompr = "spice_jpeg_wan_compression"
1573

    
1574
hvKvmSpiceLosslessImgCompr :: String
1575
hvKvmSpiceLosslessImgCompr = "spice_image_compression"
1576

    
1577
hvKvmSpicePasswordFile :: String
1578
hvKvmSpicePasswordFile = "spice_password_file"
1579

    
1580
hvKvmSpiceStreamingVideoDetection :: String
1581
hvKvmSpiceStreamingVideoDetection = "spice_streaming_video"
1582

    
1583
hvKvmSpiceTlsCiphers :: String
1584
hvKvmSpiceTlsCiphers = "spice_tls_ciphers"
1585

    
1586
hvKvmSpiceUseTls :: String
1587
hvKvmSpiceUseTls = "spice_use_tls"
1588

    
1589
hvKvmSpiceUseVdagent :: String
1590
hvKvmSpiceUseVdagent = "spice_use_vdagent"
1591

    
1592
hvKvmSpiceZlibGlzImgCompr :: String
1593
hvKvmSpiceZlibGlzImgCompr = "spice_zlib_glz_wan_compression"
1594

    
1595
hvKvmUseChroot :: String
1596
hvKvmUseChroot = "use_chroot"
1597

    
1598
hvKvmUserShutdown :: String
1599
hvKvmUserShutdown = "user_shutdown"
1600

    
1601
hvMemPath :: String
1602
hvMemPath = "mem_path"
1603

    
1604
hvMigrationBandwidth :: String
1605
hvMigrationBandwidth = "migration_bandwidth"
1606

    
1607
hvMigrationDowntime :: String
1608
hvMigrationDowntime = "migration_downtime"
1609

    
1610
hvMigrationMode :: String
1611
hvMigrationMode = "migration_mode"
1612

    
1613
hvMigrationPort :: String
1614
hvMigrationPort = "migration_port"
1615

    
1616
hvNicType :: String
1617
hvNicType = "nic_type"
1618

    
1619
hvPae :: String
1620
hvPae = "pae"
1621

    
1622
hvPassthrough :: String
1623
hvPassthrough = "pci_pass"
1624

    
1625
hvRebootBehavior :: String
1626
hvRebootBehavior = "reboot_behavior"
1627

    
1628
hvRootPath :: String
1629
hvRootPath = "root_path"
1630

    
1631
hvSecurityDomain :: String
1632
hvSecurityDomain = "security_domain"
1633

    
1634
hvSecurityModel :: String
1635
hvSecurityModel = "security_model"
1636

    
1637
hvSerialConsole :: String
1638
hvSerialConsole = "serial_console"
1639

    
1640
hvSerialSpeed :: String
1641
hvSerialSpeed = "serial_speed"
1642

    
1643
hvSoundhw :: String
1644
hvSoundhw = "soundhw"
1645

    
1646
hvUsbDevices :: String
1647
hvUsbDevices = "usb_devices"
1648

    
1649
hvUsbMouse :: String
1650
hvUsbMouse = "usb_mouse"
1651

    
1652
hvUseBootloader :: String
1653
hvUseBootloader = "use_bootloader"
1654

    
1655
hvUseLocaltime :: String
1656
hvUseLocaltime = "use_localtime"
1657

    
1658
hvVga :: String
1659
hvVga = "vga"
1660

    
1661
hvVhostNet :: String
1662
hvVhostNet = "vhost_net"
1663

    
1664
hvVifScript :: String
1665
hvVifScript = "vif_script"
1666

    
1667
hvVifType :: String
1668
hvVifType = "vif_type"
1669

    
1670
hvViridian :: String
1671
hvViridian = "viridian"
1672

    
1673
hvVncBindAddress :: String
1674
hvVncBindAddress = "vnc_bind_address"
1675

    
1676
hvVncPasswordFile :: String
1677
hvVncPasswordFile = "vnc_password_file"
1678

    
1679
hvVncTls :: String
1680
hvVncTls = "vnc_tls"
1681

    
1682
hvVncX509 :: String
1683
hvVncX509 = "vnc_x509_path"
1684

    
1685
hvVncX509Verify :: String
1686
hvVncX509Verify = "vnc_x509_verify"
1687

    
1688
hvVnetHdr :: String
1689
hvVnetHdr = "vnet_hdr"
1690

    
1691
hvXenCmd :: String
1692
hvXenCmd = "xen_cmd"
1693

    
1694
hvXenCpuid :: String
1695
hvXenCpuid = "cpuid"
1696

    
1697
hvsParameterTitles :: Map String String
1698
hvsParameterTitles =
1699
  Map.fromList
1700
  [(hvAcpi, "ACPI"),
1701
   (hvBootOrder, "Boot_order"),
1702
   (hvCdromImagePath, "CDROM_image_path"),
1703
   (hvCpuType, "cpu_type"),
1704
   (hvDiskType, "Disk_type"),
1705
   (hvInitrdPath, "Initrd_path"),
1706
   (hvKernelPath, "Kernel_path"),
1707
   (hvNicType, "NIC_type"),
1708
   (hvPae, "PAE"),
1709
   (hvPassthrough, "pci_pass"),
1710
   (hvVncBindAddress, "VNC_bind_address")]
1711

    
1712
hvsParameters :: FrozenSet String
1713
hvsParameters = ConstantUtils.mkSet $ Map.keys hvsParameterTypes
1714

    
1715
hvsParameterTypes :: Map String VType
1716
hvsParameterTypes = Map.fromList
1717
  [ (hvAcpi,                            VTypeBool)
1718
  , (hvBlockdevPrefix,                  VTypeString)
1719
  , (hvBootloaderArgs,                  VTypeString)
1720
  , (hvBootloaderPath,                  VTypeString)
1721
  , (hvBootOrder,                       VTypeString)
1722
  , (hvCdromImagePath,                  VTypeString)
1723
  , (hvCpuCap,                          VTypeInt)
1724
  , (hvCpuCores,                        VTypeInt)
1725
  , (hvCpuMask,                         VTypeString)
1726
  , (hvCpuSockets,                      VTypeInt)
1727
  , (hvCpuThreads,                      VTypeInt)
1728
  , (hvCpuType,                         VTypeString)
1729
  , (hvCpuWeight,                       VTypeInt)
1730
  , (hvDeviceModel,                     VTypeString)
1731
  , (hvDiskCache,                       VTypeString)
1732
  , (hvDiskType,                        VTypeString)
1733
  , (hvInitrdPath,                      VTypeString)
1734
  , (hvInitScript,                      VTypeString)
1735
  , (hvKernelArgs,                      VTypeString)
1736
  , (hvKernelPath,                      VTypeString)
1737
  , (hvKeymap,                          VTypeString)
1738
  , (hvKvmCdrom2ImagePath,              VTypeString)
1739
  , (hvKvmCdromDiskType,                VTypeString)
1740
  , (hvKvmExtra,                        VTypeString)
1741
  , (hvKvmFlag,                         VTypeString)
1742
  , (hvKvmFloppyImagePath,              VTypeString)
1743
  , (hvKvmMachineVersion,               VTypeString)
1744
  , (hvKvmPath,                         VTypeString)
1745
  , (hvKvmSpiceAudioCompr,              VTypeBool)
1746
  , (hvKvmSpiceBind,                    VTypeString)
1747
  , (hvKvmSpiceIpVersion,               VTypeInt)
1748
  , (hvKvmSpiceJpegImgCompr,            VTypeString)
1749
  , (hvKvmSpiceLosslessImgCompr,        VTypeString)
1750
  , (hvKvmSpicePasswordFile,            VTypeString)
1751
  , (hvKvmSpiceStreamingVideoDetection, VTypeString)
1752
  , (hvKvmSpiceTlsCiphers,              VTypeString)
1753
  , (hvKvmSpiceUseTls,                  VTypeBool)
1754
  , (hvKvmSpiceUseVdagent,              VTypeBool)
1755
  , (hvKvmSpiceZlibGlzImgCompr,         VTypeString)
1756
  , (hvKvmUseChroot,                    VTypeBool)
1757
  , (hvKvmUserShutdown,                 VTypeBool)
1758
  , (hvMemPath,                         VTypeString)
1759
  , (hvMigrationBandwidth,              VTypeInt)
1760
  , (hvMigrationDowntime,               VTypeInt)
1761
  , (hvMigrationMode,                   VTypeString)
1762
  , (hvMigrationPort,                   VTypeInt)
1763
  , (hvNicType,                         VTypeString)
1764
  , (hvPae,                             VTypeBool)
1765
  , (hvPassthrough,                     VTypeString)
1766
  , (hvRebootBehavior,                  VTypeString)
1767
  , (hvRootPath,                        VTypeMaybeString)
1768
  , (hvSecurityDomain,                  VTypeString)
1769
  , (hvSecurityModel,                   VTypeString)
1770
  , (hvSerialConsole,                   VTypeBool)
1771
  , (hvSerialSpeed,                     VTypeInt)
1772
  , (hvSoundhw,                         VTypeString)
1773
  , (hvUsbDevices,                      VTypeString)
1774
  , (hvUsbMouse,                        VTypeString)
1775
  , (hvUseBootloader,                   VTypeBool)
1776
  , (hvUseLocaltime,                    VTypeBool)
1777
  , (hvVga,                             VTypeString)
1778
  , (hvVhostNet,                        VTypeBool)
1779
  , (hvVifScript,                       VTypeString)
1780
  , (hvVifType,                         VTypeString)
1781
  , (hvViridian,                        VTypeBool)
1782
  , (hvVncBindAddress,                  VTypeString)
1783
  , (hvVncPasswordFile,                 VTypeString)
1784
  , (hvVncTls,                          VTypeBool)
1785
  , (hvVncX509,                         VTypeString)
1786
  , (hvVncX509Verify,                   VTypeBool)
1787
  , (hvVnetHdr,                         VTypeBool)
1788
  , (hvXenCmd,                          VTypeString)
1789
  , (hvXenCpuid,                        VTypeString)
1790
  ]
1791

    
1792
-- * Migration statuses
1793

    
1794
hvMigrationActive :: String
1795
hvMigrationActive = "active"
1796

    
1797
hvMigrationCancelled :: String
1798
hvMigrationCancelled = "cancelled"
1799

    
1800
hvMigrationCompleted :: String
1801
hvMigrationCompleted = "completed"
1802

    
1803
hvMigrationFailed :: String
1804
hvMigrationFailed = "failed"
1805

    
1806
hvMigrationValidStatuses :: FrozenSet String
1807
hvMigrationValidStatuses =
1808
  ConstantUtils.mkSet [hvMigrationActive,
1809
                       hvMigrationCancelled,
1810
                       hvMigrationCompleted,
1811
                       hvMigrationFailed]
1812

    
1813
hvMigrationFailedStatuses :: FrozenSet String
1814
hvMigrationFailedStatuses =
1815
  ConstantUtils.mkSet [hvMigrationFailed, hvMigrationCancelled]
1816

    
1817
-- | KVM-specific statuses
1818
--
1819
-- FIXME: this constant seems unnecessary
1820
hvKvmMigrationValidStatuses :: FrozenSet String
1821
hvKvmMigrationValidStatuses = hvMigrationValidStatuses
1822

    
1823
-- | Node info keys
1824
hvNodeinfoKeyVersion :: String
1825
hvNodeinfoKeyVersion = "hv_version"
1826

    
1827
-- * Hypervisor state
1828

    
1829
hvstCpuNode :: String
1830
hvstCpuNode = "cpu_node"
1831

    
1832
hvstCpuTotal :: String
1833
hvstCpuTotal = "cpu_total"
1834

    
1835
hvstMemoryHv :: String
1836
hvstMemoryHv = "mem_hv"
1837

    
1838
hvstMemoryNode :: String
1839
hvstMemoryNode = "mem_node"
1840

    
1841
hvstMemoryTotal :: String
1842
hvstMemoryTotal = "mem_total"
1843

    
1844
hvstsParameters :: FrozenSet String
1845
hvstsParameters =
1846
  ConstantUtils.mkSet [hvstCpuNode,
1847
                       hvstCpuTotal,
1848
                       hvstMemoryHv,
1849
                       hvstMemoryNode,
1850
                       hvstMemoryTotal]
1851

    
1852
hvstDefaults :: Map String Int
1853
hvstDefaults =
1854
  Map.fromList
1855
  [(hvstCpuNode, 1),
1856
   (hvstCpuTotal, 1),
1857
   (hvstMemoryHv, 0),
1858
   (hvstMemoryTotal, 0),
1859
   (hvstMemoryNode, 0)]
1860

    
1861
hvstsParameterTypes :: Map String VType
1862
hvstsParameterTypes =
1863
  Map.fromList [(hvstMemoryTotal, VTypeInt),
1864
                (hvstMemoryNode, VTypeInt),
1865
                (hvstMemoryHv, VTypeInt),
1866
                (hvstCpuTotal, VTypeInt),
1867
                (hvstCpuNode, VTypeInt)]
1868

    
1869
-- * Disk state
1870

    
1871
dsDiskOverhead :: String
1872
dsDiskOverhead = "disk_overhead"
1873

    
1874
dsDiskReserved :: String
1875
dsDiskReserved = "disk_reserved"
1876

    
1877
dsDiskTotal :: String
1878
dsDiskTotal = "disk_total"
1879

    
1880
dsDefaults :: Map String Int
1881
dsDefaults =
1882
  Map.fromList
1883
  [(dsDiskTotal, 0),
1884
   (dsDiskReserved, 0),
1885
   (dsDiskOverhead, 0)]
1886

    
1887
dssParameterTypes :: Map String VType
1888
dssParameterTypes =
1889
  Map.fromList [(dsDiskTotal, VTypeInt),
1890
                (dsDiskReserved, VTypeInt),
1891
                (dsDiskOverhead, VTypeInt)]
1892

    
1893
dssParameters :: FrozenSet String
1894
dssParameters =
1895
  ConstantUtils.mkSet [dsDiskTotal, dsDiskReserved, dsDiskOverhead]
1896

    
1897
dsValidTypes :: FrozenSet String
1898
dsValidTypes = ConstantUtils.mkSet [Types.diskTemplateToRaw DTPlain]
1899

    
1900
-- Backend parameter names
1901

    
1902
beAlwaysFailover :: String
1903
beAlwaysFailover = "always_failover"
1904

    
1905
beAutoBalance :: String
1906
beAutoBalance = "auto_balance"
1907

    
1908
beMaxmem :: String
1909
beMaxmem = "maxmem"
1910

    
1911
-- | Deprecated and replaced by max and min mem
1912
beMemory :: String
1913
beMemory = "memory"
1914

    
1915
beMinmem :: String
1916
beMinmem = "minmem"
1917

    
1918
beSpindleUse :: String
1919
beSpindleUse = "spindle_use"
1920

    
1921
beVcpus :: String
1922
beVcpus = "vcpus"
1923

    
1924
besParameterTypes :: Map String VType
1925
besParameterTypes =
1926
  Map.fromList [(beAlwaysFailover, VTypeBool),
1927
                (beAutoBalance, VTypeBool),
1928
                (beMaxmem, VTypeSize),
1929
                (beMinmem, VTypeSize),
1930
                (beSpindleUse, VTypeInt),
1931
                (beVcpus, VTypeInt)]
1932

    
1933
besParameterTitles :: Map String String
1934
besParameterTitles =
1935
  Map.fromList [(beAutoBalance, "Auto_balance"),
1936
                (beMinmem, "ConfigMinMem"),
1937
                (beVcpus, "ConfigVCPUs"),
1938
                (beMaxmem, "ConfigMaxMem")]
1939

    
1940
besParameterCompat :: Map String VType
1941
besParameterCompat = Map.insert beMemory VTypeSize besParameterTypes
1942

    
1943
besParameters :: FrozenSet String
1944
besParameters =
1945
  ConstantUtils.mkSet [beAlwaysFailover,
1946
                       beAutoBalance,
1947
                       beMaxmem,
1948
                       beMinmem,
1949
                       beSpindleUse,
1950
                       beVcpus]
1951

    
1952
-- | Instance specs
1953
--
1954
-- FIXME: these should be associated with 'Ganeti.HTools.Types.ISpec'
1955

    
1956
ispecMemSize :: String
1957
ispecMemSize = ConstantUtils.ispecMemSize
1958

    
1959
ispecCpuCount :: String
1960
ispecCpuCount = ConstantUtils.ispecCpuCount
1961

    
1962
ispecDiskCount :: String
1963
ispecDiskCount = ConstantUtils.ispecDiskCount
1964

    
1965
ispecDiskSize :: String
1966
ispecDiskSize = ConstantUtils.ispecDiskSize
1967

    
1968
ispecNicCount :: String
1969
ispecNicCount = ConstantUtils.ispecNicCount
1970

    
1971
ispecSpindleUse :: String
1972
ispecSpindleUse = ConstantUtils.ispecSpindleUse
1973

    
1974
ispecsParameterTypes :: Map String VType
1975
ispecsParameterTypes =
1976
  Map.fromList
1977
  [(ConstantUtils.ispecDiskSize, VTypeInt),
1978
   (ConstantUtils.ispecCpuCount, VTypeInt),
1979
   (ConstantUtils.ispecSpindleUse, VTypeInt),
1980
   (ConstantUtils.ispecMemSize, VTypeInt),
1981
   (ConstantUtils.ispecNicCount, VTypeInt),
1982
   (ConstantUtils.ispecDiskCount, VTypeInt)]
1983

    
1984
ispecsParameters :: FrozenSet String
1985
ispecsParameters =
1986
  ConstantUtils.mkSet [ConstantUtils.ispecCpuCount,
1987
                       ConstantUtils.ispecDiskCount,
1988
                       ConstantUtils.ispecDiskSize,
1989
                       ConstantUtils.ispecMemSize,
1990
                       ConstantUtils.ispecNicCount,
1991
                       ConstantUtils.ispecSpindleUse]
1992

    
1993
ispecsMinmax :: String
1994
ispecsMinmax = ConstantUtils.ispecsMinmax
1995

    
1996
ispecsMax :: String
1997
ispecsMax = "max"
1998

    
1999
ispecsMin :: String
2000
ispecsMin = "min"
2001

    
2002
ispecsStd :: String
2003
ispecsStd = ConstantUtils.ispecsStd
2004

    
2005
ipolicyDts :: String
2006
ipolicyDts = ConstantUtils.ipolicyDts
2007

    
2008
ipolicyVcpuRatio :: String
2009
ipolicyVcpuRatio = ConstantUtils.ipolicyVcpuRatio
2010

    
2011
ipolicySpindleRatio :: String
2012
ipolicySpindleRatio = ConstantUtils.ipolicySpindleRatio
2013

    
2014
ispecsMinmaxKeys :: FrozenSet String
2015
ispecsMinmaxKeys = ConstantUtils.mkSet [ispecsMax, ispecsMin]
2016

    
2017
ipolicyParameters :: FrozenSet String
2018
ipolicyParameters =
2019
  ConstantUtils.mkSet [ConstantUtils.ipolicyVcpuRatio,
2020
                       ConstantUtils.ipolicySpindleRatio]
2021

    
2022
ipolicyAllKeys :: FrozenSet String
2023
ipolicyAllKeys =
2024
  ConstantUtils.union ipolicyParameters $
2025
  ConstantUtils.mkSet [ConstantUtils.ipolicyDts,
2026
                       ConstantUtils.ispecsMinmax,
2027
                       ispecsStd]
2028

    
2029
-- | Node parameter names
2030

    
2031
ndExclusiveStorage :: String
2032
ndExclusiveStorage = "exclusive_storage"
2033

    
2034
ndOobProgram :: String
2035
ndOobProgram = "oob_program"
2036

    
2037
ndSpindleCount :: String
2038
ndSpindleCount = "spindle_count"
2039

    
2040
ndOvs :: String
2041
ndOvs = "ovs"
2042

    
2043
ndOvsLink :: String
2044
ndOvsLink = "ovs_link"
2045

    
2046
ndOvsName :: String
2047
ndOvsName = "ovs_name"
2048

    
2049
ndSshPort :: String
2050
ndSshPort = "ssh_port"
2051

    
2052
ndsParameterTypes :: Map String VType
2053
ndsParameterTypes =
2054
  Map.fromList
2055
  [(ndExclusiveStorage, VTypeBool),
2056
   (ndOobProgram, VTypeString),
2057
   (ndOvs, VTypeBool),
2058
   (ndOvsLink, VTypeMaybeString),
2059
   (ndOvsName, VTypeMaybeString),
2060
   (ndSpindleCount, VTypeInt),
2061
   (ndSshPort, VTypeInt)]
2062

    
2063
ndsParameters :: FrozenSet String
2064
ndsParameters = ConstantUtils.mkSet (Map.keys ndsParameterTypes)
2065

    
2066
ndsParameterTitles :: Map String String
2067
ndsParameterTitles =
2068
  Map.fromList
2069
  [(ndExclusiveStorage, "ExclusiveStorage"),
2070
   (ndOobProgram, "OutOfBandProgram"),
2071
   (ndOvs, "OpenvSwitch"),
2072
   (ndOvsLink, "OpenvSwitchLink"),
2073
   (ndOvsName, "OpenvSwitchName"),
2074
   (ndSpindleCount, "SpindleCount")]
2075

    
2076
-- * Logical Disks parameters
2077

    
2078
ldpAccess :: String
2079
ldpAccess = "access"
2080

    
2081
ldpBarriers :: String
2082
ldpBarriers = "disabled-barriers"
2083

    
2084
ldpDefaultMetavg :: String
2085
ldpDefaultMetavg = "default-metavg"
2086

    
2087
ldpDelayTarget :: String
2088
ldpDelayTarget = "c-delay-target"
2089

    
2090
ldpDiskCustom :: String
2091
ldpDiskCustom = "disk-custom"
2092

    
2093
ldpDynamicResync :: String
2094
ldpDynamicResync = "dynamic-resync"
2095

    
2096
ldpFillTarget :: String
2097
ldpFillTarget = "c-fill-target"
2098

    
2099
ldpMaxRate :: String
2100
ldpMaxRate = "c-max-rate"
2101

    
2102
ldpMinRate :: String
2103
ldpMinRate = "c-min-rate"
2104

    
2105
ldpNetCustom :: String
2106
ldpNetCustom = "net-custom"
2107

    
2108
ldpNoMetaFlush :: String
2109
ldpNoMetaFlush = "disable-meta-flush"
2110

    
2111
ldpPlanAhead :: String
2112
ldpPlanAhead = "c-plan-ahead"
2113

    
2114
ldpPool :: String
2115
ldpPool = "pool"
2116

    
2117
ldpProtocol :: String
2118
ldpProtocol = "protocol"
2119

    
2120
ldpResyncRate :: String
2121
ldpResyncRate = "resync-rate"
2122

    
2123
ldpStripes :: String
2124
ldpStripes = "stripes"
2125

    
2126
diskLdTypes :: Map String VType
2127
diskLdTypes =
2128
  Map.fromList
2129
  [(ldpAccess, VTypeString),
2130
   (ldpResyncRate, VTypeInt),
2131
   (ldpStripes, VTypeInt),
2132
   (ldpBarriers, VTypeString),
2133
   (ldpNoMetaFlush, VTypeBool),
2134
   (ldpDefaultMetavg, VTypeString),
2135
   (ldpDiskCustom, VTypeString),
2136
   (ldpNetCustom, VTypeString),
2137
   (ldpProtocol, VTypeString),
2138
   (ldpDynamicResync, VTypeBool),
2139
   (ldpPlanAhead, VTypeInt),
2140
   (ldpFillTarget, VTypeInt),
2141
   (ldpDelayTarget, VTypeInt),
2142
   (ldpMaxRate, VTypeInt),
2143
   (ldpMinRate, VTypeInt),
2144
   (ldpPool, VTypeString)]
2145

    
2146
diskLdParameters :: FrozenSet String
2147
diskLdParameters = ConstantUtils.mkSet (Map.keys diskLdTypes)
2148

    
2149
-- * Disk template parameters
2150
--
2151
-- Disk template parameters can be set/changed by the user via
2152
-- gnt-cluster and gnt-group)
2153

    
2154
drbdResyncRate :: String
2155
drbdResyncRate = "resync-rate"
2156

    
2157
drbdDataStripes :: String
2158
drbdDataStripes = "data-stripes"
2159

    
2160
drbdMetaStripes :: String
2161
drbdMetaStripes = "meta-stripes"
2162

    
2163
drbdDiskBarriers :: String
2164
drbdDiskBarriers = "disk-barriers"
2165

    
2166
drbdMetaBarriers :: String
2167
drbdMetaBarriers = "meta-barriers"
2168

    
2169
drbdDefaultMetavg :: String
2170
drbdDefaultMetavg = "metavg"
2171

    
2172
drbdDiskCustom :: String
2173
drbdDiskCustom = "disk-custom"
2174

    
2175
drbdNetCustom :: String
2176
drbdNetCustom = "net-custom"
2177

    
2178
drbdProtocol :: String
2179
drbdProtocol = "protocol"
2180

    
2181
drbdDynamicResync :: String
2182
drbdDynamicResync = "dynamic-resync"
2183

    
2184
drbdPlanAhead :: String
2185
drbdPlanAhead = "c-plan-ahead"
2186

    
2187
drbdFillTarget :: String
2188
drbdFillTarget = "c-fill-target"
2189

    
2190
drbdDelayTarget :: String
2191
drbdDelayTarget = "c-delay-target"
2192

    
2193
drbdMaxRate :: String
2194
drbdMaxRate = "c-max-rate"
2195

    
2196
drbdMinRate :: String
2197
drbdMinRate = "c-min-rate"
2198

    
2199
lvStripes :: String
2200
lvStripes = "stripes"
2201

    
2202
rbdAccess :: String
2203
rbdAccess = "access"
2204

    
2205
rbdPool :: String
2206
rbdPool = "pool"
2207

    
2208
diskDtTypes :: Map String VType
2209
diskDtTypes =
2210
  Map.fromList [(drbdResyncRate, VTypeInt),
2211
                (drbdDataStripes, VTypeInt),
2212
                (drbdMetaStripes, VTypeInt),
2213
                (drbdDiskBarriers, VTypeString),
2214
                (drbdMetaBarriers, VTypeBool),
2215
                (drbdDefaultMetavg, VTypeString),
2216
                (drbdDiskCustom, VTypeString),
2217
                (drbdNetCustom, VTypeString),
2218
                (drbdProtocol, VTypeString),
2219
                (drbdDynamicResync, VTypeBool),
2220
                (drbdPlanAhead, VTypeInt),
2221
                (drbdFillTarget, VTypeInt),
2222
                (drbdDelayTarget, VTypeInt),
2223
                (drbdMaxRate, VTypeInt),
2224
                (drbdMinRate, VTypeInt),
2225
                (lvStripes, VTypeInt),
2226
                (rbdAccess, VTypeString),
2227
                (rbdPool, VTypeString),
2228
                (glusterHost, VTypeString),
2229
                (glusterVolume, VTypeString),
2230
                (glusterPort, VTypeInt)
2231
               ]
2232

    
2233
diskDtParameters :: FrozenSet String
2234
diskDtParameters = ConstantUtils.mkSet (Map.keys diskDtTypes)
2235

    
2236
-- * Dynamic disk parameters
2237

    
2238
ddpLocalIp :: String
2239
ddpLocalIp = "local-ip"
2240

    
2241
ddpRemoteIp :: String
2242
ddpRemoteIp = "remote-ip"
2243

    
2244
ddpPort :: String
2245
ddpPort = "port"
2246

    
2247
ddpLocalMinor :: String
2248
ddpLocalMinor = "local-minor"
2249

    
2250
ddpRemoteMinor :: String
2251
ddpRemoteMinor = "remote-minor"
2252

    
2253
-- * OOB supported commands
2254

    
2255
oobPowerOn :: String
2256
oobPowerOn = Types.oobCommandToRaw OobPowerOn
2257

    
2258
oobPowerOff :: String
2259
oobPowerOff = Types.oobCommandToRaw OobPowerOff
2260

    
2261
oobPowerCycle :: String
2262
oobPowerCycle = Types.oobCommandToRaw OobPowerCycle
2263

    
2264
oobPowerStatus :: String
2265
oobPowerStatus = Types.oobCommandToRaw OobPowerStatus
2266

    
2267
oobHealth :: String
2268
oobHealth = Types.oobCommandToRaw OobHealth
2269

    
2270
oobCommands :: FrozenSet String
2271
oobCommands = ConstantUtils.mkSet $ map Types.oobCommandToRaw [minBound..]
2272

    
2273
oobPowerStatusPowered :: String
2274
oobPowerStatusPowered = "powered"
2275

    
2276
-- | 60 seconds
2277
oobTimeout :: Int
2278
oobTimeout = 60
2279

    
2280
-- | 2 seconds
2281
oobPowerDelay :: Double
2282
oobPowerDelay = 2.0
2283

    
2284
oobStatusCritical :: String
2285
oobStatusCritical = Types.oobStatusToRaw OobStatusCritical
2286

    
2287
oobStatusOk :: String
2288
oobStatusOk = Types.oobStatusToRaw OobStatusOk
2289

    
2290
oobStatusUnknown :: String
2291
oobStatusUnknown = Types.oobStatusToRaw OobStatusUnknown
2292

    
2293
oobStatusWarning :: String
2294
oobStatusWarning = Types.oobStatusToRaw OobStatusWarning
2295

    
2296
oobStatuses :: FrozenSet String
2297
oobStatuses = ConstantUtils.mkSet $ map Types.oobStatusToRaw [minBound..]
2298

    
2299
-- | Instance Parameters Profile
2300
ppDefault :: String
2301
ppDefault = "default"
2302

    
2303
-- * nic* constants are used inside the ganeti config
2304

    
2305
nicLink :: String
2306
nicLink = "link"
2307

    
2308
nicMode :: String
2309
nicMode = "mode"
2310

    
2311
nicVlan :: String
2312
nicVlan = "vlan"
2313

    
2314
nicsParameterTypes :: Map String VType
2315
nicsParameterTypes =
2316
  Map.fromList [(nicMode, vtypeString),
2317
                (nicLink, vtypeString),
2318
                (nicVlan, vtypeString)]
2319

    
2320
nicsParameters :: FrozenSet String
2321
nicsParameters = ConstantUtils.mkSet (Map.keys nicsParameterTypes)
2322

    
2323
nicModeBridged :: String
2324
nicModeBridged = Types.nICModeToRaw NMBridged
2325

    
2326
nicModeRouted :: String
2327
nicModeRouted = Types.nICModeToRaw NMRouted
2328

    
2329
nicModeOvs :: String
2330
nicModeOvs = Types.nICModeToRaw NMOvs
2331

    
2332
nicIpPool :: String
2333
nicIpPool = Types.nICModeToRaw NMPool
2334

    
2335
nicValidModes :: FrozenSet String
2336
nicValidModes = ConstantUtils.mkSet $ map Types.nICModeToRaw [minBound..]
2337

    
2338
releaseAction :: String
2339
releaseAction = "release"
2340

    
2341
reserveAction :: String
2342
reserveAction = "reserve"
2343

    
2344
-- * idisk* constants are used in opcodes, to create/change disks
2345

    
2346
idiskAdopt :: String
2347
idiskAdopt = "adopt"
2348

    
2349
idiskMetavg :: String
2350
idiskMetavg = "metavg"
2351

    
2352
idiskMode :: String
2353
idiskMode = "mode"
2354

    
2355
idiskName :: String
2356
idiskName = "name"
2357

    
2358
idiskSize :: String
2359
idiskSize = "size"
2360

    
2361
idiskSpindles :: String
2362
idiskSpindles = "spindles"
2363

    
2364
idiskVg :: String
2365
idiskVg = "vg"
2366

    
2367
idiskProvider :: String
2368
idiskProvider = "provider"
2369

    
2370
idiskParamsTypes :: Map String VType
2371
idiskParamsTypes =
2372
  Map.fromList [(idiskSize, VTypeSize),
2373
                (idiskSpindles, VTypeInt),
2374
                (idiskMode, VTypeString),
2375
                (idiskAdopt, VTypeString),
2376
                (idiskVg, VTypeString),
2377
                (idiskMetavg, VTypeString),
2378
                (idiskProvider, VTypeString),
2379
                (idiskName, VTypeMaybeString)]
2380

    
2381
idiskParams :: FrozenSet String
2382
idiskParams = ConstantUtils.mkSet (Map.keys idiskParamsTypes)
2383

    
2384
modifiableIdiskParamsTypes :: Map String VType
2385
modifiableIdiskParamsTypes =
2386
  Map.fromList [(idiskMode, VTypeString),
2387
                (idiskName, VTypeString)]
2388

    
2389
modifiableIdiskParams :: FrozenSet String
2390
modifiableIdiskParams =
2391
  ConstantUtils.mkSet (Map.keys modifiableIdiskParamsTypes)
2392

    
2393
-- * inic* constants are used in opcodes, to create/change nics
2394

    
2395
inicBridge :: String
2396
inicBridge = "bridge"
2397

    
2398
inicIp :: String
2399
inicIp = "ip"
2400

    
2401
inicLink :: String
2402
inicLink = "link"
2403

    
2404
inicMac :: String
2405
inicMac = "mac"
2406

    
2407
inicMode :: String
2408
inicMode = "mode"
2409

    
2410
inicName :: String
2411
inicName = "name"
2412

    
2413
inicNetwork :: String
2414
inicNetwork = "network"
2415

    
2416
inicVlan :: String
2417
inicVlan = "vlan"
2418

    
2419
inicParamsTypes :: Map String VType
2420
inicParamsTypes =
2421
  Map.fromList [(inicBridge, VTypeMaybeString),
2422
                (inicIp, VTypeMaybeString),
2423
                (inicLink, VTypeString),
2424
                (inicMac, VTypeString),
2425
                (inicMode, VTypeString),
2426
                (inicName, VTypeMaybeString),
2427
                (inicNetwork, VTypeMaybeString),
2428
                (inicVlan, VTypeMaybeString)]
2429

    
2430
inicParams :: FrozenSet String
2431
inicParams = ConstantUtils.mkSet (Map.keys inicParamsTypes)
2432

    
2433
-- * Hypervisor constants
2434

    
2435
htXenPvm :: String
2436
htXenPvm = Types.hypervisorToRaw XenPvm
2437

    
2438
htFake :: String
2439
htFake = Types.hypervisorToRaw Fake
2440

    
2441
htXenHvm :: String
2442
htXenHvm = Types.hypervisorToRaw XenHvm
2443

    
2444
htKvm :: String
2445
htKvm = Types.hypervisorToRaw Kvm
2446

    
2447
htChroot :: String
2448
htChroot = Types.hypervisorToRaw Chroot
2449

    
2450
htLxc :: String
2451
htLxc = Types.hypervisorToRaw Lxc
2452

    
2453
hyperTypes :: FrozenSet String
2454
hyperTypes = ConstantUtils.mkSet $ map Types.hypervisorToRaw [minBound..]
2455

    
2456
htsReqPort :: FrozenSet String
2457
htsReqPort = ConstantUtils.mkSet [htXenHvm, htKvm]
2458

    
2459
vncBasePort :: Int
2460
vncBasePort = 5900
2461

    
2462
vncDefaultBindAddress :: String
2463
vncDefaultBindAddress = ip4AddressAny
2464

    
2465
-- * NIC types
2466

    
2467
htNicE1000 :: String
2468
htNicE1000 = "e1000"
2469

    
2470
htNicI82551 :: String
2471
htNicI82551 = "i82551"
2472

    
2473
htNicI8259er :: String
2474
htNicI8259er = "i82559er"
2475

    
2476
htNicI85557b :: String
2477
htNicI85557b = "i82557b"
2478

    
2479
htNicNe2kIsa :: String
2480
htNicNe2kIsa = "ne2k_isa"
2481

    
2482
htNicNe2kPci :: String
2483
htNicNe2kPci = "ne2k_pci"
2484

    
2485
htNicParavirtual :: String
2486
htNicParavirtual = "paravirtual"
2487

    
2488
htNicPcnet :: String
2489
htNicPcnet = "pcnet"
2490

    
2491
htNicRtl8139 :: String
2492
htNicRtl8139 = "rtl8139"
2493

    
2494
htHvmValidNicTypes :: FrozenSet String
2495
htHvmValidNicTypes =
2496
  ConstantUtils.mkSet [htNicE1000,
2497
                       htNicNe2kIsa,
2498
                       htNicNe2kPci,
2499
                       htNicParavirtual,
2500
                       htNicRtl8139]
2501

    
2502
htKvmValidNicTypes :: FrozenSet String
2503
htKvmValidNicTypes =
2504
  ConstantUtils.mkSet [htNicE1000,
2505
                       htNicI82551,
2506
                       htNicI8259er,
2507
                       htNicI85557b,
2508
                       htNicNe2kIsa,
2509
                       htNicNe2kPci,
2510
                       htNicParavirtual,
2511
                       htNicPcnet,
2512
                       htNicRtl8139]
2513

    
2514
-- * Vif types
2515

    
2516
-- | Default vif type in xen-hvm
2517
htHvmVifIoemu :: String
2518
htHvmVifIoemu = "ioemu"
2519

    
2520
htHvmVifVif :: String
2521
htHvmVifVif = "vif"
2522

    
2523
htHvmValidVifTypes :: FrozenSet String
2524
htHvmValidVifTypes = ConstantUtils.mkSet [htHvmVifIoemu, htHvmVifVif]
2525

    
2526
-- * Disk types
2527

    
2528
htDiskIde :: String
2529
htDiskIde = "ide"
2530

    
2531
htDiskIoemu :: String
2532
htDiskIoemu = "ioemu"
2533

    
2534
htDiskMtd :: String
2535
htDiskMtd = "mtd"
2536

    
2537
htDiskParavirtual :: String
2538
htDiskParavirtual = "paravirtual"
2539

    
2540
htDiskPflash :: String
2541
htDiskPflash = "pflash"
2542

    
2543
htDiskScsi :: String
2544
htDiskScsi = "scsi"
2545

    
2546
htDiskSd :: String
2547
htDiskSd = "sd"
2548

    
2549
htHvmValidDiskTypes :: FrozenSet String
2550
htHvmValidDiskTypes = ConstantUtils.mkSet [htDiskIoemu, htDiskParavirtual]
2551

    
2552
htKvmValidDiskTypes :: FrozenSet String
2553
htKvmValidDiskTypes =
2554
  ConstantUtils.mkSet [htDiskIde,
2555
                       htDiskMtd,
2556
                       htDiskParavirtual,
2557
                       htDiskPflash,
2558
                       htDiskScsi,
2559
                       htDiskSd]
2560

    
2561
htCacheDefault :: String
2562
htCacheDefault = "default"
2563

    
2564
htCacheNone :: String
2565
htCacheNone = "none"
2566

    
2567
htCacheWback :: String
2568
htCacheWback = "writeback"
2569

    
2570
htCacheWthrough :: String
2571
htCacheWthrough = "writethrough"
2572

    
2573
htValidCacheTypes :: FrozenSet String
2574
htValidCacheTypes =
2575
  ConstantUtils.mkSet [htCacheDefault,
2576
                       htCacheNone,
2577
                       htCacheWback,
2578
                       htCacheWthrough]
2579

    
2580
-- * Mouse types
2581

    
2582
htMouseMouse :: String
2583
htMouseMouse = "mouse"
2584

    
2585
htMouseTablet :: String
2586
htMouseTablet = "tablet"
2587

    
2588
htKvmValidMouseTypes :: FrozenSet String
2589
htKvmValidMouseTypes = ConstantUtils.mkSet [htMouseMouse, htMouseTablet]
2590

    
2591
-- * Boot order
2592

    
2593
htBoCdrom :: String
2594
htBoCdrom = "cdrom"
2595

    
2596
htBoDisk :: String
2597
htBoDisk = "disk"
2598

    
2599
htBoFloppy :: String
2600
htBoFloppy = "floppy"
2601

    
2602
htBoNetwork :: String
2603
htBoNetwork = "network"
2604

    
2605
htKvmValidBoTypes :: FrozenSet String
2606
htKvmValidBoTypes =
2607
  ConstantUtils.mkSet [htBoCdrom, htBoDisk, htBoFloppy, htBoNetwork]
2608

    
2609
-- * SPICE lossless image compression options
2610

    
2611
htKvmSpiceLosslessImgComprAutoGlz :: String
2612
htKvmSpiceLosslessImgComprAutoGlz = "auto_glz"
2613

    
2614
htKvmSpiceLosslessImgComprAutoLz :: String
2615
htKvmSpiceLosslessImgComprAutoLz = "auto_lz"
2616

    
2617
htKvmSpiceLosslessImgComprGlz :: String
2618
htKvmSpiceLosslessImgComprGlz = "glz"
2619

    
2620
htKvmSpiceLosslessImgComprLz :: String
2621
htKvmSpiceLosslessImgComprLz = "lz"
2622

    
2623
htKvmSpiceLosslessImgComprOff :: String
2624
htKvmSpiceLosslessImgComprOff = "off"
2625

    
2626
htKvmSpiceLosslessImgComprQuic :: String
2627
htKvmSpiceLosslessImgComprQuic = "quic"
2628

    
2629
htKvmSpiceValidLosslessImgComprOptions :: FrozenSet String
2630
htKvmSpiceValidLosslessImgComprOptions =
2631
  ConstantUtils.mkSet [htKvmSpiceLosslessImgComprAutoGlz,
2632
                       htKvmSpiceLosslessImgComprAutoLz,
2633
                       htKvmSpiceLosslessImgComprGlz,
2634
                       htKvmSpiceLosslessImgComprLz,
2635
                       htKvmSpiceLosslessImgComprOff,
2636
                       htKvmSpiceLosslessImgComprQuic]
2637

    
2638
htKvmSpiceLossyImgComprAlways :: String
2639
htKvmSpiceLossyImgComprAlways = "always"
2640

    
2641
htKvmSpiceLossyImgComprAuto :: String
2642
htKvmSpiceLossyImgComprAuto = "auto"
2643

    
2644
htKvmSpiceLossyImgComprNever :: String
2645
htKvmSpiceLossyImgComprNever = "never"
2646

    
2647
htKvmSpiceValidLossyImgComprOptions :: FrozenSet String
2648
htKvmSpiceValidLossyImgComprOptions =
2649
  ConstantUtils.mkSet [htKvmSpiceLossyImgComprAlways,
2650
                       htKvmSpiceLossyImgComprAuto,
2651
                       htKvmSpiceLossyImgComprNever]
2652

    
2653
-- * SPICE video stream detection
2654

    
2655
htKvmSpiceVideoStreamDetectionAll :: String
2656
htKvmSpiceVideoStreamDetectionAll = "all"
2657

    
2658
htKvmSpiceVideoStreamDetectionFilter :: String
2659
htKvmSpiceVideoStreamDetectionFilter = "filter"
2660

    
2661
htKvmSpiceVideoStreamDetectionOff :: String
2662
htKvmSpiceVideoStreamDetectionOff = "off"
2663

    
2664
htKvmSpiceValidVideoStreamDetectionOptions :: FrozenSet String
2665
htKvmSpiceValidVideoStreamDetectionOptions =
2666
  ConstantUtils.mkSet [htKvmSpiceVideoStreamDetectionAll,
2667
                       htKvmSpiceVideoStreamDetectionFilter,
2668
                       htKvmSpiceVideoStreamDetectionOff]
2669

    
2670
-- * Security models
2671

    
2672
htSmNone :: String
2673
htSmNone = "none"
2674

    
2675
htSmPool :: String
2676
htSmPool = "pool"
2677

    
2678
htSmUser :: String
2679
htSmUser = "user"
2680

    
2681
htKvmValidSmTypes :: FrozenSet String
2682
htKvmValidSmTypes = ConstantUtils.mkSet [htSmNone, htSmPool, htSmUser]
2683

    
2684
-- * Kvm flag values
2685

    
2686
htKvmDisabled :: String
2687
htKvmDisabled = "disabled"
2688

    
2689
htKvmEnabled :: String
2690
htKvmEnabled = "enabled"
2691

    
2692
htKvmFlagValues :: FrozenSet String
2693
htKvmFlagValues = ConstantUtils.mkSet [htKvmDisabled, htKvmEnabled]
2694

    
2695
-- * Migration type
2696

    
2697
htMigrationLive :: String
2698
htMigrationLive = Types.migrationModeToRaw MigrationLive
2699

    
2700
htMigrationNonlive :: String
2701
htMigrationNonlive = Types.migrationModeToRaw MigrationNonLive
2702

    
2703
htMigrationModes :: FrozenSet String
2704
htMigrationModes =
2705
  ConstantUtils.mkSet $ map Types.migrationModeToRaw [minBound..]
2706

    
2707
-- * Cluster verify steps
2708

    
2709
verifyNplusoneMem :: String
2710
verifyNplusoneMem = Types.verifyOptionalChecksToRaw VerifyNPlusOneMem
2711

    
2712
verifyOptionalChecks :: FrozenSet String
2713
verifyOptionalChecks =
2714
  ConstantUtils.mkSet $ map Types.verifyOptionalChecksToRaw [minBound..]
2715

    
2716
-- * Cluster Verify error classes
2717

    
2718
cvTcluster :: String
2719
cvTcluster = "cluster"
2720

    
2721
cvTgroup :: String
2722
cvTgroup = "group"
2723

    
2724
cvTnode :: String
2725
cvTnode = "node"
2726

    
2727
cvTinstance :: String
2728
cvTinstance = "instance"
2729

    
2730
-- * Cluster Verify error levels
2731

    
2732
cvWarning :: String
2733
cvWarning = "WARNING"
2734

    
2735
cvError :: String
2736
cvError = "ERROR"
2737

    
2738
-- * Cluster Verify error codes and documentation
2739

    
2740
cvEclustercert :: (String, String, String)
2741
cvEclustercert =
2742
  ("cluster",
2743
   Types.cVErrorCodeToRaw CvECLUSTERCERT,
2744
   "Cluster certificate files verification failure")
2745

    
2746
cvEclusterclientcert :: (String, String, String)
2747
cvEclusterclientcert =
2748
  ("cluster",
2749
   Types.cVErrorCodeToRaw CvECLUSTERCLIENTCERT,
2750
   "Cluster client certificate files verification failure")
2751

    
2752
cvEclustercfg :: (String, String, String)
2753
cvEclustercfg =
2754
  ("cluster",
2755
   Types.cVErrorCodeToRaw CvECLUSTERCFG,
2756
   "Cluster configuration verification failure")
2757

    
2758
cvEclusterdanglinginst :: (String, String, String)
2759
cvEclusterdanglinginst =
2760
  ("node",
2761
   Types.cVErrorCodeToRaw CvECLUSTERDANGLINGINST,
2762
   "Some instances have a non-existing primary node")
2763

    
2764
cvEclusterdanglingnodes :: (String, String, String)
2765
cvEclusterdanglingnodes =
2766
  ("node",
2767
   Types.cVErrorCodeToRaw CvECLUSTERDANGLINGNODES,
2768
   "Some nodes belong to non-existing groups")
2769

    
2770
cvEclusterfilecheck :: (String, String, String)
2771
cvEclusterfilecheck =
2772
  ("cluster",
2773
   Types.cVErrorCodeToRaw CvECLUSTERFILECHECK,
2774
   "Cluster configuration verification failure")
2775

    
2776
cvEgroupdifferentpvsize :: (String, String, String)
2777
cvEgroupdifferentpvsize =
2778
  ("group",
2779
   Types.cVErrorCodeToRaw CvEGROUPDIFFERENTPVSIZE,
2780
   "PVs in the group have different sizes")
2781

    
2782
cvEinstancebadnode :: (String, String, String)
2783
cvEinstancebadnode =
2784
  ("instance",
2785
   Types.cVErrorCodeToRaw CvEINSTANCEBADNODE,
2786
   "Instance marked as running lives on an offline node")
2787

    
2788
cvEinstancedown :: (String, String, String)
2789
cvEinstancedown =
2790
  ("instance",
2791
   Types.cVErrorCodeToRaw CvEINSTANCEDOWN,
2792
   "Instance not running on its primary node")
2793

    
2794
cvEinstancefaultydisk :: (String, String, String)
2795
cvEinstancefaultydisk =
2796
  ("instance",
2797
   Types.cVErrorCodeToRaw CvEINSTANCEFAULTYDISK,
2798
   "Impossible to retrieve status for a disk")
2799

    
2800
cvEinstancelayout :: (String, String, String)
2801
cvEinstancelayout =
2802
  ("instance",
2803
   Types.cVErrorCodeToRaw CvEINSTANCELAYOUT,
2804
   "Instance has multiple secondary nodes")
2805

    
2806
cvEinstancemissingcfgparameter :: (String, String, String)
2807
cvEinstancemissingcfgparameter =
2808
  ("instance",
2809
   Types.cVErrorCodeToRaw CvEINSTANCEMISSINGCFGPARAMETER,
2810
   "A configuration parameter for an instance is missing")
2811

    
2812
cvEinstancemissingdisk :: (String, String, String)
2813
cvEinstancemissingdisk =
2814
  ("instance",
2815
   Types.cVErrorCodeToRaw CvEINSTANCEMISSINGDISK,
2816
   "Missing volume on an instance")
2817

    
2818
cvEinstancepolicy :: (String, String, String)
2819
cvEinstancepolicy =
2820
  ("instance",
2821
   Types.cVErrorCodeToRaw CvEINSTANCEPOLICY,
2822
   "Instance does not meet policy")
2823

    
2824
cvEinstancesplitgroups :: (String, String, String)
2825
cvEinstancesplitgroups =
2826
  ("instance",
2827
   Types.cVErrorCodeToRaw CvEINSTANCESPLITGROUPS,
2828
   "Instance with primary and secondary nodes in different groups")
2829

    
2830
cvEinstanceunsuitablenode :: (String, String, String)
2831
cvEinstanceunsuitablenode =
2832
  ("instance",
2833
   Types.cVErrorCodeToRaw CvEINSTANCEUNSUITABLENODE,
2834
   "Instance running on nodes that are not suitable for it")
2835

    
2836
cvEinstancewrongnode :: (String, String, String)
2837
cvEinstancewrongnode =
2838
  ("instance",
2839
   Types.cVErrorCodeToRaw CvEINSTANCEWRONGNODE,
2840
   "Instance running on the wrong node")
2841

    
2842
cvEnodedrbd :: (String, String, String)
2843
cvEnodedrbd =
2844
  ("node",
2845
   Types.cVErrorCodeToRaw CvENODEDRBD,
2846
   "Error parsing the DRBD status file")
2847

    
2848
cvEnodedrbdhelper :: (String, String, String)
2849
cvEnodedrbdhelper =
2850
  ("node",
2851
   Types.cVErrorCodeToRaw CvENODEDRBDHELPER,
2852
   "Error caused by the DRBD helper")
2853

    
2854
cvEnodedrbdversion :: (String, String, String)
2855
cvEnodedrbdversion =
2856
  ("node",
2857
   Types.cVErrorCodeToRaw CvENODEDRBDVERSION,
2858
   "DRBD version mismatch within a node group")
2859

    
2860
cvEnodefilecheck :: (String, String, String)
2861
cvEnodefilecheck =
2862
  ("node",
2863
   Types.cVErrorCodeToRaw CvENODEFILECHECK,
2864
   "Error retrieving the checksum of the node files")
2865

    
2866
cvEnodefilestoragepaths :: (String, String, String)
2867
cvEnodefilestoragepaths =
2868
  ("node",
2869
   Types.cVErrorCodeToRaw CvENODEFILESTORAGEPATHS,
2870
   "Detected bad file storage paths")
2871

    
2872
cvEnodefilestoragepathunusable :: (String, String, String)
2873
cvEnodefilestoragepathunusable =
2874
  ("node",
2875
   Types.cVErrorCodeToRaw CvENODEFILESTORAGEPATHUNUSABLE,
2876
   "File storage path unusable")
2877

    
2878
cvEnodehooks :: (String, String, String)
2879
cvEnodehooks =
2880
  ("node",
2881
   Types.cVErrorCodeToRaw CvENODEHOOKS,
2882
   "Communication failure in hooks execution")
2883

    
2884
cvEnodehv :: (String, String, String)
2885
cvEnodehv =
2886
  ("node",
2887
   Types.cVErrorCodeToRaw CvENODEHV,
2888
   "Hypervisor parameters verification failure")
2889

    
2890
cvEnodelvm :: (String, String, String)
2891
cvEnodelvm =
2892
  ("node",
2893
   Types.cVErrorCodeToRaw CvENODELVM,
2894
   "LVM-related node error")
2895

    
2896
cvEnoden1 :: (String, String, String)
2897
cvEnoden1 =
2898
  ("node",
2899
   Types.cVErrorCodeToRaw CvENODEN1,
2900
   "Not enough memory to accommodate instance failovers")
2901

    
2902
cvEnodenet :: (String, String, String)
2903
cvEnodenet =
2904
  ("node",
2905
   Types.cVErrorCodeToRaw CvENODENET,
2906
   "Network-related node error")
2907

    
2908
cvEnodeoobpath :: (String, String, String)
2909
cvEnodeoobpath =
2910
  ("node",
2911
   Types.cVErrorCodeToRaw CvENODEOOBPATH,
2912
   "Invalid Out Of Band path")
2913

    
2914
cvEnodeorphaninstance :: (String, String, String)
2915
cvEnodeorphaninstance =
2916
  ("node",
2917
   Types.cVErrorCodeToRaw CvENODEORPHANINSTANCE,
2918
   "Unknown intance running on a node")
2919

    
2920
cvEnodeorphanlv :: (String, String, String)
2921
cvEnodeorphanlv =
2922
  ("node",
2923
   Types.cVErrorCodeToRaw CvENODEORPHANLV,
2924
   "Unknown LVM logical volume")
2925

    
2926
cvEnodeos :: (String, String, String)
2927
cvEnodeos =
2928
  ("node",
2929
   Types.cVErrorCodeToRaw CvENODEOS,
2930
   "OS-related node error")
2931

    
2932
cvEnoderpc :: (String, String, String)
2933
cvEnoderpc =
2934
  ("node",
2935
   Types.cVErrorCodeToRaw CvENODERPC,
2936
   "Error during connection to the primary node of an instance")
2937

    
2938
cvEnodesetup :: (String, String, String)
2939
cvEnodesetup =
2940
  ("node",
2941
   Types.cVErrorCodeToRaw CvENODESETUP,
2942
   "Node setup error")
2943

    
2944
cvEnodesharedfilestoragepathunusable :: (String, String, String)
2945
cvEnodesharedfilestoragepathunusable =
2946
  ("node",
2947
   Types.cVErrorCodeToRaw CvENODESHAREDFILESTORAGEPATHUNUSABLE,
2948
   "Shared file storage path unusable")
2949

    
2950
cvEnodessh :: (String, String, String)
2951
cvEnodessh =
2952
  ("node",
2953
   Types.cVErrorCodeToRaw CvENODESSH,
2954
   "SSH-related node error")
2955

    
2956
cvEnodetime :: (String, String, String)
2957
cvEnodetime =
2958
  ("node",
2959
   Types.cVErrorCodeToRaw CvENODETIME,
2960
   "Node returned invalid time")
2961

    
2962
cvEnodeuserscripts :: (String, String, String)
2963
cvEnodeuserscripts =
2964
  ("node",
2965
   Types.cVErrorCodeToRaw CvENODEUSERSCRIPTS,
2966
   "User scripts not present or not executable")
2967

    
2968
cvEnodeversion :: (String, String, String)
2969
cvEnodeversion =
2970
  ("node",
2971
   Types.cVErrorCodeToRaw CvENODEVERSION,
2972
   "Protocol version mismatch or Ganeti version mismatch")
2973

    
2974
cvAllEcodes :: FrozenSet (String, String, String)
2975
cvAllEcodes =
2976
  ConstantUtils.mkSet
2977
  [cvEclustercert,
2978
   cvEclustercfg,
2979
   cvEclusterdanglinginst,
2980
   cvEclusterdanglingnodes,
2981
   cvEclusterfilecheck,
2982
   cvEgroupdifferentpvsize,
2983
   cvEinstancebadnode,
2984
   cvEinstancedown,
2985
   cvEinstancefaultydisk,
2986
   cvEinstancelayout,
2987
   cvEinstancemissingcfgparameter,
2988
   cvEinstancemissingdisk,
2989
   cvEinstancepolicy,
2990
   cvEinstancesplitgroups,
2991
   cvEinstanceunsuitablenode,
2992
   cvEinstancewrongnode,
2993
   cvEnodedrbd,
2994
   cvEnodedrbdhelper,
2995
   cvEnodedrbdversion,
2996
   cvEnodefilecheck,
2997
   cvEnodefilestoragepaths,
2998
   cvEnodefilestoragepathunusable,
2999
   cvEnodehooks,
3000
   cvEnodehv,
3001
   cvEnodelvm,
3002
   cvEnoden1,
3003
   cvEnodenet,
3004
   cvEnodeoobpath,
3005
   cvEnodeorphaninstance,
3006
   cvEnodeorphanlv,
3007
   cvEnodeos,
3008
   cvEnoderpc,
3009
   cvEnodesetup,
3010
   cvEnodesharedfilestoragepathunusable,
3011
   cvEnodessh,
3012
   cvEnodetime,
3013
   cvEnodeuserscripts,
3014
   cvEnodeversion]
3015

    
3016
cvAllEcodesStrings :: FrozenSet String
3017
cvAllEcodesStrings =
3018
  ConstantUtils.mkSet $ map Types.cVErrorCodeToRaw [minBound..]
3019

    
3020
-- * Node verify constants
3021

    
3022
nvBridges :: String
3023
nvBridges = "bridges"
3024

    
3025
nvClientCert :: String
3026
nvClientCert = "client-cert"
3027

    
3028
nvDrbdhelper :: String
3029
nvDrbdhelper = "drbd-helper"
3030

    
3031
nvDrbdversion :: String
3032
nvDrbdversion = "drbd-version"
3033

    
3034
nvDrbdlist :: String
3035
nvDrbdlist = "drbd-list"
3036

    
3037
nvExclusivepvs :: String
3038
nvExclusivepvs = "exclusive-pvs"
3039

    
3040
nvFilelist :: String
3041
nvFilelist = "filelist"
3042

    
3043
nvAcceptedStoragePaths :: String
3044
nvAcceptedStoragePaths = "allowed-file-storage-paths"
3045

    
3046
nvFileStoragePath :: String
3047
nvFileStoragePath = "file-storage-path"
3048

    
3049
nvSharedFileStoragePath :: String
3050
nvSharedFileStoragePath = "shared-file-storage-path"
3051

    
3052
nvHvinfo :: String
3053
nvHvinfo = "hvinfo"
3054

    
3055
nvHvparams :: String
3056
nvHvparams = "hvparms"
3057

    
3058
nvHypervisor :: String
3059
nvHypervisor = "hypervisor"
3060

    
3061
nvInstancelist :: String
3062
nvInstancelist = "instancelist"
3063

    
3064
nvLvlist :: String
3065
nvLvlist = "lvlist"
3066

    
3067
nvMasterip :: String
3068
nvMasterip = "master-ip"
3069

    
3070
nvNodelist :: String
3071
nvNodelist = "nodelist"
3072

    
3073
nvNodenettest :: String
3074
nvNodenettest = "node-net-test"
3075

    
3076
nvNodesetup :: String
3077
nvNodesetup = "nodesetup"
3078

    
3079
nvOobPaths :: String
3080
nvOobPaths = "oob-paths"
3081

    
3082
nvOslist :: String
3083
nvOslist = "oslist"
3084

    
3085
nvPvlist :: String
3086
nvPvlist = "pvlist"
3087

    
3088
nvTime :: String
3089
nvTime = "time"
3090

    
3091
nvUserscripts :: String
3092
nvUserscripts = "user-scripts"
3093

    
3094
nvVersion :: String
3095
nvVersion = "version"
3096

    
3097
nvVglist :: String
3098
nvVglist = "vglist"
3099

    
3100
nvVmnodes :: String
3101
nvVmnodes = "vmnodes"
3102

    
3103
-- * Instance status
3104

    
3105
inststAdmindown :: String
3106
inststAdmindown = Types.instanceStatusToRaw StatusDown
3107

    
3108
inststAdminoffline :: String
3109
inststAdminoffline = Types.instanceStatusToRaw StatusOffline
3110

    
3111
inststErrordown :: String
3112
inststErrordown = Types.instanceStatusToRaw ErrorDown
3113

    
3114
inststErrorup :: String
3115
inststErrorup = Types.instanceStatusToRaw ErrorUp
3116

    
3117
inststNodedown :: String
3118
inststNodedown = Types.instanceStatusToRaw NodeDown
3119

    
3120
inststNodeoffline :: String
3121
inststNodeoffline = Types.instanceStatusToRaw NodeOffline
3122

    
3123
inststRunning :: String
3124
inststRunning = Types.instanceStatusToRaw Running
3125

    
3126
inststUserdown :: String
3127
inststUserdown = Types.instanceStatusToRaw UserDown
3128

    
3129
inststWrongnode :: String
3130
inststWrongnode = Types.instanceStatusToRaw WrongNode
3131

    
3132
inststAll :: FrozenSet String
3133
inststAll = ConstantUtils.mkSet $ map Types.instanceStatusToRaw [minBound..]
3134

    
3135
-- * Admin states
3136

    
3137
adminstDown :: String
3138
adminstDown = Types.adminStateToRaw AdminDown
3139

    
3140
adminstOffline :: String
3141
adminstOffline = Types.adminStateToRaw AdminOffline
3142

    
3143
adminstUp :: String
3144
adminstUp = Types.adminStateToRaw AdminUp
3145

    
3146
adminstAll :: FrozenSet String
3147
adminstAll = ConstantUtils.mkSet $ map Types.adminStateToRaw [minBound..]
3148

    
3149
-- * Node roles
3150

    
3151
nrDrained :: String
3152
nrDrained = Types.nodeRoleToRaw NRDrained
3153

    
3154
nrMaster :: String
3155
nrMaster = Types.nodeRoleToRaw NRMaster
3156

    
3157
nrMcandidate :: String
3158
nrMcandidate = Types.nodeRoleToRaw NRCandidate
3159

    
3160
nrOffline :: String
3161
nrOffline = Types.nodeRoleToRaw NROffline
3162

    
3163
nrRegular :: String
3164
nrRegular = Types.nodeRoleToRaw NRRegular
3165

    
3166
nrAll :: FrozenSet String
3167
nrAll = ConstantUtils.mkSet $ map Types.nodeRoleToRaw [minBound..]
3168

    
3169
-- * SSL certificate check constants (in days)
3170

    
3171
sslCertExpirationError :: Int
3172
sslCertExpirationError = 7
3173

    
3174
sslCertExpirationWarn :: Int
3175
sslCertExpirationWarn = 30
3176

    
3177
-- * Allocator framework constants
3178

    
3179
iallocatorVersion :: Int
3180
iallocatorVersion = 2
3181

    
3182
iallocatorDirIn :: String
3183
iallocatorDirIn = Types.iAllocatorTestDirToRaw IAllocatorDirIn
3184

    
3185
iallocatorDirOut :: String
3186
iallocatorDirOut = Types.iAllocatorTestDirToRaw IAllocatorDirOut
3187

    
3188
validIallocatorDirections :: FrozenSet String
3189
validIallocatorDirections =
3190
  ConstantUtils.mkSet $ map Types.iAllocatorTestDirToRaw [minBound..]
3191

    
3192
iallocatorModeAlloc :: String
3193
iallocatorModeAlloc = Types.iAllocatorModeToRaw IAllocatorAlloc
3194

    
3195
iallocatorModeChgGroup :: String
3196
iallocatorModeChgGroup = Types.iAllocatorModeToRaw IAllocatorChangeGroup
3197

    
3198
iallocatorModeMultiAlloc :: String
3199
iallocatorModeMultiAlloc = Types.iAllocatorModeToRaw IAllocatorMultiAlloc
3200

    
3201
iallocatorModeNodeEvac :: String
3202
iallocatorModeNodeEvac = Types.iAllocatorModeToRaw IAllocatorNodeEvac
3203

    
3204
iallocatorModeReloc :: String
3205
iallocatorModeReloc = Types.iAllocatorModeToRaw IAllocatorReloc
3206

    
3207
validIallocatorModes :: FrozenSet String
3208
validIallocatorModes =
3209
  ConstantUtils.mkSet $ map Types.iAllocatorModeToRaw [minBound..]
3210

    
3211
iallocatorSearchPath :: [String]
3212
iallocatorSearchPath = AutoConf.iallocatorSearchPath
3213

    
3214
defaultIallocatorShortcut :: String
3215
defaultIallocatorShortcut = "."
3216

    
3217
-- * Opportunistic allocator usage
3218

    
3219
-- | Time delay in seconds between repeated opportunistic instance creations.
3220
-- Rather than failing with an informative error message if the opportunistic
3221
-- creation cannot grab enough nodes, for some uses it is better to retry the
3222
-- creation with an interval between attempts. This is a reasonable default.
3223
defaultOpportunisticRetryInterval :: Int
3224
defaultOpportunisticRetryInterval = 30
3225

    
3226
-- * Node evacuation
3227

    
3228
nodeEvacPri :: String
3229
nodeEvacPri = Types.evacModeToRaw ChangePrimary
3230

    
3231
nodeEvacSec :: String
3232
nodeEvacSec = Types.evacModeToRaw ChangeSecondary
3233

    
3234
nodeEvacAll :: String
3235
nodeEvacAll = Types.evacModeToRaw ChangeAll
3236

    
3237
nodeEvacModes :: FrozenSet String
3238
nodeEvacModes = ConstantUtils.mkSet $ map Types.evacModeToRaw [minBound..]
3239

    
3240
-- * Job queue
3241

    
3242
jobQueueVersion :: Int
3243
jobQueueVersion = 1
3244

    
3245
jobQueueSizeHardLimit :: Int
3246
jobQueueSizeHardLimit = 5000
3247

    
3248
jobQueueFilesPerms :: Int
3249
jobQueueFilesPerms = 0o640
3250

    
3251
-- * Unchanged job return
3252

    
3253
jobNotchanged :: String
3254
jobNotchanged = "nochange"
3255

    
3256
-- * Job status
3257

    
3258
jobStatusQueued :: String
3259
jobStatusQueued = Types.jobStatusToRaw JOB_STATUS_QUEUED
3260

    
3261
jobStatusWaiting :: String
3262
jobStatusWaiting = Types.jobStatusToRaw JOB_STATUS_WAITING
3263

    
3264
jobStatusCanceling :: String
3265
jobStatusCanceling = Types.jobStatusToRaw JOB_STATUS_CANCELING
3266

    
3267
jobStatusRunning :: String
3268
jobStatusRunning = Types.jobStatusToRaw JOB_STATUS_RUNNING
3269

    
3270
jobStatusCanceled :: String
3271
jobStatusCanceled = Types.jobStatusToRaw JOB_STATUS_CANCELED
3272

    
3273
jobStatusSuccess :: String
3274
jobStatusSuccess = Types.jobStatusToRaw JOB_STATUS_SUCCESS
3275

    
3276
jobStatusError :: String
3277
jobStatusError = Types.jobStatusToRaw JOB_STATUS_ERROR
3278

    
3279
jobsPending :: FrozenSet String
3280
jobsPending =
3281
  ConstantUtils.mkSet [jobStatusQueued, jobStatusWaiting, jobStatusCanceling]
3282

    
3283
jobsFinalized :: FrozenSet String
3284
jobsFinalized =
3285
  ConstantUtils.mkSet $ map Types.finalizedJobStatusToRaw [minBound..]
3286

    
3287
jobStatusAll :: FrozenSet String
3288
jobStatusAll = ConstantUtils.mkSet $ map Types.jobStatusToRaw [minBound..]
3289

    
3290
-- * OpCode status
3291

    
3292
-- ** Not yet finalized opcodes
3293

    
3294
opStatusCanceling :: String
3295
opStatusCanceling = "canceling"
3296

    
3297
opStatusQueued :: String
3298
opStatusQueued = "queued"
3299

    
3300
opStatusRunning :: String
3301
opStatusRunning = "running"
3302

    
3303
opStatusWaiting :: String
3304
opStatusWaiting = "waiting"
3305

    
3306
-- ** Finalized opcodes
3307

    
3308
opStatusCanceled :: String
3309
opStatusCanceled = "canceled"
3310

    
3311
opStatusError :: String
3312
opStatusError = "error"
3313

    
3314
opStatusSuccess :: String
3315
opStatusSuccess = "success"
3316

    
3317
opsFinalized :: FrozenSet String
3318
opsFinalized =
3319
  ConstantUtils.mkSet [opStatusCanceled, opStatusError, opStatusSuccess]
3320

    
3321
-- * OpCode priority
3322

    
3323
opPrioLowest :: Int
3324
opPrioLowest = 19
3325

    
3326
opPrioHighest :: Int
3327
opPrioHighest = -20
3328

    
3329
opPrioLow :: Int
3330
opPrioLow = Types.opSubmitPriorityToRaw OpPrioLow
3331

    
3332
opPrioNormal :: Int
3333
opPrioNormal = Types.opSubmitPriorityToRaw OpPrioNormal
3334

    
3335
opPrioHigh :: Int
3336
opPrioHigh = Types.opSubmitPriorityToRaw OpPrioHigh
3337

    
3338
opPrioSubmitValid :: FrozenSet Int
3339
opPrioSubmitValid = ConstantUtils.mkSet [opPrioLow, opPrioNormal, opPrioHigh]
3340

    
3341
opPrioDefault :: Int
3342
opPrioDefault = opPrioNormal
3343

    
3344
-- * Lock recalculate mode
3345

    
3346
locksAppend :: String
3347
locksAppend = "append"
3348

    
3349
locksReplace :: String
3350
locksReplace = "replace"
3351

    
3352
-- * Lock timeout
3353
--
3354
-- The lock timeout (sum) before we transition into blocking acquire
3355
-- (this can still be reset by priority change).  Computed as max time
3356
-- (10 hours) before we should actually go into blocking acquire,
3357
-- given that we start from the default priority level.
3358

    
3359
lockAttemptsMaxwait :: Double
3360
lockAttemptsMaxwait = 15.0
3361

    
3362
lockAttemptsMinwait :: Double
3363
lockAttemptsMinwait = 1.0
3364

    
3365
lockAttemptsTimeout :: Int
3366
lockAttemptsTimeout = (10 * 3600) `div` (opPrioDefault - opPrioHighest)
3367

    
3368
-- * Execution log types
3369

    
3370
elogMessage :: String
3371
elogMessage = Types.eLogTypeToRaw ELogMessage
3372

    
3373
elogRemoteImport :: String
3374
elogRemoteImport = Types.eLogTypeToRaw ELogRemoteImport
3375

    
3376
elogJqueueTest :: String
3377
elogJqueueTest = Types.eLogTypeToRaw ELogJqueueTest
3378

    
3379
elogDelayTest :: String
3380
elogDelayTest = Types.eLogTypeToRaw ELogDelayTest
3381

    
3382
-- * /etc/hosts modification
3383

    
3384
etcHostsAdd :: String
3385
etcHostsAdd = "add"
3386

    
3387
etcHostsRemove :: String
3388
etcHostsRemove = "remove"
3389

    
3390
-- * Job queue test
3391

    
3392
jqtMsgprefix :: String
3393
jqtMsgprefix = "TESTMSG="
3394

    
3395
jqtExec :: String
3396
jqtExec = "exec"
3397

    
3398
jqtExpandnames :: String
3399
jqtExpandnames = "expandnames"
3400

    
3401
jqtLogmsg :: String
3402
jqtLogmsg = "logmsg"
3403

    
3404
jqtStartmsg :: String
3405
jqtStartmsg = "startmsg"
3406

    
3407
jqtAll :: FrozenSet String
3408
jqtAll = ConstantUtils.mkSet [jqtExec, jqtExpandnames, jqtLogmsg, jqtStartmsg]
3409

    
3410
-- * Query resources
3411

    
3412
qrCluster :: String
3413
qrCluster = "cluster"
3414

    
3415
qrExport :: String
3416
qrExport = "export"
3417

    
3418
qrExtstorage :: String
3419
qrExtstorage = "extstorage"
3420

    
3421
qrGroup :: String
3422
qrGroup = "group"
3423

    
3424
qrInstance :: String
3425
qrInstance = "instance"
3426

    
3427
qrJob :: String
3428
qrJob = "job"
3429

    
3430
qrLock :: String
3431
qrLock = "lock"
3432

    
3433
qrNetwork :: String
3434
qrNetwork = "network"
3435

    
3436
qrNode :: String
3437
qrNode = "node"
3438

    
3439
qrOs :: String
3440
qrOs = "os"
3441

    
3442
-- | List of resources which can be queried using 'Ganeti.OpCodes.OpQuery'
3443
qrViaOp :: FrozenSet String
3444
qrViaOp =
3445
  ConstantUtils.mkSet [qrCluster,
3446
                       qrOs,
3447
                       qrExtstorage]
3448

    
3449
-- | List of resources which can be queried using Local UniX Interface
3450
qrViaLuxi :: FrozenSet String
3451
qrViaLuxi = ConstantUtils.mkSet [qrGroup,
3452
                                 qrExport,
3453
                                 qrInstance,
3454
                                 qrJob,
3455
                                 qrLock,
3456
                                 qrNetwork,
3457
                                 qrNode]
3458

    
3459
-- | List of resources which can be queried using RAPI
3460
qrViaRapi :: FrozenSet String
3461
qrViaRapi = qrViaLuxi
3462

    
3463
-- | List of resources which can be queried via RAPI including PUT requests
3464
qrViaRapiPut :: FrozenSet String
3465
qrViaRapiPut = ConstantUtils.mkSet [qrLock, qrJob]
3466

    
3467
-- * Query field types
3468

    
3469
qftBool :: String
3470
qftBool = "bool"
3471

    
3472
qftNumber :: String
3473
qftNumber = "number"
3474

    
3475
qftOther :: String
3476
qftOther = "other"
3477

    
3478
qftText :: String
3479
qftText = "text"
3480

    
3481
qftTimestamp :: String
3482
qftTimestamp = "timestamp"
3483

    
3484
qftUnit :: String
3485
qftUnit = "unit"
3486

    
3487
qftUnknown :: String
3488
qftUnknown = "unknown"
3489

    
3490
qftAll :: FrozenSet String
3491
qftAll =
3492
  ConstantUtils.mkSet [qftBool,
3493
                       qftNumber,
3494
                       qftOther,
3495
                       qftText,
3496
                       qftTimestamp,
3497
                       qftUnit,
3498
                       qftUnknown]
3499

    
3500
-- * Query result field status
3501
--
3502
-- Don't change or reuse values as they're used by clients.
3503
--
3504
-- FIXME: link with 'Ganeti.Query.Language.ResultStatus'
3505

    
3506
-- | No data (e.g. RPC error), can be used instead of 'rsOffline'
3507
rsNodata :: Int
3508
rsNodata = 2
3509

    
3510
rsNormal :: Int
3511
rsNormal = 0
3512

    
3513
-- | Resource marked offline
3514
rsOffline :: Int
3515
rsOffline = 4
3516

    
3517
-- | Value unavailable/unsupported for item; if this field is
3518
-- supported but we cannot get the data for the moment, 'rsNodata' or
3519
-- 'rsOffline' should be used
3520
rsUnavail :: Int
3521
rsUnavail = 3
3522

    
3523
rsUnknown :: Int
3524
rsUnknown = 1
3525

    
3526
rsAll :: FrozenSet Int
3527
rsAll =
3528
  ConstantUtils.mkSet [rsNodata,
3529
                       rsNormal,
3530
                       rsOffline,
3531
                       rsUnavail,
3532
                       rsUnknown]
3533

    
3534
-- | Special field cases and their verbose/terse formatting
3535
rssDescription :: Map Int (String, String)
3536
rssDescription =
3537
  Map.fromList [(rsUnknown, ("(unknown)", "??")),
3538
                (rsNodata, ("(nodata)", "?")),
3539
                (rsOffline, ("(offline)", "*")),
3540
                (rsUnavail, ("(unavail)", "-"))]
3541

    
3542
-- * Max dynamic devices
3543

    
3544
maxDisks :: Int
3545
maxDisks = Types.maxDisks
3546

    
3547
maxNics :: Int
3548
maxNics = Types.maxNics
3549

    
3550
-- | SSCONF file prefix
3551
ssconfFileprefix :: String
3552
ssconfFileprefix = "ssconf_"
3553

    
3554
-- * SSCONF keys
3555

    
3556
ssClusterName :: String
3557
ssClusterName = "cluster_name"
3558

    
3559
ssClusterTags :: String
3560
ssClusterTags = "cluster_tags"
3561

    
3562
ssFileStorageDir :: String
3563
ssFileStorageDir = "file_storage_dir"
3564

    
3565
ssSharedFileStorageDir :: String
3566
ssSharedFileStorageDir = "shared_file_storage_dir"
3567

    
3568
ssGlusterStorageDir :: String
3569
ssGlusterStorageDir = "gluster_storage_dir"
3570

    
3571
ssMasterCandidates :: String
3572
ssMasterCandidates = "master_candidates"
3573

    
3574
ssMasterCandidatesIps :: String
3575
ssMasterCandidatesIps = "master_candidates_ips"
3576

    
3577
ssMasterCandidatesCerts :: String
3578
ssMasterCandidatesCerts = "master_candidates_certs"
3579

    
3580
ssMasterIp :: String
3581
ssMasterIp = "master_ip"
3582

    
3583
ssMasterNetdev :: String
3584
ssMasterNetdev = "master_netdev"
3585

    
3586
ssMasterNetmask :: String
3587
ssMasterNetmask = "master_netmask"
3588

    
3589
ssMasterNode :: String
3590
ssMasterNode = "master_node"
3591

    
3592
ssNodeList :: String
3593
ssNodeList = "node_list"
3594

    
3595
ssNodePrimaryIps :: String
3596
ssNodePrimaryIps = "node_primary_ips"
3597

    
3598
ssNodeSecondaryIps :: String
3599
ssNodeSecondaryIps = "node_secondary_ips"
3600

    
3601
ssOfflineNodes :: String
3602
ssOfflineNodes = "offline_nodes"
3603

    
3604
ssOnlineNodes :: String
3605
ssOnlineNodes = "online_nodes"
3606

    
3607
ssPrimaryIpFamily :: String
3608
ssPrimaryIpFamily = "primary_ip_family"
3609

    
3610
ssInstanceList :: String
3611
ssInstanceList = "instance_list"
3612

    
3613
ssReleaseVersion :: String
3614
ssReleaseVersion = "release_version"
3615

    
3616
ssHypervisorList :: String
3617
ssHypervisorList = "hypervisor_list"
3618

    
3619
ssMaintainNodeHealth :: String
3620
ssMaintainNodeHealth = "maintain_node_health"
3621

    
3622
ssUidPool :: String
3623
ssUidPool = "uid_pool"
3624

    
3625
ssNodegroups :: String
3626
ssNodegroups = "nodegroups"
3627

    
3628
ssNetworks :: String
3629
ssNetworks = "networks"
3630

    
3631
-- | This is not a complete SSCONF key, but the prefix for the
3632
-- hypervisor keys
3633
ssHvparamsPref :: String
3634
ssHvparamsPref = "hvparams_"
3635

    
3636
-- * Hvparams keys
3637

    
3638
ssHvparamsXenChroot :: String
3639
ssHvparamsXenChroot = ssHvparamsPref ++ htChroot
3640

    
3641
ssHvparamsXenFake :: String
3642
ssHvparamsXenFake = ssHvparamsPref ++ htFake
3643

    
3644
ssHvparamsXenHvm :: String
3645
ssHvparamsXenHvm = ssHvparamsPref ++ htXenHvm
3646

    
3647
ssHvparamsXenKvm :: String
3648
ssHvparamsXenKvm = ssHvparamsPref ++ htKvm
3649

    
3650
ssHvparamsXenLxc :: String
3651
ssHvparamsXenLxc = ssHvparamsPref ++ htLxc
3652

    
3653
ssHvparamsXenPvm :: String
3654
ssHvparamsXenPvm = ssHvparamsPref ++ htXenPvm
3655

    
3656
validSsHvparamsKeys :: FrozenSet String
3657
validSsHvparamsKeys =
3658
  ConstantUtils.mkSet [ssHvparamsXenChroot,
3659
                       ssHvparamsXenLxc,
3660
                       ssHvparamsXenFake,
3661
                       ssHvparamsXenHvm,
3662
                       ssHvparamsXenKvm,
3663
                       ssHvparamsXenPvm]
3664

    
3665
ssFilePerms :: Int
3666
ssFilePerms = 0o444
3667

    
3668
-- | Cluster wide default parameters
3669
defaultEnabledHypervisor :: String
3670
defaultEnabledHypervisor = htXenPvm
3671

    
3672
hvcDefaults :: Map Hypervisor (Map String PyValueEx)
3673
hvcDefaults =
3674
  Map.fromList
3675
  [ (XenPvm, Map.fromList
3676
             [ (hvUseBootloader,  PyValueEx False)
3677
             , (hvBootloaderPath, PyValueEx xenBootloader)
3678
             , (hvBootloaderArgs, PyValueEx "")
3679
             , (hvKernelPath,     PyValueEx xenKernel)
3680
             , (hvInitrdPath,     PyValueEx "")
3681
             , (hvRootPath,       PyValueEx "/dev/xvda1")
3682
             , (hvKernelArgs,     PyValueEx "ro")
3683
             , (hvMigrationPort,  PyValueEx (8002 :: Int))
3684
             , (hvMigrationMode,  PyValueEx htMigrationLive)
3685
             , (hvBlockdevPrefix, PyValueEx "sd")
3686
             , (hvRebootBehavior, PyValueEx instanceRebootAllowed)
3687
             , (hvCpuMask,        PyValueEx cpuPinningAll)
3688
             , (hvCpuCap,         PyValueEx (0 :: Int))
3689
             , (hvCpuWeight,      PyValueEx (256 :: Int))
3690
             , (hvVifScript,      PyValueEx "")
3691
             , (hvXenCmd,         PyValueEx xenCmdXm)
3692
             , (hvXenCpuid,       PyValueEx "")
3693
             , (hvSoundhw,        PyValueEx "")
3694
             ])
3695
  , (XenHvm, Map.fromList
3696
             [ (hvBootOrder,      PyValueEx "cd")
3697
             , (hvCdromImagePath, PyValueEx "")
3698
             , (hvNicType,        PyValueEx htNicRtl8139)
3699
             , (hvDiskType,       PyValueEx htDiskParavirtual)
3700
             , (hvVncBindAddress, PyValueEx ip4AddressAny)
3701
             , (hvAcpi,           PyValueEx True)
3702
             , (hvPae,            PyValueEx True)
3703
             , (hvKernelPath,     PyValueEx "/usr/lib/xen/boot/hvmloader")
3704
             , (hvDeviceModel,    PyValueEx "/usr/lib/xen/bin/qemu-dm")
3705
             , (hvMigrationPort,  PyValueEx (8002 :: Int))
3706
             , (hvMigrationMode,  PyValueEx htMigrationNonlive)
3707
             , (hvUseLocaltime,   PyValueEx False)
3708
             , (hvBlockdevPrefix, PyValueEx "hd")
3709
             , (hvPassthrough,    PyValueEx "")
3710
             , (hvRebootBehavior, PyValueEx instanceRebootAllowed)
3711
             , (hvCpuMask,        PyValueEx cpuPinningAll)
3712
             , (hvCpuCap,         PyValueEx (0 :: Int))
3713
             , (hvCpuWeight,      PyValueEx (256 :: Int))
3714
             , (hvVifType,        PyValueEx htHvmVifIoemu)
3715
             , (hvVifScript,      PyValueEx "")
3716
             , (hvViridian,       PyValueEx False)
3717
             , (hvXenCmd,         PyValueEx xenCmdXm)
3718
             , (hvXenCpuid,       PyValueEx "")
3719
             , (hvSoundhw,        PyValueEx "")
3720
             ])
3721
  , (Kvm, Map.fromList
3722
          [ (hvKvmPath,                         PyValueEx kvmPath)
3723
          , (hvKernelPath,                      PyValueEx kvmKernel)
3724
          , (hvInitrdPath,                      PyValueEx "")
3725
          , (hvKernelArgs,                      PyValueEx "ro")
3726
          , (hvRootPath,                        PyValueEx "/dev/vda1")
3727
          , (hvAcpi,                            PyValueEx True)
3728
          , (hvSerialConsole,                   PyValueEx True)
3729
          , (hvSerialSpeed,                     PyValueEx (38400 :: Int))
3730
          , (hvVncBindAddress,                  PyValueEx "")
3731
          , (hvVncTls,                          PyValueEx False)
3732
          , (hvVncX509,                         PyValueEx "")
3733
          , (hvVncX509Verify,                   PyValueEx False)
3734
          , (hvVncPasswordFile,                 PyValueEx "")
3735
          , (hvKvmSpiceBind,                    PyValueEx "")
3736
          , (hvKvmSpiceIpVersion,           PyValueEx ifaceNoIpVersionSpecified)
3737
          , (hvKvmSpicePasswordFile,            PyValueEx "")
3738
          , (hvKvmSpiceLosslessImgCompr,        PyValueEx "")
3739
          , (hvKvmSpiceJpegImgCompr,            PyValueEx "")
3740
          , (hvKvmSpiceZlibGlzImgCompr,         PyValueEx "")
3741
          , (hvKvmSpiceStreamingVideoDetection, PyValueEx "")
3742
          , (hvKvmSpiceAudioCompr,              PyValueEx True)
3743
          , (hvKvmSpiceUseTls,                  PyValueEx False)
3744
          , (hvKvmSpiceTlsCiphers,              PyValueEx opensslCiphers)
3745
          , (hvKvmSpiceUseVdagent,              PyValueEx True)
3746
          , (hvKvmFloppyImagePath,              PyValueEx "")
3747
          , (hvCdromImagePath,                  PyValueEx "")
3748
          , (hvKvmCdrom2ImagePath,              PyValueEx "")
3749
          , (hvBootOrder,                       PyValueEx htBoDisk)
3750
          , (hvNicType,                         PyValueEx htNicParavirtual)
3751
          , (hvDiskType,                        PyValueEx htDiskParavirtual)
3752
          , (hvKvmCdromDiskType,                PyValueEx "")
3753
          , (hvUsbMouse,                        PyValueEx "")
3754
          , (hvKeymap,                          PyValueEx "")
3755
          , (hvMigrationPort,                   PyValueEx (8102 :: Int))
3756
          , (hvMigrationBandwidth,              PyValueEx (32 :: Int))
3757
          , (hvMigrationDowntime,               PyValueEx (30 :: Int))
3758
          , (hvMigrationMode,                   PyValueEx htMigrationLive)
3759
          , (hvUseLocaltime,                    PyValueEx False)
3760
          , (hvDiskCache,                       PyValueEx htCacheDefault)
3761
          , (hvSecurityModel,                   PyValueEx htSmNone)
3762
          , (hvSecurityDomain,                  PyValueEx "")
3763
          , (hvKvmFlag,                         PyValueEx "")
3764
          , (hvVhostNet,                        PyValueEx False)
3765
          , (hvKvmUseChroot,                    PyValueEx False)
3766
          , (hvKvmUserShutdown,                 PyValueEx False)
3767
          , (hvMemPath,                         PyValueEx "")
3768
          , (hvRebootBehavior,                  PyValueEx instanceRebootAllowed)
3769
          , (hvCpuMask,                         PyValueEx cpuPinningAll)
3770
          , (hvCpuType,                         PyValueEx "")
3771
          , (hvCpuCores,                        PyValueEx (0 :: Int))
3772
          , (hvCpuThreads,                      PyValueEx (0 :: Int))
3773
          , (hvCpuSockets,                      PyValueEx (0 :: Int))
3774
          , (hvSoundhw,                         PyValueEx "")
3775
          , (hvUsbDevices,                      PyValueEx "")
3776
          , (hvVga,                             PyValueEx "")
3777
          , (hvKvmExtra,                        PyValueEx "")
3778
          , (hvKvmMachineVersion,               PyValueEx "")
3779
          , (hvVnetHdr,                         PyValueEx True)])
3780
  , (Fake, Map.fromList [(hvMigrationMode, PyValueEx htMigrationLive)])
3781
  , (Chroot, Map.fromList [(hvInitScript, PyValueEx "/ganeti-chroot")])
3782
  , (Lxc, Map.fromList [(hvCpuMask, PyValueEx "")])
3783
  ]
3784

    
3785
hvcGlobals :: FrozenSet String
3786
hvcGlobals =
3787
  ConstantUtils.mkSet [hvMigrationBandwidth,
3788
                       hvMigrationMode,
3789
                       hvMigrationPort,
3790
                       hvXenCmd]
3791

    
3792
becDefaults :: Map String PyValueEx
3793
becDefaults =
3794
  Map.fromList
3795
  [ (beMinmem, PyValueEx (128 :: Int))
3796
  , (beMaxmem, PyValueEx (128 :: Int))
3797
  , (beVcpus, PyValueEx (1 :: Int))
3798
  , (beAutoBalance, PyValueEx True)
3799
  , (beAlwaysFailover, PyValueEx False)
3800
  , (beSpindleUse, PyValueEx (1 :: Int))
3801
  ]
3802

    
3803
ndcDefaults :: Map String PyValueEx
3804
ndcDefaults =
3805
  Map.fromList
3806
  [ (ndOobProgram,       PyValueEx "")
3807
  , (ndSpindleCount,     PyValueEx (1 :: Int))
3808
  , (ndExclusiveStorage, PyValueEx False)
3809
  , (ndOvs,              PyValueEx False)
3810
  , (ndOvsName,          PyValueEx defaultOvs)
3811
  , (ndOvsLink,          PyValueEx "")
3812
  , (ndSshPort,          PyValueEx (22 :: Int))
3813
  ]
3814

    
3815
ndcGlobals :: FrozenSet String
3816
ndcGlobals = ConstantUtils.mkSet [ndExclusiveStorage]
3817

    
3818
-- | Default delay target measured in sectors
3819
defaultDelayTarget :: Int
3820
defaultDelayTarget = 1
3821

    
3822
defaultDiskCustom :: String
3823
defaultDiskCustom = ""
3824

    
3825
defaultDiskResync :: Bool
3826
defaultDiskResync = False
3827

    
3828
-- | Default fill target measured in sectors
3829
defaultFillTarget :: Int
3830
defaultFillTarget = 0
3831

    
3832
-- | Default mininum rate measured in KiB/s
3833
defaultMinRate :: Int
3834
defaultMinRate = 4 * 1024
3835

    
3836
defaultNetCustom :: String
3837
defaultNetCustom = ""
3838

    
3839
-- | Default plan ahead measured in sectors
3840
--
3841
-- The default values for the DRBD dynamic resync speed algorithm are
3842
-- taken from the drbsetup 8.3.11 man page, except for c-plan-ahead
3843
-- (that we don't need to set to 0, because we have a separate option
3844
-- to enable it) and for c-max-rate, that we cap to the default value
3845
-- for the static resync rate.
3846
defaultPlanAhead :: Int
3847
defaultPlanAhead = 20
3848

    
3849
defaultRbdPool :: String
3850
defaultRbdPool = "rbd"
3851

    
3852
diskLdDefaults :: Map DiskTemplate (Map String PyValueEx)
3853
diskLdDefaults =
3854
  Map.fromList
3855
  [ (DTBlock, Map.empty)
3856
  , (DTDrbd8, Map.fromList
3857
              [ (ldpBarriers,      PyValueEx drbdBarriers)
3858
              , (ldpDefaultMetavg, PyValueEx defaultVg)
3859
              , (ldpDelayTarget,   PyValueEx defaultDelayTarget)
3860
              , (ldpDiskCustom,    PyValueEx defaultDiskCustom)
3861
              , (ldpDynamicResync, PyValueEx defaultDiskResync)
3862
              , (ldpFillTarget,    PyValueEx defaultFillTarget)
3863
              , (ldpMaxRate,       PyValueEx classicDrbdSyncSpeed)
3864
              , (ldpMinRate,       PyValueEx defaultMinRate)
3865
              , (ldpNetCustom,     PyValueEx defaultNetCustom)
3866
              , (ldpNoMetaFlush,   PyValueEx drbdNoMetaFlush)
3867
              , (ldpPlanAhead,     PyValueEx defaultPlanAhead)
3868
              , (ldpProtocol,      PyValueEx drbdDefaultNetProtocol)
3869
              , (ldpResyncRate,    PyValueEx classicDrbdSyncSpeed)
3870
              ])
3871
  , (DTExt, Map.empty)
3872
  , (DTFile, Map.empty)
3873
  , (DTPlain, Map.fromList [(ldpStripes, PyValueEx lvmStripecount)])
3874
  , (DTRbd, Map.fromList
3875
            [ (ldpPool, PyValueEx defaultRbdPool)
3876
            , (ldpAccess, PyValueEx diskKernelspace)
3877
            ])
3878
  , (DTSharedFile, Map.empty)
3879
  , (DTGluster, Map.fromList
3880
                [ (rbdAccess, PyValueEx diskKernelspace)
3881
                , (glusterHost, PyValueEx glusterHostDefault)
3882
                , (glusterVolume, PyValueEx glusterVolumeDefault)
3883
                , (glusterPort, PyValueEx glusterPortDefault)
3884
                ])
3885
  ]
3886

    
3887
diskDtDefaults :: Map DiskTemplate (Map String PyValueEx)
3888
diskDtDefaults =
3889
  Map.fromList
3890
  [ (DTBlock,      Map.empty)
3891
  , (DTDiskless,   Map.empty)
3892
  , (DTDrbd8,      Map.fromList
3893
                   [ (drbdDataStripes,   PyValueEx lvmStripecount)
3894
                   , (drbdDefaultMetavg, PyValueEx defaultVg)
3895
                   , (drbdDelayTarget,   PyValueEx defaultDelayTarget)
3896
                   , (drbdDiskBarriers,  PyValueEx drbdBarriers)
3897
                   , (drbdDiskCustom,    PyValueEx defaultDiskCustom)
3898
                   , (drbdDynamicResync, PyValueEx defaultDiskResync)
3899
                   , (drbdFillTarget,    PyValueEx defaultFillTarget)
3900
                   , (drbdMaxRate,       PyValueEx classicDrbdSyncSpeed)
3901
                   , (drbdMetaBarriers,  PyValueEx drbdNoMetaFlush)
3902
                   , (drbdMetaStripes,   PyValueEx lvmStripecount)
3903
                   , (drbdMinRate,       PyValueEx defaultMinRate)
3904
                   , (drbdNetCustom,     PyValueEx defaultNetCustom)
3905
                   , (drbdPlanAhead,     PyValueEx defaultPlanAhead)
3906
                   , (drbdProtocol,      PyValueEx drbdDefaultNetProtocol)
3907
                   , (drbdResyncRate,    PyValueEx classicDrbdSyncSpeed)
3908
                   ])
3909
  , (DTExt,        Map.empty)
3910
  , (DTFile,       Map.empty)
3911
  , (DTPlain,      Map.fromList [(lvStripes, PyValueEx lvmStripecount)])
3912
  , (DTRbd,        Map.fromList
3913
                   [ (rbdPool, PyValueEx defaultRbdPool)
3914
                   , (rbdAccess, PyValueEx diskKernelspace)
3915
                   ])
3916
  , (DTSharedFile, Map.empty)
3917
  , (DTGluster, Map.fromList
3918
                [ (rbdAccess, PyValueEx diskKernelspace)
3919
                , (glusterHost, PyValueEx glusterHostDefault)
3920
                , (glusterVolume, PyValueEx glusterVolumeDefault)
3921
                , (glusterPort, PyValueEx glusterPortDefault)
3922
                ])
3923
  ]
3924

    
3925
niccDefaults :: Map String PyValueEx
3926
niccDefaults =
3927
  Map.fromList
3928
  [ (nicMode, PyValueEx nicModeBridged)
3929
  , (nicLink, PyValueEx defaultBridge)
3930
  , (nicVlan, PyValueEx "")
3931
  ]
3932

    
3933
-- | All of the following values are quite arbitrary - there are no
3934
-- "good" defaults, these must be customised per-site
3935
ispecsMinmaxDefaults :: Map String (Map String Int)
3936
ispecsMinmaxDefaults =
3937
  Map.fromList
3938
  [(ispecsMin,
3939
    Map.fromList
3940
    [(ConstantUtils.ispecMemSize, Types.iSpecMemorySize Types.defMinISpec),
3941
     (ConstantUtils.ispecCpuCount, Types.iSpecCpuCount Types.defMinISpec),
3942
     (ConstantUtils.ispecDiskCount, Types.iSpecDiskCount Types.defMinISpec),
3943
     (ConstantUtils.ispecDiskSize, Types.iSpecDiskSize Types.defMinISpec),
3944
     (ConstantUtils.ispecNicCount, Types.iSpecNicCount Types.defMinISpec),
3945
     (ConstantUtils.ispecSpindleUse, Types.iSpecSpindleUse Types.defMinISpec)]),
3946
   (ispecsMax,
3947
    Map.fromList
3948
    [(ConstantUtils.ispecMemSize, Types.iSpecMemorySize Types.defMaxISpec),
3949
     (ConstantUtils.ispecCpuCount, Types.iSpecCpuCount Types.defMaxISpec),
3950
     (ConstantUtils.ispecDiskCount, Types.iSpecDiskCount Types.defMaxISpec),
3951
     (ConstantUtils.ispecDiskSize, Types.iSpecDiskSize Types.defMaxISpec),
3952
     (ConstantUtils.ispecNicCount, Types.iSpecNicCount Types.defMaxISpec),
3953
     (ConstantUtils.ispecSpindleUse, Types.iSpecSpindleUse Types.defMaxISpec)])]
3954

    
3955
ipolicyDefaults :: Map String PyValueEx
3956
ipolicyDefaults =
3957
  Map.fromList
3958
  [ (ispecsMinmax,        PyValueEx [ispecsMinmaxDefaults])
3959
  , (ispecsStd,           PyValueEx (Map.fromList
3960
                                     [ (ispecMemSize,    128)
3961
                                     , (ispecCpuCount,   1)
3962
                                     , (ispecDiskCount,  1)
3963
                                     , (ispecDiskSize,   1024)
3964
                                     , (ispecNicCount,   1)
3965
                                     , (ispecSpindleUse, 1)
3966
                                     ] :: Map String Int))
3967
  , (ipolicyDts,          PyValueEx (ConstantUtils.toList diskTemplates))
3968
  , (ipolicyVcpuRatio,    PyValueEx (4.0 :: Double))
3969
  , (ipolicySpindleRatio, PyValueEx (32.0 :: Double))
3970
  ]
3971

    
3972
masterPoolSizeDefault :: Int
3973
masterPoolSizeDefault = 10
3974

    
3975
-- * Exclusive storage
3976

    
3977
-- | Error margin used to compare physical disks
3978
partMargin :: Double
3979
partMargin = 0.01
3980

    
3981
-- | Space reserved when creating instance disks
3982
partReserved :: Double
3983
partReserved = 0.02
3984

    
3985
-- * Luxid job scheduling
3986

    
3987
-- | Time intervall in seconds for polling updates on the job queue. This
3988
-- intervall is only relevant if the number of running jobs reaches the maximal
3989
-- allowed number, as otherwise new jobs will be started immediately anyway.
3990
-- Also, as jobs are watched via inotify, scheduling usually works independent
3991
-- of polling. Therefore we chose a sufficiently large interval, in the order of
3992
-- 5 minutes. As with the interval for reloading the configuration, we chose a
3993
-- prime number to avoid accidental 'same wakeup' with other processes.
3994
luxidJobqueuePollInterval :: Int
3995
luxidJobqueuePollInterval = 307
3996

    
3997
-- | The default value for the maximal number of jobs to be running at the same
3998
-- time. Once the maximal number is reached, new jobs will just be queued and
3999
-- only started, once some of the other jobs have finished.
4000
luxidMaximalRunningJobsDefault :: Int
4001
luxidMaximalRunningJobsDefault = 20
4002

    
4003
-- * WConfD
4004

    
4005
-- | Time itnervall in seconds between checks that all lock owners are still
4006
-- alive, and cleaning up the resources for the dead ones. As jobs dying without
4007
-- releasing resources is the exception, not the rule, we don't want this task
4008
-- to take up too many cycles itself. Hence we choose a sufficiently large
4009
-- intervall, in the order of 5 minutes. To avoid accidental 'same wakeup'
4010
-- with other tasks, we choose the next unused prime number.
4011
wconfdDeathdetectionIntervall :: Int
4012
wconfdDeathdetectionIntervall = 311
4013

    
4014
-- * Confd
4015

    
4016
confdProtocolVersion :: Int
4017
confdProtocolVersion = ConstantUtils.confdProtocolVersion
4018

    
4019
-- Confd request type
4020

    
4021
confdReqPing :: Int
4022
confdReqPing = Types.confdRequestTypeToRaw ReqPing
4023

    
4024
confdReqNodeRoleByname :: Int
4025
confdReqNodeRoleByname = Types.confdRequestTypeToRaw ReqNodeRoleByName
4026

    
4027
confdReqNodePipByInstanceIp :: Int
4028
confdReqNodePipByInstanceIp = Types.confdRequestTypeToRaw ReqNodePipByInstPip
4029

    
4030
confdReqClusterMaster :: Int
4031
confdReqClusterMaster = Types.confdRequestTypeToRaw ReqClusterMaster
4032

    
4033
confdReqNodePipList :: Int
4034
confdReqNodePipList = Types.confdRequestTypeToRaw ReqNodePipList
4035

    
4036
confdReqMcPipList :: Int
4037
confdReqMcPipList = Types.confdRequestTypeToRaw ReqMcPipList
4038

    
4039
confdReqInstancesIpsList :: Int
4040
confdReqInstancesIpsList = Types.confdRequestTypeToRaw ReqInstIpsList
4041

    
4042
confdReqNodeDrbd :: Int
4043
confdReqNodeDrbd = Types.confdRequestTypeToRaw ReqNodeDrbd
4044

    
4045
confdReqNodeInstances :: Int
4046
confdReqNodeInstances = Types.confdRequestTypeToRaw ReqNodeInstances
4047

    
4048
confdReqs :: FrozenSet Int
4049
confdReqs =
4050
  ConstantUtils.mkSet .
4051
  map Types.confdRequestTypeToRaw $
4052
  [minBound..] \\ [ReqNodeInstances]
4053

    
4054
-- * Confd request type
4055

    
4056
confdReqfieldName :: Int
4057
confdReqfieldName = Types.confdReqFieldToRaw ReqFieldName
4058

    
4059
confdReqfieldIp :: Int
4060
confdReqfieldIp = Types.confdReqFieldToRaw ReqFieldIp
4061

    
4062
confdReqfieldMnodePip :: Int
4063
confdReqfieldMnodePip = Types.confdReqFieldToRaw ReqFieldMNodePip
4064

    
4065
-- * Confd repl status
4066

    
4067
confdReplStatusOk :: Int
4068
confdReplStatusOk = Types.confdReplyStatusToRaw ReplyStatusOk
4069

    
4070
confdReplStatusError :: Int
4071
confdReplStatusError = Types.confdReplyStatusToRaw ReplyStatusError
4072

    
4073
confdReplStatusNotimplemented :: Int
4074
confdReplStatusNotimplemented = Types.confdReplyStatusToRaw ReplyStatusNotImpl
4075

    
4076
confdReplStatuses :: FrozenSet Int
4077
confdReplStatuses =
4078
  ConstantUtils.mkSet $ map Types.confdReplyStatusToRaw [minBound..]
4079

    
4080
-- * Confd node role
4081

    
4082
confdNodeRoleMaster :: Int
4083
confdNodeRoleMaster = Types.confdNodeRoleToRaw NodeRoleMaster
4084

    
4085
confdNodeRoleCandidate :: Int
4086
confdNodeRoleCandidate = Types.confdNodeRoleToRaw NodeRoleCandidate
4087

    
4088
confdNodeRoleOffline :: Int
4089
confdNodeRoleOffline = Types.confdNodeRoleToRaw NodeRoleOffline
4090

    
4091
confdNodeRoleDrained :: Int
4092
confdNodeRoleDrained = Types.confdNodeRoleToRaw NodeRoleDrained
4093

    
4094
confdNodeRoleRegular :: Int
4095
confdNodeRoleRegular = Types.confdNodeRoleToRaw NodeRoleRegular
4096

    
4097
-- * A few common errors for confd
4098

    
4099
confdErrorUnknownEntry :: Int
4100
confdErrorUnknownEntry = Types.confdErrorTypeToRaw ConfdErrorUnknownEntry
4101

    
4102
confdErrorInternal :: Int
4103
confdErrorInternal = Types.confdErrorTypeToRaw ConfdErrorInternal
4104

    
4105
confdErrorArgument :: Int
4106
confdErrorArgument = Types.confdErrorTypeToRaw ConfdErrorArgument
4107

    
4108
-- * Confd request query fields
4109

    
4110
confdReqqLink :: String
4111
confdReqqLink = ConstantUtils.confdReqqLink
4112

    
4113
confdReqqIp :: String
4114
confdReqqIp = ConstantUtils.confdReqqIp
4115

    
4116
confdReqqIplist :: String
4117
confdReqqIplist = ConstantUtils.confdReqqIplist
4118

    
4119
confdReqqFields :: String
4120
confdReqqFields = ConstantUtils.confdReqqFields
4121

    
4122
-- | Each request is "salted" by the current timestamp.
4123
--
4124
-- This constant decides how many seconds of skew to accept.
4125
--
4126
-- TODO: make this a default and allow the value to be more
4127
-- configurable
4128
confdMaxClockSkew :: Int
4129
confdMaxClockSkew = 2 * nodeMaxClockSkew
4130

    
4131
-- | When we haven't reloaded the config for more than this amount of
4132
-- seconds, we force a test to see if inotify is betraying us. Using a
4133
-- prime number to ensure we get less chance of 'same wakeup' with
4134
-- other processes.
4135
confdConfigReloadTimeout :: Int
4136
confdConfigReloadTimeout = 17
4137

    
4138
-- | If we receive more than one update in this amount of
4139
-- microseconds, we move to polling every RATELIMIT seconds, rather
4140
-- than relying on inotify, to be able to serve more requests.
4141
confdConfigReloadRatelimit :: Int
4142
confdConfigReloadRatelimit = 250000
4143

    
4144
-- | Magic number prepended to all confd queries.
4145
--
4146
-- This allows us to distinguish different types of confd protocols
4147
-- and handle them. For example by changing this we can move the whole
4148
-- payload to be compressed, or move away from json.
4149
confdMagicFourcc :: String
4150
confdMagicFourcc = "plj0"
4151

    
4152
-- | By default a confd request is sent to the minimum between this
4153
-- number and all MCs. 6 was chosen because even in the case of a
4154
-- disastrous 50% response rate, we should have enough answers to be
4155
-- able to compare more than one.
4156
confdDefaultReqCoverage :: Int
4157
confdDefaultReqCoverage = 6
4158

    
4159
-- | Timeout in seconds to expire pending query request in the confd
4160
-- client library. We don't actually expect any answer more than 10
4161
-- seconds after we sent a request.
4162
confdClientExpireTimeout :: Int
4163
confdClientExpireTimeout = 10
4164

    
4165
-- | Maximum UDP datagram size.
4166
--
4167
-- On IPv4: 64K - 20 (ip header size) - 8 (udp header size) = 65507
4168
-- On IPv6: 64K - 40 (ip6 header size) - 8 (udp header size) = 65487
4169
--   (assuming we can't use jumbo frames)
4170
-- We just set this to 60K, which should be enough
4171
maxUdpDataSize :: Int
4172
maxUdpDataSize = 61440
4173

    
4174
-- * User-id pool minimum/maximum acceptable user-ids
4175

    
4176
uidpoolUidMin :: Int
4177
uidpoolUidMin = 0
4178

    
4179
-- | Assuming 32 bit user-ids
4180
uidpoolUidMax :: Integer
4181
uidpoolUidMax = 2 ^ 32 - 1
4182

    
4183
-- | Name or path of the pgrep command
4184
pgrep :: String
4185
pgrep = "pgrep"
4186

    
4187
-- | Name of the node group that gets created at cluster init or
4188
-- upgrade
4189
initialNodeGroupName :: String
4190
initialNodeGroupName = "default"
4191

    
4192
-- * Possible values for NodeGroup.alloc_policy
4193

    
4194
allocPolicyLastResort :: String
4195
allocPolicyLastResort = Types.allocPolicyToRaw AllocLastResort
4196

    
4197
allocPolicyPreferred :: String
4198
allocPolicyPreferred = Types.allocPolicyToRaw AllocPreferred
4199

    
4200
allocPolicyUnallocable :: String
4201
allocPolicyUnallocable = Types.allocPolicyToRaw AllocUnallocable
4202

    
4203
validAllocPolicies :: [String]
4204
validAllocPolicies = map Types.allocPolicyToRaw [minBound..]
4205

    
4206
-- | Temporary external/shared storage parameters
4207
blockdevDriverManual :: String
4208
blockdevDriverManual = Types.blockDriverToRaw BlockDrvManual
4209

    
4210
-- | 'qemu-img' path, required for 'ovfconverter'
4211
qemuimgPath :: String
4212
qemuimgPath = AutoConf.qemuimgPath
4213

    
4214
-- | The hail iallocator
4215
iallocHail :: String
4216
iallocHail = "hail"
4217

    
4218
-- * Fake opcodes for functions that have hooks attached to them via
4219
-- backend.RunLocalHooks
4220

    
4221
fakeOpMasterTurndown :: String
4222
fakeOpMasterTurndown = "OP_CLUSTER_IP_TURNDOWN"
4223

    
4224
fakeOpMasterTurnup :: String
4225
fakeOpMasterTurnup = "OP_CLUSTER_IP_TURNUP"
4226

    
4227

    
4228
-- * Crypto Types
4229
-- Types of cryptographic tokens used in node communication
4230

    
4231
cryptoTypeSslDigest :: String
4232
cryptoTypeSslDigest = "ssl"
4233

    
4234
cryptoTypeSsh :: String
4235
cryptoTypeSsh = "ssh"
4236

    
4237
-- So far only ssl keys are used in the context of this constant
4238
cryptoTypes :: FrozenSet String
4239
cryptoTypes = ConstantUtils.mkSet [cryptoTypeSslDigest]
4240

    
4241
-- * Crypto Actions
4242
-- Actions that can be performed on crypto tokens
4243

    
4244
cryptoActionGet :: String
4245
cryptoActionGet = "get"
4246

    
4247
-- This is 'create and get'
4248
cryptoActionCreate :: String
4249
cryptoActionCreate = "create"
4250

    
4251
cryptoActions :: FrozenSet String
4252
cryptoActions = ConstantUtils.mkSet [cryptoActionGet, cryptoActionCreate]
4253

    
4254
-- * Options for CryptoActions
4255

    
4256
-- Filename of the certificate
4257
cryptoOptionCertFile :: String
4258
cryptoOptionCertFile = "cert_file"
4259

    
4260
-- Serial number of the certificate
4261
cryptoOptionSerialNo :: String
4262
cryptoOptionSerialNo = "serial_no"
4263

    
4264
-- * SSH key types
4265

    
4266
sshkDsa :: String
4267
sshkDsa = "dsa"
4268

    
4269
sshkRsa :: String
4270
sshkRsa = "rsa"
4271

    
4272
sshkAll :: FrozenSet String
4273
sshkAll = ConstantUtils.mkSet [sshkRsa, sshkDsa]
4274

    
4275
-- * SSH authorized key types
4276

    
4277
sshakDss :: String
4278
sshakDss = "ssh-dss"
4279

    
4280
sshakRsa :: String
4281
sshakRsa = "ssh-rsa"
4282

    
4283
sshakAll :: FrozenSet String
4284
sshakAll = ConstantUtils.mkSet [sshakDss, sshakRsa]
4285

    
4286
-- * SSH setup
4287

    
4288
sshsClusterName :: String
4289
sshsClusterName = "cluster_name"
4290

    
4291
sshsSshHostKey :: String
4292
sshsSshHostKey = "ssh_host_key"
4293

    
4294
sshsSshRootKey :: String
4295
sshsSshRootKey = "ssh_root_key"
4296

    
4297
sshsNodeDaemonCertificate :: String
4298
sshsNodeDaemonCertificate = "node_daemon_certificate"
4299

    
4300
-- * Key files for SSH daemon
4301

    
4302
sshHostDsaPriv :: String
4303
sshHostDsaPriv = sshConfigDir ++ "/ssh_host_dsa_key"
4304

    
4305
sshHostDsaPub :: String
4306
sshHostDsaPub = sshHostDsaPriv ++ ".pub"
4307

    
4308
sshHostRsaPriv :: String
4309
sshHostRsaPriv = sshConfigDir ++ "/ssh_host_rsa_key"
4310

    
4311
sshHostRsaPub :: String
4312
sshHostRsaPub = sshHostRsaPriv ++ ".pub"
4313

    
4314
sshDaemonKeyfiles :: Map String (String, String)
4315
sshDaemonKeyfiles =
4316
  Map.fromList [ (sshkRsa, (sshHostRsaPriv, sshHostRsaPub))
4317
               , (sshkDsa, (sshHostDsaPriv, sshHostDsaPub))
4318
               ]
4319

    
4320
-- * Node daemon setup
4321

    
4322
ndsClusterName :: String
4323
ndsClusterName = "cluster_name"
4324

    
4325
ndsNodeDaemonCertificate :: String
4326
ndsNodeDaemonCertificate = "node_daemon_certificate"
4327

    
4328
ndsSsconf :: String
4329
ndsSsconf = "ssconf"
4330

    
4331
ndsStartNodeDaemon :: String
4332
ndsStartNodeDaemon = "start_node_daemon"
4333

    
4334
-- * VCluster related constants
4335

    
4336
vClusterEtcHosts :: String
4337
vClusterEtcHosts = "/etc/hosts"
4338

    
4339
vClusterVirtPathPrefix :: String
4340
vClusterVirtPathPrefix = "/###-VIRTUAL-PATH-###,"
4341

    
4342
vClusterRootdirEnvname :: String
4343
vClusterRootdirEnvname = "GANETI_ROOTDIR"
4344

    
4345
vClusterHostnameEnvname :: String
4346
vClusterHostnameEnvname = "GANETI_HOSTNAME"
4347

    
4348
vClusterVpathWhitelist :: FrozenSet String
4349
vClusterVpathWhitelist = ConstantUtils.mkSet [ vClusterEtcHosts ]
4350

    
4351
-- * The source reasons for the execution of an OpCode
4352

    
4353
opcodeReasonSrcClient :: String
4354
opcodeReasonSrcClient = "gnt:client"
4355

    
4356
_opcodeReasonSrcDaemon :: String
4357
_opcodeReasonSrcDaemon = "gnt:daemon"
4358

    
4359
_opcodeReasonSrcMasterd :: String
4360
_opcodeReasonSrcMasterd = _opcodeReasonSrcDaemon ++ ":masterd"
4361

    
4362
opcodeReasonSrcNoded :: String
4363
opcodeReasonSrcNoded = _opcodeReasonSrcDaemon ++ ":noded"
4364

    
4365
opcodeReasonSrcOpcode :: String
4366
opcodeReasonSrcOpcode = "gnt:opcode"
4367

    
4368
opcodeReasonSrcPickup :: String
4369
opcodeReasonSrcPickup = _opcodeReasonSrcMasterd ++ ":pickup"
4370

    
4371
opcodeReasonSrcRlib2 :: String
4372
opcodeReasonSrcRlib2 = "gnt:library:rlib2"
4373

    
4374
opcodeReasonSrcUser :: String
4375
opcodeReasonSrcUser = "gnt:user"
4376

    
4377
opcodeReasonSources :: FrozenSet String
4378
opcodeReasonSources =
4379
  ConstantUtils.mkSet [opcodeReasonSrcClient,
4380
                       opcodeReasonSrcNoded,
4381
                       opcodeReasonSrcOpcode,
4382
                       opcodeReasonSrcPickup,
4383
                       opcodeReasonSrcRlib2,
4384
                       opcodeReasonSrcUser]
4385

    
4386
-- | Path generating random UUID
4387
randomUuidFile :: String
4388
randomUuidFile = ConstantUtils.randomUuidFile
4389

    
4390
-- * Auto-repair tag prefixes
4391

    
4392
autoRepairTagPrefix :: String
4393
autoRepairTagPrefix = "ganeti:watcher:autorepair:"
4394

    
4395
autoRepairTagEnabled :: String
4396
autoRepairTagEnabled = autoRepairTagPrefix
4397

    
4398
autoRepairTagPending :: String
4399
autoRepairTagPending = autoRepairTagPrefix ++ "pending:"
4400

    
4401
autoRepairTagResult :: String
4402
autoRepairTagResult = autoRepairTagPrefix ++ "result:"
4403

    
4404
autoRepairTagSuspended :: String
4405
autoRepairTagSuspended = autoRepairTagPrefix ++ "suspend:"
4406

    
4407
-- * Auto-repair levels
4408

    
4409
autoRepairFailover :: String
4410
autoRepairFailover = Types.autoRepairTypeToRaw ArFailover
4411

    
4412
autoRepairFixStorage :: String
4413
autoRepairFixStorage = Types.autoRepairTypeToRaw ArFixStorage
4414

    
4415
autoRepairMigrate :: String
4416
autoRepairMigrate = Types.autoRepairTypeToRaw ArMigrate
4417

    
4418
autoRepairReinstall :: String
4419
autoRepairReinstall = Types.autoRepairTypeToRaw ArReinstall
4420

    
4421
autoRepairAllTypes :: FrozenSet String
4422
autoRepairAllTypes =
4423
  ConstantUtils.mkSet [autoRepairFailover,
4424
                       autoRepairFixStorage,
4425
                       autoRepairMigrate,
4426
                       autoRepairReinstall]
4427

    
4428
-- * Auto-repair results
4429

    
4430
autoRepairEnoperm :: String
4431
autoRepairEnoperm = Types.autoRepairResultToRaw ArEnoperm
4432

    
4433
autoRepairFailure :: String
4434
autoRepairFailure = Types.autoRepairResultToRaw ArFailure
4435

    
4436
autoRepairSuccess :: String
4437
autoRepairSuccess = Types.autoRepairResultToRaw ArSuccess
4438

    
4439
autoRepairAllResults :: FrozenSet String
4440
autoRepairAllResults =
4441
  ConstantUtils.mkSet [autoRepairEnoperm, autoRepairFailure, autoRepairSuccess]
4442

    
4443
-- | The version identifier for builtin data collectors
4444
builtinDataCollectorVersion :: String
4445
builtinDataCollectorVersion = "B"
4446

    
4447
-- | The reason trail opcode parameter name
4448
opcodeReason :: String
4449
opcodeReason = "reason"
4450

    
4451
diskstatsFile :: String
4452
diskstatsFile = "/proc/diskstats"
4453

    
4454
-- *  CPU load collector
4455

    
4456
statFile :: String
4457
statFile = "/proc/stat"
4458

    
4459
cpuavgloadBufferSize :: Int
4460
cpuavgloadBufferSize = 150
4461

    
4462
cpuavgloadWindowSize :: Int
4463
cpuavgloadWindowSize = 600
4464

    
4465
-- * Monitoring daemon
4466

    
4467
-- | Mond's variable for periodical data collection
4468
mondTimeInterval :: Int
4469
mondTimeInterval = 5
4470

    
4471
-- | Mond's latest API version
4472
mondLatestApiVersion :: Int
4473
mondLatestApiVersion = 1
4474

    
4475
-- * Disk access modes
4476

    
4477
diskUserspace :: String
4478
diskUserspace = Types.diskAccessModeToRaw DiskUserspace
4479

    
4480
diskKernelspace :: String
4481
diskKernelspace = Types.diskAccessModeToRaw DiskKernelspace
4482

    
4483
diskValidAccessModes :: FrozenSet String
4484
diskValidAccessModes =
4485
  ConstantUtils.mkSet $ map Types.diskAccessModeToRaw [minBound..]
4486

    
4487
-- | Timeout for queue draining in upgrades
4488
upgradeQueueDrainTimeout :: Int
4489
upgradeQueueDrainTimeout = 36 * 60 * 60 -- 1.5 days
4490

    
4491
-- | Intervall at which the queue is polled during upgrades
4492
upgradeQueuePollInterval :: Int
4493
upgradeQueuePollInterval  = 10
4494

    
4495
-- * Hotplug Actions
4496

    
4497
hotplugActionAdd :: String
4498
hotplugActionAdd = Types.hotplugActionToRaw HAAdd
4499

    
4500
hotplugActionRemove :: String
4501
hotplugActionRemove = Types.hotplugActionToRaw HARemove
4502

    
4503
hotplugActionModify :: String
4504
hotplugActionModify = Types.hotplugActionToRaw HAMod
4505

    
4506
hotplugAllActions :: FrozenSet String
4507
hotplugAllActions =
4508
  ConstantUtils.mkSet $ map Types.hotplugActionToRaw [minBound..]
4509

    
4510
-- * Hotplug Device Targets
4511

    
4512
hotplugTargetNic :: String
4513
hotplugTargetNic = Types.hotplugTargetToRaw HTNic
4514

    
4515
hotplugTargetDisk :: String
4516
hotplugTargetDisk = Types.hotplugTargetToRaw HTDisk
4517

    
4518
hotplugAllTargets :: FrozenSet String
4519
hotplugAllTargets =
4520
  ConstantUtils.mkSet $ map Types.hotplugTargetToRaw [minBound..]
4521

    
4522
-- | Timeout for disk removal (seconds)
4523
diskRemoveRetryTimeout :: Int
4524
diskRemoveRetryTimeout = 30
4525

    
4526
-- | Interval between disk removal retries (seconds)
4527
diskRemoveRetryInterval :: Int
4528
diskRemoveRetryInterval  = 3
4529

    
4530
-- * UUID regex
4531

    
4532
uuidRegex :: String
4533
uuidRegex = "^[a-f0-9]{8}-[a-f0-9]{4}-[a-f0-9]{4}-[a-f0-9]{4}-[a-f0-9]{12}$"
4534

    
4535
-- * Luxi constants
4536

    
4537
luxiSocketPerms :: Int
4538
luxiSocketPerms = 0o660
4539

    
4540
luxiKeyMethod :: String
4541
luxiKeyMethod = "method"
4542

    
4543
luxiKeyArgs :: String
4544
luxiKeyArgs = "args"
4545

    
4546
luxiKeySuccess :: String
4547
luxiKeySuccess = "success"
4548

    
4549
luxiKeyResult :: String
4550
luxiKeyResult = "result"
4551

    
4552
luxiKeyVersion :: String
4553
luxiKeyVersion = "version"
4554

    
4555
luxiReqSubmitJob :: String
4556
luxiReqSubmitJob = "SubmitJob"
4557

    
4558
luxiReqSubmitJobToDrainedQueue :: String
4559
luxiReqSubmitJobToDrainedQueue = "SubmitJobToDrainedQueue"
4560

    
4561
luxiReqSubmitManyJobs :: String
4562
luxiReqSubmitManyJobs = "SubmitManyJobs"
4563

    
4564
luxiReqWaitForJobChange :: String
4565
luxiReqWaitForJobChange = "WaitForJobChange"
4566

    
4567
luxiReqPickupJob :: String
4568
luxiReqPickupJob = "PickupJob"
4569

    
4570
luxiReqCancelJob :: String
4571
luxiReqCancelJob = "CancelJob"
4572

    
4573
luxiReqArchiveJob :: String
4574
luxiReqArchiveJob = "ArchiveJob"
4575

    
4576
luxiReqChangeJobPriority :: String
4577
luxiReqChangeJobPriority = "ChangeJobPriority"
4578

    
4579
luxiReqAutoArchiveJobs :: String
4580
luxiReqAutoArchiveJobs = "AutoArchiveJobs"
4581

    
4582
luxiReqQuery :: String
4583
luxiReqQuery = "Query"
4584

    
4585
luxiReqQueryFields :: String
4586
luxiReqQueryFields = "QueryFields"
4587

    
4588
luxiReqQueryJobs :: String
4589
luxiReqQueryJobs = "QueryJobs"
4590

    
4591
luxiReqQueryInstances :: String
4592
luxiReqQueryInstances = "QueryInstances"
4593

    
4594
luxiReqQueryNodes :: String
4595
luxiReqQueryNodes = "QueryNodes"
4596

    
4597
luxiReqQueryGroups :: String
4598
luxiReqQueryGroups = "QueryGroups"
4599

    
4600
luxiReqQueryNetworks :: String
4601
luxiReqQueryNetworks = "QueryNetworks"
4602

    
4603
luxiReqQueryExports :: String
4604
luxiReqQueryExports = "QueryExports"
4605

    
4606
luxiReqQueryConfigValues :: String
4607
luxiReqQueryConfigValues = "QueryConfigValues"
4608

    
4609
luxiReqQueryClusterInfo :: String
4610
luxiReqQueryClusterInfo = "QueryClusterInfo"
4611

    
4612
luxiReqQueryTags :: String
4613
luxiReqQueryTags = "QueryTags"
4614

    
4615
luxiReqSetDrainFlag :: String
4616
luxiReqSetDrainFlag = "SetDrainFlag"
4617

    
4618
luxiReqSetWatcherPause :: String
4619
luxiReqSetWatcherPause = "SetWatcherPause"
4620

    
4621
luxiReqAll :: FrozenSet String
4622
luxiReqAll =
4623
  ConstantUtils.mkSet
4624
  [ luxiReqArchiveJob
4625
  , luxiReqAutoArchiveJobs
4626
  , luxiReqCancelJob
4627
  , luxiReqChangeJobPriority
4628
  , luxiReqQuery
4629
  , luxiReqQueryClusterInfo
4630
  , luxiReqQueryConfigValues
4631
  , luxiReqQueryExports
4632
  , luxiReqQueryFields
4633
  , luxiReqQueryGroups
4634
  , luxiReqQueryInstances
4635
  , luxiReqQueryJobs
4636
  , luxiReqQueryNodes
4637
  , luxiReqQueryNetworks
4638
  , luxiReqQueryTags
4639
  , luxiReqSetDrainFlag
4640
  , luxiReqSetWatcherPause
4641
  , luxiReqSubmitJob
4642
  , luxiReqSubmitJobToDrainedQueue
4643
  , luxiReqSubmitManyJobs
4644
  , luxiReqWaitForJobChange
4645
  , luxiReqPickupJob
4646
  ]
4647

    
4648
luxiDefCtmo :: Int
4649
luxiDefCtmo = 10
4650

    
4651
luxiDefRwto :: Int
4652
luxiDefRwto = 60
4653

    
4654
-- | 'WaitForJobChange' timeout
4655
luxiWfjcTimeout :: Int
4656
luxiWfjcTimeout = (luxiDefRwto - 1) `div` 2
4657

    
4658
-- * Query language constants
4659

    
4660
-- ** Logic operators with one or more operands, each of which is a
4661
-- filter on its own
4662

    
4663
qlangOpAnd :: String
4664
qlangOpAnd = "&"
4665

    
4666
qlangOpOr :: String
4667
qlangOpOr = "|"
4668

    
4669
-- ** Unary operators with exactly one operand
4670

    
4671
qlangOpNot :: String
4672
qlangOpNot = "!"
4673

    
4674
qlangOpTrue :: String
4675
qlangOpTrue = "?"
4676

    
4677
-- ** Binary operators with exactly two operands, the field name and
4678
-- an operator-specific value
4679

    
4680
qlangOpContains :: String
4681
qlangOpContains = "=[]"
4682

    
4683
qlangOpEqual :: String
4684
qlangOpEqual = "="
4685

    
4686
qlangOpGe :: String
4687
qlangOpGe = ">="
4688

    
4689
qlangOpGt :: String
4690
qlangOpGt = ">"
4691

    
4692
qlangOpLe :: String
4693
qlangOpLe = "<="
4694

    
4695
qlangOpLt :: String
4696
qlangOpLt = "<"
4697

    
4698
qlangOpNotEqual :: String
4699
qlangOpNotEqual = "!="
4700

    
4701
qlangOpRegexp :: String
4702
qlangOpRegexp = "=~"
4703

    
4704
-- | Characters used for detecting user-written filters (see
4705
-- L{_CheckFilter})
4706

    
4707
qlangFilterDetectionChars :: FrozenSet String
4708
qlangFilterDetectionChars =
4709
  ConstantUtils.mkSet ["!", " ", "\"", "\'",
4710
                       ")", "(", "\x0b", "\n",
4711
                       "\r", "\x0c", "/", "<",
4712
                       "\t", ">", "=", "\\", "~"]
4713

    
4714
-- | Characters used to detect globbing filters
4715
qlangGlobDetectionChars :: FrozenSet String
4716
qlangGlobDetectionChars = ConstantUtils.mkSet ["*", "?"]
4717

    
4718
-- * Error related constants
4719
--
4720
-- 'OpPrereqError' failure types
4721

    
4722
-- | Environment error (e.g. node disk error)
4723
errorsEcodeEnviron :: String
4724
errorsEcodeEnviron = "environment_error"
4725

    
4726
-- | Entity already exists
4727
errorsEcodeExists :: String
4728
errorsEcodeExists = "already_exists"
4729

    
4730
-- | Internal cluster error
4731
errorsEcodeFault :: String
4732
errorsEcodeFault = "internal_error"
4733

    
4734
-- | Wrong arguments (at syntax level)
4735
errorsEcodeInval :: String
4736
errorsEcodeInval = "wrong_input"
4737

    
4738
-- | Entity not found
4739
errorsEcodeNoent :: String
4740
errorsEcodeNoent = "unknown_entity"
4741

    
4742
-- | Not enough resources (iallocator failure, disk space, memory, etc)
4743
errorsEcodeNores :: String
4744
errorsEcodeNores = "insufficient_resources"
4745

    
4746
-- | Resource not unique (e.g. MAC or IP duplication)
4747
errorsEcodeNotunique :: String
4748
errorsEcodeNotunique = "resource_not_unique"
4749

    
4750
-- | Resolver errors
4751
errorsEcodeResolver :: String
4752
errorsEcodeResolver = "resolver_error"
4753

    
4754
-- | Wrong entity state
4755
errorsEcodeState :: String
4756
errorsEcodeState = "wrong_state"
4757

    
4758
-- | Temporarily out of resources; operation can be tried again
4759
errorsEcodeTempNores :: String
4760
errorsEcodeTempNores = "temp_insufficient_resources"
4761

    
4762
errorsEcodeAll :: FrozenSet String
4763
errorsEcodeAll =
4764
  ConstantUtils.mkSet [ errorsEcodeNores
4765
                      , errorsEcodeExists
4766
                      , errorsEcodeState
4767
                      , errorsEcodeNotunique
4768
                      , errorsEcodeTempNores
4769
                      , errorsEcodeNoent
4770
                      , errorsEcodeFault
4771
                      , errorsEcodeResolver
4772
                      , errorsEcodeInval
4773
                      , errorsEcodeEnviron
4774
                      ]
4775

    
4776
-- * Jstore related constants
4777

    
4778
jstoreJobsPerArchiveDirectory :: Int
4779
jstoreJobsPerArchiveDirectory = 10000
4780

    
4781
-- * Gluster settings
4782

    
4783
-- | Name of the Gluster host setting
4784
glusterHost :: String
4785
glusterHost = "host"
4786

    
4787
-- | Default value of the Gluster host setting
4788
glusterHostDefault :: String
4789
glusterHostDefault = "127.0.0.1"
4790

    
4791
-- | Name of the Gluster volume setting
4792
glusterVolume :: String
4793
glusterVolume = "volume"
4794

    
4795
-- | Default value of the Gluster volume setting
4796
glusterVolumeDefault :: String
4797
glusterVolumeDefault = "gv0"
4798

    
4799
-- | Name of the Gluster port setting
4800
glusterPort :: String
4801
glusterPort = "port"
4802

    
4803
-- | Default value of the Gluster port setting
4804
glusterPortDefault :: Int
4805
glusterPortDefault = 24007
4806

    
4807
-- * Instance communication
4808
--
4809
-- The instance communication attaches an additional NIC, named
4810
-- @instanceCommunicationNicPrefix@:@instanceName@ with MAC address
4811
-- prefixed by @instanceCommunicationMacPrefix@, to the instances that
4812
-- have instance communication enabled.  This NIC is part of the
4813
-- instance communication network which is supplied by the user via
4814
--
4815
--   gnt-cluster modify --instance-communication=mynetwork
4816
--
4817
-- This network is defined as @instanceCommunicationNetwork4@ for IPv4
4818
-- and @instanceCommunicationNetwork6@ for IPv6.
4819

    
4820
instanceCommunicationDoc :: String
4821
instanceCommunicationDoc =
4822
  "Enable or disable the communication mechanism for an instance"
4823

    
4824
instanceCommunicationMacPrefix :: String
4825
instanceCommunicationMacPrefix = "52:54:00"
4826

    
4827
-- | The instance communication network is a link-local IPv4/IPv6
4828
-- network because the communication is meant to be exclusive between
4829
-- the host and the guest and not routed outside the node.
4830
instanceCommunicationNetwork4 :: String
4831
instanceCommunicationNetwork4 = "169.254.0.0/16"
4832

    
4833
-- | See 'instanceCommunicationNetwork4'.
4834
instanceCommunicationNetwork6 :: String
4835
instanceCommunicationNetwork6 = "fe80::/10"
4836

    
4837
instanceCommunicationNetworkLink :: String
4838
instanceCommunicationNetworkLink = "communication_rt"
4839

    
4840
instanceCommunicationNetworkMode :: String
4841
instanceCommunicationNetworkMode = nicModeRouted
4842

    
4843
instanceCommunicationNicPrefix :: String
4844
instanceCommunicationNicPrefix = "ganeti:communication:"
4845

    
4846
-- | Parameters that should be protected
4847
--
4848
-- Python does not have a type system and can't automatically infer what should
4849
-- be the resulting type of a JSON request. As a result, it must rely on this
4850
-- list of parameter names to protect values correctly.
4851
--
4852
-- Names ending in _cluster will be treated as dicts of dicts of private values.
4853
-- Otherwise they are considered dicts of private values.
4854
privateParametersBlacklist :: [String]
4855
privateParametersBlacklist = [ "osparams_private"
4856
                             , "osparams_secret"
4857
                             , "osparams_private_cluster"
4858
                             ]
4859

    
4860
-- | Warn the user that the logging level is too low for production use.
4861
debugModeConfidentialityWarning :: String
4862
debugModeConfidentialityWarning =
4863
  "ALERT: %s started in debug mode.\n\
4864
  \ Private and secret parameters WILL be logged!\n"