Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HsConstants.hs @ 52d4f735

History | View | Annotate | Download (54.8 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
-- * Others
1079

    
1080
defaultBridge :: String
1081
defaultBridge = "xen-br0"
1082

    
1083
defaultOvs :: String
1084
defaultOvs = "switch1"
1085

    
1086
-- | 60 MiB, expressed in KiB
1087
classicDrbdSyncSpeed :: Int
1088
classicDrbdSyncSpeed = 60 * 1024
1089

    
1090
ip4AddressAny :: String
1091
ip4AddressAny = "0.0.0.0"
1092

    
1093
ip4AddressLocalhost :: String
1094
ip4AddressLocalhost = "127.0.0.1"
1095

    
1096
ip6AddressAny :: String
1097
ip6AddressAny = "::"
1098

    
1099
ip6AddressLocalhost :: String
1100
ip6AddressLocalhost = "::1"
1101

    
1102
ip4Version :: Int
1103
ip4Version = 4
1104

    
1105
ip6Version :: Int
1106
ip6Version = 6
1107

    
1108
validIpVersions :: FrozenSet Int
1109
validIpVersions = ConstantUtils.mkSet [ip4Version, ip6Version]
1110

    
1111
tcpPingTimeout :: Int
1112
tcpPingTimeout = 10
1113

    
1114
defaultVg :: String
1115
defaultVg = "xenvg"
1116

    
1117
defaultDrbdHelper :: String
1118
defaultDrbdHelper = "/bin/true"
1119

    
1120
minVgSize :: Int
1121
minVgSize = 20480
1122

    
1123
defaultMacPrefix :: String
1124
defaultMacPrefix = "aa:00:00"
1125

    
1126
-- | Default maximum instance wait time, in seconds.
1127
defaultShutdownTimeout :: Int
1128
defaultShutdownTimeout = 120
1129

    
1130
-- | Node clock skew in seconds
1131
nodeMaxClockSkew :: Int
1132
nodeMaxClockSkew = 150
1133

    
1134
-- | Time for an intra-cluster disk transfer to wait for a connection
1135
diskTransferConnectTimeout :: Int
1136
diskTransferConnectTimeout = 60
1137

    
1138
-- | Disk index separator
1139
diskSeparator :: String
1140
diskSeparator = AutoConf.diskSeparator
1141

    
1142
-- * Timeout table
1143
--
1144
-- Various time constants for the timeout table
1145

    
1146
rpcTmoUrgent :: Int
1147
rpcTmoUrgent = Types.rpcTimeoutToRaw Urgent
1148

    
1149
rpcTmoFast :: Int
1150
rpcTmoFast = Types.rpcTimeoutToRaw Fast
1151

    
1152
rpcTmoNormal :: Int
1153
rpcTmoNormal = Types.rpcTimeoutToRaw Normal
1154

    
1155
rpcTmoSlow :: Int
1156
rpcTmoSlow = Types.rpcTimeoutToRaw Slow
1157

    
1158
-- | 'rpcTmo_4hrs' contains an underscore to circumvent a limitation
1159
-- in the 'Ganeti.THH.deCamelCase' function and generate the correct
1160
-- Python name.
1161
rpcTmo_4hrs :: Int
1162
rpcTmo_4hrs = Types.rpcTimeoutToRaw FourHours
1163

    
1164
-- | 'rpcTmo_1day' contains an underscore to circumvent a limitation
1165
-- in the 'Ganeti.THH.deCamelCase' function and generate the correct
1166
-- Python name.
1167
rpcTmo_1day :: Int
1168
rpcTmo_1day = Types.rpcTimeoutToRaw OneDay
1169

    
1170
-- | Timeout for connecting to nodes (seconds)
1171
rpcConnectTimeout :: Int
1172
rpcConnectTimeout = 5
1173

    
1174
-- * VTypes
1175

    
1176
vtypeBool :: VType
1177
vtypeBool = VTypeBool
1178

    
1179
vtypeInt :: VType
1180
vtypeInt = VTypeInt
1181

    
1182
vtypeMaybeString :: VType
1183
vtypeMaybeString = VTypeMaybeString
1184

    
1185
-- | Size in MiBs
1186
vtypeSize :: VType
1187
vtypeSize = VTypeSize
1188

    
1189
vtypeString :: VType
1190
vtypeString = VTypeString
1191

    
1192
enforceableTypes :: FrozenSet VType
1193
enforceableTypes = ConstantUtils.mkSet [minBound..]
1194

    
1195
-- | Instance specs
1196
--
1197
-- FIXME: these should be associated with 'Ganeti.HTools.Types.ISpec'
1198

    
1199
ispecMemSize :: String
1200
ispecMemSize = ConstantUtils.ispecMemSize
1201

    
1202
ispecCpuCount :: String
1203
ispecCpuCount = ConstantUtils.ispecCpuCount
1204

    
1205
ispecDiskCount :: String
1206
ispecDiskCount = ConstantUtils.ispecDiskCount
1207

    
1208
ispecDiskSize :: String
1209
ispecDiskSize = ConstantUtils.ispecDiskSize
1210

    
1211
ispecNicCount :: String
1212
ispecNicCount = ConstantUtils.ispecNicCount
1213

    
1214
ispecSpindleUse :: String
1215
ispecSpindleUse = ConstantUtils.ispecSpindleUse
1216

    
1217
ispecsParameterTypes :: Map String VType
1218
ispecsParameterTypes =
1219
  Map.fromList
1220
  [(ConstantUtils.ispecDiskSize, VTypeInt),
1221
   (ConstantUtils.ispecCpuCount, VTypeInt),
1222
   (ConstantUtils.ispecSpindleUse, VTypeInt),
1223
   (ConstantUtils.ispecMemSize, VTypeInt),
1224
   (ConstantUtils.ispecNicCount, VTypeInt),
1225
   (ConstantUtils.ispecDiskCount, VTypeInt)]
1226

    
1227
ispecsParameters :: FrozenSet String
1228
ispecsParameters =
1229
  ConstantUtils.mkSet [ConstantUtils.ispecCpuCount,
1230
                       ConstantUtils.ispecDiskCount,
1231
                       ConstantUtils.ispecDiskSize,
1232
                       ConstantUtils.ispecMemSize,
1233
                       ConstantUtils.ispecNicCount,
1234
                       ConstantUtils.ispecSpindleUse]
1235

    
1236
ispecsMinmax :: String
1237
ispecsMinmax = ConstantUtils.ispecsMinmax
1238

    
1239
ispecsMax :: String
1240
ispecsMax = "max"
1241

    
1242
ispecsMin :: String
1243
ispecsMin = "min"
1244

    
1245
ispecsStd :: String
1246
ispecsStd = ConstantUtils.ispecsStd
1247

    
1248
ipolicyDts :: String
1249
ipolicyDts = ConstantUtils.ipolicyDts
1250

    
1251
ipolicyVcpuRatio :: String
1252
ipolicyVcpuRatio = ConstantUtils.ipolicyVcpuRatio
1253

    
1254
ipolicySpindleRatio :: String
1255
ipolicySpindleRatio = ConstantUtils.ipolicySpindleRatio
1256

    
1257
ispecsMinmaxKeys :: FrozenSet String
1258
ispecsMinmaxKeys = ConstantUtils.mkSet [ispecsMax, ispecsMin]
1259

    
1260
ipolicyParameters :: FrozenSet String
1261
ipolicyParameters =
1262
  ConstantUtils.mkSet [ConstantUtils.ipolicyVcpuRatio,
1263
                       ConstantUtils.ipolicySpindleRatio]
1264

    
1265
ipolicyAllKeys :: FrozenSet String
1266
ipolicyAllKeys =
1267
  ConstantUtils.union ipolicyParameters $
1268
  ConstantUtils.mkSet [ConstantUtils.ipolicyDts,
1269
                       ConstantUtils.ispecsMinmax,
1270
                       ispecsStd]
1271

    
1272
-- | Node parameter names
1273

    
1274
ndExclusiveStorage :: String
1275
ndExclusiveStorage = "exclusive_storage"
1276

    
1277
ndOobProgram :: String
1278
ndOobProgram = "oob_program"
1279

    
1280
ndSpindleCount :: String
1281
ndSpindleCount = "spindle_count"
1282

    
1283
ndOvs :: String
1284
ndOvs = "ovs"
1285

    
1286
ndOvsLink :: String
1287
ndOvsLink = "ovs_link"
1288

    
1289
ndOvsName :: String
1290
ndOvsName = "ovs_name"
1291

    
1292
ndsParameterTypes :: Map String VType
1293
ndsParameterTypes =
1294
  Map.fromList
1295
  [(ndExclusiveStorage, VTypeBool),
1296
   (ndOobProgram, VTypeString),
1297
   (ndOvs, VTypeBool),
1298
   (ndOvsLink, VTypeMaybeString),
1299
   (ndOvsName, VTypeMaybeString),
1300
   (ndSpindleCount, VTypeInt)]
1301

    
1302
ndsParameters :: FrozenSet String
1303
ndsParameters = ConstantUtils.mkSet (Map.keys ndsParameterTypes)
1304

    
1305
ndsParameterTitles :: Map String String
1306
ndsParameterTitles =
1307
  Map.fromList
1308
  [(ndExclusiveStorage, "ExclusiveStorage"),
1309
   (ndOobProgram, "OutOfBandProgram"),
1310
   (ndOvs, "OpenvSwitch"),
1311
   (ndOvsLink, "OpenvSwitchLink"),
1312
   (ndOvsName, "OpenvSwitchName"),
1313
   (ndSpindleCount, "SpindleCount")]
1314

    
1315
ipCommandPath :: String
1316
ipCommandPath = AutoConf.ipPath
1317

    
1318
-- * Reboot types
1319

    
1320
instanceRebootSoft :: String
1321
instanceRebootSoft = Types.rebootTypeToRaw RebootSoft
1322

    
1323
instanceRebootHard :: String
1324
instanceRebootHard = Types.rebootTypeToRaw RebootHard
1325

    
1326
instanceRebootFull :: String
1327
instanceRebootFull = Types.rebootTypeToRaw RebootFull
1328

    
1329
rebootTypes :: FrozenSet String
1330
rebootTypes = ConstantUtils.mkSet $ map Types.rebootTypeToRaw [minBound..]
1331

    
1332

    
1333

    
1334

    
1335

    
1336

    
1337

    
1338

    
1339
-- * OOB supported commands
1340

    
1341
oobPowerOn :: String
1342
oobPowerOn = Types.oobCommandToRaw OobPowerOn
1343

    
1344
oobPowerOff :: String
1345
oobPowerOff = Types.oobCommandToRaw OobPowerOff
1346

    
1347
oobPowerCycle :: String
1348
oobPowerCycle = Types.oobCommandToRaw OobPowerCycle
1349

    
1350
oobPowerStatus :: String
1351
oobPowerStatus = Types.oobCommandToRaw OobPowerStatus
1352

    
1353
oobHealth :: String
1354
oobHealth = Types.oobCommandToRaw OobHealth
1355

    
1356
oobCommands :: FrozenSet String
1357
oobCommands = ConstantUtils.mkSet $ map Types.oobCommandToRaw [minBound..]
1358

    
1359
oobPowerStatusPowered :: String
1360
oobPowerStatusPowered = "powered"
1361

    
1362
-- | 60 seconds
1363
oobTimeout :: Int
1364
oobTimeout = 60
1365

    
1366
-- | 2 seconds
1367
oobPowerDelay :: Double
1368
oobPowerDelay = 2.0
1369

    
1370
oobStatusCritical :: String
1371
oobStatusCritical = Types.oobStatusToRaw OobStatusCritical
1372

    
1373
oobStatusOk :: String
1374
oobStatusOk = Types.oobStatusToRaw OobStatusOk
1375

    
1376
oobStatusUnknown :: String
1377
oobStatusUnknown = Types.oobStatusToRaw OobStatusUnknown
1378

    
1379
oobStatusWarning :: String
1380
oobStatusWarning = Types.oobStatusToRaw OobStatusWarning
1381

    
1382
oobStatuses :: FrozenSet String
1383
oobStatuses = ConstantUtils.mkSet $ map Types.oobStatusToRaw [minBound..]
1384

    
1385
-- * NIC_* constants are used inside the ganeti config
1386

    
1387
nicLink :: String
1388
nicLink = "link"
1389

    
1390
nicMode :: String
1391
nicMode = "mode"
1392

    
1393
nicVlan :: String
1394
nicVlan = "vlan"
1395

    
1396
nicModeBridged :: String
1397
nicModeBridged = Types.nICModeToRaw NMBridged
1398

    
1399
nicModeRouted :: String
1400
nicModeRouted = Types.nICModeToRaw NMRouted
1401

    
1402
nicModeOvs :: String
1403
nicModeOvs = Types.nICModeToRaw NMOvs
1404

    
1405
nicIpPool :: String
1406
nicIpPool = Types.nICModeToRaw NMPool
1407

    
1408
nicValidModes :: FrozenSet String
1409
nicValidModes = ConstantUtils.mkSet $ map Types.nICModeToRaw [minBound..]
1410

    
1411
-- * Hypervisor constants
1412

    
1413
htXenPvm :: String
1414
htXenPvm = Types.hypervisorToRaw XenPvm
1415

    
1416
htFake :: String
1417
htFake = Types.hypervisorToRaw Fake
1418

    
1419
htXenHvm :: String
1420
htXenHvm = Types.hypervisorToRaw XenHvm
1421

    
1422
htKvm :: String
1423
htKvm = Types.hypervisorToRaw Kvm
1424

    
1425
htChroot :: String
1426
htChroot = Types.hypervisorToRaw Chroot
1427

    
1428
htLxc :: String
1429
htLxc = Types.hypervisorToRaw Lxc
1430

    
1431
hyperTypes :: FrozenSet String
1432
hyperTypes = ConstantUtils.mkSet $ map Types.hypervisorToRaw [minBound..]
1433

    
1434
htsReqPort :: FrozenSet String
1435
htsReqPort = ConstantUtils.mkSet [htXenHvm, htKvm]
1436

    
1437
-- * Migration type
1438

    
1439
htMigrationLive :: String
1440
htMigrationLive = Types.migrationModeToRaw MigrationLive
1441

    
1442
htMigrationNonlive :: String
1443
htMigrationNonlive = Types.migrationModeToRaw MigrationNonLive
1444

    
1445
htMigrationModes :: FrozenSet String
1446
htMigrationModes =
1447
  ConstantUtils.mkSet $ map Types.migrationModeToRaw [minBound..]
1448

    
1449
-- * Cluster verify steps
1450

    
1451
verifyNplusoneMem :: String
1452
verifyNplusoneMem = Types.verifyOptionalChecksToRaw VerifyNPlusOneMem
1453

    
1454
verifyOptionalChecks :: FrozenSet String
1455
verifyOptionalChecks =
1456
  ConstantUtils.mkSet $ map Types.verifyOptionalChecksToRaw [minBound..]
1457

    
1458
-- * Cluster Verify error classes
1459

    
1460
cvTcluster :: String
1461
cvTcluster = "cluster"
1462

    
1463
cvTgroup :: String
1464
cvTgroup = "group"
1465

    
1466
cvTnode :: String
1467
cvTnode = "node"
1468

    
1469
cvTinstance :: String
1470
cvTinstance = "instance"
1471

    
1472
-- * Cluster Verify error codes and documentation
1473

    
1474
cvEclustercert :: (String, String, String)
1475
cvEclustercert =
1476
  ("cluster",
1477
   Types.cVErrorCodeToRaw CvECLUSTERCERT,
1478
   "Cluster certificate files verification failure")
1479

    
1480
cvEclustercfg :: (String, String, String)
1481
cvEclustercfg =
1482
  ("cluster",
1483
   Types.cVErrorCodeToRaw CvECLUSTERCFG,
1484
   "Cluster configuration verification failure")
1485

    
1486
cvEclusterdanglinginst :: (String, String, String)
1487
cvEclusterdanglinginst =
1488
  ("node",
1489
   Types.cVErrorCodeToRaw CvECLUSTERDANGLINGINST,
1490
   "Some instances have a non-existing primary node")
1491

    
1492
cvEclusterdanglingnodes :: (String, String, String)
1493
cvEclusterdanglingnodes =
1494
  ("node",
1495
   Types.cVErrorCodeToRaw CvECLUSTERDANGLINGNODES,
1496
   "Some nodes belong to non-existing groups")
1497

    
1498
cvEclusterfilecheck :: (String, String, String)
1499
cvEclusterfilecheck =
1500
  ("cluster",
1501
   Types.cVErrorCodeToRaw CvECLUSTERFILECHECK,
1502
   "Cluster configuration verification failure")
1503

    
1504
cvEgroupdifferentpvsize :: (String, String, String)
1505
cvEgroupdifferentpvsize =
1506
  ("group",
1507
   Types.cVErrorCodeToRaw CvEGROUPDIFFERENTPVSIZE,
1508
   "PVs in the group have different sizes")
1509

    
1510
cvEinstancebadnode :: (String, String, String)
1511
cvEinstancebadnode =
1512
  ("instance",
1513
   Types.cVErrorCodeToRaw CvEINSTANCEBADNODE,
1514
   "Instance marked as running lives on an offline node")
1515

    
1516
cvEinstancedown :: (String, String, String)
1517
cvEinstancedown =
1518
  ("instance",
1519
   Types.cVErrorCodeToRaw CvEINSTANCEDOWN,
1520
   "Instance not running on its primary node")
1521

    
1522
cvEinstancefaultydisk :: (String, String, String)
1523
cvEinstancefaultydisk =
1524
  ("instance",
1525
   Types.cVErrorCodeToRaw CvEINSTANCEFAULTYDISK,
1526
   "Impossible to retrieve status for a disk")
1527

    
1528
cvEinstancelayout :: (String, String, String)
1529
cvEinstancelayout =
1530
  ("instance",
1531
   Types.cVErrorCodeToRaw CvEINSTANCELAYOUT,
1532
   "Instance has multiple secondary nodes")
1533

    
1534
cvEinstancemissingcfgparameter :: (String, String, String)
1535
cvEinstancemissingcfgparameter =
1536
  ("instance",
1537
   Types.cVErrorCodeToRaw CvEINSTANCEMISSINGCFGPARAMETER,
1538
   "A configuration parameter for an instance is missing")
1539

    
1540
cvEinstancemissingdisk :: (String, String, String)
1541
cvEinstancemissingdisk =
1542
  ("instance",
1543
   Types.cVErrorCodeToRaw CvEINSTANCEMISSINGDISK,
1544
   "Missing volume on an instance")
1545

    
1546
cvEinstancepolicy :: (String, String, String)
1547
cvEinstancepolicy =
1548
  ("instance",
1549
   Types.cVErrorCodeToRaw CvEINSTANCEPOLICY,
1550
   "Instance does not meet policy")
1551

    
1552
cvEinstancesplitgroups :: (String, String, String)
1553
cvEinstancesplitgroups =
1554
  ("instance",
1555
   Types.cVErrorCodeToRaw CvEINSTANCESPLITGROUPS,
1556
   "Instance with primary and secondary nodes in different groups")
1557

    
1558
cvEinstanceunsuitablenode :: (String, String, String)
1559
cvEinstanceunsuitablenode =
1560
  ("instance",
1561
   Types.cVErrorCodeToRaw CvEINSTANCEUNSUITABLENODE,
1562
   "Instance running on nodes that are not suitable for it")
1563

    
1564
cvEinstancewrongnode :: (String, String, String)
1565
cvEinstancewrongnode =
1566
  ("instance",
1567
   Types.cVErrorCodeToRaw CvEINSTANCEWRONGNODE,
1568
   "Instance running on the wrong node")
1569

    
1570
cvEnodedrbd :: (String, String, String)
1571
cvEnodedrbd =
1572
  ("node",
1573
   Types.cVErrorCodeToRaw CvENODEDRBD,
1574
   "Error parsing the DRBD status file")
1575

    
1576
cvEnodedrbdhelper :: (String, String, String)
1577
cvEnodedrbdhelper =
1578
  ("node",
1579
   Types.cVErrorCodeToRaw CvENODEDRBDHELPER,
1580
   "Error caused by the DRBD helper")
1581

    
1582
cvEnodedrbdversion :: (String, String, String)
1583
cvEnodedrbdversion =
1584
  ("node",
1585
   Types.cVErrorCodeToRaw CvENODEDRBDVERSION,
1586
   "DRBD version mismatch within a node group")
1587

    
1588
cvEnodefilecheck :: (String, String, String)
1589
cvEnodefilecheck =
1590
  ("node",
1591
   Types.cVErrorCodeToRaw CvENODEFILECHECK,
1592
   "Error retrieving the checksum of the node files")
1593

    
1594
cvEnodefilestoragepaths :: (String, String, String)
1595
cvEnodefilestoragepaths =
1596
  ("node",
1597
   Types.cVErrorCodeToRaw CvENODEFILESTORAGEPATHS,
1598
   "Detected bad file storage paths")
1599

    
1600
cvEnodefilestoragepathunusable :: (String, String, String)
1601
cvEnodefilestoragepathunusable =
1602
  ("node",
1603
   Types.cVErrorCodeToRaw CvENODEFILESTORAGEPATHUNUSABLE,
1604
   "File storage path unusable")
1605

    
1606
cvEnodehooks :: (String, String, String)
1607
cvEnodehooks =
1608
  ("node",
1609
   Types.cVErrorCodeToRaw CvENODEHOOKS,
1610
   "Communication failure in hooks execution")
1611

    
1612
cvEnodehv :: (String, String, String)
1613
cvEnodehv =
1614
  ("node",
1615
   Types.cVErrorCodeToRaw CvENODEHV,
1616
   "Hypervisor parameters verification failure")
1617

    
1618
cvEnodelvm :: (String, String, String)
1619
cvEnodelvm =
1620
  ("node",
1621
   Types.cVErrorCodeToRaw CvENODELVM,
1622
   "LVM-related node error")
1623

    
1624
cvEnoden1 :: (String, String, String)
1625
cvEnoden1 =
1626
  ("node",
1627
   Types.cVErrorCodeToRaw CvENODEN1,
1628
   "Not enough memory to accommodate instance failovers")
1629

    
1630
cvEnodenet :: (String, String, String)
1631
cvEnodenet =
1632
  ("node",
1633
   Types.cVErrorCodeToRaw CvENODENET,
1634
   "Network-related node error")
1635

    
1636
cvEnodeoobpath :: (String, String, String)
1637
cvEnodeoobpath =
1638
  ("node",
1639
   Types.cVErrorCodeToRaw CvENODEOOBPATH,
1640
   "Invalid Out Of Band path")
1641

    
1642
cvEnodeorphaninstance :: (String, String, String)
1643
cvEnodeorphaninstance =
1644
  ("node",
1645
   Types.cVErrorCodeToRaw CvENODEORPHANINSTANCE,
1646
   "Unknown intance running on a node")
1647

    
1648
cvEnodeorphanlv :: (String, String, String)
1649
cvEnodeorphanlv =
1650
  ("node",
1651
   Types.cVErrorCodeToRaw CvENODEORPHANLV,
1652
   "Unknown LVM logical volume")
1653

    
1654
cvEnodeos :: (String, String, String)
1655
cvEnodeos =
1656
  ("node",
1657
   Types.cVErrorCodeToRaw CvENODEOS,
1658
   "OS-related node error")
1659

    
1660
cvEnoderpc :: (String, String, String)
1661
cvEnoderpc =
1662
  ("node",
1663
   Types.cVErrorCodeToRaw CvENODERPC,
1664
   "Error during connection to the primary node of an instance")
1665

    
1666
cvEnodesetup :: (String, String, String)
1667
cvEnodesetup =
1668
  ("node",
1669
   Types.cVErrorCodeToRaw CvENODESETUP,
1670
   "Node setup error")
1671

    
1672
cvEnodesharedfilestoragepathunusable :: (String, String, String)
1673
cvEnodesharedfilestoragepathunusable =
1674
  ("node",
1675
   Types.cVErrorCodeToRaw CvENODESHAREDFILESTORAGEPATHUNUSABLE,
1676
   "Shared file storage path unusable")
1677

    
1678
cvEnodessh :: (String, String, String)
1679
cvEnodessh =
1680
  ("node",
1681
   Types.cVErrorCodeToRaw CvENODESSH,
1682
   "SSH-related node error")
1683

    
1684
cvEnodetime :: (String, String, String)
1685
cvEnodetime =
1686
  ("node",
1687
   Types.cVErrorCodeToRaw CvENODETIME,
1688
   "Node returned invalid time")
1689

    
1690
cvEnodeuserscripts :: (String, String, String)
1691
cvEnodeuserscripts =
1692
  ("node",
1693
   Types.cVErrorCodeToRaw CvENODEUSERSCRIPTS,
1694
   "User scripts not present or not executable")
1695

    
1696
cvEnodeversion :: (String, String, String)
1697
cvEnodeversion =
1698
  ("node",
1699
   Types.cVErrorCodeToRaw CvENODEVERSION,
1700
   "Protocol version mismatch or Ganeti version mismatch")
1701

    
1702
cvAllEcodes :: FrozenSet (String, String, String)
1703
cvAllEcodes =
1704
  ConstantUtils.mkSet
1705
  [cvEclustercert,
1706
   cvEclustercfg,
1707
   cvEclusterdanglinginst,
1708
   cvEclusterdanglingnodes,
1709
   cvEclusterfilecheck,
1710
   cvEgroupdifferentpvsize,
1711
   cvEinstancebadnode,
1712
   cvEinstancedown,
1713
   cvEinstancefaultydisk,
1714
   cvEinstancelayout,
1715
   cvEinstancemissingcfgparameter,
1716
   cvEinstancemissingdisk,
1717
   cvEinstancepolicy,
1718
   cvEinstancesplitgroups,
1719
   cvEinstanceunsuitablenode,
1720
   cvEinstancewrongnode,
1721
   cvEnodedrbd,
1722
   cvEnodedrbdhelper,
1723
   cvEnodedrbdversion,
1724
   cvEnodefilecheck,
1725
   cvEnodefilestoragepaths,
1726
   cvEnodefilestoragepathunusable,
1727
   cvEnodehooks,
1728
   cvEnodehv,
1729
   cvEnodelvm,
1730
   cvEnoden1,
1731
   cvEnodenet,
1732
   cvEnodeoobpath,
1733
   cvEnodeorphaninstance,
1734
   cvEnodeorphanlv,
1735
   cvEnodeos,
1736
   cvEnoderpc,
1737
   cvEnodesetup,
1738
   cvEnodesharedfilestoragepathunusable,
1739
   cvEnodessh,
1740
   cvEnodetime,
1741
   cvEnodeuserscripts,
1742
   cvEnodeversion]
1743

    
1744
cvAllEcodesStrings :: FrozenSet String
1745
cvAllEcodesStrings =
1746
  ConstantUtils.mkSet $ map Types.cVErrorCodeToRaw [minBound..]
1747

    
1748
-- * Instance status
1749

    
1750
inststAdmindown :: String
1751
inststAdmindown = Types.instanceStatusToRaw StatusDown
1752

    
1753
inststAdminoffline :: String
1754
inststAdminoffline = Types.instanceStatusToRaw StatusOffline
1755

    
1756
inststErrordown :: String
1757
inststErrordown = Types.instanceStatusToRaw ErrorDown
1758

    
1759
inststErrorup :: String
1760
inststErrorup = Types.instanceStatusToRaw ErrorUp
1761

    
1762
inststNodedown :: String
1763
inststNodedown = Types.instanceStatusToRaw NodeDown
1764

    
1765
inststNodeoffline :: String
1766
inststNodeoffline = Types.instanceStatusToRaw NodeOffline
1767

    
1768
inststRunning :: String
1769
inststRunning = Types.instanceStatusToRaw Running
1770

    
1771
inststWrongnode :: String
1772
inststWrongnode = Types.instanceStatusToRaw WrongNode
1773

    
1774
inststAll :: FrozenSet String
1775
inststAll = ConstantUtils.mkSet $ map Types.instanceStatusToRaw [minBound..]
1776

    
1777
-- * Admin states
1778

    
1779
adminstDown :: String
1780
adminstDown = Types.adminStateToRaw AdminDown
1781

    
1782
adminstOffline :: String
1783
adminstOffline = Types.adminStateToRaw AdminOffline
1784

    
1785
adminstUp :: String
1786
adminstUp = Types.adminStateToRaw AdminUp
1787

    
1788
adminstAll :: FrozenSet String
1789
adminstAll = ConstantUtils.mkSet $ map Types.adminStateToRaw [minBound..]
1790

    
1791
-- * Node roles
1792

    
1793
nrDrained :: String
1794
nrDrained = Types.nodeRoleToRaw NRDrained
1795

    
1796
nrMaster :: String
1797
nrMaster = Types.nodeRoleToRaw NRMaster
1798

    
1799
nrMcandidate :: String
1800
nrMcandidate = Types.nodeRoleToRaw NRCandidate
1801

    
1802
nrOffline :: String
1803
nrOffline = Types.nodeRoleToRaw NROffline
1804

    
1805
nrRegular :: String
1806
nrRegular = Types.nodeRoleToRaw NRRegular
1807

    
1808
nrAll :: FrozenSet String
1809
nrAll = ConstantUtils.mkSet $ map Types.nodeRoleToRaw [minBound..]
1810

    
1811
-- * Allocator framework constants
1812

    
1813
iallocatorVersion :: Int
1814
iallocatorVersion = 2
1815

    
1816
iallocatorDirIn :: String
1817
iallocatorDirIn = Types.iAllocatorTestDirToRaw IAllocatorDirIn
1818

    
1819
iallocatorDirOut :: String
1820
iallocatorDirOut = Types.iAllocatorTestDirToRaw IAllocatorDirOut
1821

    
1822
validIallocatorDirections :: FrozenSet String
1823
validIallocatorDirections =
1824
  ConstantUtils.mkSet $ map Types.iAllocatorTestDirToRaw [minBound..]
1825

    
1826
iallocatorModeAlloc :: String
1827
iallocatorModeAlloc = Types.iAllocatorModeToRaw IAllocatorAlloc
1828

    
1829
iallocatorModeChgGroup :: String
1830
iallocatorModeChgGroup = Types.iAllocatorModeToRaw IAllocatorChangeGroup
1831

    
1832
iallocatorModeMultiAlloc :: String
1833
iallocatorModeMultiAlloc = Types.iAllocatorModeToRaw IAllocatorMultiAlloc
1834

    
1835
iallocatorModeNodeEvac :: String
1836
iallocatorModeNodeEvac = Types.iAllocatorModeToRaw IAllocatorNodeEvac
1837

    
1838
iallocatorModeReloc :: String
1839
iallocatorModeReloc = Types.iAllocatorModeToRaw IAllocatorReloc
1840

    
1841
validIallocatorModes :: FrozenSet String
1842
validIallocatorModes =
1843
  ConstantUtils.mkSet $ map Types.iAllocatorModeToRaw [minBound..]
1844

    
1845
iallocatorSearchPath :: [String]
1846
iallocatorSearchPath = AutoConf.iallocatorSearchPath
1847

    
1848
defaultIallocatorShortcut :: String
1849
defaultIallocatorShortcut = "."
1850

    
1851
-- * Node evacuation
1852

    
1853
nodeEvacPri :: String
1854
nodeEvacPri = Types.evacModeToRaw ChangePrimary
1855

    
1856
nodeEvacSec :: String
1857
nodeEvacSec = Types.evacModeToRaw ChangeSecondary
1858

    
1859
nodeEvacAll :: String
1860
nodeEvacAll = Types.evacModeToRaw ChangeAll
1861

    
1862
nodeEvacModes :: FrozenSet String
1863
nodeEvacModes = ConstantUtils.mkSet $ map Types.evacModeToRaw [minBound..]
1864

    
1865
-- * Job status
1866

    
1867
jobStatusQueued :: String
1868
jobStatusQueued = Types.jobStatusToRaw JOB_STATUS_QUEUED
1869

    
1870
jobStatusWaiting :: String
1871
jobStatusWaiting = Types.jobStatusToRaw JOB_STATUS_WAITING
1872

    
1873
jobStatusCanceling :: String
1874
jobStatusCanceling = Types.jobStatusToRaw JOB_STATUS_CANCELING
1875

    
1876
jobStatusRunning :: String
1877
jobStatusRunning = Types.jobStatusToRaw JOB_STATUS_RUNNING
1878

    
1879
jobStatusCanceled :: String
1880
jobStatusCanceled = Types.jobStatusToRaw JOB_STATUS_CANCELED
1881

    
1882
jobStatusSuccess :: String
1883
jobStatusSuccess = Types.jobStatusToRaw JOB_STATUS_SUCCESS
1884

    
1885
jobStatusError :: String
1886
jobStatusError = Types.jobStatusToRaw JOB_STATUS_ERROR
1887

    
1888
jobsPending :: FrozenSet String
1889
jobsPending =
1890
  ConstantUtils.mkSet [jobStatusQueued, jobStatusWaiting, jobStatusCanceling]
1891

    
1892
jobsFinalized :: FrozenSet String
1893
jobsFinalized =
1894
  ConstantUtils.mkSet $ map Types.finalizedJobStatusToRaw [minBound..]
1895

    
1896
jobStatusAll :: FrozenSet String
1897
jobStatusAll = ConstantUtils.mkSet $ map Types.jobStatusToRaw [minBound..]
1898

    
1899
-- * OpCode status
1900

    
1901
-- ** Not yet finalized opcodes
1902

    
1903
opStatusCanceling :: String
1904
opStatusCanceling = "canceling"
1905

    
1906
opStatusQueued :: String
1907
opStatusQueued = "queued"
1908

    
1909
opStatusRunning :: String
1910
opStatusRunning = "running"
1911

    
1912
opStatusWaiting :: String
1913
opStatusWaiting = "waiting"
1914

    
1915
-- ** Finalized opcodes
1916

    
1917
opStatusCanceled :: String
1918
opStatusCanceled = "canceled"
1919

    
1920
opStatusError :: String
1921
opStatusError = "error"
1922

    
1923
opStatusSuccess :: String
1924
opStatusSuccess = "success"
1925

    
1926
opsFinalized :: FrozenSet String
1927
opsFinalized =
1928
  ConstantUtils.mkSet [opStatusCanceled, opStatusError, opStatusSuccess]
1929

    
1930
-- * OpCode priority
1931

    
1932
opPrioLowest :: Int
1933
opPrioLowest = 19
1934

    
1935
opPrioHighest :: Int
1936
opPrioHighest = -20
1937

    
1938
opPrioLow :: Int
1939
opPrioLow = Types.opSubmitPriorityToRaw OpPrioLow
1940

    
1941
opPrioNormal :: Int
1942
opPrioNormal = Types.opSubmitPriorityToRaw OpPrioNormal
1943

    
1944
opPrioHigh :: Int
1945
opPrioHigh = Types.opSubmitPriorityToRaw OpPrioHigh
1946

    
1947
opPrioSubmitValid :: FrozenSet Int
1948
opPrioSubmitValid = ConstantUtils.mkSet [opPrioLow, opPrioNormal, opPrioHigh]
1949

    
1950
opPrioDefault :: Int
1951
opPrioDefault = opPrioNormal
1952

    
1953
-- * Execution log types
1954

    
1955
elogMessage :: String
1956
elogMessage = Types.eLogTypeToRaw ELogMessage
1957

    
1958
elogRemoteImport :: String
1959
elogRemoteImport = Types.eLogTypeToRaw ELogRemoteImport
1960

    
1961
elogJqueueTest :: String
1962
elogJqueueTest = Types.eLogTypeToRaw ELogJqueueTest
1963

    
1964
-- * Confd
1965

    
1966
confdProtocolVersion :: Int
1967
confdProtocolVersion = ConstantUtils.confdProtocolVersion
1968

    
1969
-- Confd request type
1970

    
1971
confdReqPing :: Int
1972
confdReqPing = Types.confdRequestTypeToRaw ReqPing
1973

    
1974
confdReqNodeRoleByname :: Int
1975
confdReqNodeRoleByname = Types.confdRequestTypeToRaw ReqNodeRoleByName
1976

    
1977
confdReqNodePipByInstanceIp :: Int
1978
confdReqNodePipByInstanceIp = Types.confdRequestTypeToRaw ReqNodePipByInstPip
1979

    
1980
confdReqClusterMaster :: Int
1981
confdReqClusterMaster = Types.confdRequestTypeToRaw ReqClusterMaster
1982

    
1983
confdReqNodePipList :: Int
1984
confdReqNodePipList = Types.confdRequestTypeToRaw ReqNodePipList
1985

    
1986
confdReqMcPipList :: Int
1987
confdReqMcPipList = Types.confdRequestTypeToRaw ReqMcPipList
1988

    
1989
confdReqInstancesIpsList :: Int
1990
confdReqInstancesIpsList = Types.confdRequestTypeToRaw ReqInstIpsList
1991

    
1992
confdReqNodeDrbd :: Int
1993
confdReqNodeDrbd = Types.confdRequestTypeToRaw ReqNodeDrbd
1994

    
1995
confdReqNodeInstances :: Int
1996
confdReqNodeInstances = Types.confdRequestTypeToRaw ReqNodeInstances
1997

    
1998
confdReqs :: FrozenSet Int
1999
confdReqs =
2000
  ConstantUtils.mkSet .
2001
  map Types.confdRequestTypeToRaw $
2002
  [minBound..] \\ [ReqNodeInstances]
2003

    
2004
-- * Confd request type
2005

    
2006
confdReqfieldName :: Int
2007
confdReqfieldName = Types.confdReqFieldToRaw ReqFieldName
2008

    
2009
confdReqfieldIp :: Int
2010
confdReqfieldIp = Types.confdReqFieldToRaw ReqFieldIp
2011

    
2012
confdReqfieldMnodePip :: Int
2013
confdReqfieldMnodePip = Types.confdReqFieldToRaw ReqFieldMNodePip
2014

    
2015
-- * Confd repl status
2016

    
2017
confdReplStatusOk :: Int
2018
confdReplStatusOk = Types.confdReplyStatusToRaw ReplyStatusOk
2019

    
2020
confdReplStatusError :: Int
2021
confdReplStatusError = Types.confdReplyStatusToRaw ReplyStatusError
2022

    
2023
confdReplStatusNotimplemented :: Int
2024
confdReplStatusNotimplemented = Types.confdReplyStatusToRaw ReplyStatusNotImpl
2025

    
2026
confdReplStatuses :: FrozenSet Int
2027
confdReplStatuses =
2028
  ConstantUtils.mkSet $ map Types.confdReplyStatusToRaw [minBound..]
2029

    
2030
-- * Confd node role
2031

    
2032
confdNodeRoleMaster :: Int
2033
confdNodeRoleMaster = Types.confdNodeRoleToRaw NodeRoleMaster
2034

    
2035
confdNodeRoleCandidate :: Int
2036
confdNodeRoleCandidate = Types.confdNodeRoleToRaw NodeRoleCandidate
2037

    
2038
confdNodeRoleOffline :: Int
2039
confdNodeRoleOffline = Types.confdNodeRoleToRaw NodeRoleOffline
2040

    
2041
confdNodeRoleDrained :: Int
2042
confdNodeRoleDrained = Types.confdNodeRoleToRaw NodeRoleDrained
2043

    
2044
confdNodeRoleRegular :: Int
2045
confdNodeRoleRegular = Types.confdNodeRoleToRaw NodeRoleRegular
2046

    
2047
-- * A few common errors for confd
2048

    
2049
confdErrorUnknownEntry :: Int
2050
confdErrorUnknownEntry = Types.confdErrorTypeToRaw ConfdErrorUnknownEntry
2051

    
2052
confdErrorInternal :: Int
2053
confdErrorInternal = Types.confdErrorTypeToRaw ConfdErrorInternal
2054

    
2055
confdErrorArgument :: Int
2056
confdErrorArgument = Types.confdErrorTypeToRaw ConfdErrorArgument
2057

    
2058
-- * Confd request query fields
2059

    
2060
confdReqqLink :: String
2061
confdReqqLink = ConstantUtils.confdReqqLink
2062

    
2063
confdReqqIp :: String
2064
confdReqqIp = ConstantUtils.confdReqqIp
2065

    
2066
confdReqqIplist :: String
2067
confdReqqIplist = ConstantUtils.confdReqqIplist
2068

    
2069
confdReqqFields :: String
2070
confdReqqFields = ConstantUtils.confdReqqFields
2071

    
2072
-- | Each request is "salted" by the current timestamp.
2073
--
2074
-- This constant decides how many seconds of skew to accept.
2075
--
2076
-- TODO: make this a default and allow the value to be more
2077
-- configurable
2078
confdMaxClockSkew :: Int
2079
confdMaxClockSkew = 2 * nodeMaxClockSkew
2080

    
2081
-- | When we haven't reloaded the config for more than this amount of
2082
-- seconds, we force a test to see if inotify is betraying us. Using a
2083
-- prime number to ensure we get less chance of 'same wakeup' with
2084
-- other processes.
2085
confdConfigReloadTimeout :: Int
2086
confdConfigReloadTimeout = 17
2087

    
2088
-- | If we receive more than one update in this amount of
2089
-- microseconds, we move to polling every RATELIMIT seconds, rather
2090
-- than relying on inotify, to be able to serve more requests.
2091
confdConfigReloadRatelimit :: Int
2092
confdConfigReloadRatelimit = 250000
2093

    
2094
-- | Magic number prepended to all confd queries.
2095
--
2096
-- This allows us to distinguish different types of confd protocols
2097
-- and handle them. For example by changing this we can move the whole
2098
-- payload to be compressed, or move away from json.
2099
confdMagicFourcc :: String
2100
confdMagicFourcc = "plj0"
2101

    
2102
-- | By default a confd request is sent to the minimum between this
2103
-- number and all MCs. 6 was chosen because even in the case of a
2104
-- disastrous 50% response rate, we should have enough answers to be
2105
-- able to compare more than one.
2106
confdDefaultReqCoverage :: Int
2107
confdDefaultReqCoverage = 6
2108

    
2109
-- | Timeout in seconds to expire pending query request in the confd
2110
-- client library. We don't actually expect any answer more than 10
2111
-- seconds after we sent a request.
2112
confdClientExpireTimeout :: Int
2113
confdClientExpireTimeout = 10
2114

    
2115
-- * Possible values for NodeGroup.alloc_policy
2116

    
2117
allocPolicyLastResort :: String
2118
allocPolicyLastResort = Types.allocPolicyToRaw AllocLastResort
2119

    
2120
allocPolicyPreferred :: String
2121
allocPolicyPreferred = Types.allocPolicyToRaw AllocPreferred
2122

    
2123
allocPolicyUnallocable :: String
2124
allocPolicyUnallocable = Types.allocPolicyToRaw AllocUnallocable
2125

    
2126
validAllocPolicies :: [String]
2127
validAllocPolicies = map Types.allocPolicyToRaw [minBound..]
2128

    
2129
-- | Temporary external/shared storage parameters
2130
blockdevDriverManual :: String
2131
blockdevDriverManual = Types.blockDriverToRaw BlockDrvManual
2132

    
2133
-- | 'qemu-img' path, required for 'ovfconverter'
2134
qemuimgPath :: String
2135
qemuimgPath = AutoConf.qemuimgPath
2136

    
2137
-- | Whether htools was enabled at compilation time
2138
--
2139
-- FIXME: this should be moved next to the other enable constants,
2140
-- such as, 'enableConfd', and renamed to 'enableHtools'.
2141
htools :: Bool
2142
htools = AutoConf.htools
2143

    
2144
-- * Key files for SSH daemon
2145

    
2146
sshHostDsaPriv :: String
2147
sshHostDsaPriv = sshConfigDir ++ "/ssh_host_dsa_key"
2148

    
2149
sshHostDsaPub :: String
2150
sshHostDsaPub = sshHostDsaPriv ++ ".pub"
2151

    
2152
sshHostRsaPriv :: String
2153
sshHostRsaPriv = sshConfigDir ++ "/ssh_host_rsa_key"
2154

    
2155
sshHostRsaPub :: String
2156
sshHostRsaPub = sshHostRsaPriv ++ ".pub"
2157

    
2158
-- | Path generating random UUID
2159
randomUuidFile :: String
2160
randomUuidFile = ConstantUtils.randomUuidFile
2161

    
2162
-- * Auto-repair tag prefixes
2163

    
2164
autoRepairTagPrefix :: String
2165
autoRepairTagPrefix = "ganeti:watcher:autorepair:"
2166

    
2167
autoRepairTagEnabled :: String
2168
autoRepairTagEnabled = autoRepairTagPrefix
2169

    
2170
autoRepairTagPending :: String
2171
autoRepairTagPending = autoRepairTagPrefix ++ "pending:"
2172

    
2173
autoRepairTagResult :: String
2174
autoRepairTagResult = autoRepairTagPrefix ++ "result:"
2175

    
2176
autoRepairTagSuspended :: String
2177
autoRepairTagSuspended = autoRepairTagPrefix ++ "suspend:"
2178

    
2179
-- * Auto-repair levels
2180

    
2181
autoRepairFailover :: String
2182
autoRepairFailover = "failover"
2183

    
2184
autoRepairFixStorage :: String
2185
autoRepairFixStorage = "fix-storage"
2186

    
2187
autoRepairMigrate :: String
2188
autoRepairMigrate = "migrate"
2189

    
2190
autoRepairReinstall :: String
2191
autoRepairReinstall = "reinstall"
2192

    
2193
autoRepairAllTypes :: FrozenSet String
2194
autoRepairAllTypes =
2195
  ConstantUtils.mkSet [autoRepairFailover,
2196
                       autoRepairFixStorage,
2197
                       autoRepairMigrate,
2198
                       autoRepairReinstall]
2199

    
2200
-- * Auto-repair results
2201

    
2202
autoRepairEnoperm :: String
2203
autoRepairEnoperm = "enoperm"
2204

    
2205
autoRepairFailure :: String
2206
autoRepairFailure = "failure"
2207

    
2208
autoRepairSuccess :: String
2209
autoRepairSuccess = "success"
2210

    
2211
autoRepairAllResults :: FrozenSet String
2212
autoRepairAllResults =
2213
  ConstantUtils.mkSet [autoRepairEnoperm, autoRepairFailure, autoRepairSuccess]
2214

    
2215
-- | The version identifier for builtin data collectors
2216
builtinDataCollectorVersion :: String
2217
builtinDataCollectorVersion = "B"
2218

    
2219
-- | The reason trail opcode parameter name
2220
opcodeReason :: String
2221
opcodeReason = "reason"
2222

    
2223
diskstatsFile :: String
2224
diskstatsFile = "/proc/diskstats"
2225

    
2226
-- *  CPU load collector
2227

    
2228
statFile :: String
2229
statFile = "/proc/stat"
2230

    
2231
cpuavgloadBufferSize :: Int
2232
cpuavgloadBufferSize = 150
2233

    
2234
cpuavgloadWindowSize :: Int
2235
cpuavgloadWindowSize = 600
2236

    
2237
-- | Mond's variable for periodical data collection
2238
mondTimeInterval :: Int
2239
mondTimeInterval = 5
2240

    
2241
-- * Disk access modes
2242

    
2243
diskUserspace :: String
2244
diskUserspace = Types.diskAccessModeToRaw DiskUserspace
2245

    
2246
diskKernelspace :: String
2247
diskKernelspace = Types.diskAccessModeToRaw DiskKernelspace
2248

    
2249
diskValidAccessModes :: FrozenSet String
2250
diskValidAccessModes =
2251
  ConstantUtils.mkSet $ map Types.diskAccessModeToRaw [minBound..]
2252

    
2253
-- | Timeout for queue draining in upgrades
2254
upgradeQueueDrainTimeout :: Int
2255
upgradeQueueDrainTimeout = 36 * 60 * 60 -- 1.5 days
2256

    
2257
-- | Intervall at which the queue is polled during upgrades
2258
upgradeQueuePollInterval :: Int
2259
upgradeQueuePollInterval  = 10