Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HsConstants.hs @ 6e18cc0d

History | View | Annotate | Download (53.5 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
-- * Dynamic device modification
994

    
995
ddmAdd :: String
996
ddmAdd = Types.ddmFullToRaw DdmFullAdd
997

    
998
ddmModify :: String
999
ddmModify = Types.ddmFullToRaw DdmFullModify
1000

    
1001
ddmRemove :: String
1002
ddmRemove = Types.ddmFullToRaw DdmFullRemove
1003

    
1004
ddmsValues :: FrozenSet String
1005
ddmsValues = ConstantUtils.mkSet [ddmAdd, ddmRemove]
1006

    
1007
ddmsValuesWithModify :: FrozenSet String
1008
ddmsValuesWithModify = ConstantUtils.mkSet $ map Types.ddmFullToRaw [minBound..]
1009

    
1010
-- * Common exit codes
1011

    
1012
exitSuccess :: Int
1013
exitSuccess = 0
1014

    
1015
exitFailure :: Int
1016
exitFailure = ConstantUtils.exitFailure
1017

    
1018
exitNotcluster :: Int
1019
exitNotcluster = 5
1020

    
1021
exitNotmaster :: Int
1022
exitNotmaster = 11
1023

    
1024
exitNodesetupError :: Int
1025
exitNodesetupError = 12
1026

    
1027
-- | Need user confirmation
1028
exitConfirmation :: Int
1029
exitConfirmation = 13
1030

    
1031
-- | Exit code for query operations with unknown fields
1032
exitUnknownField :: Int
1033
exitUnknownField = 14
1034

    
1035
-- * Tags
1036

    
1037
tagCluster :: String
1038
tagCluster = Types.tagKindToRaw TagKindCluster
1039

    
1040
tagInstance :: String
1041
tagInstance = Types.tagKindToRaw TagKindInstance
1042

    
1043
tagNetwork :: String
1044
tagNetwork = Types.tagKindToRaw TagKindNetwork
1045

    
1046
tagNode :: String
1047
tagNode = Types.tagKindToRaw TagKindNode
1048

    
1049
tagNodegroup :: String
1050
tagNodegroup = Types.tagKindToRaw TagKindGroup
1051

    
1052
validTagTypes :: FrozenSet String
1053
validTagTypes = ConstantUtils.mkSet $ map Types.tagKindToRaw [minBound..]
1054

    
1055
maxTagLen :: Int
1056
maxTagLen = 128
1057

    
1058
maxTagsPerObj :: Int
1059
maxTagsPerObj = 4096
1060

    
1061
-- | Node clock skew in seconds
1062
nodeMaxClockSkew :: Int
1063
nodeMaxClockSkew = 150
1064

    
1065
-- | Disk index separator
1066
diskSeparator :: String
1067
diskSeparator = AutoConf.diskSeparator
1068

    
1069
-- * Timeout table
1070
--
1071
-- Various time constants for the timeout table
1072

    
1073
rpcTmoUrgent :: Int
1074
rpcTmoUrgent = Types.rpcTimeoutToRaw Urgent
1075

    
1076
rpcTmoFast :: Int
1077
rpcTmoFast = Types.rpcTimeoutToRaw Fast
1078

    
1079
rpcTmoNormal :: Int
1080
rpcTmoNormal = Types.rpcTimeoutToRaw Normal
1081

    
1082
rpcTmoSlow :: Int
1083
rpcTmoSlow = Types.rpcTimeoutToRaw Slow
1084

    
1085
-- | 'rpcTmo_4hrs' contains an underscore to circumvent a limitation
1086
-- in the 'Ganeti.THH.deCamelCase' function and generate the correct
1087
-- Python name.
1088
rpcTmo_4hrs :: Int
1089
rpcTmo_4hrs = Types.rpcTimeoutToRaw FourHours
1090

    
1091
-- | 'rpcTmo_1day' contains an underscore to circumvent a limitation
1092
-- in the 'Ganeti.THH.deCamelCase' function and generate the correct
1093
-- Python name.
1094
rpcTmo_1day :: Int
1095
rpcTmo_1day = Types.rpcTimeoutToRaw OneDay
1096

    
1097
-- | Timeout for connecting to nodes (seconds)
1098
rpcConnectTimeout :: Int
1099
rpcConnectTimeout = 5
1100

    
1101
-- * VTypes
1102

    
1103
vtypeBool :: VType
1104
vtypeBool = VTypeBool
1105

    
1106
vtypeInt :: VType
1107
vtypeInt = VTypeInt
1108

    
1109
vtypeMaybeString :: VType
1110
vtypeMaybeString = VTypeMaybeString
1111

    
1112
-- | Size in MiBs
1113
vtypeSize :: VType
1114
vtypeSize = VTypeSize
1115

    
1116
vtypeString :: VType
1117
vtypeString = VTypeString
1118

    
1119
enforceableTypes :: FrozenSet VType
1120
enforceableTypes = ConstantUtils.mkSet [minBound..]
1121

    
1122
-- | Instance specs
1123
--
1124
-- FIXME: these should be associated with 'Ganeti.HTools.Types.ISpec'
1125

    
1126
ispecMemSize :: String
1127
ispecMemSize = ConstantUtils.ispecMemSize
1128

    
1129
ispecCpuCount :: String
1130
ispecCpuCount = ConstantUtils.ispecCpuCount
1131

    
1132
ispecDiskCount :: String
1133
ispecDiskCount = ConstantUtils.ispecDiskCount
1134

    
1135
ispecDiskSize :: String
1136
ispecDiskSize = ConstantUtils.ispecDiskSize
1137

    
1138
ispecNicCount :: String
1139
ispecNicCount = ConstantUtils.ispecNicCount
1140

    
1141
ispecSpindleUse :: String
1142
ispecSpindleUse = ConstantUtils.ispecSpindleUse
1143

    
1144
ispecsParameterTypes :: Map String VType
1145
ispecsParameterTypes =
1146
  Map.fromList
1147
  [(ConstantUtils.ispecDiskSize, VTypeInt),
1148
   (ConstantUtils.ispecCpuCount, VTypeInt),
1149
   (ConstantUtils.ispecSpindleUse, VTypeInt),
1150
   (ConstantUtils.ispecMemSize, VTypeInt),
1151
   (ConstantUtils.ispecNicCount, VTypeInt),
1152
   (ConstantUtils.ispecDiskCount, VTypeInt)]
1153

    
1154
ispecsParameters :: FrozenSet String
1155
ispecsParameters =
1156
  ConstantUtils.mkSet [ConstantUtils.ispecCpuCount,
1157
                       ConstantUtils.ispecDiskCount,
1158
                       ConstantUtils.ispecDiskSize,
1159
                       ConstantUtils.ispecMemSize,
1160
                       ConstantUtils.ispecNicCount,
1161
                       ConstantUtils.ispecSpindleUse]
1162

    
1163
ispecsMinmax :: String
1164
ispecsMinmax = ConstantUtils.ispecsMinmax
1165

    
1166
ispecsMax :: String
1167
ispecsMax = "max"
1168

    
1169
ispecsMin :: String
1170
ispecsMin = "min"
1171

    
1172
ispecsStd :: String
1173
ispecsStd = ConstantUtils.ispecsStd
1174

    
1175
ipolicyDts :: String
1176
ipolicyDts = ConstantUtils.ipolicyDts
1177

    
1178
ipolicyVcpuRatio :: String
1179
ipolicyVcpuRatio = ConstantUtils.ipolicyVcpuRatio
1180

    
1181
ipolicySpindleRatio :: String
1182
ipolicySpindleRatio = ConstantUtils.ipolicySpindleRatio
1183

    
1184
ispecsMinmaxKeys :: FrozenSet String
1185
ispecsMinmaxKeys = ConstantUtils.mkSet [ispecsMax, ispecsMin]
1186

    
1187
ipolicyParameters :: FrozenSet String
1188
ipolicyParameters =
1189
  ConstantUtils.mkSet [ConstantUtils.ipolicyVcpuRatio,
1190
                       ConstantUtils.ipolicySpindleRatio]
1191

    
1192
ipolicyAllKeys :: FrozenSet String
1193
ipolicyAllKeys =
1194
  ConstantUtils.union ipolicyParameters $
1195
  ConstantUtils.mkSet [ConstantUtils.ipolicyDts,
1196
                       ConstantUtils.ispecsMinmax,
1197
                       ispecsStd]
1198

    
1199
-- | Node parameter names
1200

    
1201
ndExclusiveStorage :: String
1202
ndExclusiveStorage = "exclusive_storage"
1203

    
1204
ndOobProgram :: String
1205
ndOobProgram = "oob_program"
1206

    
1207
ndSpindleCount :: String
1208
ndSpindleCount = "spindle_count"
1209

    
1210
ndOvs :: String
1211
ndOvs = "ovs"
1212

    
1213
ndOvsLink :: String
1214
ndOvsLink = "ovs_link"
1215

    
1216
ndOvsName :: String
1217
ndOvsName = "ovs_name"
1218

    
1219
ndsParameterTypes :: Map String VType
1220
ndsParameterTypes =
1221
  Map.fromList
1222
  [(ndExclusiveStorage, VTypeBool),
1223
   (ndOobProgram, VTypeString),
1224
   (ndOvs, VTypeBool),
1225
   (ndOvsLink, VTypeMaybeString),
1226
   (ndOvsName, VTypeMaybeString),
1227
   (ndSpindleCount, VTypeInt)]
1228

    
1229
ndsParameters :: FrozenSet String
1230
ndsParameters = ConstantUtils.mkSet (Map.keys ndsParameterTypes)
1231

    
1232
ndsParameterTitles :: Map String String
1233
ndsParameterTitles =
1234
  Map.fromList
1235
  [(ndExclusiveStorage, "ExclusiveStorage"),
1236
   (ndOobProgram, "OutOfBandProgram"),
1237
   (ndOvs, "OpenvSwitch"),
1238
   (ndOvsLink, "OpenvSwitchLink"),
1239
   (ndOvsName, "OpenvSwitchName"),
1240
   (ndSpindleCount, "SpindleCount")]
1241

    
1242
ipCommandPath :: String
1243
ipCommandPath = AutoConf.ipPath
1244

    
1245
-- * Reboot types
1246

    
1247
instanceRebootSoft :: String
1248
instanceRebootSoft = Types.rebootTypeToRaw RebootSoft
1249

    
1250
instanceRebootHard :: String
1251
instanceRebootHard = Types.rebootTypeToRaw RebootHard
1252

    
1253
instanceRebootFull :: String
1254
instanceRebootFull = Types.rebootTypeToRaw RebootFull
1255

    
1256
rebootTypes :: FrozenSet String
1257
rebootTypes = ConstantUtils.mkSet $ map Types.rebootTypeToRaw [minBound..]
1258

    
1259

    
1260

    
1261

    
1262

    
1263

    
1264

    
1265

    
1266
-- * OOB supported commands
1267

    
1268
oobPowerOn :: String
1269
oobPowerOn = Types.oobCommandToRaw OobPowerOn
1270

    
1271
oobPowerOff :: String
1272
oobPowerOff = Types.oobCommandToRaw OobPowerOff
1273

    
1274
oobPowerCycle :: String
1275
oobPowerCycle = Types.oobCommandToRaw OobPowerCycle
1276

    
1277
oobPowerStatus :: String
1278
oobPowerStatus = Types.oobCommandToRaw OobPowerStatus
1279

    
1280
oobHealth :: String
1281
oobHealth = Types.oobCommandToRaw OobHealth
1282

    
1283
oobCommands :: FrozenSet String
1284
oobCommands = ConstantUtils.mkSet $ map Types.oobCommandToRaw [minBound..]
1285

    
1286
oobPowerStatusPowered :: String
1287
oobPowerStatusPowered = "powered"
1288

    
1289
-- | 60 seconds
1290
oobTimeout :: Int
1291
oobTimeout = 60
1292

    
1293
-- | 2 seconds
1294
oobPowerDelay :: Double
1295
oobPowerDelay = 2.0
1296

    
1297
oobStatusCritical :: String
1298
oobStatusCritical = Types.oobStatusToRaw OobStatusCritical
1299

    
1300
oobStatusOk :: String
1301
oobStatusOk = Types.oobStatusToRaw OobStatusOk
1302

    
1303
oobStatusUnknown :: String
1304
oobStatusUnknown = Types.oobStatusToRaw OobStatusUnknown
1305

    
1306
oobStatusWarning :: String
1307
oobStatusWarning = Types.oobStatusToRaw OobStatusWarning
1308

    
1309
oobStatuses :: FrozenSet String
1310
oobStatuses = ConstantUtils.mkSet $ map Types.oobStatusToRaw [minBound..]
1311

    
1312
-- * NIC_* constants are used inside the ganeti config
1313

    
1314
nicLink :: String
1315
nicLink = "link"
1316

    
1317
nicMode :: String
1318
nicMode = "mode"
1319

    
1320
nicVlan :: String
1321
nicVlan = "vlan"
1322

    
1323
nicModeBridged :: String
1324
nicModeBridged = Types.nICModeToRaw NMBridged
1325

    
1326
nicModeRouted :: String
1327
nicModeRouted = Types.nICModeToRaw NMRouted
1328

    
1329
nicModeOvs :: String
1330
nicModeOvs = Types.nICModeToRaw NMOvs
1331

    
1332
nicIpPool :: String
1333
nicIpPool = Types.nICModeToRaw NMPool
1334

    
1335
nicValidModes :: FrozenSet String
1336
nicValidModes = ConstantUtils.mkSet $ map Types.nICModeToRaw [minBound..]
1337

    
1338
-- * Hypervisor constants
1339

    
1340
htXenPvm :: String
1341
htXenPvm = Types.hypervisorToRaw XenPvm
1342

    
1343
htFake :: String
1344
htFake = Types.hypervisorToRaw Fake
1345

    
1346
htXenHvm :: String
1347
htXenHvm = Types.hypervisorToRaw XenHvm
1348

    
1349
htKvm :: String
1350
htKvm = Types.hypervisorToRaw Kvm
1351

    
1352
htChroot :: String
1353
htChroot = Types.hypervisorToRaw Chroot
1354

    
1355
htLxc :: String
1356
htLxc = Types.hypervisorToRaw Lxc
1357

    
1358
hyperTypes :: FrozenSet String
1359
hyperTypes = ConstantUtils.mkSet $ map Types.hypervisorToRaw [minBound..]
1360

    
1361
htsReqPort :: FrozenSet String
1362
htsReqPort = ConstantUtils.mkSet [htXenHvm, htKvm]
1363

    
1364
-- * Migration type
1365

    
1366
htMigrationLive :: String
1367
htMigrationLive = Types.migrationModeToRaw MigrationLive
1368

    
1369
htMigrationNonlive :: String
1370
htMigrationNonlive = Types.migrationModeToRaw MigrationNonLive
1371

    
1372
htMigrationModes :: FrozenSet String
1373
htMigrationModes =
1374
  ConstantUtils.mkSet $ map Types.migrationModeToRaw [minBound..]
1375

    
1376
-- * Cluster verify steps
1377

    
1378
verifyNplusoneMem :: String
1379
verifyNplusoneMem = Types.verifyOptionalChecksToRaw VerifyNPlusOneMem
1380

    
1381
verifyOptionalChecks :: FrozenSet String
1382
verifyOptionalChecks =
1383
  ConstantUtils.mkSet $ map Types.verifyOptionalChecksToRaw [minBound..]
1384

    
1385
-- * Cluster Verify error classes
1386

    
1387
cvTcluster :: String
1388
cvTcluster = "cluster"
1389

    
1390
cvTgroup :: String
1391
cvTgroup = "group"
1392

    
1393
cvTnode :: String
1394
cvTnode = "node"
1395

    
1396
cvTinstance :: String
1397
cvTinstance = "instance"
1398

    
1399
-- * Cluster Verify error codes and documentation
1400

    
1401
cvEclustercert :: (String, String, String)
1402
cvEclustercert =
1403
  ("cluster",
1404
   Types.cVErrorCodeToRaw CvECLUSTERCERT,
1405
   "Cluster certificate files verification failure")
1406

    
1407
cvEclustercfg :: (String, String, String)
1408
cvEclustercfg =
1409
  ("cluster",
1410
   Types.cVErrorCodeToRaw CvECLUSTERCFG,
1411
   "Cluster configuration verification failure")
1412

    
1413
cvEclusterdanglinginst :: (String, String, String)
1414
cvEclusterdanglinginst =
1415
  ("node",
1416
   Types.cVErrorCodeToRaw CvECLUSTERDANGLINGINST,
1417
   "Some instances have a non-existing primary node")
1418

    
1419
cvEclusterdanglingnodes :: (String, String, String)
1420
cvEclusterdanglingnodes =
1421
  ("node",
1422
   Types.cVErrorCodeToRaw CvECLUSTERDANGLINGNODES,
1423
   "Some nodes belong to non-existing groups")
1424

    
1425
cvEclusterfilecheck :: (String, String, String)
1426
cvEclusterfilecheck =
1427
  ("cluster",
1428
   Types.cVErrorCodeToRaw CvECLUSTERFILECHECK,
1429
   "Cluster configuration verification failure")
1430

    
1431
cvEgroupdifferentpvsize :: (String, String, String)
1432
cvEgroupdifferentpvsize =
1433
  ("group",
1434
   Types.cVErrorCodeToRaw CvEGROUPDIFFERENTPVSIZE,
1435
   "PVs in the group have different sizes")
1436

    
1437
cvEinstancebadnode :: (String, String, String)
1438
cvEinstancebadnode =
1439
  ("instance",
1440
   Types.cVErrorCodeToRaw CvEINSTANCEBADNODE,
1441
   "Instance marked as running lives on an offline node")
1442

    
1443
cvEinstancedown :: (String, String, String)
1444
cvEinstancedown =
1445
  ("instance",
1446
   Types.cVErrorCodeToRaw CvEINSTANCEDOWN,
1447
   "Instance not running on its primary node")
1448

    
1449
cvEinstancefaultydisk :: (String, String, String)
1450
cvEinstancefaultydisk =
1451
  ("instance",
1452
   Types.cVErrorCodeToRaw CvEINSTANCEFAULTYDISK,
1453
   "Impossible to retrieve status for a disk")
1454

    
1455
cvEinstancelayout :: (String, String, String)
1456
cvEinstancelayout =
1457
  ("instance",
1458
   Types.cVErrorCodeToRaw CvEINSTANCELAYOUT,
1459
   "Instance has multiple secondary nodes")
1460

    
1461
cvEinstancemissingcfgparameter :: (String, String, String)
1462
cvEinstancemissingcfgparameter =
1463
  ("instance",
1464
   Types.cVErrorCodeToRaw CvEINSTANCEMISSINGCFGPARAMETER,
1465
   "A configuration parameter for an instance is missing")
1466

    
1467
cvEinstancemissingdisk :: (String, String, String)
1468
cvEinstancemissingdisk =
1469
  ("instance",
1470
   Types.cVErrorCodeToRaw CvEINSTANCEMISSINGDISK,
1471
   "Missing volume on an instance")
1472

    
1473
cvEinstancepolicy :: (String, String, String)
1474
cvEinstancepolicy =
1475
  ("instance",
1476
   Types.cVErrorCodeToRaw CvEINSTANCEPOLICY,
1477
   "Instance does not meet policy")
1478

    
1479
cvEinstancesplitgroups :: (String, String, String)
1480
cvEinstancesplitgroups =
1481
  ("instance",
1482
   Types.cVErrorCodeToRaw CvEINSTANCESPLITGROUPS,
1483
   "Instance with primary and secondary nodes in different groups")
1484

    
1485
cvEinstanceunsuitablenode :: (String, String, String)
1486
cvEinstanceunsuitablenode =
1487
  ("instance",
1488
   Types.cVErrorCodeToRaw CvEINSTANCEUNSUITABLENODE,
1489
   "Instance running on nodes that are not suitable for it")
1490

    
1491
cvEinstancewrongnode :: (String, String, String)
1492
cvEinstancewrongnode =
1493
  ("instance",
1494
   Types.cVErrorCodeToRaw CvEINSTANCEWRONGNODE,
1495
   "Instance running on the wrong node")
1496

    
1497
cvEnodedrbd :: (String, String, String)
1498
cvEnodedrbd =
1499
  ("node",
1500
   Types.cVErrorCodeToRaw CvENODEDRBD,
1501
   "Error parsing the DRBD status file")
1502

    
1503
cvEnodedrbdhelper :: (String, String, String)
1504
cvEnodedrbdhelper =
1505
  ("node",
1506
   Types.cVErrorCodeToRaw CvENODEDRBDHELPER,
1507
   "Error caused by the DRBD helper")
1508

    
1509
cvEnodedrbdversion :: (String, String, String)
1510
cvEnodedrbdversion =
1511
  ("node",
1512
   Types.cVErrorCodeToRaw CvENODEDRBDVERSION,
1513
   "DRBD version mismatch within a node group")
1514

    
1515
cvEnodefilecheck :: (String, String, String)
1516
cvEnodefilecheck =
1517
  ("node",
1518
   Types.cVErrorCodeToRaw CvENODEFILECHECK,
1519
   "Error retrieving the checksum of the node files")
1520

    
1521
cvEnodefilestoragepaths :: (String, String, String)
1522
cvEnodefilestoragepaths =
1523
  ("node",
1524
   Types.cVErrorCodeToRaw CvENODEFILESTORAGEPATHS,
1525
   "Detected bad file storage paths")
1526

    
1527
cvEnodefilestoragepathunusable :: (String, String, String)
1528
cvEnodefilestoragepathunusable =
1529
  ("node",
1530
   Types.cVErrorCodeToRaw CvENODEFILESTORAGEPATHUNUSABLE,
1531
   "File storage path unusable")
1532

    
1533
cvEnodehooks :: (String, String, String)
1534
cvEnodehooks =
1535
  ("node",
1536
   Types.cVErrorCodeToRaw CvENODEHOOKS,
1537
   "Communication failure in hooks execution")
1538

    
1539
cvEnodehv :: (String, String, String)
1540
cvEnodehv =
1541
  ("node",
1542
   Types.cVErrorCodeToRaw CvENODEHV,
1543
   "Hypervisor parameters verification failure")
1544

    
1545
cvEnodelvm :: (String, String, String)
1546
cvEnodelvm =
1547
  ("node",
1548
   Types.cVErrorCodeToRaw CvENODELVM,
1549
   "LVM-related node error")
1550

    
1551
cvEnoden1 :: (String, String, String)
1552
cvEnoden1 =
1553
  ("node",
1554
   Types.cVErrorCodeToRaw CvENODEN1,
1555
   "Not enough memory to accommodate instance failovers")
1556

    
1557
cvEnodenet :: (String, String, String)
1558
cvEnodenet =
1559
  ("node",
1560
   Types.cVErrorCodeToRaw CvENODENET,
1561
   "Network-related node error")
1562

    
1563
cvEnodeoobpath :: (String, String, String)
1564
cvEnodeoobpath =
1565
  ("node",
1566
   Types.cVErrorCodeToRaw CvENODEOOBPATH,
1567
   "Invalid Out Of Band path")
1568

    
1569
cvEnodeorphaninstance :: (String, String, String)
1570
cvEnodeorphaninstance =
1571
  ("node",
1572
   Types.cVErrorCodeToRaw CvENODEORPHANINSTANCE,
1573
   "Unknown intance running on a node")
1574

    
1575
cvEnodeorphanlv :: (String, String, String)
1576
cvEnodeorphanlv =
1577
  ("node",
1578
   Types.cVErrorCodeToRaw CvENODEORPHANLV,
1579
   "Unknown LVM logical volume")
1580

    
1581
cvEnodeos :: (String, String, String)
1582
cvEnodeos =
1583
  ("node",
1584
   Types.cVErrorCodeToRaw CvENODEOS,
1585
   "OS-related node error")
1586

    
1587
cvEnoderpc :: (String, String, String)
1588
cvEnoderpc =
1589
  ("node",
1590
   Types.cVErrorCodeToRaw CvENODERPC,
1591
   "Error during connection to the primary node of an instance")
1592

    
1593
cvEnodesetup :: (String, String, String)
1594
cvEnodesetup =
1595
  ("node",
1596
   Types.cVErrorCodeToRaw CvENODESETUP,
1597
   "Node setup error")
1598

    
1599
cvEnodesharedfilestoragepathunusable :: (String, String, String)
1600
cvEnodesharedfilestoragepathunusable =
1601
  ("node",
1602
   Types.cVErrorCodeToRaw CvENODESHAREDFILESTORAGEPATHUNUSABLE,
1603
   "Shared file storage path unusable")
1604

    
1605
cvEnodessh :: (String, String, String)
1606
cvEnodessh =
1607
  ("node",
1608
   Types.cVErrorCodeToRaw CvENODESSH,
1609
   "SSH-related node error")
1610

    
1611
cvEnodetime :: (String, String, String)
1612
cvEnodetime =
1613
  ("node",
1614
   Types.cVErrorCodeToRaw CvENODETIME,
1615
   "Node returned invalid time")
1616

    
1617
cvEnodeuserscripts :: (String, String, String)
1618
cvEnodeuserscripts =
1619
  ("node",
1620
   Types.cVErrorCodeToRaw CvENODEUSERSCRIPTS,
1621
   "User scripts not present or not executable")
1622

    
1623
cvEnodeversion :: (String, String, String)
1624
cvEnodeversion =
1625
  ("node",
1626
   Types.cVErrorCodeToRaw CvENODEVERSION,
1627
   "Protocol version mismatch or Ganeti version mismatch")
1628

    
1629
cvAllEcodes :: FrozenSet (String, String, String)
1630
cvAllEcodes =
1631
  ConstantUtils.mkSet
1632
  [cvEclustercert,
1633
   cvEclustercfg,
1634
   cvEclusterdanglinginst,
1635
   cvEclusterdanglingnodes,
1636
   cvEclusterfilecheck,
1637
   cvEgroupdifferentpvsize,
1638
   cvEinstancebadnode,
1639
   cvEinstancedown,
1640
   cvEinstancefaultydisk,
1641
   cvEinstancelayout,
1642
   cvEinstancemissingcfgparameter,
1643
   cvEinstancemissingdisk,
1644
   cvEinstancepolicy,
1645
   cvEinstancesplitgroups,
1646
   cvEinstanceunsuitablenode,
1647
   cvEinstancewrongnode,
1648
   cvEnodedrbd,
1649
   cvEnodedrbdhelper,
1650
   cvEnodedrbdversion,
1651
   cvEnodefilecheck,
1652
   cvEnodefilestoragepaths,
1653
   cvEnodefilestoragepathunusable,
1654
   cvEnodehooks,
1655
   cvEnodehv,
1656
   cvEnodelvm,
1657
   cvEnoden1,
1658
   cvEnodenet,
1659
   cvEnodeoobpath,
1660
   cvEnodeorphaninstance,
1661
   cvEnodeorphanlv,
1662
   cvEnodeos,
1663
   cvEnoderpc,
1664
   cvEnodesetup,
1665
   cvEnodesharedfilestoragepathunusable,
1666
   cvEnodessh,
1667
   cvEnodetime,
1668
   cvEnodeuserscripts,
1669
   cvEnodeversion]
1670

    
1671
cvAllEcodesStrings :: FrozenSet String
1672
cvAllEcodesStrings =
1673
  ConstantUtils.mkSet $ map Types.cVErrorCodeToRaw [minBound..]
1674

    
1675
-- * Instance status
1676

    
1677
inststAdmindown :: String
1678
inststAdmindown = Types.instanceStatusToRaw StatusDown
1679

    
1680
inststAdminoffline :: String
1681
inststAdminoffline = Types.instanceStatusToRaw StatusOffline
1682

    
1683
inststErrordown :: String
1684
inststErrordown = Types.instanceStatusToRaw ErrorDown
1685

    
1686
inststErrorup :: String
1687
inststErrorup = Types.instanceStatusToRaw ErrorUp
1688

    
1689
inststNodedown :: String
1690
inststNodedown = Types.instanceStatusToRaw NodeDown
1691

    
1692
inststNodeoffline :: String
1693
inststNodeoffline = Types.instanceStatusToRaw NodeOffline
1694

    
1695
inststRunning :: String
1696
inststRunning = Types.instanceStatusToRaw Running
1697

    
1698
inststWrongnode :: String
1699
inststWrongnode = Types.instanceStatusToRaw WrongNode
1700

    
1701
inststAll :: FrozenSet String
1702
inststAll = ConstantUtils.mkSet $ map Types.instanceStatusToRaw [minBound..]
1703

    
1704
-- * Admin states
1705

    
1706
adminstDown :: String
1707
adminstDown = Types.adminStateToRaw AdminDown
1708

    
1709
adminstOffline :: String
1710
adminstOffline = Types.adminStateToRaw AdminOffline
1711

    
1712
adminstUp :: String
1713
adminstUp = Types.adminStateToRaw AdminUp
1714

    
1715
adminstAll :: FrozenSet String
1716
adminstAll = ConstantUtils.mkSet $ map Types.adminStateToRaw [minBound..]
1717

    
1718
-- * Node roles
1719

    
1720
nrDrained :: String
1721
nrDrained = Types.nodeRoleToRaw NRDrained
1722

    
1723
nrMaster :: String
1724
nrMaster = Types.nodeRoleToRaw NRMaster
1725

    
1726
nrMcandidate :: String
1727
nrMcandidate = Types.nodeRoleToRaw NRCandidate
1728

    
1729
nrOffline :: String
1730
nrOffline = Types.nodeRoleToRaw NROffline
1731

    
1732
nrRegular :: String
1733
nrRegular = Types.nodeRoleToRaw NRRegular
1734

    
1735
nrAll :: FrozenSet String
1736
nrAll = ConstantUtils.mkSet $ map Types.nodeRoleToRaw [minBound..]
1737

    
1738
-- * Allocator framework constants
1739

    
1740
iallocatorVersion :: Int
1741
iallocatorVersion = 2
1742

    
1743
iallocatorDirIn :: String
1744
iallocatorDirIn = Types.iAllocatorTestDirToRaw IAllocatorDirIn
1745

    
1746
iallocatorDirOut :: String
1747
iallocatorDirOut = Types.iAllocatorTestDirToRaw IAllocatorDirOut
1748

    
1749
validIallocatorDirections :: FrozenSet String
1750
validIallocatorDirections =
1751
  ConstantUtils.mkSet $ map Types.iAllocatorTestDirToRaw [minBound..]
1752

    
1753
iallocatorModeAlloc :: String
1754
iallocatorModeAlloc = Types.iAllocatorModeToRaw IAllocatorAlloc
1755

    
1756
iallocatorModeChgGroup :: String
1757
iallocatorModeChgGroup = Types.iAllocatorModeToRaw IAllocatorChangeGroup
1758

    
1759
iallocatorModeMultiAlloc :: String
1760
iallocatorModeMultiAlloc = Types.iAllocatorModeToRaw IAllocatorMultiAlloc
1761

    
1762
iallocatorModeNodeEvac :: String
1763
iallocatorModeNodeEvac = Types.iAllocatorModeToRaw IAllocatorNodeEvac
1764

    
1765
iallocatorModeReloc :: String
1766
iallocatorModeReloc = Types.iAllocatorModeToRaw IAllocatorReloc
1767

    
1768
validIallocatorModes :: FrozenSet String
1769
validIallocatorModes =
1770
  ConstantUtils.mkSet $ map Types.iAllocatorModeToRaw [minBound..]
1771

    
1772
iallocatorSearchPath :: [String]
1773
iallocatorSearchPath = AutoConf.iallocatorSearchPath
1774

    
1775
defaultIallocatorShortcut :: String
1776
defaultIallocatorShortcut = "."
1777

    
1778
-- * Node evacuation
1779

    
1780
nodeEvacPri :: String
1781
nodeEvacPri = Types.evacModeToRaw ChangePrimary
1782

    
1783
nodeEvacSec :: String
1784
nodeEvacSec = Types.evacModeToRaw ChangeSecondary
1785

    
1786
nodeEvacAll :: String
1787
nodeEvacAll = Types.evacModeToRaw ChangeAll
1788

    
1789
nodeEvacModes :: FrozenSet String
1790
nodeEvacModes = ConstantUtils.mkSet $ map Types.evacModeToRaw [minBound..]
1791

    
1792
-- * Job status
1793

    
1794
jobStatusQueued :: String
1795
jobStatusQueued = Types.jobStatusToRaw JOB_STATUS_QUEUED
1796

    
1797
jobStatusWaiting :: String
1798
jobStatusWaiting = Types.jobStatusToRaw JOB_STATUS_WAITING
1799

    
1800
jobStatusCanceling :: String
1801
jobStatusCanceling = Types.jobStatusToRaw JOB_STATUS_CANCELING
1802

    
1803
jobStatusRunning :: String
1804
jobStatusRunning = Types.jobStatusToRaw JOB_STATUS_RUNNING
1805

    
1806
jobStatusCanceled :: String
1807
jobStatusCanceled = Types.jobStatusToRaw JOB_STATUS_CANCELED
1808

    
1809
jobStatusSuccess :: String
1810
jobStatusSuccess = Types.jobStatusToRaw JOB_STATUS_SUCCESS
1811

    
1812
jobStatusError :: String
1813
jobStatusError = Types.jobStatusToRaw JOB_STATUS_ERROR
1814

    
1815
jobsPending :: FrozenSet String
1816
jobsPending =
1817
  ConstantUtils.mkSet [jobStatusQueued, jobStatusWaiting, jobStatusCanceling]
1818

    
1819
jobsFinalized :: FrozenSet String
1820
jobsFinalized =
1821
  ConstantUtils.mkSet $ map Types.finalizedJobStatusToRaw [minBound..]
1822

    
1823
jobStatusAll :: FrozenSet String
1824
jobStatusAll = ConstantUtils.mkSet $ map Types.jobStatusToRaw [minBound..]
1825

    
1826
-- * OpCode status
1827

    
1828
-- ** Not yet finalized opcodes
1829

    
1830
opStatusCanceling :: String
1831
opStatusCanceling = "canceling"
1832

    
1833
opStatusQueued :: String
1834
opStatusQueued = "queued"
1835

    
1836
opStatusRunning :: String
1837
opStatusRunning = "running"
1838

    
1839
opStatusWaiting :: String
1840
opStatusWaiting = "waiting"
1841

    
1842
-- ** Finalized opcodes
1843

    
1844
opStatusCanceled :: String
1845
opStatusCanceled = "canceled"
1846

    
1847
opStatusError :: String
1848
opStatusError = "error"
1849

    
1850
opStatusSuccess :: String
1851
opStatusSuccess = "success"
1852

    
1853
opsFinalized :: FrozenSet String
1854
opsFinalized =
1855
  ConstantUtils.mkSet [opStatusCanceled, opStatusError, opStatusSuccess]
1856

    
1857
-- * OpCode priority
1858

    
1859
opPrioLowest :: Int
1860
opPrioLowest = 19
1861

    
1862
opPrioHighest :: Int
1863
opPrioHighest = -20
1864

    
1865
opPrioLow :: Int
1866
opPrioLow = Types.opSubmitPriorityToRaw OpPrioLow
1867

    
1868
opPrioNormal :: Int
1869
opPrioNormal = Types.opSubmitPriorityToRaw OpPrioNormal
1870

    
1871
opPrioHigh :: Int
1872
opPrioHigh = Types.opSubmitPriorityToRaw OpPrioHigh
1873

    
1874
opPrioSubmitValid :: FrozenSet Int
1875
opPrioSubmitValid = ConstantUtils.mkSet [opPrioLow, opPrioNormal, opPrioHigh]
1876

    
1877
opPrioDefault :: Int
1878
opPrioDefault = opPrioNormal
1879

    
1880
-- * Execution log types
1881

    
1882
elogMessage :: String
1883
elogMessage = Types.eLogTypeToRaw ELogMessage
1884

    
1885
elogRemoteImport :: String
1886
elogRemoteImport = Types.eLogTypeToRaw ELogRemoteImport
1887

    
1888
elogJqueueTest :: String
1889
elogJqueueTest = Types.eLogTypeToRaw ELogJqueueTest
1890

    
1891
-- * Confd
1892

    
1893
confdProtocolVersion :: Int
1894
confdProtocolVersion = ConstantUtils.confdProtocolVersion
1895

    
1896
-- Confd request type
1897

    
1898
confdReqPing :: Int
1899
confdReqPing = Types.confdRequestTypeToRaw ReqPing
1900

    
1901
confdReqNodeRoleByname :: Int
1902
confdReqNodeRoleByname = Types.confdRequestTypeToRaw ReqNodeRoleByName
1903

    
1904
confdReqNodePipByInstanceIp :: Int
1905
confdReqNodePipByInstanceIp = Types.confdRequestTypeToRaw ReqNodePipByInstPip
1906

    
1907
confdReqClusterMaster :: Int
1908
confdReqClusterMaster = Types.confdRequestTypeToRaw ReqClusterMaster
1909

    
1910
confdReqNodePipList :: Int
1911
confdReqNodePipList = Types.confdRequestTypeToRaw ReqNodePipList
1912

    
1913
confdReqMcPipList :: Int
1914
confdReqMcPipList = Types.confdRequestTypeToRaw ReqMcPipList
1915

    
1916
confdReqInstancesIpsList :: Int
1917
confdReqInstancesIpsList = Types.confdRequestTypeToRaw ReqInstIpsList
1918

    
1919
confdReqNodeDrbd :: Int
1920
confdReqNodeDrbd = Types.confdRequestTypeToRaw ReqNodeDrbd
1921

    
1922
confdReqNodeInstances :: Int
1923
confdReqNodeInstances = Types.confdRequestTypeToRaw ReqNodeInstances
1924

    
1925
confdReqs :: FrozenSet Int
1926
confdReqs =
1927
  ConstantUtils.mkSet .
1928
  map Types.confdRequestTypeToRaw $
1929
  [minBound..] \\ [ReqNodeInstances]
1930

    
1931
-- * Confd request type
1932

    
1933
confdReqfieldName :: Int
1934
confdReqfieldName = Types.confdReqFieldToRaw ReqFieldName
1935

    
1936
confdReqfieldIp :: Int
1937
confdReqfieldIp = Types.confdReqFieldToRaw ReqFieldIp
1938

    
1939
confdReqfieldMnodePip :: Int
1940
confdReqfieldMnodePip = Types.confdReqFieldToRaw ReqFieldMNodePip
1941

    
1942
-- * Confd repl status
1943

    
1944
confdReplStatusOk :: Int
1945
confdReplStatusOk = Types.confdReplyStatusToRaw ReplyStatusOk
1946

    
1947
confdReplStatusError :: Int
1948
confdReplStatusError = Types.confdReplyStatusToRaw ReplyStatusError
1949

    
1950
confdReplStatusNotimplemented :: Int
1951
confdReplStatusNotimplemented = Types.confdReplyStatusToRaw ReplyStatusNotImpl
1952

    
1953
confdReplStatuses :: FrozenSet Int
1954
confdReplStatuses =
1955
  ConstantUtils.mkSet $ map Types.confdReplyStatusToRaw [minBound..]
1956

    
1957
-- * Confd node role
1958

    
1959
confdNodeRoleMaster :: Int
1960
confdNodeRoleMaster = Types.confdNodeRoleToRaw NodeRoleMaster
1961

    
1962
confdNodeRoleCandidate :: Int
1963
confdNodeRoleCandidate = Types.confdNodeRoleToRaw NodeRoleCandidate
1964

    
1965
confdNodeRoleOffline :: Int
1966
confdNodeRoleOffline = Types.confdNodeRoleToRaw NodeRoleOffline
1967

    
1968
confdNodeRoleDrained :: Int
1969
confdNodeRoleDrained = Types.confdNodeRoleToRaw NodeRoleDrained
1970

    
1971
confdNodeRoleRegular :: Int
1972
confdNodeRoleRegular = Types.confdNodeRoleToRaw NodeRoleRegular
1973

    
1974
-- * A few common errors for confd
1975

    
1976
confdErrorUnknownEntry :: Int
1977
confdErrorUnknownEntry = Types.confdErrorTypeToRaw ConfdErrorUnknownEntry
1978

    
1979
confdErrorInternal :: Int
1980
confdErrorInternal = Types.confdErrorTypeToRaw ConfdErrorInternal
1981

    
1982
confdErrorArgument :: Int
1983
confdErrorArgument = Types.confdErrorTypeToRaw ConfdErrorArgument
1984

    
1985
-- * Confd request query fields
1986

    
1987
confdReqqLink :: String
1988
confdReqqLink = ConstantUtils.confdReqqLink
1989

    
1990
confdReqqIp :: String
1991
confdReqqIp = ConstantUtils.confdReqqIp
1992

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

    
1996
confdReqqFields :: String
1997
confdReqqFields = ConstantUtils.confdReqqFields
1998

    
1999
-- | Each request is "salted" by the current timestamp.
2000
--
2001
-- This constant decides how many seconds of skew to accept.
2002
--
2003
-- TODO: make this a default and allow the value to be more
2004
-- configurable
2005
confdMaxClockSkew :: Int
2006
confdMaxClockSkew = 2 * nodeMaxClockSkew
2007

    
2008
-- | When we haven't reloaded the config for more than this amount of
2009
-- seconds, we force a test to see if inotify is betraying us. Using a
2010
-- prime number to ensure we get less chance of 'same wakeup' with
2011
-- other processes.
2012
confdConfigReloadTimeout :: Int
2013
confdConfigReloadTimeout = 17
2014

    
2015
-- | If we receive more than one update in this amount of
2016
-- microseconds, we move to polling every RATELIMIT seconds, rather
2017
-- than relying on inotify, to be able to serve more requests.
2018
confdConfigReloadRatelimit :: Int
2019
confdConfigReloadRatelimit = 250000
2020

    
2021
-- | Magic number prepended to all confd queries.
2022
--
2023
-- This allows us to distinguish different types of confd protocols
2024
-- and handle them. For example by changing this we can move the whole
2025
-- payload to be compressed, or move away from json.
2026
confdMagicFourcc :: String
2027
confdMagicFourcc = "plj0"
2028

    
2029
-- | By default a confd request is sent to the minimum between this
2030
-- number and all MCs. 6 was chosen because even in the case of a
2031
-- disastrous 50% response rate, we should have enough answers to be
2032
-- able to compare more than one.
2033
confdDefaultReqCoverage :: Int
2034
confdDefaultReqCoverage = 6
2035

    
2036
-- | Timeout in seconds to expire pending query request in the confd
2037
-- client library. We don't actually expect any answer more than 10
2038
-- seconds after we sent a request.
2039
confdClientExpireTimeout :: Int
2040
confdClientExpireTimeout = 10
2041

    
2042
-- * Possible values for NodeGroup.alloc_policy
2043

    
2044
allocPolicyLastResort :: String
2045
allocPolicyLastResort = Types.allocPolicyToRaw AllocLastResort
2046

    
2047
allocPolicyPreferred :: String
2048
allocPolicyPreferred = Types.allocPolicyToRaw AllocPreferred
2049

    
2050
allocPolicyUnallocable :: String
2051
allocPolicyUnallocable = Types.allocPolicyToRaw AllocUnallocable
2052

    
2053
validAllocPolicies :: [String]
2054
validAllocPolicies = map Types.allocPolicyToRaw [minBound..]
2055

    
2056
-- | Temporary external/shared storage parameters
2057
blockdevDriverManual :: String
2058
blockdevDriverManual = Types.blockDriverToRaw BlockDrvManual
2059

    
2060
-- | 'qemu-img' path, required for 'ovfconverter'
2061
qemuimgPath :: String
2062
qemuimgPath = AutoConf.qemuimgPath
2063

    
2064
-- | Whether htools was enabled at compilation time
2065
--
2066
-- FIXME: this should be moved next to the other enable constants,
2067
-- such as, 'enableConfd', and renamed to 'enableHtools'.
2068
htools :: Bool
2069
htools = AutoConf.htools
2070

    
2071
-- * Key files for SSH daemon
2072

    
2073
sshHostDsaPriv :: String
2074
sshHostDsaPriv = sshConfigDir ++ "/ssh_host_dsa_key"
2075

    
2076
sshHostDsaPub :: String
2077
sshHostDsaPub = sshHostDsaPriv ++ ".pub"
2078

    
2079
sshHostRsaPriv :: String
2080
sshHostRsaPriv = sshConfigDir ++ "/ssh_host_rsa_key"
2081

    
2082
sshHostRsaPub :: String
2083
sshHostRsaPub = sshHostRsaPriv ++ ".pub"
2084

    
2085
-- | Path generating random UUID
2086
randomUuidFile :: String
2087
randomUuidFile = ConstantUtils.randomUuidFile
2088

    
2089
-- * Auto-repair tag prefixes
2090

    
2091
autoRepairTagPrefix :: String
2092
autoRepairTagPrefix = "ganeti:watcher:autorepair:"
2093

    
2094
autoRepairTagEnabled :: String
2095
autoRepairTagEnabled = autoRepairTagPrefix
2096

    
2097
autoRepairTagPending :: String
2098
autoRepairTagPending = autoRepairTagPrefix ++ "pending:"
2099

    
2100
autoRepairTagResult :: String
2101
autoRepairTagResult = autoRepairTagPrefix ++ "result:"
2102

    
2103
autoRepairTagSuspended :: String
2104
autoRepairTagSuspended = autoRepairTagPrefix ++ "suspend:"
2105

    
2106
-- * Auto-repair levels
2107

    
2108
autoRepairFailover :: String
2109
autoRepairFailover = "failover"
2110

    
2111
autoRepairFixStorage :: String
2112
autoRepairFixStorage = "fix-storage"
2113

    
2114
autoRepairMigrate :: String
2115
autoRepairMigrate = "migrate"
2116

    
2117
autoRepairReinstall :: String
2118
autoRepairReinstall = "reinstall"
2119

    
2120
autoRepairAllTypes :: FrozenSet String
2121
autoRepairAllTypes =
2122
  ConstantUtils.mkSet [autoRepairFailover,
2123
                       autoRepairFixStorage,
2124
                       autoRepairMigrate,
2125
                       autoRepairReinstall]
2126

    
2127
-- * Auto-repair results
2128

    
2129
autoRepairEnoperm :: String
2130
autoRepairEnoperm = "enoperm"
2131

    
2132
autoRepairFailure :: String
2133
autoRepairFailure = "failure"
2134

    
2135
autoRepairSuccess :: String
2136
autoRepairSuccess = "success"
2137

    
2138
autoRepairAllResults :: FrozenSet String
2139
autoRepairAllResults =
2140
  ConstantUtils.mkSet [autoRepairEnoperm, autoRepairFailure, autoRepairSuccess]
2141

    
2142
-- | The version identifier for builtin data collectors
2143
builtinDataCollectorVersion :: String
2144
builtinDataCollectorVersion = "B"
2145

    
2146
-- | The reason trail opcode parameter name
2147
opcodeReason :: String
2148
opcodeReason = "reason"
2149

    
2150
diskstatsFile :: String
2151
diskstatsFile = "/proc/diskstats"
2152

    
2153
-- *  CPU load collector
2154

    
2155
statFile :: String
2156
statFile = "/proc/stat"
2157

    
2158
cpuavgloadBufferSize :: Int
2159
cpuavgloadBufferSize = 150
2160

    
2161
cpuavgloadWindowSize :: Int
2162
cpuavgloadWindowSize = 600
2163

    
2164
-- | Mond's variable for periodical data collection
2165
mondTimeInterval :: Int
2166
mondTimeInterval = 5
2167

    
2168
-- * Disk access modes
2169

    
2170
diskUserspace :: String
2171
diskUserspace = Types.diskAccessModeToRaw DiskUserspace
2172

    
2173
diskKernelspace :: String
2174
diskKernelspace = Types.diskAccessModeToRaw DiskKernelspace
2175

    
2176
diskValidAccessModes :: FrozenSet String
2177
diskValidAccessModes =
2178
  ConstantUtils.mkSet $ map Types.diskAccessModeToRaw [minBound..]
2179

    
2180
-- | Timeout for queue draining in upgrades
2181
upgradeQueueDrainTimeout :: Int
2182
upgradeQueueDrainTimeout = 36 * 60 * 60 -- 1.5 days
2183

    
2184
-- | Intervall at which the queue is polled during upgrades
2185
upgradeQueuePollInterval :: Int
2186
upgradeQueuePollInterval  = 10