Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HsConstants.hs @ 343dcda8

History | View | Annotate | Download (53.7 kB)

1
{-| HsConstants contains the Haskell constants
2

    
3
This is a transitional module complementary to 'Ganeti.Constants'.  It
4
is intended to contain the Haskell constants that are meant to be
5
generated in 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 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.HsConstants where
38

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

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

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

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

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

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

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

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

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

    
80
-- * 'autoconf' constants for Python only ('lib/pathutils.py')
81

    
82
-- ** Build-time constants
83

    
84
exportDir :: String
85
exportDir = AutoConf.exportDir
86

    
87
osSearchPath :: [String]
88
osSearchPath = AutoConf.osSearchPath
89

    
90
esSearchPath :: [String]
91
esSearchPath = AutoConf.esSearchPath
92

    
93
sshConfigDir :: String
94
sshConfigDir = AutoConf.sshConfigDir
95

    
96
xenConfigDir :: String
97
xenConfigDir = AutoConf.xenConfigDir
98

    
99
sysconfdir :: String
100
sysconfdir = AutoConf.sysconfdir
101

    
102
toolsdir :: String
103
toolsdir = AutoConf.toolsdir
104

    
105
localstatedir :: String
106
localstatedir = AutoConf.localstatedir
107

    
108
-- ** Paths which don't change for a virtual cluster
109

    
110
pkglibdir :: String
111
pkglibdir = AutoConf.pkglibdir
112

    
113
sharedir :: String
114
sharedir = AutoConf.sharedir
115

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

    
118
manPages :: Map String Int
119
manPages = Map.fromList AutoConf.manPages
120

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

    
123
versionedsharedir :: String
124
versionedsharedir = AutoConf.versionedsharedir
125

    
126
-- * 'autoconf' constants for Python only ('tests/py/docs_unittest.py')
127

    
128
gntScripts :: [String]
129
gntScripts = AutoConf.gntScripts
130

    
131
-- * Various versions
132

    
133
releaseVersion :: String
134
releaseVersion = AutoConf.packageVersion
135

    
136
versionMajor :: Int
137
versionMajor = AutoConf.versionMajor
138

    
139
versionMinor :: Int
140
versionMinor = AutoConf.versionMinor
141

    
142
versionRevision :: Int
143
versionRevision = AutoConf.versionRevision
144

    
145
dirVersion :: String
146
dirVersion = AutoConf.dirVersion
147

    
148
osApiV10 :: Int
149
osApiV10 = 10
150

    
151
osApiV15 :: Int
152
osApiV15 = 15
153

    
154
osApiV20 :: Int
155
osApiV20 = 20
156

    
157
osApiVersions :: FrozenSet Int
158
osApiVersions = ConstantUtils.mkSet [osApiV10, osApiV15, osApiV20]
159

    
160
exportVersion :: Int
161
exportVersion = 0
162

    
163
rapiVersion :: Int
164
rapiVersion = 2
165

    
166
configMajor :: Int
167
configMajor = AutoConf.versionMajor
168

    
169
configMinor :: Int
170
configMinor = AutoConf.versionMinor
171

    
172
-- | The configuration is supposed to remain stable across
173
-- revisions. Therefore, the revision number is cleared to '0'.
174
configRevision :: Int
175
configRevision = 0
176

    
177
configVersion :: Int
178
configVersion = buildVersion configMajor configMinor configRevision
179

    
180
-- | Similarly to the configuration (see 'configRevision'), the
181
-- protocols are supposed to remain stable across revisions.
182
protocolVersion :: Int
183
protocolVersion = buildVersion configMajor configMinor configRevision
184

    
185
-- * User separation
186

    
187
daemonsGroup :: String
188
daemonsGroup = Runtime.daemonGroup (ExtraGroup DaemonsGroup)
189

    
190
adminGroup :: String
191
adminGroup = Runtime.daemonGroup (ExtraGroup AdminGroup)
192

    
193
masterdUser :: String
194
masterdUser = Runtime.daemonUser GanetiMasterd
195

    
196
masterdGroup :: String
197
masterdGroup = Runtime.daemonGroup (DaemonGroup GanetiMasterd)
198

    
199
rapiUser :: String
200
rapiUser = Runtime.daemonUser GanetiRapi
201

    
202
rapiGroup :: String
203
rapiGroup = Runtime.daemonGroup (DaemonGroup GanetiRapi)
204

    
205
confdUser :: String
206
confdUser = Runtime.daemonUser GanetiConfd
207

    
208
confdGroup :: String
209
confdGroup = Runtime.daemonGroup (DaemonGroup GanetiConfd)
210

    
211
luxidUser :: String
212
luxidUser = Runtime.daemonUser GanetiLuxid
213

    
214
luxidGroup :: String
215
luxidGroup = Runtime.daemonGroup (DaemonGroup GanetiLuxid)
216

    
217
nodedUser :: String
218
nodedUser = Runtime.daemonUser GanetiNoded
219

    
220
nodedGroup :: String
221
nodedGroup = Runtime.daemonGroup (DaemonGroup GanetiNoded)
222

    
223
mondUser :: String
224
mondUser = Runtime.daemonUser GanetiMond
225

    
226
mondGroup :: String
227
mondGroup = Runtime.daemonGroup (DaemonGroup GanetiMond)
228

    
229
sshLoginUser :: String
230
sshLoginUser = AutoConf.sshLoginUser
231

    
232
sshConsoleUser :: String
233
sshConsoleUser = AutoConf.sshConsoleUser
234

    
235
-- * Cpu pinning separators and constants
236

    
237
cpuPinningSep :: String
238
cpuPinningSep = ":"
239

    
240
cpuPinningAll :: String
241
cpuPinningAll = "all"
242

    
243
-- | Internal representation of "all"
244
cpuPinningAllVal :: Int
245
cpuPinningAllVal = -1
246

    
247
-- | One "all" entry in a CPU list means CPU pinning is off
248
cpuPinningOff :: [Int]
249
cpuPinningOff = [cpuPinningAllVal]
250

    
251
-- | A Xen-specific implementation detail is that there is no way to
252
-- actually say "use any cpu for pinning" in a Xen configuration file,
253
-- as opposed to the command line, where you can say
254
-- @
255
-- xm vcpu-pin <domain> <vcpu> all
256
-- @
257
--
258
-- The workaround used in Xen is "0-63" (see source code function
259
-- "xm_vcpu_pin" in @<xen-source>/tools/python/xen/xm/main.py@).
260
--
261
-- To support future changes, the following constant is treated as a
262
-- blackbox string that simply means "use any cpu for pinning under
263
-- xen".
264
cpuPinningAllXen :: String
265
cpuPinningAllXen = "0-63"
266

    
267
-- | A KVM-specific implementation detail - the following value is
268
-- used to set CPU affinity to all processors (--0 through --31), per
269
-- taskset man page.
270
--
271
-- FIXME: This only works for machines with up to 32 CPU cores
272
cpuPinningAllKvm :: Int
273
cpuPinningAllKvm = 0xFFFFFFFF
274

    
275
-- * Wipe
276

    
277
ddCmd :: String
278
ddCmd = "dd"
279

    
280
-- | 1GB
281
maxWipeChunk :: Int
282
maxWipeChunk = 1024
283

    
284
minWipeChunkPercent :: Int
285
minWipeChunkPercent = 10
286

    
287
-- * Directories
288

    
289
runDirsMode :: Int
290
runDirsMode = 0o775
291

    
292
secureDirMode :: Int
293
secureDirMode = 0o700
294

    
295
secureFileMode :: Int
296
secureFileMode = 0o600
297

    
298
adoptableBlockdevRoot :: String
299
adoptableBlockdevRoot = "/dev/disk/"
300

    
301
-- * 'autoconf' enable/disable
302

    
303
enableConfd :: Bool
304
enableConfd = AutoConf.enableConfd
305

    
306
enableMond :: Bool
307
enableMond = AutoConf.enableMond
308

    
309
enableRestrictedCommands :: Bool
310
enableRestrictedCommands = AutoConf.enableRestrictedCommands
311

    
312
enableSplitQuery :: Bool
313
enableSplitQuery = AutoConf.enableSplitQuery
314

    
315
-- * SSH constants
316

    
317
ssh :: String
318
ssh = "ssh"
319

    
320
scp :: String
321
scp = "scp"
322

    
323
-- * Daemons
324

    
325
confd :: String
326
confd = Runtime.daemonName GanetiConfd
327

    
328
masterd :: String
329
masterd = Runtime.daemonName GanetiMasterd
330

    
331
mond :: String
332
mond = Runtime.daemonName GanetiMond
333

    
334
noded :: String
335
noded = Runtime.daemonName GanetiNoded
336

    
337
luxid :: String
338
luxid = Runtime.daemonName GanetiLuxid
339

    
340
rapi :: String
341
rapi = Runtime.daemonName GanetiRapi
342

    
343
daemons :: FrozenSet String
344
daemons =
345
  ConstantUtils.mkSet [confd,
346
                       luxid,
347
                       masterd,
348
                       mond,
349
                       noded,
350
                       rapi]
351

    
352
defaultConfdPort :: Int
353
defaultConfdPort = 1814
354

    
355
defaultMondPort :: Int
356
defaultMondPort = 1815
357

    
358
defaultNodedPort :: Int
359
defaultNodedPort = 1811
360

    
361
defaultRapiPort :: Int
362
defaultRapiPort = 5080
363

    
364
daemonsPorts :: Map String (Protocol, Int)
365
daemonsPorts =
366
  Map.fromList [(confd, (Udp, defaultConfdPort)),
367
                (mond, (Tcp, defaultMondPort)),
368
                (noded, (Tcp, defaultNodedPort)),
369
                (rapi, (Tcp, defaultRapiPort)),
370
                (ssh, (Tcp, 22))]
371

    
372
firstDrbdPort :: Int
373
firstDrbdPort = 11000
374

    
375
lastDrbdPort :: Int
376
lastDrbdPort = 14999
377

    
378
daemonsLogbase :: Map String String
379
daemonsLogbase =
380
  Map.fromList
381
  [ (Runtime.daemonName d, Runtime.daemonLogBase d) | d <- [minBound..] ]
382

    
383
extraLogreasonAccess :: String
384
extraLogreasonAccess = Runtime.daemonsExtraLogbase GanetiMond AccessLog
385

    
386
extraLogreasonError :: String
387
extraLogreasonError = Runtime.daemonsExtraLogbase GanetiMond ErrorLog
388

    
389
devConsole :: String
390
devConsole = ConstantUtils.devConsole
391

    
392
procMounts :: String
393
procMounts = "/proc/mounts"
394

    
395
-- * Luxi (Local UniX Interface) related constants
396

    
397
luxiEom :: PythonChar
398
luxiEom = PythonChar '\x03'
399

    
400
-- | Environment variable for the luxi override socket
401
luxiOverride :: String
402
luxiOverride = "FORCE_LUXI_SOCKET"
403

    
404
luxiOverrideMaster :: String
405
luxiOverrideMaster = "master"
406

    
407
luxiOverrideQuery :: String
408
luxiOverrideQuery = "query"
409

    
410
luxiVersion :: Int
411
luxiVersion = configVersion
412

    
413
-- * Syslog
414

    
415
syslogUsage :: String
416
syslogUsage = AutoConf.syslogUsage
417

    
418
syslogNo :: String
419
syslogNo = Logging.syslogUsageToRaw SyslogNo
420

    
421
syslogYes :: String
422
syslogYes = Logging.syslogUsageToRaw SyslogYes
423

    
424
syslogOnly :: String
425
syslogOnly = Logging.syslogUsageToRaw SyslogOnly
426

    
427
syslogSocket :: String
428
syslogSocket = "/dev/log"
429

    
430
exportConfFile :: String
431
exportConfFile = "config.ini"
432

    
433
-- * Xen
434

    
435
xenBootloader :: String
436
xenBootloader = AutoConf.xenBootloader
437

    
438
xenCmdXl :: String
439
xenCmdXl = "xl"
440

    
441
xenCmdXm :: String
442
xenCmdXm = "xm"
443

    
444
xenInitrd :: String
445
xenInitrd = AutoConf.xenInitrd
446

    
447
xenKernel :: String
448
xenKernel = AutoConf.xenKernel
449

    
450
-- FIXME: perhaps rename to 'validXenCommands' for consistency with
451
-- other constants
452
knownXenCommands :: FrozenSet String
453
knownXenCommands = ConstantUtils.mkSet [xenCmdXl, xenCmdXm]
454

    
455
-- * KVM and socat
456

    
457
kvmPath :: String
458
kvmPath = AutoConf.kvmPath
459

    
460
kvmKernel :: String
461
kvmKernel = AutoConf.kvmKernel
462

    
463
socatEscapeCode :: String
464
socatEscapeCode = "0x1d"
465

    
466
socatPath :: String
467
socatPath = AutoConf.socatPath
468

    
469
socatUseCompress :: Bool
470
socatUseCompress = AutoConf.socatUseCompress
471

    
472
socatUseEscape :: Bool
473
socatUseEscape = AutoConf.socatUseEscape
474

    
475
-- * Console types
476

    
477
-- | Display a message for console access
478
consMessage :: String
479
consMessage = "msg"
480

    
481
-- | Console as SPICE server
482
consSpice :: String
483
consSpice = "spice"
484

    
485
-- | Console as SSH command
486
consSsh :: String
487
consSsh = "ssh"
488

    
489
-- | Console as VNC server
490
consVnc :: String
491
consVnc = "vnc"
492

    
493
consAll :: FrozenSet String
494
consAll = ConstantUtils.mkSet [consMessage, consSpice, consSsh, consVnc]
495

    
496
-- | RSA key bit length
497
--
498
-- For RSA keys more bits are better, but they also make operations
499
-- more expensive. NIST SP 800-131 recommends a minimum of 2048 bits
500
-- from the year 2010 on.
501
rsaKeyBits :: Int
502
rsaKeyBits = 2048
503

    
504
-- | Ciphers allowed for SSL connections.
505
--
506
-- For the format, see ciphers(1). A better way to disable ciphers
507
-- would be to use the exclamation mark (!), but socat versions below
508
-- 1.5 can't parse exclamation marks in options properly. When
509
-- modifying the ciphers, ensure not to accidentially add something
510
-- after it's been removed. Use the "openssl" utility to check the
511
-- allowed ciphers, e.g.  "openssl ciphers -v HIGH:-DES".
512
opensslCiphers :: String
513
opensslCiphers = "HIGH:-DES:-3DES:-EXPORT:-ADH"
514

    
515
-- * X509
516

    
517
-- | commonName (CN) used in certificates
518
x509CertCn :: String
519
x509CertCn = "ganeti.example.com"
520

    
521
-- | Default validity of certificates in days
522
x509CertDefaultValidity :: Int
523
x509CertDefaultValidity = 365 * 5
524

    
525
x509CertSignatureHeader :: String
526
x509CertSignatureHeader = "X-Ganeti-Signature"
527

    
528
-- | Digest used to sign certificates ("openssl x509" uses SHA1 by default)
529
x509CertSignDigest :: String
530
x509CertSignDigest = "SHA1"
531

    
532
-- * Import/export daemon mode
533

    
534
iemExport :: String
535
iemExport = "export"
536

    
537
iemImport :: String
538
iemImport = "import"
539

    
540
-- * Import/export transport compression
541

    
542
iecGzip :: String
543
iecGzip = "gzip"
544

    
545
iecNone :: String
546
iecNone = "none"
547

    
548
iecAll :: [String]
549
iecAll = [iecGzip, iecNone]
550

    
551
ieCustomSize :: String
552
ieCustomSize = "fd"
553

    
554
-- * Import/export I/O
555

    
556
-- | Direct file I/O, equivalent to a shell's I/O redirection using
557
-- '<' or '>'
558
ieioFile :: String
559
ieioFile = "file"
560

    
561
-- | Raw block device I/O using "dd"
562
ieioRawDisk :: String
563
ieioRawDisk = "raw"
564

    
565
-- | OS definition import/export script
566
ieioScript :: String
567
ieioScript = "script"
568

    
569
-- * Hooks
570

    
571
hooksNameCfgupdate :: String
572
hooksNameCfgupdate = "config-update"
573

    
574
hooksNameWatcher :: String
575
hooksNameWatcher = "watcher"
576

    
577
hooksPath :: String
578
hooksPath = "/sbin:/bin:/usr/sbin:/usr/bin"
579

    
580
hooksPhasePost :: String
581
hooksPhasePost = "post"
582

    
583
hooksPhasePre :: String
584
hooksPhasePre = "pre"
585

    
586
hooksVersion :: Int
587
hooksVersion = 2
588

    
589
-- * Hooks subject type (what object type does the LU deal with)
590

    
591
htypeCluster :: String
592
htypeCluster = "CLUSTER"
593

    
594
htypeGroup :: String
595
htypeGroup = "GROUP"
596

    
597
htypeInstance :: String
598
htypeInstance = "INSTANCE"
599

    
600
htypeNetwork :: String
601
htypeNetwork = "NETWORK"
602

    
603
htypeNode :: String
604
htypeNode = "NODE"
605

    
606
-- * Hkr
607

    
608
hkrSkip :: Int
609
hkrSkip = 0
610

    
611
hkrFail :: Int
612
hkrFail = 1
613

    
614
hkrSuccess :: Int
615
hkrSuccess = 2
616

    
617
-- * Storage types
618

    
619
stBlock :: String
620
stBlock = Types.storageTypeToRaw StorageBlock
621

    
622
stDiskless :: String
623
stDiskless = Types.storageTypeToRaw StorageDiskless
624

    
625
stExt :: String
626
stExt = Types.storageTypeToRaw StorageExt
627

    
628
stFile :: String
629
stFile = Types.storageTypeToRaw StorageFile
630

    
631
stLvmPv :: String
632
stLvmPv = Types.storageTypeToRaw StorageLvmPv
633

    
634
stLvmVg :: String
635
stLvmVg = Types.storageTypeToRaw StorageLvmVg
636

    
637
stRados :: String
638
stRados = Types.storageTypeToRaw StorageRados
639

    
640
storageTypes :: FrozenSet String
641
storageTypes = ConstantUtils.mkSet $ map Types.storageTypeToRaw [minBound..]
642

    
643
-- | The set of storage types for which storage reporting is available
644
--
645
-- FIXME: Remove this, once storage reporting is available for all
646
-- types.
647
stsReport :: FrozenSet String
648
stsReport = ConstantUtils.mkSet [stFile, stLvmPv, stLvmVg]
649

    
650
-- * Storage fields
651
-- ** First two are valid in LU context only, not passed to backend
652

    
653
sfNode :: String
654
sfNode = "node"
655

    
656
sfType :: String
657
sfType = "type"
658

    
659
-- ** and the rest are valid in backend
660

    
661
sfAllocatable :: String
662
sfAllocatable = Types.storageFieldToRaw SFAllocatable
663

    
664
sfFree :: String
665
sfFree = Types.storageFieldToRaw SFFree
666

    
667
sfName :: String
668
sfName = Types.storageFieldToRaw SFName
669

    
670
sfSize :: String
671
sfSize = Types.storageFieldToRaw SFSize
672

    
673
sfUsed :: String
674
sfUsed = Types.storageFieldToRaw SFUsed
675

    
676
validStorageFields :: FrozenSet String
677
validStorageFields =
678
  ConstantUtils.mkSet $ map Types.storageFieldToRaw [minBound..] ++
679
                        [sfNode, sfType]
680

    
681
modifiableStorageFields :: Map String (FrozenSet String)
682
modifiableStorageFields =
683
  Map.fromList [(Types.storageTypeToRaw StorageLvmPv,
684
                 ConstantUtils.mkSet [sfAllocatable])]
685

    
686
-- * Storage operations
687

    
688
soFixConsistency :: String
689
soFixConsistency = "fix-consistency"
690

    
691
validStorageOperations :: Map String (FrozenSet String)
692
validStorageOperations =
693
  Map.fromList [(Types.storageTypeToRaw StorageLvmVg,
694
                 ConstantUtils.mkSet [soFixConsistency])]
695

    
696
-- * Volume fields
697

    
698
vfDev :: String
699
vfDev = "dev"
700

    
701
vfInstance :: String
702
vfInstance = "instance"
703

    
704
vfName :: String
705
vfName = "name"
706

    
707
vfNode :: String
708
vfNode = "node"
709

    
710
vfPhys :: String
711
vfPhys = "phys"
712

    
713
vfSize :: String
714
vfSize = "size"
715

    
716
vfVg :: String
717
vfVg = "vg"
718

    
719
-- * Local disk status
720

    
721
ldsFaulty :: Int
722
ldsFaulty = Types.localDiskStatusToRaw DiskStatusFaulty
723

    
724
ldsOkay :: Int
725
ldsOkay = Types.localDiskStatusToRaw DiskStatusOk
726

    
727
ldsUnknown :: Int
728
ldsUnknown = Types.localDiskStatusToRaw DiskStatusUnknown
729

    
730
ldsNames :: Map Int String
731
ldsNames =
732
  Map.fromList [ (Types.localDiskStatusToRaw ds,
733
                  localDiskStatusName ds) | ds <- [minBound..] ]
734

    
735
-- * Disk template types
736

    
737
dtDiskless :: String
738
dtDiskless = Types.diskTemplateToRaw DTDiskless
739

    
740
dtFile :: String
741
dtFile = Types.diskTemplateToRaw DTFile
742

    
743
dtSharedFile :: String
744
dtSharedFile = Types.diskTemplateToRaw DTSharedFile
745

    
746
dtPlain :: String
747
dtPlain = Types.diskTemplateToRaw DTPlain
748

    
749
dtBlock :: String
750
dtBlock = Types.diskTemplateToRaw DTBlock
751

    
752
dtDrbd8 :: String
753
dtDrbd8 = Types.diskTemplateToRaw DTDrbd8
754

    
755
dtRbd :: String
756
dtRbd = Types.diskTemplateToRaw DTRbd
757

    
758
dtExt :: String
759
dtExt = Types.diskTemplateToRaw DTExt
760

    
761
-- | This is used to order determine the default disk template when
762
-- the list of enabled disk templates is inferred from the current
763
-- state of the cluster.  This only happens on an upgrade from a
764
-- version of Ganeti that did not support the 'enabled_disk_templates'
765
-- so far.
766
diskTemplatePreference :: [String]
767
diskTemplatePreference =
768
  map Types.diskTemplateToRaw
769
  [DTBlock, DTDiskless, DTDrbd8, DTExt, DTFile, DTPlain, DTRbd, DTSharedFile]
770

    
771
diskTemplates :: FrozenSet String
772
diskTemplates = ConstantUtils.mkSet $ map Types.diskTemplateToRaw [minBound..]
773

    
774
-- | Disk templates that are enabled by default
775
defaultEnabledDiskTemplates :: [String]
776
defaultEnabledDiskTemplates = map Types.diskTemplateToRaw [DTDrbd8, DTPlain]
777

    
778
-- | Mapping of disk templates to storage types
779
mapDiskTemplateStorageType :: Map String String
780
mapDiskTemplateStorageType =
781
  Map.fromList $
782
  map (Types.diskTemplateToRaw *** Types.storageTypeToRaw)
783
  [(DTBlock, StorageBlock),
784
   (DTDrbd8, StorageLvmVg),
785
   (DTExt, StorageExt),
786
   (DTSharedFile, StorageFile),
787
   (DTFile, StorageFile),
788
   (DTDiskless, StorageDiskless),
789
   (DTPlain, StorageLvmVg),
790
   (DTRbd, StorageRados)]
791

    
792
-- | The set of network-mirrored disk templates
793
dtsIntMirror :: FrozenSet String
794
dtsIntMirror = ConstantUtils.mkSet [dtDrbd8]
795

    
796
-- | 'DTDiskless' is 'trivially' externally mirrored
797
dtsExtMirror :: FrozenSet String
798
dtsExtMirror =
799
  ConstantUtils.mkSet $
800
  map Types.diskTemplateToRaw [DTDiskless, DTBlock, DTExt, DTSharedFile, DTRbd]
801

    
802
-- | The set of non-lvm-based disk templates
803
dtsNotLvm :: FrozenSet String
804
dtsNotLvm =
805
  ConstantUtils.mkSet $
806
  map Types.diskTemplateToRaw
807
  [DTSharedFile, DTDiskless, DTBlock, DTExt, DTFile, DTRbd]
808

    
809
-- | The set of disk templates which can be grown
810
dtsGrowable :: FrozenSet String
811
dtsGrowable =
812
  ConstantUtils.mkSet $
813
  map Types.diskTemplateToRaw
814
  [DTSharedFile, DTDrbd8, DTPlain, DTExt, DTFile, DTRbd]
815

    
816
-- | The set of disk templates that allow adoption
817
dtsMayAdopt :: FrozenSet String
818
dtsMayAdopt =
819
  ConstantUtils.mkSet $ map Types.diskTemplateToRaw [DTBlock, DTPlain]
820

    
821
-- | The set of disk templates that *must* use adoption
822
dtsMustAdopt :: FrozenSet String
823
dtsMustAdopt = ConstantUtils.mkSet [Types.diskTemplateToRaw DTBlock]
824

    
825
-- | The set of disk templates that allow migrations
826
dtsMirrored :: FrozenSet String
827
dtsMirrored = dtsIntMirror `ConstantUtils.union` dtsExtMirror
828

    
829
-- | The set of file based disk templates
830
dtsFilebased :: FrozenSet String
831
dtsFilebased =
832
  ConstantUtils.mkSet $ map Types.diskTemplateToRaw [DTSharedFile, DTFile]
833

    
834
-- | The set of disk templates that can be moved by copying
835
--
836
-- Note: a requirement is that they're not accessed externally or
837
-- shared between nodes; in particular, sharedfile is not suitable.
838
dtsCopyable :: FrozenSet String
839
dtsCopyable =
840
  ConstantUtils.mkSet $ map Types.diskTemplateToRaw [DTPlain, DTFile]
841

    
842
-- | The set of disk templates that are supported by exclusive_storage
843
dtsExclStorage :: FrozenSet String
844
dtsExclStorage = ConstantUtils.mkSet $ map Types.diskTemplateToRaw [DTPlain]
845

    
846
-- | Templates for which we don't perform checks on free space
847
dtsNoFreeSpaceCheck :: FrozenSet String
848
dtsNoFreeSpaceCheck =
849
  ConstantUtils.mkSet $
850
  map Types.diskTemplateToRaw [DTExt, DTSharedFile, DTFile, DTRbd]
851

    
852
dtsBlock :: FrozenSet String
853
dtsBlock =
854
  ConstantUtils.mkSet $
855
  map Types.diskTemplateToRaw [DTPlain, DTDrbd8, DTBlock, DTRbd, DTExt]
856

    
857
-- * Drbd
858

    
859
drbdHmacAlg :: String
860
drbdHmacAlg = "md5"
861

    
862
drbdDefaultNetProtocol :: String
863
drbdDefaultNetProtocol = "C"
864

    
865
drbdMigrationNetProtocol :: String
866
drbdMigrationNetProtocol = "C"
867

    
868
drbdStatusFile :: String
869
drbdStatusFile = "/proc/drbd"
870

    
871
-- | Size of DRBD meta block device
872
drbdMetaSize :: Int
873
drbdMetaSize = 128
874

    
875
-- * Drbd barrier types
876

    
877
drbdBDiskBarriers :: String
878
drbdBDiskBarriers = "b"
879

    
880
drbdBDiskDrain :: String
881
drbdBDiskDrain = "d"
882

    
883
drbdBDiskFlush :: String
884
drbdBDiskFlush = "f"
885

    
886
drbdBNone :: String
887
drbdBNone = "n"
888

    
889
-- | Rbd tool command
890
rbdCmd :: String
891
rbdCmd = "rbd"
892

    
893
-- * File backend driver
894

    
895
fdBlktap :: String
896
fdBlktap = Types.fileDriverToRaw FileBlktap
897

    
898
fdLoop :: String
899
fdLoop = Types.fileDriverToRaw FileLoop
900

    
901
fileDriver :: FrozenSet String
902
fileDriver =
903
  ConstantUtils.mkSet $
904
  map Types.fileDriverToRaw [minBound..]
905

    
906
-- | The set of drbd-like disk types
907
ldsDrbd :: FrozenSet String
908
ldsDrbd = ConstantUtils.mkSet [Types.diskTemplateToRaw DTDrbd8]
909

    
910
-- * Disk access mode
911

    
912
diskRdonly :: String
913
diskRdonly = Types.diskModeToRaw DiskRdOnly
914

    
915
diskRdwr :: String
916
diskRdwr = Types.diskModeToRaw DiskRdWr
917

    
918
diskAccessSet :: FrozenSet String
919
diskAccessSet = ConstantUtils.mkSet $ map Types.diskModeToRaw [minBound..]
920

    
921
-- * Disk replacement mode
922

    
923
replaceDiskAuto :: String
924
replaceDiskAuto = Types.replaceDisksModeToRaw ReplaceAuto
925

    
926
replaceDiskChg :: String
927
replaceDiskChg = Types.replaceDisksModeToRaw ReplaceNewSecondary
928

    
929
replaceDiskPri :: String
930
replaceDiskPri = Types.replaceDisksModeToRaw ReplaceOnPrimary
931

    
932
replaceDiskSec :: String
933
replaceDiskSec = Types.replaceDisksModeToRaw ReplaceOnSecondary
934

    
935
replaceModes :: FrozenSet String
936
replaceModes =
937
  ConstantUtils.mkSet $ map Types.replaceDisksModeToRaw [minBound..]
938

    
939
-- * Instance export mode
940

    
941
exportModeLocal :: String
942
exportModeLocal = Types.exportModeToRaw ExportModeLocal
943

    
944
exportModeRemote :: String
945
exportModeRemote = Types.exportModeToRaw ExportModeRemote
946

    
947
exportModes :: FrozenSet String
948
exportModes = ConstantUtils.mkSet $ map Types.exportModeToRaw [minBound..]
949

    
950
-- * Instance creation modes
951

    
952
instanceCreate :: String
953
instanceCreate = Types.instCreateModeToRaw InstCreate
954

    
955
instanceImport :: String
956
instanceImport = Types.instCreateModeToRaw InstImport
957

    
958
instanceRemoteImport :: String
959
instanceRemoteImport = Types.instCreateModeToRaw InstRemoteImport
960

    
961
instanceCreateModes :: FrozenSet String
962
instanceCreateModes =
963
  ConstantUtils.mkSet $ map Types.instCreateModeToRaw [minBound..]
964

    
965
-- * Remote import/export handshake message and version
966

    
967
rieHandshake :: String
968
rieHandshake = "Hi, I'm Ganeti"
969

    
970
rieVersion :: Int
971
rieVersion = 0
972

    
973
-- | Remote import/export certificate validity in seconds
974
rieCertValidity :: Int
975
rieCertValidity = 24 * 60 * 60
976

    
977
-- | Export only: how long to wait per connection attempt (seconds)
978
rieConnectAttemptTimeout :: Int
979
rieConnectAttemptTimeout = 20
980

    
981
-- | Export only: number of attempts to connect
982
rieConnectRetries :: Int
983
rieConnectRetries = 10
984

    
985
-- | Overall timeout for establishing connection
986
rieConnectTimeout :: Int
987
rieConnectTimeout = 180
988

    
989
-- | Give child process up to 5 seconds to exit after sending a signal
990
childLingerTimeout :: Double
991
childLingerTimeout = 5.0
992

    
993
-- * Import/export config options
994

    
995
inisectBep :: String
996
inisectBep = "backend"
997

    
998
inisectExp :: String
999
inisectExp = "export"
1000

    
1001
inisectHyp :: String
1002
inisectHyp = "hypervisor"
1003

    
1004
inisectIns :: String
1005
inisectIns = "instance"
1006

    
1007
inisectOsp :: String
1008
inisectOsp = "os"
1009

    
1010
-- * Dynamic device modification
1011

    
1012
ddmAdd :: String
1013
ddmAdd = Types.ddmFullToRaw DdmFullAdd
1014

    
1015
ddmModify :: String
1016
ddmModify = Types.ddmFullToRaw DdmFullModify
1017

    
1018
ddmRemove :: String
1019
ddmRemove = Types.ddmFullToRaw DdmFullRemove
1020

    
1021
ddmsValues :: FrozenSet String
1022
ddmsValues = ConstantUtils.mkSet [ddmAdd, ddmRemove]
1023

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

    
1027
-- * Common exit codes
1028

    
1029
exitSuccess :: Int
1030
exitSuccess = 0
1031

    
1032
exitFailure :: Int
1033
exitFailure = ConstantUtils.exitFailure
1034

    
1035
exitNotcluster :: Int
1036
exitNotcluster = 5
1037

    
1038
exitNotmaster :: Int
1039
exitNotmaster = 11
1040

    
1041
exitNodesetupError :: Int
1042
exitNodesetupError = 12
1043

    
1044
-- | Need user confirmation
1045
exitConfirmation :: Int
1046
exitConfirmation = 13
1047

    
1048
-- | Exit code for query operations with unknown fields
1049
exitUnknownField :: Int
1050
exitUnknownField = 14
1051

    
1052
-- * Tags
1053

    
1054
tagCluster :: String
1055
tagCluster = Types.tagKindToRaw TagKindCluster
1056

    
1057
tagInstance :: String
1058
tagInstance = Types.tagKindToRaw TagKindInstance
1059

    
1060
tagNetwork :: String
1061
tagNetwork = Types.tagKindToRaw TagKindNetwork
1062

    
1063
tagNode :: String
1064
tagNode = Types.tagKindToRaw TagKindNode
1065

    
1066
tagNodegroup :: String
1067
tagNodegroup = Types.tagKindToRaw TagKindGroup
1068

    
1069
validTagTypes :: FrozenSet String
1070
validTagTypes = ConstantUtils.mkSet $ map Types.tagKindToRaw [minBound..]
1071

    
1072
maxTagLen :: Int
1073
maxTagLen = 128
1074

    
1075
maxTagsPerObj :: Int
1076
maxTagsPerObj = 4096
1077

    
1078
-- | Node clock skew in seconds
1079
nodeMaxClockSkew :: Int
1080
nodeMaxClockSkew = 150
1081

    
1082
-- | Disk index separator
1083
diskSeparator :: String
1084
diskSeparator = AutoConf.diskSeparator
1085

    
1086
-- * Timeout table
1087
--
1088
-- Various time constants for the timeout table
1089

    
1090
rpcTmoUrgent :: Int
1091
rpcTmoUrgent = Types.rpcTimeoutToRaw Urgent
1092

    
1093
rpcTmoFast :: Int
1094
rpcTmoFast = Types.rpcTimeoutToRaw Fast
1095

    
1096
rpcTmoNormal :: Int
1097
rpcTmoNormal = Types.rpcTimeoutToRaw Normal
1098

    
1099
rpcTmoSlow :: Int
1100
rpcTmoSlow = Types.rpcTimeoutToRaw Slow
1101

    
1102
-- | 'rpcTmo_4hrs' contains an underscore to circumvent a limitation
1103
-- in the 'Ganeti.THH.deCamelCase' function and generate the correct
1104
-- Python name.
1105
rpcTmo_4hrs :: Int
1106
rpcTmo_4hrs = Types.rpcTimeoutToRaw FourHours
1107

    
1108
-- | 'rpcTmo_1day' contains an underscore to circumvent a limitation
1109
-- in the 'Ganeti.THH.deCamelCase' function and generate the correct
1110
-- Python name.
1111
rpcTmo_1day :: Int
1112
rpcTmo_1day = Types.rpcTimeoutToRaw OneDay
1113

    
1114
-- | Timeout for connecting to nodes (seconds)
1115
rpcConnectTimeout :: Int
1116
rpcConnectTimeout = 5
1117

    
1118
-- * VTypes
1119

    
1120
vtypeBool :: VType
1121
vtypeBool = VTypeBool
1122

    
1123
vtypeInt :: VType
1124
vtypeInt = VTypeInt
1125

    
1126
vtypeMaybeString :: VType
1127
vtypeMaybeString = VTypeMaybeString
1128

    
1129
-- | Size in MiBs
1130
vtypeSize :: VType
1131
vtypeSize = VTypeSize
1132

    
1133
vtypeString :: VType
1134
vtypeString = VTypeString
1135

    
1136
enforceableTypes :: FrozenSet VType
1137
enforceableTypes = ConstantUtils.mkSet [minBound..]
1138

    
1139
-- | Instance specs
1140
--
1141
-- FIXME: these should be associated with 'Ganeti.HTools.Types.ISpec'
1142

    
1143
ispecMemSize :: String
1144
ispecMemSize = ConstantUtils.ispecMemSize
1145

    
1146
ispecCpuCount :: String
1147
ispecCpuCount = ConstantUtils.ispecCpuCount
1148

    
1149
ispecDiskCount :: String
1150
ispecDiskCount = ConstantUtils.ispecDiskCount
1151

    
1152
ispecDiskSize :: String
1153
ispecDiskSize = ConstantUtils.ispecDiskSize
1154

    
1155
ispecNicCount :: String
1156
ispecNicCount = ConstantUtils.ispecNicCount
1157

    
1158
ispecSpindleUse :: String
1159
ispecSpindleUse = ConstantUtils.ispecSpindleUse
1160

    
1161
ispecsParameterTypes :: Map String VType
1162
ispecsParameterTypes =
1163
  Map.fromList
1164
  [(ConstantUtils.ispecDiskSize, VTypeInt),
1165
   (ConstantUtils.ispecCpuCount, VTypeInt),
1166
   (ConstantUtils.ispecSpindleUse, VTypeInt),
1167
   (ConstantUtils.ispecMemSize, VTypeInt),
1168
   (ConstantUtils.ispecNicCount, VTypeInt),
1169
   (ConstantUtils.ispecDiskCount, VTypeInt)]
1170

    
1171
ispecsParameters :: FrozenSet String
1172
ispecsParameters =
1173
  ConstantUtils.mkSet [ConstantUtils.ispecCpuCount,
1174
                       ConstantUtils.ispecDiskCount,
1175
                       ConstantUtils.ispecDiskSize,
1176
                       ConstantUtils.ispecMemSize,
1177
                       ConstantUtils.ispecNicCount,
1178
                       ConstantUtils.ispecSpindleUse]
1179

    
1180
ispecsMinmax :: String
1181
ispecsMinmax = ConstantUtils.ispecsMinmax
1182

    
1183
ispecsMax :: String
1184
ispecsMax = "max"
1185

    
1186
ispecsMin :: String
1187
ispecsMin = "min"
1188

    
1189
ispecsStd :: String
1190
ispecsStd = ConstantUtils.ispecsStd
1191

    
1192
ipolicyDts :: String
1193
ipolicyDts = ConstantUtils.ipolicyDts
1194

    
1195
ipolicyVcpuRatio :: String
1196
ipolicyVcpuRatio = ConstantUtils.ipolicyVcpuRatio
1197

    
1198
ipolicySpindleRatio :: String
1199
ipolicySpindleRatio = ConstantUtils.ipolicySpindleRatio
1200

    
1201
ispecsMinmaxKeys :: FrozenSet String
1202
ispecsMinmaxKeys = ConstantUtils.mkSet [ispecsMax, ispecsMin]
1203

    
1204
ipolicyParameters :: FrozenSet String
1205
ipolicyParameters =
1206
  ConstantUtils.mkSet [ConstantUtils.ipolicyVcpuRatio,
1207
                       ConstantUtils.ipolicySpindleRatio]
1208

    
1209
ipolicyAllKeys :: FrozenSet String
1210
ipolicyAllKeys =
1211
  ConstantUtils.union ipolicyParameters $
1212
  ConstantUtils.mkSet [ConstantUtils.ipolicyDts,
1213
                       ConstantUtils.ispecsMinmax,
1214
                       ispecsStd]
1215

    
1216
-- | Node parameter names
1217

    
1218
ndExclusiveStorage :: String
1219
ndExclusiveStorage = "exclusive_storage"
1220

    
1221
ndOobProgram :: String
1222
ndOobProgram = "oob_program"
1223

    
1224
ndSpindleCount :: String
1225
ndSpindleCount = "spindle_count"
1226

    
1227
ndOvs :: String
1228
ndOvs = "ovs"
1229

    
1230
ndOvsLink :: String
1231
ndOvsLink = "ovs_link"
1232

    
1233
ndOvsName :: String
1234
ndOvsName = "ovs_name"
1235

    
1236
ndsParameterTypes :: Map String VType
1237
ndsParameterTypes =
1238
  Map.fromList
1239
  [(ndExclusiveStorage, VTypeBool),
1240
   (ndOobProgram, VTypeString),
1241
   (ndOvs, VTypeBool),
1242
   (ndOvsLink, VTypeMaybeString),
1243
   (ndOvsName, VTypeMaybeString),
1244
   (ndSpindleCount, VTypeInt)]
1245

    
1246
ndsParameters :: FrozenSet String
1247
ndsParameters = ConstantUtils.mkSet (Map.keys ndsParameterTypes)
1248

    
1249
ndsParameterTitles :: Map String String
1250
ndsParameterTitles =
1251
  Map.fromList
1252
  [(ndExclusiveStorage, "ExclusiveStorage"),
1253
   (ndOobProgram, "OutOfBandProgram"),
1254
   (ndOvs, "OpenvSwitch"),
1255
   (ndOvsLink, "OpenvSwitchLink"),
1256
   (ndOvsName, "OpenvSwitchName"),
1257
   (ndSpindleCount, "SpindleCount")]
1258

    
1259
ipCommandPath :: String
1260
ipCommandPath = AutoConf.ipPath
1261

    
1262
-- * Reboot types
1263

    
1264
instanceRebootSoft :: String
1265
instanceRebootSoft = Types.rebootTypeToRaw RebootSoft
1266

    
1267
instanceRebootHard :: String
1268
instanceRebootHard = Types.rebootTypeToRaw RebootHard
1269

    
1270
instanceRebootFull :: String
1271
instanceRebootFull = Types.rebootTypeToRaw RebootFull
1272

    
1273
rebootTypes :: FrozenSet String
1274
rebootTypes = ConstantUtils.mkSet $ map Types.rebootTypeToRaw [minBound..]
1275

    
1276

    
1277

    
1278

    
1279

    
1280

    
1281

    
1282

    
1283
-- * OOB supported commands
1284

    
1285
oobPowerOn :: String
1286
oobPowerOn = Types.oobCommandToRaw OobPowerOn
1287

    
1288
oobPowerOff :: String
1289
oobPowerOff = Types.oobCommandToRaw OobPowerOff
1290

    
1291
oobPowerCycle :: String
1292
oobPowerCycle = Types.oobCommandToRaw OobPowerCycle
1293

    
1294
oobPowerStatus :: String
1295
oobPowerStatus = Types.oobCommandToRaw OobPowerStatus
1296

    
1297
oobHealth :: String
1298
oobHealth = Types.oobCommandToRaw OobHealth
1299

    
1300
oobCommands :: FrozenSet String
1301
oobCommands = ConstantUtils.mkSet $ map Types.oobCommandToRaw [minBound..]
1302

    
1303
oobPowerStatusPowered :: String
1304
oobPowerStatusPowered = "powered"
1305

    
1306
-- | 60 seconds
1307
oobTimeout :: Int
1308
oobTimeout = 60
1309

    
1310
-- | 2 seconds
1311
oobPowerDelay :: Double
1312
oobPowerDelay = 2.0
1313

    
1314
oobStatusCritical :: String
1315
oobStatusCritical = Types.oobStatusToRaw OobStatusCritical
1316

    
1317
oobStatusOk :: String
1318
oobStatusOk = Types.oobStatusToRaw OobStatusOk
1319

    
1320
oobStatusUnknown :: String
1321
oobStatusUnknown = Types.oobStatusToRaw OobStatusUnknown
1322

    
1323
oobStatusWarning :: String
1324
oobStatusWarning = Types.oobStatusToRaw OobStatusWarning
1325

    
1326
oobStatuses :: FrozenSet String
1327
oobStatuses = ConstantUtils.mkSet $ map Types.oobStatusToRaw [minBound..]
1328

    
1329
-- * NIC_* constants are used inside the ganeti config
1330

    
1331
nicLink :: String
1332
nicLink = "link"
1333

    
1334
nicMode :: String
1335
nicMode = "mode"
1336

    
1337
nicVlan :: String
1338
nicVlan = "vlan"
1339

    
1340
nicModeBridged :: String
1341
nicModeBridged = Types.nICModeToRaw NMBridged
1342

    
1343
nicModeRouted :: String
1344
nicModeRouted = Types.nICModeToRaw NMRouted
1345

    
1346
nicModeOvs :: String
1347
nicModeOvs = Types.nICModeToRaw NMOvs
1348

    
1349
nicIpPool :: String
1350
nicIpPool = Types.nICModeToRaw NMPool
1351

    
1352
nicValidModes :: FrozenSet String
1353
nicValidModes = ConstantUtils.mkSet $ map Types.nICModeToRaw [minBound..]
1354

    
1355
-- * Hypervisor constants
1356

    
1357
htXenPvm :: String
1358
htXenPvm = Types.hypervisorToRaw XenPvm
1359

    
1360
htFake :: String
1361
htFake = Types.hypervisorToRaw Fake
1362

    
1363
htXenHvm :: String
1364
htXenHvm = Types.hypervisorToRaw XenHvm
1365

    
1366
htKvm :: String
1367
htKvm = Types.hypervisorToRaw Kvm
1368

    
1369
htChroot :: String
1370
htChroot = Types.hypervisorToRaw Chroot
1371

    
1372
htLxc :: String
1373
htLxc = Types.hypervisorToRaw Lxc
1374

    
1375
hyperTypes :: FrozenSet String
1376
hyperTypes = ConstantUtils.mkSet $ map Types.hypervisorToRaw [minBound..]
1377

    
1378
htsReqPort :: FrozenSet String
1379
htsReqPort = ConstantUtils.mkSet [htXenHvm, htKvm]
1380

    
1381
-- * Migration type
1382

    
1383
htMigrationLive :: String
1384
htMigrationLive = Types.migrationModeToRaw MigrationLive
1385

    
1386
htMigrationNonlive :: String
1387
htMigrationNonlive = Types.migrationModeToRaw MigrationNonLive
1388

    
1389
htMigrationModes :: FrozenSet String
1390
htMigrationModes =
1391
  ConstantUtils.mkSet $ map Types.migrationModeToRaw [minBound..]
1392

    
1393
-- * Cluster verify steps
1394

    
1395
verifyNplusoneMem :: String
1396
verifyNplusoneMem = Types.verifyOptionalChecksToRaw VerifyNPlusOneMem
1397

    
1398
verifyOptionalChecks :: FrozenSet String
1399
verifyOptionalChecks =
1400
  ConstantUtils.mkSet $ map Types.verifyOptionalChecksToRaw [minBound..]
1401

    
1402
-- * Cluster Verify error classes
1403

    
1404
cvTcluster :: String
1405
cvTcluster = "cluster"
1406

    
1407
cvTgroup :: String
1408
cvTgroup = "group"
1409

    
1410
cvTnode :: String
1411
cvTnode = "node"
1412

    
1413
cvTinstance :: String
1414
cvTinstance = "instance"
1415

    
1416
-- * Cluster Verify error codes and documentation
1417

    
1418
cvEclustercert :: (String, String, String)
1419
cvEclustercert =
1420
  ("cluster",
1421
   Types.cVErrorCodeToRaw CvECLUSTERCERT,
1422
   "Cluster certificate files verification failure")
1423

    
1424
cvEclustercfg :: (String, String, String)
1425
cvEclustercfg =
1426
  ("cluster",
1427
   Types.cVErrorCodeToRaw CvECLUSTERCFG,
1428
   "Cluster configuration verification failure")
1429

    
1430
cvEclusterdanglinginst :: (String, String, String)
1431
cvEclusterdanglinginst =
1432
  ("node",
1433
   Types.cVErrorCodeToRaw CvECLUSTERDANGLINGINST,
1434
   "Some instances have a non-existing primary node")
1435

    
1436
cvEclusterdanglingnodes :: (String, String, String)
1437
cvEclusterdanglingnodes =
1438
  ("node",
1439
   Types.cVErrorCodeToRaw CvECLUSTERDANGLINGNODES,
1440
   "Some nodes belong to non-existing groups")
1441

    
1442
cvEclusterfilecheck :: (String, String, String)
1443
cvEclusterfilecheck =
1444
  ("cluster",
1445
   Types.cVErrorCodeToRaw CvECLUSTERFILECHECK,
1446
   "Cluster configuration verification failure")
1447

    
1448
cvEgroupdifferentpvsize :: (String, String, String)
1449
cvEgroupdifferentpvsize =
1450
  ("group",
1451
   Types.cVErrorCodeToRaw CvEGROUPDIFFERENTPVSIZE,
1452
   "PVs in the group have different sizes")
1453

    
1454
cvEinstancebadnode :: (String, String, String)
1455
cvEinstancebadnode =
1456
  ("instance",
1457
   Types.cVErrorCodeToRaw CvEINSTANCEBADNODE,
1458
   "Instance marked as running lives on an offline node")
1459

    
1460
cvEinstancedown :: (String, String, String)
1461
cvEinstancedown =
1462
  ("instance",
1463
   Types.cVErrorCodeToRaw CvEINSTANCEDOWN,
1464
   "Instance not running on its primary node")
1465

    
1466
cvEinstancefaultydisk :: (String, String, String)
1467
cvEinstancefaultydisk =
1468
  ("instance",
1469
   Types.cVErrorCodeToRaw CvEINSTANCEFAULTYDISK,
1470
   "Impossible to retrieve status for a disk")
1471

    
1472
cvEinstancelayout :: (String, String, String)
1473
cvEinstancelayout =
1474
  ("instance",
1475
   Types.cVErrorCodeToRaw CvEINSTANCELAYOUT,
1476
   "Instance has multiple secondary nodes")
1477

    
1478
cvEinstancemissingcfgparameter :: (String, String, String)
1479
cvEinstancemissingcfgparameter =
1480
  ("instance",
1481
   Types.cVErrorCodeToRaw CvEINSTANCEMISSINGCFGPARAMETER,
1482
   "A configuration parameter for an instance is missing")
1483

    
1484
cvEinstancemissingdisk :: (String, String, String)
1485
cvEinstancemissingdisk =
1486
  ("instance",
1487
   Types.cVErrorCodeToRaw CvEINSTANCEMISSINGDISK,
1488
   "Missing volume on an instance")
1489

    
1490
cvEinstancepolicy :: (String, String, String)
1491
cvEinstancepolicy =
1492
  ("instance",
1493
   Types.cVErrorCodeToRaw CvEINSTANCEPOLICY,
1494
   "Instance does not meet policy")
1495

    
1496
cvEinstancesplitgroups :: (String, String, String)
1497
cvEinstancesplitgroups =
1498
  ("instance",
1499
   Types.cVErrorCodeToRaw CvEINSTANCESPLITGROUPS,
1500
   "Instance with primary and secondary nodes in different groups")
1501

    
1502
cvEinstanceunsuitablenode :: (String, String, String)
1503
cvEinstanceunsuitablenode =
1504
  ("instance",
1505
   Types.cVErrorCodeToRaw CvEINSTANCEUNSUITABLENODE,
1506
   "Instance running on nodes that are not suitable for it")
1507

    
1508
cvEinstancewrongnode :: (String, String, String)
1509
cvEinstancewrongnode =
1510
  ("instance",
1511
   Types.cVErrorCodeToRaw CvEINSTANCEWRONGNODE,
1512
   "Instance running on the wrong node")
1513

    
1514
cvEnodedrbd :: (String, String, String)
1515
cvEnodedrbd =
1516
  ("node",
1517
   Types.cVErrorCodeToRaw CvENODEDRBD,
1518
   "Error parsing the DRBD status file")
1519

    
1520
cvEnodedrbdhelper :: (String, String, String)
1521
cvEnodedrbdhelper =
1522
  ("node",
1523
   Types.cVErrorCodeToRaw CvENODEDRBDHELPER,
1524
   "Error caused by the DRBD helper")
1525

    
1526
cvEnodedrbdversion :: (String, String, String)
1527
cvEnodedrbdversion =
1528
  ("node",
1529
   Types.cVErrorCodeToRaw CvENODEDRBDVERSION,
1530
   "DRBD version mismatch within a node group")
1531

    
1532
cvEnodefilecheck :: (String, String, String)
1533
cvEnodefilecheck =
1534
  ("node",
1535
   Types.cVErrorCodeToRaw CvENODEFILECHECK,
1536
   "Error retrieving the checksum of the node files")
1537

    
1538
cvEnodefilestoragepaths :: (String, String, String)
1539
cvEnodefilestoragepaths =
1540
  ("node",
1541
   Types.cVErrorCodeToRaw CvENODEFILESTORAGEPATHS,
1542
   "Detected bad file storage paths")
1543

    
1544
cvEnodefilestoragepathunusable :: (String, String, String)
1545
cvEnodefilestoragepathunusable =
1546
  ("node",
1547
   Types.cVErrorCodeToRaw CvENODEFILESTORAGEPATHUNUSABLE,
1548
   "File storage path unusable")
1549

    
1550
cvEnodehooks :: (String, String, String)
1551
cvEnodehooks =
1552
  ("node",
1553
   Types.cVErrorCodeToRaw CvENODEHOOKS,
1554
   "Communication failure in hooks execution")
1555

    
1556
cvEnodehv :: (String, String, String)
1557
cvEnodehv =
1558
  ("node",
1559
   Types.cVErrorCodeToRaw CvENODEHV,
1560
   "Hypervisor parameters verification failure")
1561

    
1562
cvEnodelvm :: (String, String, String)
1563
cvEnodelvm =
1564
  ("node",
1565
   Types.cVErrorCodeToRaw CvENODELVM,
1566
   "LVM-related node error")
1567

    
1568
cvEnoden1 :: (String, String, String)
1569
cvEnoden1 =
1570
  ("node",
1571
   Types.cVErrorCodeToRaw CvENODEN1,
1572
   "Not enough memory to accommodate instance failovers")
1573

    
1574
cvEnodenet :: (String, String, String)
1575
cvEnodenet =
1576
  ("node",
1577
   Types.cVErrorCodeToRaw CvENODENET,
1578
   "Network-related node error")
1579

    
1580
cvEnodeoobpath :: (String, String, String)
1581
cvEnodeoobpath =
1582
  ("node",
1583
   Types.cVErrorCodeToRaw CvENODEOOBPATH,
1584
   "Invalid Out Of Band path")
1585

    
1586
cvEnodeorphaninstance :: (String, String, String)
1587
cvEnodeorphaninstance =
1588
  ("node",
1589
   Types.cVErrorCodeToRaw CvENODEORPHANINSTANCE,
1590
   "Unknown intance running on a node")
1591

    
1592
cvEnodeorphanlv :: (String, String, String)
1593
cvEnodeorphanlv =
1594
  ("node",
1595
   Types.cVErrorCodeToRaw CvENODEORPHANLV,
1596
   "Unknown LVM logical volume")
1597

    
1598
cvEnodeos :: (String, String, String)
1599
cvEnodeos =
1600
  ("node",
1601
   Types.cVErrorCodeToRaw CvENODEOS,
1602
   "OS-related node error")
1603

    
1604
cvEnoderpc :: (String, String, String)
1605
cvEnoderpc =
1606
  ("node",
1607
   Types.cVErrorCodeToRaw CvENODERPC,
1608
   "Error during connection to the primary node of an instance")
1609

    
1610
cvEnodesetup :: (String, String, String)
1611
cvEnodesetup =
1612
  ("node",
1613
   Types.cVErrorCodeToRaw CvENODESETUP,
1614
   "Node setup error")
1615

    
1616
cvEnodesharedfilestoragepathunusable :: (String, String, String)
1617
cvEnodesharedfilestoragepathunusable =
1618
  ("node",
1619
   Types.cVErrorCodeToRaw CvENODESHAREDFILESTORAGEPATHUNUSABLE,
1620
   "Shared file storage path unusable")
1621

    
1622
cvEnodessh :: (String, String, String)
1623
cvEnodessh =
1624
  ("node",
1625
   Types.cVErrorCodeToRaw CvENODESSH,
1626
   "SSH-related node error")
1627

    
1628
cvEnodetime :: (String, String, String)
1629
cvEnodetime =
1630
  ("node",
1631
   Types.cVErrorCodeToRaw CvENODETIME,
1632
   "Node returned invalid time")
1633

    
1634
cvEnodeuserscripts :: (String, String, String)
1635
cvEnodeuserscripts =
1636
  ("node",
1637
   Types.cVErrorCodeToRaw CvENODEUSERSCRIPTS,
1638
   "User scripts not present or not executable")
1639

    
1640
cvEnodeversion :: (String, String, String)
1641
cvEnodeversion =
1642
  ("node",
1643
   Types.cVErrorCodeToRaw CvENODEVERSION,
1644
   "Protocol version mismatch or Ganeti version mismatch")
1645

    
1646
cvAllEcodes :: FrozenSet (String, String, String)
1647
cvAllEcodes =
1648
  ConstantUtils.mkSet
1649
  [cvEclustercert,
1650
   cvEclustercfg,
1651
   cvEclusterdanglinginst,
1652
   cvEclusterdanglingnodes,
1653
   cvEclusterfilecheck,
1654
   cvEgroupdifferentpvsize,
1655
   cvEinstancebadnode,
1656
   cvEinstancedown,
1657
   cvEinstancefaultydisk,
1658
   cvEinstancelayout,
1659
   cvEinstancemissingcfgparameter,
1660
   cvEinstancemissingdisk,
1661
   cvEinstancepolicy,
1662
   cvEinstancesplitgroups,
1663
   cvEinstanceunsuitablenode,
1664
   cvEinstancewrongnode,
1665
   cvEnodedrbd,
1666
   cvEnodedrbdhelper,
1667
   cvEnodedrbdversion,
1668
   cvEnodefilecheck,
1669
   cvEnodefilestoragepaths,
1670
   cvEnodefilestoragepathunusable,
1671
   cvEnodehooks,
1672
   cvEnodehv,
1673
   cvEnodelvm,
1674
   cvEnoden1,
1675
   cvEnodenet,
1676
   cvEnodeoobpath,
1677
   cvEnodeorphaninstance,
1678
   cvEnodeorphanlv,
1679
   cvEnodeos,
1680
   cvEnoderpc,
1681
   cvEnodesetup,
1682
   cvEnodesharedfilestoragepathunusable,
1683
   cvEnodessh,
1684
   cvEnodetime,
1685
   cvEnodeuserscripts,
1686
   cvEnodeversion]
1687

    
1688
cvAllEcodesStrings :: FrozenSet String
1689
cvAllEcodesStrings =
1690
  ConstantUtils.mkSet $ map Types.cVErrorCodeToRaw [minBound..]
1691

    
1692
-- * Instance status
1693

    
1694
inststAdmindown :: String
1695
inststAdmindown = Types.instanceStatusToRaw StatusDown
1696

    
1697
inststAdminoffline :: String
1698
inststAdminoffline = Types.instanceStatusToRaw StatusOffline
1699

    
1700
inststErrordown :: String
1701
inststErrordown = Types.instanceStatusToRaw ErrorDown
1702

    
1703
inststErrorup :: String
1704
inststErrorup = Types.instanceStatusToRaw ErrorUp
1705

    
1706
inststNodedown :: String
1707
inststNodedown = Types.instanceStatusToRaw NodeDown
1708

    
1709
inststNodeoffline :: String
1710
inststNodeoffline = Types.instanceStatusToRaw NodeOffline
1711

    
1712
inststRunning :: String
1713
inststRunning = Types.instanceStatusToRaw Running
1714

    
1715
inststWrongnode :: String
1716
inststWrongnode = Types.instanceStatusToRaw WrongNode
1717

    
1718
inststAll :: FrozenSet String
1719
inststAll = ConstantUtils.mkSet $ map Types.instanceStatusToRaw [minBound..]
1720

    
1721
-- * Admin states
1722

    
1723
adminstDown :: String
1724
adminstDown = Types.adminStateToRaw AdminDown
1725

    
1726
adminstOffline :: String
1727
adminstOffline = Types.adminStateToRaw AdminOffline
1728

    
1729
adminstUp :: String
1730
adminstUp = Types.adminStateToRaw AdminUp
1731

    
1732
adminstAll :: FrozenSet String
1733
adminstAll = ConstantUtils.mkSet $ map Types.adminStateToRaw [minBound..]
1734

    
1735
-- * Node roles
1736

    
1737
nrDrained :: String
1738
nrDrained = Types.nodeRoleToRaw NRDrained
1739

    
1740
nrMaster :: String
1741
nrMaster = Types.nodeRoleToRaw NRMaster
1742

    
1743
nrMcandidate :: String
1744
nrMcandidate = Types.nodeRoleToRaw NRCandidate
1745

    
1746
nrOffline :: String
1747
nrOffline = Types.nodeRoleToRaw NROffline
1748

    
1749
nrRegular :: String
1750
nrRegular = Types.nodeRoleToRaw NRRegular
1751

    
1752
nrAll :: FrozenSet String
1753
nrAll = ConstantUtils.mkSet $ map Types.nodeRoleToRaw [minBound..]
1754

    
1755
-- * Allocator framework constants
1756

    
1757
iallocatorVersion :: Int
1758
iallocatorVersion = 2
1759

    
1760
iallocatorDirIn :: String
1761
iallocatorDirIn = Types.iAllocatorTestDirToRaw IAllocatorDirIn
1762

    
1763
iallocatorDirOut :: String
1764
iallocatorDirOut = Types.iAllocatorTestDirToRaw IAllocatorDirOut
1765

    
1766
validIallocatorDirections :: FrozenSet String
1767
validIallocatorDirections =
1768
  ConstantUtils.mkSet $ map Types.iAllocatorTestDirToRaw [minBound..]
1769

    
1770
iallocatorModeAlloc :: String
1771
iallocatorModeAlloc = Types.iAllocatorModeToRaw IAllocatorAlloc
1772

    
1773
iallocatorModeChgGroup :: String
1774
iallocatorModeChgGroup = Types.iAllocatorModeToRaw IAllocatorChangeGroup
1775

    
1776
iallocatorModeMultiAlloc :: String
1777
iallocatorModeMultiAlloc = Types.iAllocatorModeToRaw IAllocatorMultiAlloc
1778

    
1779
iallocatorModeNodeEvac :: String
1780
iallocatorModeNodeEvac = Types.iAllocatorModeToRaw IAllocatorNodeEvac
1781

    
1782
iallocatorModeReloc :: String
1783
iallocatorModeReloc = Types.iAllocatorModeToRaw IAllocatorReloc
1784

    
1785
validIallocatorModes :: FrozenSet String
1786
validIallocatorModes =
1787
  ConstantUtils.mkSet $ map Types.iAllocatorModeToRaw [minBound..]
1788

    
1789
iallocatorSearchPath :: [String]
1790
iallocatorSearchPath = AutoConf.iallocatorSearchPath
1791

    
1792
defaultIallocatorShortcut :: String
1793
defaultIallocatorShortcut = "."
1794

    
1795
-- * Node evacuation
1796

    
1797
nodeEvacPri :: String
1798
nodeEvacPri = Types.evacModeToRaw ChangePrimary
1799

    
1800
nodeEvacSec :: String
1801
nodeEvacSec = Types.evacModeToRaw ChangeSecondary
1802

    
1803
nodeEvacAll :: String
1804
nodeEvacAll = Types.evacModeToRaw ChangeAll
1805

    
1806
nodeEvacModes :: FrozenSet String
1807
nodeEvacModes = ConstantUtils.mkSet $ map Types.evacModeToRaw [minBound..]
1808

    
1809
-- * Job status
1810

    
1811
jobStatusQueued :: String
1812
jobStatusQueued = Types.jobStatusToRaw JOB_STATUS_QUEUED
1813

    
1814
jobStatusWaiting :: String
1815
jobStatusWaiting = Types.jobStatusToRaw JOB_STATUS_WAITING
1816

    
1817
jobStatusCanceling :: String
1818
jobStatusCanceling = Types.jobStatusToRaw JOB_STATUS_CANCELING
1819

    
1820
jobStatusRunning :: String
1821
jobStatusRunning = Types.jobStatusToRaw JOB_STATUS_RUNNING
1822

    
1823
jobStatusCanceled :: String
1824
jobStatusCanceled = Types.jobStatusToRaw JOB_STATUS_CANCELED
1825

    
1826
jobStatusSuccess :: String
1827
jobStatusSuccess = Types.jobStatusToRaw JOB_STATUS_SUCCESS
1828

    
1829
jobStatusError :: String
1830
jobStatusError = Types.jobStatusToRaw JOB_STATUS_ERROR
1831

    
1832
jobsPending :: FrozenSet String
1833
jobsPending =
1834
  ConstantUtils.mkSet [jobStatusQueued, jobStatusWaiting, jobStatusCanceling]
1835

    
1836
jobsFinalized :: FrozenSet String
1837
jobsFinalized =
1838
  ConstantUtils.mkSet $ map Types.finalizedJobStatusToRaw [minBound..]
1839

    
1840
jobStatusAll :: FrozenSet String
1841
jobStatusAll = ConstantUtils.mkSet $ map Types.jobStatusToRaw [minBound..]
1842

    
1843
-- * OpCode status
1844

    
1845
-- ** Not yet finalized opcodes
1846

    
1847
opStatusCanceling :: String
1848
opStatusCanceling = "canceling"
1849

    
1850
opStatusQueued :: String
1851
opStatusQueued = "queued"
1852

    
1853
opStatusRunning :: String
1854
opStatusRunning = "running"
1855

    
1856
opStatusWaiting :: String
1857
opStatusWaiting = "waiting"
1858

    
1859
-- ** Finalized opcodes
1860

    
1861
opStatusCanceled :: String
1862
opStatusCanceled = "canceled"
1863

    
1864
opStatusError :: String
1865
opStatusError = "error"
1866

    
1867
opStatusSuccess :: String
1868
opStatusSuccess = "success"
1869

    
1870
opsFinalized :: FrozenSet String
1871
opsFinalized =
1872
  ConstantUtils.mkSet [opStatusCanceled, opStatusError, opStatusSuccess]
1873

    
1874
-- * OpCode priority
1875

    
1876
opPrioLowest :: Int
1877
opPrioLowest = 19
1878

    
1879
opPrioHighest :: Int
1880
opPrioHighest = -20
1881

    
1882
opPrioLow :: Int
1883
opPrioLow = Types.opSubmitPriorityToRaw OpPrioLow
1884

    
1885
opPrioNormal :: Int
1886
opPrioNormal = Types.opSubmitPriorityToRaw OpPrioNormal
1887

    
1888
opPrioHigh :: Int
1889
opPrioHigh = Types.opSubmitPriorityToRaw OpPrioHigh
1890

    
1891
opPrioSubmitValid :: FrozenSet Int
1892
opPrioSubmitValid = ConstantUtils.mkSet [opPrioLow, opPrioNormal, opPrioHigh]
1893

    
1894
opPrioDefault :: Int
1895
opPrioDefault = opPrioNormal
1896

    
1897
-- * Execution log types
1898

    
1899
elogMessage :: String
1900
elogMessage = Types.eLogTypeToRaw ELogMessage
1901

    
1902
elogRemoteImport :: String
1903
elogRemoteImport = Types.eLogTypeToRaw ELogRemoteImport
1904

    
1905
elogJqueueTest :: String
1906
elogJqueueTest = Types.eLogTypeToRaw ELogJqueueTest
1907

    
1908
-- * Confd
1909

    
1910
confdProtocolVersion :: Int
1911
confdProtocolVersion = ConstantUtils.confdProtocolVersion
1912

    
1913
-- Confd request type
1914

    
1915
confdReqPing :: Int
1916
confdReqPing = Types.confdRequestTypeToRaw ReqPing
1917

    
1918
confdReqNodeRoleByname :: Int
1919
confdReqNodeRoleByname = Types.confdRequestTypeToRaw ReqNodeRoleByName
1920

    
1921
confdReqNodePipByInstanceIp :: Int
1922
confdReqNodePipByInstanceIp = Types.confdRequestTypeToRaw ReqNodePipByInstPip
1923

    
1924
confdReqClusterMaster :: Int
1925
confdReqClusterMaster = Types.confdRequestTypeToRaw ReqClusterMaster
1926

    
1927
confdReqNodePipList :: Int
1928
confdReqNodePipList = Types.confdRequestTypeToRaw ReqNodePipList
1929

    
1930
confdReqMcPipList :: Int
1931
confdReqMcPipList = Types.confdRequestTypeToRaw ReqMcPipList
1932

    
1933
confdReqInstancesIpsList :: Int
1934
confdReqInstancesIpsList = Types.confdRequestTypeToRaw ReqInstIpsList
1935

    
1936
confdReqNodeDrbd :: Int
1937
confdReqNodeDrbd = Types.confdRequestTypeToRaw ReqNodeDrbd
1938

    
1939
confdReqNodeInstances :: Int
1940
confdReqNodeInstances = Types.confdRequestTypeToRaw ReqNodeInstances
1941

    
1942
confdReqs :: FrozenSet Int
1943
confdReqs =
1944
  ConstantUtils.mkSet .
1945
  map Types.confdRequestTypeToRaw $
1946
  [minBound..] \\ [ReqNodeInstances]
1947

    
1948
-- * Confd request type
1949

    
1950
confdReqfieldName :: Int
1951
confdReqfieldName = Types.confdReqFieldToRaw ReqFieldName
1952

    
1953
confdReqfieldIp :: Int
1954
confdReqfieldIp = Types.confdReqFieldToRaw ReqFieldIp
1955

    
1956
confdReqfieldMnodePip :: Int
1957
confdReqfieldMnodePip = Types.confdReqFieldToRaw ReqFieldMNodePip
1958

    
1959
-- * Confd repl status
1960

    
1961
confdReplStatusOk :: Int
1962
confdReplStatusOk = Types.confdReplyStatusToRaw ReplyStatusOk
1963

    
1964
confdReplStatusError :: Int
1965
confdReplStatusError = Types.confdReplyStatusToRaw ReplyStatusError
1966

    
1967
confdReplStatusNotimplemented :: Int
1968
confdReplStatusNotimplemented = Types.confdReplyStatusToRaw ReplyStatusNotImpl
1969

    
1970
confdReplStatuses :: FrozenSet Int
1971
confdReplStatuses =
1972
  ConstantUtils.mkSet $ map Types.confdReplyStatusToRaw [minBound..]
1973

    
1974
-- * Confd node role
1975

    
1976
confdNodeRoleMaster :: Int
1977
confdNodeRoleMaster = Types.confdNodeRoleToRaw NodeRoleMaster
1978

    
1979
confdNodeRoleCandidate :: Int
1980
confdNodeRoleCandidate = Types.confdNodeRoleToRaw NodeRoleCandidate
1981

    
1982
confdNodeRoleOffline :: Int
1983
confdNodeRoleOffline = Types.confdNodeRoleToRaw NodeRoleOffline
1984

    
1985
confdNodeRoleDrained :: Int
1986
confdNodeRoleDrained = Types.confdNodeRoleToRaw NodeRoleDrained
1987

    
1988
confdNodeRoleRegular :: Int
1989
confdNodeRoleRegular = Types.confdNodeRoleToRaw NodeRoleRegular
1990

    
1991
-- * A few common errors for confd
1992

    
1993
confdErrorUnknownEntry :: Int
1994
confdErrorUnknownEntry = Types.confdErrorTypeToRaw ConfdErrorUnknownEntry
1995

    
1996
confdErrorInternal :: Int
1997
confdErrorInternal = Types.confdErrorTypeToRaw ConfdErrorInternal
1998

    
1999
confdErrorArgument :: Int
2000
confdErrorArgument = Types.confdErrorTypeToRaw ConfdErrorArgument
2001

    
2002
-- * Confd request query fields
2003

    
2004
confdReqqLink :: String
2005
confdReqqLink = ConstantUtils.confdReqqLink
2006

    
2007
confdReqqIp :: String
2008
confdReqqIp = ConstantUtils.confdReqqIp
2009

    
2010
confdReqqIplist :: String
2011
confdReqqIplist = ConstantUtils.confdReqqIplist
2012

    
2013
confdReqqFields :: String
2014
confdReqqFields = ConstantUtils.confdReqqFields
2015

    
2016
-- | Each request is "salted" by the current timestamp.
2017
--
2018
-- This constant decides how many seconds of skew to accept.
2019
--
2020
-- TODO: make this a default and allow the value to be more
2021
-- configurable
2022
confdMaxClockSkew :: Int
2023
confdMaxClockSkew = 2 * nodeMaxClockSkew
2024

    
2025
-- | When we haven't reloaded the config for more than this amount of
2026
-- seconds, we force a test to see if inotify is betraying us. Using a
2027
-- prime number to ensure we get less chance of 'same wakeup' with
2028
-- other processes.
2029
confdConfigReloadTimeout :: Int
2030
confdConfigReloadTimeout = 17
2031

    
2032
-- | If we receive more than one update in this amount of
2033
-- microseconds, we move to polling every RATELIMIT seconds, rather
2034
-- than relying on inotify, to be able to serve more requests.
2035
confdConfigReloadRatelimit :: Int
2036
confdConfigReloadRatelimit = 250000
2037

    
2038
-- | Magic number prepended to all confd queries.
2039
--
2040
-- This allows us to distinguish different types of confd protocols
2041
-- and handle them. For example by changing this we can move the whole
2042
-- payload to be compressed, or move away from json.
2043
confdMagicFourcc :: String
2044
confdMagicFourcc = "plj0"
2045

    
2046
-- | By default a confd request is sent to the minimum between this
2047
-- number and all MCs. 6 was chosen because even in the case of a
2048
-- disastrous 50% response rate, we should have enough answers to be
2049
-- able to compare more than one.
2050
confdDefaultReqCoverage :: Int
2051
confdDefaultReqCoverage = 6
2052

    
2053
-- | Timeout in seconds to expire pending query request in the confd
2054
-- client library. We don't actually expect any answer more than 10
2055
-- seconds after we sent a request.
2056
confdClientExpireTimeout :: Int
2057
confdClientExpireTimeout = 10
2058

    
2059
-- * Possible values for NodeGroup.alloc_policy
2060

    
2061
allocPolicyLastResort :: String
2062
allocPolicyLastResort = Types.allocPolicyToRaw AllocLastResort
2063

    
2064
allocPolicyPreferred :: String
2065
allocPolicyPreferred = Types.allocPolicyToRaw AllocPreferred
2066

    
2067
allocPolicyUnallocable :: String
2068
allocPolicyUnallocable = Types.allocPolicyToRaw AllocUnallocable
2069

    
2070
validAllocPolicies :: [String]
2071
validAllocPolicies = map Types.allocPolicyToRaw [minBound..]
2072

    
2073
-- | Temporary external/shared storage parameters
2074
blockdevDriverManual :: String
2075
blockdevDriverManual = Types.blockDriverToRaw BlockDrvManual
2076

    
2077
-- | 'qemu-img' path, required for 'ovfconverter'
2078
qemuimgPath :: String
2079
qemuimgPath = AutoConf.qemuimgPath
2080

    
2081
-- | Whether htools was enabled at compilation time
2082
--
2083
-- FIXME: this should be moved next to the other enable constants,
2084
-- such as, 'enableConfd', and renamed to 'enableHtools'.
2085
htools :: Bool
2086
htools = AutoConf.htools
2087

    
2088
-- * Key files for SSH daemon
2089

    
2090
sshHostDsaPriv :: String
2091
sshHostDsaPriv = sshConfigDir ++ "/ssh_host_dsa_key"
2092

    
2093
sshHostDsaPub :: String
2094
sshHostDsaPub = sshHostDsaPriv ++ ".pub"
2095

    
2096
sshHostRsaPriv :: String
2097
sshHostRsaPriv = sshConfigDir ++ "/ssh_host_rsa_key"
2098

    
2099
sshHostRsaPub :: String
2100
sshHostRsaPub = sshHostRsaPriv ++ ".pub"
2101

    
2102
-- | Path generating random UUID
2103
randomUuidFile :: String
2104
randomUuidFile = ConstantUtils.randomUuidFile
2105

    
2106
-- * Auto-repair tag prefixes
2107

    
2108
autoRepairTagPrefix :: String
2109
autoRepairTagPrefix = "ganeti:watcher:autorepair:"
2110

    
2111
autoRepairTagEnabled :: String
2112
autoRepairTagEnabled = autoRepairTagPrefix
2113

    
2114
autoRepairTagPending :: String
2115
autoRepairTagPending = autoRepairTagPrefix ++ "pending:"
2116

    
2117
autoRepairTagResult :: String
2118
autoRepairTagResult = autoRepairTagPrefix ++ "result:"
2119

    
2120
autoRepairTagSuspended :: String
2121
autoRepairTagSuspended = autoRepairTagPrefix ++ "suspend:"
2122

    
2123
-- * Auto-repair levels
2124

    
2125
autoRepairFailover :: String
2126
autoRepairFailover = "failover"
2127

    
2128
autoRepairFixStorage :: String
2129
autoRepairFixStorage = "fix-storage"
2130

    
2131
autoRepairMigrate :: String
2132
autoRepairMigrate = "migrate"
2133

    
2134
autoRepairReinstall :: String
2135
autoRepairReinstall = "reinstall"
2136

    
2137
autoRepairAllTypes :: FrozenSet String
2138
autoRepairAllTypes =
2139
  ConstantUtils.mkSet [autoRepairFailover,
2140
                       autoRepairFixStorage,
2141
                       autoRepairMigrate,
2142
                       autoRepairReinstall]
2143

    
2144
-- * Auto-repair results
2145

    
2146
autoRepairEnoperm :: String
2147
autoRepairEnoperm = "enoperm"
2148

    
2149
autoRepairFailure :: String
2150
autoRepairFailure = "failure"
2151

    
2152
autoRepairSuccess :: String
2153
autoRepairSuccess = "success"
2154

    
2155
autoRepairAllResults :: FrozenSet String
2156
autoRepairAllResults =
2157
  ConstantUtils.mkSet [autoRepairEnoperm, autoRepairFailure, autoRepairSuccess]
2158

    
2159
-- | The version identifier for builtin data collectors
2160
builtinDataCollectorVersion :: String
2161
builtinDataCollectorVersion = "B"
2162

    
2163
-- | The reason trail opcode parameter name
2164
opcodeReason :: String
2165
opcodeReason = "reason"
2166

    
2167
diskstatsFile :: String
2168
diskstatsFile = "/proc/diskstats"
2169

    
2170
-- *  CPU load collector
2171

    
2172
statFile :: String
2173
statFile = "/proc/stat"
2174

    
2175
cpuavgloadBufferSize :: Int
2176
cpuavgloadBufferSize = 150
2177

    
2178
cpuavgloadWindowSize :: Int
2179
cpuavgloadWindowSize = 600
2180

    
2181
-- | Mond's variable for periodical data collection
2182
mondTimeInterval :: Int
2183
mondTimeInterval = 5
2184

    
2185
-- * Disk access modes
2186

    
2187
diskUserspace :: String
2188
diskUserspace = Types.diskAccessModeToRaw DiskUserspace
2189

    
2190
diskKernelspace :: String
2191
diskKernelspace = Types.diskAccessModeToRaw DiskKernelspace
2192

    
2193
diskValidAccessModes :: FrozenSet String
2194
diskValidAccessModes =
2195
  ConstantUtils.mkSet $ map Types.diskAccessModeToRaw [minBound..]
2196

    
2197
-- | Timeout for queue draining in upgrades
2198
upgradeQueueDrainTimeout :: Int
2199
upgradeQueueDrainTimeout = 36 * 60 * 60 -- 1.5 days
2200

    
2201
-- | Intervall at which the queue is polled during upgrades
2202
upgradeQueuePollInterval :: Int
2203
upgradeQueuePollInterval  = 10