Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HsConstants.hs @ 0412a686

History | View | Annotate | Download (47.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 Data.List ((\\))
40
import Data.Map (Map)
41
import qualified Data.Map as Map (fromList, keys, insert)
42

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

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

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

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

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

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

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

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

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

    
81
-- ** Build-time constants
82

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
130
-- * Various versions
131

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

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

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

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

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

    
147
osApiV10 :: Int
148
osApiV10 = 10
149

    
150
osApiV15 :: Int
151
osApiV15 = 15
152

    
153
osApiV20 :: Int
154
osApiV20 = 20
155

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

    
159
exportVersion :: Int
160
exportVersion = 0
161

    
162
rapiVersion :: Int
163
rapiVersion = 2
164

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

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

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

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

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

    
184
-- * User separation
185

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
234
-- * Cpu pinning separators and constants
235

    
236
cpuPinningSep :: String
237
cpuPinningSep = ":"
238

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

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

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

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

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

    
274
-- * Wipe
275

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

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

    
283
minWipeChunkPercent :: Int
284
minWipeChunkPercent = 10
285

    
286
-- * Directories
287

    
288
runDirsMode :: Int
289
runDirsMode = 0o775
290

    
291
secureDirMode :: Int
292
secureDirMode = 0o700
293

    
294
secureFileMode :: Int
295
secureFileMode = 0o600
296

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

    
300
-- * 'autoconf' enable/disable
301

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

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

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

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

    
314
-- * SSH constants
315

    
316
ssh :: String
317
ssh = "ssh"
318

    
319
scp :: String
320
scp = "scp"
321

    
322
-- * Daemons
323

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

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

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

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

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

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

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

    
351
defaultConfdPort :: Int
352
defaultConfdPort = 1814
353

    
354
defaultMondPort :: Int
355
defaultMondPort = 1815
356

    
357
defaultNodedPort :: Int
358
defaultNodedPort = 1811
359

    
360
defaultRapiPort :: Int
361
defaultRapiPort = 5080
362

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

    
371
firstDrbdPort :: Int
372
firstDrbdPort = 11000
373

    
374
lastDrbdPort :: Int
375
lastDrbdPort = 14999
376

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

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

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

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

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

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

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

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

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

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

    
409
luxiVersion :: Int
410
luxiVersion = configVersion
411

    
412
-- * Syslog
413

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

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

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

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

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

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

    
432
-- * Xen
433

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

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

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

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

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

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

    
454
-- * KVM and socat
455

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

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

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

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

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

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

    
474
-- * Storage types
475

    
476
stBlock :: String
477
stBlock = Types.storageTypeToRaw StorageBlock
478

    
479
stDiskless :: String
480
stDiskless = Types.storageTypeToRaw StorageDiskless
481

    
482
stExt :: String
483
stExt = Types.storageTypeToRaw StorageExt
484

    
485
stFile :: String
486
stFile = Types.storageTypeToRaw StorageFile
487

    
488
stLvmPv :: String
489
stLvmPv = Types.storageTypeToRaw StorageLvmPv
490

    
491
stLvmVg :: String
492
stLvmVg = Types.storageTypeToRaw StorageLvmVg
493

    
494
stRados :: String
495
stRados = Types.storageTypeToRaw StorageRados
496

    
497
storageTypes :: FrozenSet String
498
storageTypes = ConstantUtils.mkSet $ map Types.storageTypeToRaw [minBound..]
499

    
500
-- * Storage fields
501
-- ** First two are valid in LU context only, not passed to backend
502

    
503
sfNode :: String
504
sfNode = "node"
505

    
506
sfType :: String
507
sfType = "type"
508

    
509
-- ** and the rest are valid in backend
510

    
511
sfAllocatable :: String
512
sfAllocatable = Types.storageFieldToRaw SFAllocatable
513

    
514
sfFree :: String
515
sfFree = Types.storageFieldToRaw SFFree
516

    
517
sfName :: String
518
sfName = Types.storageFieldToRaw SFName
519

    
520
sfSize :: String
521
sfSize = Types.storageFieldToRaw SFSize
522

    
523
sfUsed :: String
524
sfUsed = Types.storageFieldToRaw SFUsed
525

    
526
-- * Local disk status
527

    
528
ldsFaulty :: Int
529
ldsFaulty = Types.localDiskStatusToRaw DiskStatusFaulty
530

    
531
ldsOkay :: Int
532
ldsOkay = Types.localDiskStatusToRaw DiskStatusOk
533

    
534
ldsUnknown :: Int
535
ldsUnknown = Types.localDiskStatusToRaw DiskStatusUnknown
536

    
537
ldsNames :: Map Int String
538
ldsNames =
539
  Map.fromList [ (Types.localDiskStatusToRaw ds,
540
                  localDiskStatusName ds) | ds <- [minBound..] ]
541

    
542
-- * Disk template types
543

    
544
dtDiskless :: String
545
dtDiskless = Types.diskTemplateToRaw DTDiskless
546

    
547
dtFile :: String
548
dtFile = Types.diskTemplateToRaw DTFile
549

    
550
dtSharedFile :: String
551
dtSharedFile = Types.diskTemplateToRaw DTSharedFile
552

    
553
dtPlain :: String
554
dtPlain = Types.diskTemplateToRaw DTPlain
555

    
556
dtBlock :: String
557
dtBlock = Types.diskTemplateToRaw DTBlock
558

    
559
dtDrbd8 :: String
560
dtDrbd8 = Types.diskTemplateToRaw DTDrbd8
561

    
562
dtRbd :: String
563
dtRbd = Types.diskTemplateToRaw DTRbd
564

    
565
dtExt :: String
566
dtExt = Types.diskTemplateToRaw DTExt
567

    
568
-- | This is used to order determine the default disk template when
569
-- the list of enabled disk templates is inferred from the current
570
-- state of the cluster.  This only happens on an upgrade from a
571
-- version of Ganeti that did not support the 'enabled_disk_templates'
572
-- so far.
573
diskTemplatePreference :: [String]
574
diskTemplatePreference =
575
  map Types.diskTemplateToRaw
576
  [DTBlock, DTDiskless, DTDrbd8, DTExt, DTFile, DTPlain, DTRbd, DTSharedFile]
577

    
578
diskTemplates :: FrozenSet String
579
diskTemplates = ConstantUtils.mkSet $ map Types.diskTemplateToRaw [minBound..]
580

    
581
-- | Disk templates that are enabled by default
582
defaultEnabledDiskTemplates :: [String]
583
defaultEnabledDiskTemplates = map Types.diskTemplateToRaw [DTDrbd8, DTPlain]
584

    
585
-- | The set of network-mirrored disk templates
586
dtsIntMirror :: FrozenSet String
587
dtsIntMirror = ConstantUtils.mkSet [dtDrbd8]
588

    
589
-- | 'DTDiskless' is 'trivially' externally mirrored
590
dtsExtMirror :: FrozenSet String
591
dtsExtMirror =
592
  ConstantUtils.mkSet $
593
  map Types.diskTemplateToRaw [DTDiskless, DTBlock, DTExt, DTSharedFile, DTRbd]
594

    
595
-- | The set of non-lvm-based disk templates
596
dtsNotLvm :: FrozenSet String
597
dtsNotLvm =
598
  ConstantUtils.mkSet $
599
  map Types.diskTemplateToRaw
600
  [DTSharedFile, DTDiskless, DTBlock, DTExt, DTFile, DTRbd]
601

    
602
-- | The set of disk templates which can be grown
603
dtsGrowable :: FrozenSet String
604
dtsGrowable =
605
  ConstantUtils.mkSet $
606
  map Types.diskTemplateToRaw
607
  [DTSharedFile, DTDrbd8, DTPlain, DTExt, DTFile, DTRbd]
608

    
609
-- | The set of disk templates that allow adoption
610
dtsMayAdopt :: FrozenSet String
611
dtsMayAdopt =
612
  ConstantUtils.mkSet $ map Types.diskTemplateToRaw [DTBlock, DTPlain]
613

    
614
-- | The set of disk templates that *must* use adoption
615
dtsMustAdopt :: FrozenSet String
616
dtsMustAdopt = ConstantUtils.mkSet [Types.diskTemplateToRaw DTBlock]
617

    
618
-- | The set of disk templates that allow migrations
619
dtsMirrored :: FrozenSet String
620
dtsMirrored = dtsIntMirror `ConstantUtils.union` dtsExtMirror
621

    
622
-- | The set of file based disk templates
623
dtsFilebased :: FrozenSet String
624
dtsFilebased =
625
  ConstantUtils.mkSet $ map Types.diskTemplateToRaw [DTSharedFile, DTFile]
626

    
627
-- | The set of disk templates that can be moved by copying
628
--
629
-- Note: a requirement is that they're not accessed externally or
630
-- shared between nodes; in particular, sharedfile is not suitable.
631
dtsCopyable :: FrozenSet String
632
dtsCopyable =
633
  ConstantUtils.mkSet $ map Types.diskTemplateToRaw [DTPlain, DTFile]
634

    
635
-- | The set of disk templates that are supported by exclusive_storage
636
dtsExclStorage :: FrozenSet String
637
dtsExclStorage = ConstantUtils.mkSet $ map Types.diskTemplateToRaw [DTPlain]
638

    
639
-- | Templates for which we don't perform checks on free space
640
dtsNoFreeSpaceCheck :: FrozenSet String
641
dtsNoFreeSpaceCheck =
642
  ConstantUtils.mkSet $
643
  map Types.diskTemplateToRaw [DTExt, DTSharedFile, DTFile, DTRbd]
644

    
645
dtsBlock :: FrozenSet String
646
dtsBlock =
647
  ConstantUtils.mkSet $
648
  map Types.diskTemplateToRaw [DTPlain, DTDrbd8, DTBlock, DTRbd, DTExt]
649

    
650
-- * File backend driver
651

    
652
fdBlktap :: String
653
fdBlktap = Types.fileDriverToRaw FileBlktap
654

    
655
fdLoop :: String
656
fdLoop = Types.fileDriverToRaw FileLoop
657

    
658
fileDriver :: FrozenSet String
659
fileDriver =
660
  ConstantUtils.mkSet $
661
  map Types.fileDriverToRaw [minBound..]
662

    
663
-- | The set of drbd-like disk types
664
ldsDrbd :: FrozenSet String
665
ldsDrbd = ConstantUtils.mkSet [Types.diskTemplateToRaw DTDrbd8]
666

    
667
-- * Disk access mode
668

    
669
diskRdonly :: String
670
diskRdonly = Types.diskModeToRaw DiskRdOnly
671

    
672
diskRdwr :: String
673
diskRdwr = Types.diskModeToRaw DiskRdWr
674

    
675
diskAccessSet :: FrozenSet String
676
diskAccessSet = ConstantUtils.mkSet $ map Types.diskModeToRaw [minBound..]
677

    
678
-- * Disk replacement mode
679

    
680
replaceDiskAuto :: String
681
replaceDiskAuto = Types.replaceDisksModeToRaw ReplaceAuto
682

    
683
replaceDiskChg :: String
684
replaceDiskChg = Types.replaceDisksModeToRaw ReplaceNewSecondary
685

    
686
replaceDiskPri :: String
687
replaceDiskPri = Types.replaceDisksModeToRaw ReplaceOnPrimary
688

    
689
replaceDiskSec :: String
690
replaceDiskSec = Types.replaceDisksModeToRaw ReplaceOnSecondary
691

    
692
replaceModes :: FrozenSet String
693
replaceModes =
694
  ConstantUtils.mkSet $ map Types.replaceDisksModeToRaw [minBound..]
695

    
696
-- * Instance export mode
697

    
698
exportModeLocal :: String
699
exportModeLocal = Types.exportModeToRaw ExportModeLocal
700

    
701
exportModeRemote :: String
702
exportModeRemote = Types.exportModeToRaw ExportModeRemote
703

    
704
exportModes :: FrozenSet String
705
exportModes = ConstantUtils.mkSet $ map Types.exportModeToRaw [minBound..]
706

    
707
-- * Instance creation modes
708

    
709
instanceCreate :: String
710
instanceCreate = Types.instCreateModeToRaw InstCreate
711

    
712
instanceImport :: String
713
instanceImport = Types.instCreateModeToRaw InstImport
714

    
715
instanceRemoteImport :: String
716
instanceRemoteImport = Types.instCreateModeToRaw InstRemoteImport
717

    
718
instanceCreateModes :: FrozenSet String
719
instanceCreateModes =
720
  ConstantUtils.mkSet $ map Types.instCreateModeToRaw [minBound..]
721

    
722
-- * Dynamic device modification
723

    
724
ddmAdd :: String
725
ddmAdd = Types.ddmFullToRaw DdmFullAdd
726

    
727
ddmModify :: String
728
ddmModify = Types.ddmFullToRaw DdmFullModify
729

    
730
ddmRemove :: String
731
ddmRemove = Types.ddmFullToRaw DdmFullRemove
732

    
733
ddmsValues :: FrozenSet String
734
ddmsValues = ConstantUtils.mkSet [ddmAdd, ddmRemove]
735

    
736
ddmsValuesWithModify :: FrozenSet String
737
ddmsValuesWithModify = ConstantUtils.mkSet $ map Types.ddmFullToRaw [minBound..]
738

    
739
-- * Common exit codes
740

    
741
exitSuccess :: Int
742
exitSuccess = 0
743

    
744
exitFailure :: Int
745
exitFailure = ConstantUtils.exitFailure
746

    
747
exitNotcluster :: Int
748
exitNotcluster = 5
749

    
750
exitNotmaster :: Int
751
exitNotmaster = 11
752

    
753
exitNodesetupError :: Int
754
exitNodesetupError = 12
755

    
756
-- | Need user confirmation
757
exitConfirmation :: Int
758
exitConfirmation = 13
759

    
760
-- | Exit code for query operations with unknown fields
761
exitUnknownField :: Int
762
exitUnknownField = 14
763

    
764
-- * Tags
765

    
766
tagCluster :: String
767
tagCluster = Types.tagKindToRaw TagKindCluster
768

    
769
tagInstance :: String
770
tagInstance = Types.tagKindToRaw TagKindInstance
771

    
772
tagNetwork :: String
773
tagNetwork = Types.tagKindToRaw TagKindNetwork
774

    
775
tagNode :: String
776
tagNode = Types.tagKindToRaw TagKindNode
777

    
778
tagNodegroup :: String
779
tagNodegroup = Types.tagKindToRaw TagKindGroup
780

    
781
validTagTypes :: FrozenSet String
782
validTagTypes = ConstantUtils.mkSet $ map Types.tagKindToRaw [minBound..]
783

    
784
maxTagLen :: Int
785
maxTagLen = 128
786

    
787
maxTagsPerObj :: Int
788
maxTagsPerObj = 4096
789

    
790
-- | Node clock skew in seconds
791
nodeMaxClockSkew :: Int
792
nodeMaxClockSkew = 150
793

    
794
-- | Disk index separator
795
diskSeparator :: String
796
diskSeparator = AutoConf.diskSeparator
797

    
798
-- * Timeout table
799
--
800
-- Various time constants for the timeout table
801

    
802
rpcTmoUrgent :: Int
803
rpcTmoUrgent = Types.rpcTimeoutToRaw Urgent
804

    
805
rpcTmoFast :: Int
806
rpcTmoFast = Types.rpcTimeoutToRaw Fast
807

    
808
rpcTmoNormal :: Int
809
rpcTmoNormal = Types.rpcTimeoutToRaw Normal
810

    
811
rpcTmoSlow :: Int
812
rpcTmoSlow = Types.rpcTimeoutToRaw Slow
813

    
814
-- | 'rpcTmo_4hrs' contains an underscore to circumvent a limitation
815
-- in the 'Ganeti.THH.deCamelCase' function and generate the correct
816
-- Python name.
817
rpcTmo_4hrs :: Int
818
rpcTmo_4hrs = Types.rpcTimeoutToRaw FourHours
819

    
820
-- | 'rpcTmo_1day' contains an underscore to circumvent a limitation
821
-- in the 'Ganeti.THH.deCamelCase' function and generate the correct
822
-- Python name.
823
rpcTmo_1day :: Int
824
rpcTmo_1day = Types.rpcTimeoutToRaw OneDay
825

    
826
-- | Timeout for connecting to nodes (seconds)
827
rpcConnectTimeout :: Int
828
rpcConnectTimeout = 5
829

    
830
-- * VTypes
831

    
832
vtypeBool :: VType
833
vtypeBool = VTypeBool
834

    
835
vtypeInt :: VType
836
vtypeInt = VTypeInt
837

    
838
vtypeMaybeString :: VType
839
vtypeMaybeString = VTypeMaybeString
840

    
841
-- | Size in MiBs
842
vtypeSize :: VType
843
vtypeSize = VTypeSize
844

    
845
vtypeString :: VType
846
vtypeString = VTypeString
847

    
848
enforceableTypes :: FrozenSet VType
849
enforceableTypes = ConstantUtils.mkSet [minBound..]
850

    
851
-- | Instance specs
852
--
853
-- FIXME: these should be associated with 'Ganeti.HTools.Types.ISpec'
854

    
855
ispecMemSize :: String
856
ispecMemSize = ConstantUtils.ispecMemSize
857

    
858
ispecCpuCount :: String
859
ispecCpuCount = ConstantUtils.ispecCpuCount
860

    
861
ispecDiskCount :: String
862
ispecDiskCount = ConstantUtils.ispecDiskCount
863

    
864
ispecDiskSize :: String
865
ispecDiskSize = ConstantUtils.ispecDiskSize
866

    
867
ispecNicCount :: String
868
ispecNicCount = ConstantUtils.ispecNicCount
869

    
870
ispecSpindleUse :: String
871
ispecSpindleUse = ConstantUtils.ispecSpindleUse
872

    
873
ispecsParameterTypes :: Map String VType
874
ispecsParameterTypes =
875
  Map.fromList
876
  [(ConstantUtils.ispecDiskSize, VTypeInt),
877
   (ConstantUtils.ispecCpuCount, VTypeInt),
878
   (ConstantUtils.ispecSpindleUse, VTypeInt),
879
   (ConstantUtils.ispecMemSize, VTypeInt),
880
   (ConstantUtils.ispecNicCount, VTypeInt),
881
   (ConstantUtils.ispecDiskCount, VTypeInt)]
882

    
883
ispecsParameters :: FrozenSet String
884
ispecsParameters =
885
  ConstantUtils.mkSet [ConstantUtils.ispecCpuCount,
886
                       ConstantUtils.ispecDiskCount,
887
                       ConstantUtils.ispecDiskSize,
888
                       ConstantUtils.ispecMemSize,
889
                       ConstantUtils.ispecNicCount,
890
                       ConstantUtils.ispecSpindleUse]
891

    
892
ispecsMinmax :: String
893
ispecsMinmax = ConstantUtils.ispecsMinmax
894

    
895
ispecsMax :: String
896
ispecsMax = "max"
897

    
898
ispecsMin :: String
899
ispecsMin = "min"
900

    
901
ispecsStd :: String
902
ispecsStd = ConstantUtils.ispecsStd
903

    
904
ipolicyDts :: String
905
ipolicyDts = ConstantUtils.ipolicyDts
906

    
907
ipolicyVcpuRatio :: String
908
ipolicyVcpuRatio = ConstantUtils.ipolicyVcpuRatio
909

    
910
ipolicySpindleRatio :: String
911
ipolicySpindleRatio = ConstantUtils.ipolicySpindleRatio
912

    
913
ispecsMinmaxKeys :: FrozenSet String
914
ispecsMinmaxKeys = ConstantUtils.mkSet [ispecsMax, ispecsMin]
915

    
916
ipolicyParameters :: FrozenSet String
917
ipolicyParameters =
918
  ConstantUtils.mkSet [ConstantUtils.ipolicyVcpuRatio,
919
                       ConstantUtils.ipolicySpindleRatio]
920

    
921
ipolicyAllKeys :: FrozenSet String
922
ipolicyAllKeys =
923
  ConstantUtils.union ipolicyParameters $
924
  ConstantUtils.mkSet [ConstantUtils.ipolicyDts,
925
                       ConstantUtils.ispecsMinmax,
926
                       ispecsStd]
927

    
928
-- | Node parameter names
929

    
930
ndExclusiveStorage :: String
931
ndExclusiveStorage = "exclusive_storage"
932

    
933
ndOobProgram :: String
934
ndOobProgram = "oob_program"
935

    
936
ndSpindleCount :: String
937
ndSpindleCount = "spindle_count"
938

    
939
ndOvs :: String
940
ndOvs = "ovs"
941

    
942
ndOvsLink :: String
943
ndOvsLink = "ovs_link"
944

    
945
ndOvsName :: String
946
ndOvsName = "ovs_name"
947

    
948
ndsParameterTypes :: Map String VType
949
ndsParameterTypes =
950
  Map.fromList
951
  [(ndExclusiveStorage, VTypeBool),
952
   (ndOobProgram, VTypeString),
953
   (ndOvs, VTypeBool),
954
   (ndOvsLink, VTypeMaybeString),
955
   (ndOvsName, VTypeMaybeString),
956
   (ndSpindleCount, VTypeInt)]
957

    
958
ndsParameters :: FrozenSet String
959
ndsParameters = ConstantUtils.mkSet (Map.keys ndsParameterTypes)
960

    
961
ndsParameterTitles :: Map String String
962
ndsParameterTitles =
963
  Map.fromList
964
  [(ndExclusiveStorage, "ExclusiveStorage"),
965
   (ndOobProgram, "OutOfBandProgram"),
966
   (ndOvs, "OpenvSwitch"),
967
   (ndOvsLink, "OpenvSwitchLink"),
968
   (ndOvsName, "OpenvSwitchName"),
969
   (ndSpindleCount, "SpindleCount")]
970

    
971
ipCommandPath :: String
972
ipCommandPath = AutoConf.ipPath
973

    
974
-- * Reboot types
975

    
976
instanceRebootSoft :: String
977
instanceRebootSoft = Types.rebootTypeToRaw RebootSoft
978

    
979
instanceRebootHard :: String
980
instanceRebootHard = Types.rebootTypeToRaw RebootHard
981

    
982
instanceRebootFull :: String
983
instanceRebootFull = Types.rebootTypeToRaw RebootFull
984

    
985
rebootTypes :: FrozenSet String
986
rebootTypes = ConstantUtils.mkSet $ map Types.rebootTypeToRaw [minBound..]
987

    
988

    
989

    
990

    
991

    
992

    
993

    
994

    
995
-- * OOB supported commands
996

    
997
oobPowerOn :: String
998
oobPowerOn = Types.oobCommandToRaw OobPowerOn
999

    
1000
oobPowerOff :: String
1001
oobPowerOff = Types.oobCommandToRaw OobPowerOff
1002

    
1003
oobPowerCycle :: String
1004
oobPowerCycle = Types.oobCommandToRaw OobPowerCycle
1005

    
1006
oobPowerStatus :: String
1007
oobPowerStatus = Types.oobCommandToRaw OobPowerStatus
1008

    
1009
oobHealth :: String
1010
oobHealth = Types.oobCommandToRaw OobHealth
1011

    
1012
oobCommands :: FrozenSet String
1013
oobCommands = ConstantUtils.mkSet $ map Types.oobCommandToRaw [minBound..]
1014

    
1015
oobPowerStatusPowered :: String
1016
oobPowerStatusPowered = "powered"
1017

    
1018
-- | 60 seconds
1019
oobTimeout :: Int
1020
oobTimeout = 60
1021

    
1022
-- | 2 seconds
1023
oobPowerDelay :: Double
1024
oobPowerDelay = 2.0
1025

    
1026
oobStatusCritical :: String
1027
oobStatusCritical = Types.oobStatusToRaw OobStatusCritical
1028

    
1029
oobStatusOk :: String
1030
oobStatusOk = Types.oobStatusToRaw OobStatusOk
1031

    
1032
oobStatusUnknown :: String
1033
oobStatusUnknown = Types.oobStatusToRaw OobStatusUnknown
1034

    
1035
oobStatusWarning :: String
1036
oobStatusWarning = Types.oobStatusToRaw OobStatusWarning
1037

    
1038
oobStatuses :: FrozenSet String
1039
oobStatuses = ConstantUtils.mkSet $ map Types.oobStatusToRaw [minBound..]
1040

    
1041
-- * NIC_* constants are used inside the ganeti config
1042

    
1043
nicLink :: String
1044
nicLink = "link"
1045

    
1046
nicMode :: String
1047
nicMode = "mode"
1048

    
1049
nicVlan :: String
1050
nicVlan = "vlan"
1051

    
1052
nicModeBridged :: String
1053
nicModeBridged = Types.nICModeToRaw NMBridged
1054

    
1055
nicModeRouted :: String
1056
nicModeRouted = Types.nICModeToRaw NMRouted
1057

    
1058
nicModeOvs :: String
1059
nicModeOvs = Types.nICModeToRaw NMOvs
1060

    
1061
nicIpPool :: String
1062
nicIpPool = Types.nICModeToRaw NMPool
1063

    
1064
nicValidModes :: FrozenSet String
1065
nicValidModes = ConstantUtils.mkSet $ map Types.nICModeToRaw [minBound..]
1066

    
1067
-- * Hypervisor constants
1068

    
1069
htXenPvm :: String
1070
htXenPvm = Types.hypervisorToRaw XenPvm
1071

    
1072
htFake :: String
1073
htFake = Types.hypervisorToRaw Fake
1074

    
1075
htXenHvm :: String
1076
htXenHvm = Types.hypervisorToRaw XenHvm
1077

    
1078
htKvm :: String
1079
htKvm = Types.hypervisorToRaw Kvm
1080

    
1081
htChroot :: String
1082
htChroot = Types.hypervisorToRaw Chroot
1083

    
1084
htLxc :: String
1085
htLxc = Types.hypervisorToRaw Lxc
1086

    
1087
hyperTypes :: FrozenSet String
1088
hyperTypes = ConstantUtils.mkSet $ map Types.hypervisorToRaw [minBound..]
1089

    
1090
htsReqPort :: FrozenSet String
1091
htsReqPort = ConstantUtils.mkSet [htXenHvm, htKvm]
1092

    
1093
-- * Migration type
1094

    
1095
htMigrationLive :: String
1096
htMigrationLive = Types.migrationModeToRaw MigrationLive
1097

    
1098
htMigrationNonlive :: String
1099
htMigrationNonlive = Types.migrationModeToRaw MigrationNonLive
1100

    
1101
htMigrationModes :: FrozenSet String
1102
htMigrationModes =
1103
  ConstantUtils.mkSet $ map Types.migrationModeToRaw [minBound..]
1104

    
1105
-- * Cluster verify steps
1106

    
1107
verifyNplusoneMem :: String
1108
verifyNplusoneMem = Types.verifyOptionalChecksToRaw VerifyNPlusOneMem
1109

    
1110
verifyOptionalChecks :: FrozenSet String
1111
verifyOptionalChecks =
1112
  ConstantUtils.mkSet $ map Types.verifyOptionalChecksToRaw [minBound..]
1113

    
1114
-- * Cluster Verify error classes
1115

    
1116
cvTcluster :: String
1117
cvTcluster = "cluster"
1118

    
1119
cvTgroup :: String
1120
cvTgroup = "group"
1121

    
1122
cvTnode :: String
1123
cvTnode = "node"
1124

    
1125
cvTinstance :: String
1126
cvTinstance = "instance"
1127

    
1128
-- * Cluster Verify error codes and documentation
1129

    
1130
cvEclustercert :: (String, String, String)
1131
cvEclustercert =
1132
  ("cluster",
1133
   Types.cVErrorCodeToRaw CvECLUSTERCERT,
1134
   "Cluster certificate files verification failure")
1135

    
1136
cvEclustercfg :: (String, String, String)
1137
cvEclustercfg =
1138
  ("cluster",
1139
   Types.cVErrorCodeToRaw CvECLUSTERCFG,
1140
   "Cluster configuration verification failure")
1141

    
1142
cvEclusterdanglinginst :: (String, String, String)
1143
cvEclusterdanglinginst =
1144
  ("node",
1145
   Types.cVErrorCodeToRaw CvECLUSTERDANGLINGINST,
1146
   "Some instances have a non-existing primary node")
1147

    
1148
cvEclusterdanglingnodes :: (String, String, String)
1149
cvEclusterdanglingnodes =
1150
  ("node",
1151
   Types.cVErrorCodeToRaw CvECLUSTERDANGLINGNODES,
1152
   "Some nodes belong to non-existing groups")
1153

    
1154
cvEclusterfilecheck :: (String, String, String)
1155
cvEclusterfilecheck =
1156
  ("cluster",
1157
   Types.cVErrorCodeToRaw CvECLUSTERFILECHECK,
1158
   "Cluster configuration verification failure")
1159

    
1160
cvEgroupdifferentpvsize :: (String, String, String)
1161
cvEgroupdifferentpvsize =
1162
  ("group",
1163
   Types.cVErrorCodeToRaw CvEGROUPDIFFERENTPVSIZE,
1164
   "PVs in the group have different sizes")
1165

    
1166
cvEinstancebadnode :: (String, String, String)
1167
cvEinstancebadnode =
1168
  ("instance",
1169
   Types.cVErrorCodeToRaw CvEINSTANCEBADNODE,
1170
   "Instance marked as running lives on an offline node")
1171

    
1172
cvEinstancedown :: (String, String, String)
1173
cvEinstancedown =
1174
  ("instance",
1175
   Types.cVErrorCodeToRaw CvEINSTANCEDOWN,
1176
   "Instance not running on its primary node")
1177

    
1178
cvEinstancefaultydisk :: (String, String, String)
1179
cvEinstancefaultydisk =
1180
  ("instance",
1181
   Types.cVErrorCodeToRaw CvEINSTANCEFAULTYDISK,
1182
   "Impossible to retrieve status for a disk")
1183

    
1184
cvEinstancelayout :: (String, String, String)
1185
cvEinstancelayout =
1186
  ("instance",
1187
   Types.cVErrorCodeToRaw CvEINSTANCELAYOUT,
1188
   "Instance has multiple secondary nodes")
1189

    
1190
cvEinstancemissingcfgparameter :: (String, String, String)
1191
cvEinstancemissingcfgparameter =
1192
  ("instance",
1193
   Types.cVErrorCodeToRaw CvEINSTANCEMISSINGCFGPARAMETER,
1194
   "A configuration parameter for an instance is missing")
1195

    
1196
cvEinstancemissingdisk :: (String, String, String)
1197
cvEinstancemissingdisk =
1198
  ("instance",
1199
   Types.cVErrorCodeToRaw CvEINSTANCEMISSINGDISK,
1200
   "Missing volume on an instance")
1201

    
1202
cvEinstancepolicy :: (String, String, String)
1203
cvEinstancepolicy =
1204
  ("instance",
1205
   Types.cVErrorCodeToRaw CvEINSTANCEPOLICY,
1206
   "Instance does not meet policy")
1207

    
1208
cvEinstancesplitgroups :: (String, String, String)
1209
cvEinstancesplitgroups =
1210
  ("instance",
1211
   Types.cVErrorCodeToRaw CvEINSTANCESPLITGROUPS,
1212
   "Instance with primary and secondary nodes in different groups")
1213

    
1214
cvEinstanceunsuitablenode :: (String, String, String)
1215
cvEinstanceunsuitablenode =
1216
  ("instance",
1217
   Types.cVErrorCodeToRaw CvEINSTANCEUNSUITABLENODE,
1218
   "Instance running on nodes that are not suitable for it")
1219

    
1220
cvEinstancewrongnode :: (String, String, String)
1221
cvEinstancewrongnode =
1222
  ("instance",
1223
   Types.cVErrorCodeToRaw CvEINSTANCEWRONGNODE,
1224
   "Instance running on the wrong node")
1225

    
1226
cvEnodedrbd :: (String, String, String)
1227
cvEnodedrbd =
1228
  ("node",
1229
   Types.cVErrorCodeToRaw CvENODEDRBD,
1230
   "Error parsing the DRBD status file")
1231

    
1232
cvEnodedrbdhelper :: (String, String, String)
1233
cvEnodedrbdhelper =
1234
  ("node",
1235
   Types.cVErrorCodeToRaw CvENODEDRBDHELPER,
1236
   "Error caused by the DRBD helper")
1237

    
1238
cvEnodedrbdversion :: (String, String, String)
1239
cvEnodedrbdversion =
1240
  ("node",
1241
   Types.cVErrorCodeToRaw CvENODEDRBDVERSION,
1242
   "DRBD version mismatch within a node group")
1243

    
1244
cvEnodefilecheck :: (String, String, String)
1245
cvEnodefilecheck =
1246
  ("node",
1247
   Types.cVErrorCodeToRaw CvENODEFILECHECK,
1248
   "Error retrieving the checksum of the node files")
1249

    
1250
cvEnodefilestoragepaths :: (String, String, String)
1251
cvEnodefilestoragepaths =
1252
  ("node",
1253
   Types.cVErrorCodeToRaw CvENODEFILESTORAGEPATHS,
1254
   "Detected bad file storage paths")
1255

    
1256
cvEnodefilestoragepathunusable :: (String, String, String)
1257
cvEnodefilestoragepathunusable =
1258
  ("node",
1259
   Types.cVErrorCodeToRaw CvENODEFILESTORAGEPATHUNUSABLE,
1260
   "File storage path unusable")
1261

    
1262
cvEnodehooks :: (String, String, String)
1263
cvEnodehooks =
1264
  ("node",
1265
   Types.cVErrorCodeToRaw CvENODEHOOKS,
1266
   "Communication failure in hooks execution")
1267

    
1268
cvEnodehv :: (String, String, String)
1269
cvEnodehv =
1270
  ("node",
1271
   Types.cVErrorCodeToRaw CvENODEHV,
1272
   "Hypervisor parameters verification failure")
1273

    
1274
cvEnodelvm :: (String, String, String)
1275
cvEnodelvm =
1276
  ("node",
1277
   Types.cVErrorCodeToRaw CvENODELVM,
1278
   "LVM-related node error")
1279

    
1280
cvEnoden1 :: (String, String, String)
1281
cvEnoden1 =
1282
  ("node",
1283
   Types.cVErrorCodeToRaw CvENODEN1,
1284
   "Not enough memory to accommodate instance failovers")
1285

    
1286
cvEnodenet :: (String, String, String)
1287
cvEnodenet =
1288
  ("node",
1289
   Types.cVErrorCodeToRaw CvENODENET,
1290
   "Network-related node error")
1291

    
1292
cvEnodeoobpath :: (String, String, String)
1293
cvEnodeoobpath =
1294
  ("node",
1295
   Types.cVErrorCodeToRaw CvENODEOOBPATH,
1296
   "Invalid Out Of Band path")
1297

    
1298
cvEnodeorphaninstance :: (String, String, String)
1299
cvEnodeorphaninstance =
1300
  ("node",
1301
   Types.cVErrorCodeToRaw CvENODEORPHANINSTANCE,
1302
   "Unknown intance running on a node")
1303

    
1304
cvEnodeorphanlv :: (String, String, String)
1305
cvEnodeorphanlv =
1306
  ("node",
1307
   Types.cVErrorCodeToRaw CvENODEORPHANLV,
1308
   "Unknown LVM logical volume")
1309

    
1310
cvEnodeos :: (String, String, String)
1311
cvEnodeos =
1312
  ("node",
1313
   Types.cVErrorCodeToRaw CvENODEOS,
1314
   "OS-related node error")
1315

    
1316
cvEnoderpc :: (String, String, String)
1317
cvEnoderpc =
1318
  ("node",
1319
   Types.cVErrorCodeToRaw CvENODERPC,
1320
   "Error during connection to the primary node of an instance")
1321

    
1322
cvEnodesetup :: (String, String, String)
1323
cvEnodesetup =
1324
  ("node",
1325
   Types.cVErrorCodeToRaw CvENODESETUP,
1326
   "Node setup error")
1327

    
1328
cvEnodesharedfilestoragepathunusable :: (String, String, String)
1329
cvEnodesharedfilestoragepathunusable =
1330
  ("node",
1331
   Types.cVErrorCodeToRaw CvENODESHAREDFILESTORAGEPATHUNUSABLE,
1332
   "Shared file storage path unusable")
1333

    
1334
cvEnodessh :: (String, String, String)
1335
cvEnodessh =
1336
  ("node",
1337
   Types.cVErrorCodeToRaw CvENODESSH,
1338
   "SSH-related node error")
1339

    
1340
cvEnodetime :: (String, String, String)
1341
cvEnodetime =
1342
  ("node",
1343
   Types.cVErrorCodeToRaw CvENODETIME,
1344
   "Node returned invalid time")
1345

    
1346
cvEnodeuserscripts :: (String, String, String)
1347
cvEnodeuserscripts =
1348
  ("node",
1349
   Types.cVErrorCodeToRaw CvENODEUSERSCRIPTS,
1350
   "User scripts not present or not executable")
1351

    
1352
cvEnodeversion :: (String, String, String)
1353
cvEnodeversion =
1354
  ("node",
1355
   Types.cVErrorCodeToRaw CvENODEVERSION,
1356
   "Protocol version mismatch or Ganeti version mismatch")
1357

    
1358
cvAllEcodes :: FrozenSet (String, String, String)
1359
cvAllEcodes =
1360
  ConstantUtils.mkSet
1361
  [cvEclustercert,
1362
   cvEclustercfg,
1363
   cvEclusterdanglinginst,
1364
   cvEclusterdanglingnodes,
1365
   cvEclusterfilecheck,
1366
   cvEgroupdifferentpvsize,
1367
   cvEinstancebadnode,
1368
   cvEinstancedown,
1369
   cvEinstancefaultydisk,
1370
   cvEinstancelayout,
1371
   cvEinstancemissingcfgparameter,
1372
   cvEinstancemissingdisk,
1373
   cvEinstancepolicy,
1374
   cvEinstancesplitgroups,
1375
   cvEinstanceunsuitablenode,
1376
   cvEinstancewrongnode,
1377
   cvEnodedrbd,
1378
   cvEnodedrbdhelper,
1379
   cvEnodedrbdversion,
1380
   cvEnodefilecheck,
1381
   cvEnodefilestoragepaths,
1382
   cvEnodefilestoragepathunusable,
1383
   cvEnodehooks,
1384
   cvEnodehv,
1385
   cvEnodelvm,
1386
   cvEnoden1,
1387
   cvEnodenet,
1388
   cvEnodeoobpath,
1389
   cvEnodeorphaninstance,
1390
   cvEnodeorphanlv,
1391
   cvEnodeos,
1392
   cvEnoderpc,
1393
   cvEnodesetup,
1394
   cvEnodesharedfilestoragepathunusable,
1395
   cvEnodessh,
1396
   cvEnodetime,
1397
   cvEnodeuserscripts,
1398
   cvEnodeversion]
1399

    
1400
cvAllEcodesStrings :: FrozenSet String
1401
cvAllEcodesStrings =
1402
  ConstantUtils.mkSet $ map Types.cVErrorCodeToRaw [minBound..]
1403

    
1404
-- * Instance status
1405

    
1406
inststAdmindown :: String
1407
inststAdmindown = Types.instanceStatusToRaw StatusDown
1408

    
1409
inststAdminoffline :: String
1410
inststAdminoffline = Types.instanceStatusToRaw StatusOffline
1411

    
1412
inststErrordown :: String
1413
inststErrordown = Types.instanceStatusToRaw ErrorDown
1414

    
1415
inststErrorup :: String
1416
inststErrorup = Types.instanceStatusToRaw ErrorUp
1417

    
1418
inststNodedown :: String
1419
inststNodedown = Types.instanceStatusToRaw NodeDown
1420

    
1421
inststNodeoffline :: String
1422
inststNodeoffline = Types.instanceStatusToRaw NodeOffline
1423

    
1424
inststRunning :: String
1425
inststRunning = Types.instanceStatusToRaw Running
1426

    
1427
inststWrongnode :: String
1428
inststWrongnode = Types.instanceStatusToRaw WrongNode
1429

    
1430
inststAll :: FrozenSet String
1431
inststAll = ConstantUtils.mkSet $ map Types.instanceStatusToRaw [minBound..]
1432

    
1433
-- * Admin states
1434

    
1435
adminstDown :: String
1436
adminstDown = Types.adminStateToRaw AdminDown
1437

    
1438
adminstOffline :: String
1439
adminstOffline = Types.adminStateToRaw AdminOffline
1440

    
1441
adminstUp :: String
1442
adminstUp = Types.adminStateToRaw AdminUp
1443

    
1444
adminstAll :: FrozenSet String
1445
adminstAll = ConstantUtils.mkSet $ map Types.adminStateToRaw [minBound..]
1446

    
1447
-- * Node roles
1448

    
1449
nrDrained :: String
1450
nrDrained = Types.nodeRoleToRaw NRDrained
1451

    
1452
nrMaster :: String
1453
nrMaster = Types.nodeRoleToRaw NRMaster
1454

    
1455
nrMcandidate :: String
1456
nrMcandidate = Types.nodeRoleToRaw NRCandidate
1457

    
1458
nrOffline :: String
1459
nrOffline = Types.nodeRoleToRaw NROffline
1460

    
1461
nrRegular :: String
1462
nrRegular = Types.nodeRoleToRaw NRRegular
1463

    
1464
nrAll :: FrozenSet String
1465
nrAll = ConstantUtils.mkSet $ map Types.nodeRoleToRaw [minBound..]
1466

    
1467
-- * Allocator framework constants
1468

    
1469
iallocatorVersion :: Int
1470
iallocatorVersion = 2
1471

    
1472
iallocatorDirIn :: String
1473
iallocatorDirIn = Types.iAllocatorTestDirToRaw IAllocatorDirIn
1474

    
1475
iallocatorDirOut :: String
1476
iallocatorDirOut = Types.iAllocatorTestDirToRaw IAllocatorDirOut
1477

    
1478
validIallocatorDirections :: FrozenSet String
1479
validIallocatorDirections =
1480
  ConstantUtils.mkSet $ map Types.iAllocatorTestDirToRaw [minBound..]
1481

    
1482
iallocatorModeAlloc :: String
1483
iallocatorModeAlloc = Types.iAllocatorModeToRaw IAllocatorAlloc
1484

    
1485
iallocatorModeChgGroup :: String
1486
iallocatorModeChgGroup = Types.iAllocatorModeToRaw IAllocatorChangeGroup
1487

    
1488
iallocatorModeMultiAlloc :: String
1489
iallocatorModeMultiAlloc = Types.iAllocatorModeToRaw IAllocatorMultiAlloc
1490

    
1491
iallocatorModeNodeEvac :: String
1492
iallocatorModeNodeEvac = Types.iAllocatorModeToRaw IAllocatorNodeEvac
1493

    
1494
iallocatorModeReloc :: String
1495
iallocatorModeReloc = Types.iAllocatorModeToRaw IAllocatorReloc
1496

    
1497
validIallocatorModes :: FrozenSet String
1498
validIallocatorModes =
1499
  ConstantUtils.mkSet $ map Types.iAllocatorModeToRaw [minBound..]
1500

    
1501
iallocatorSearchPath :: [String]
1502
iallocatorSearchPath = AutoConf.iallocatorSearchPath
1503

    
1504
defaultIallocatorShortcut :: String
1505
defaultIallocatorShortcut = "."
1506

    
1507
-- * Node evacuation
1508

    
1509
nodeEvacPri :: String
1510
nodeEvacPri = Types.evacModeToRaw ChangePrimary
1511

    
1512
nodeEvacSec :: String
1513
nodeEvacSec = Types.evacModeToRaw ChangeSecondary
1514

    
1515
nodeEvacAll :: String
1516
nodeEvacAll = Types.evacModeToRaw ChangeAll
1517

    
1518
nodeEvacModes :: FrozenSet String
1519
nodeEvacModes = ConstantUtils.mkSet $ map Types.evacModeToRaw [minBound..]
1520

    
1521
-- * Job status
1522

    
1523
jobStatusQueued :: String
1524
jobStatusQueued = Types.jobStatusToRaw JOB_STATUS_QUEUED
1525

    
1526
jobStatusWaiting :: String
1527
jobStatusWaiting = Types.jobStatusToRaw JOB_STATUS_WAITING
1528

    
1529
jobStatusCanceling :: String
1530
jobStatusCanceling = Types.jobStatusToRaw JOB_STATUS_CANCELING
1531

    
1532
jobStatusRunning :: String
1533
jobStatusRunning = Types.jobStatusToRaw JOB_STATUS_RUNNING
1534

    
1535
jobStatusCanceled :: String
1536
jobStatusCanceled = Types.jobStatusToRaw JOB_STATUS_CANCELED
1537

    
1538
jobStatusSuccess :: String
1539
jobStatusSuccess = Types.jobStatusToRaw JOB_STATUS_SUCCESS
1540

    
1541
jobStatusError :: String
1542
jobStatusError = Types.jobStatusToRaw JOB_STATUS_ERROR
1543

    
1544
jobsPending :: FrozenSet String
1545
jobsPending =
1546
  ConstantUtils.mkSet [jobStatusQueued, jobStatusWaiting, jobStatusCanceling]
1547

    
1548
jobsFinalized :: FrozenSet String
1549
jobsFinalized =
1550
  ConstantUtils.mkSet $ map Types.finalizedJobStatusToRaw [minBound..]
1551

    
1552
jobStatusAll :: FrozenSet String
1553
jobStatusAll = ConstantUtils.mkSet $ map Types.jobStatusToRaw [minBound..]
1554

    
1555
-- * OpCode status
1556

    
1557
-- ** Not yet finalized opcodes
1558

    
1559
opStatusCanceling :: String
1560
opStatusCanceling = "canceling"
1561

    
1562
opStatusQueued :: String
1563
opStatusQueued = "queued"
1564

    
1565
opStatusRunning :: String
1566
opStatusRunning = "running"
1567

    
1568
opStatusWaiting :: String
1569
opStatusWaiting = "waiting"
1570

    
1571
-- ** Finalized opcodes
1572

    
1573
opStatusCanceled :: String
1574
opStatusCanceled = "canceled"
1575

    
1576
opStatusError :: String
1577
opStatusError = "error"
1578

    
1579
opStatusSuccess :: String
1580
opStatusSuccess = "success"
1581

    
1582
opsFinalized :: FrozenSet String
1583
opsFinalized =
1584
  ConstantUtils.mkSet [opStatusCanceled, opStatusError, opStatusSuccess]
1585

    
1586
-- * OpCode priority
1587

    
1588
opPrioLowest :: Int
1589
opPrioLowest = 19
1590

    
1591
opPrioHighest :: Int
1592
opPrioHighest = -20
1593

    
1594
opPrioLow :: Int
1595
opPrioLow = Types.opSubmitPriorityToRaw OpPrioLow
1596

    
1597
opPrioNormal :: Int
1598
opPrioNormal = Types.opSubmitPriorityToRaw OpPrioNormal
1599

    
1600
opPrioHigh :: Int
1601
opPrioHigh = Types.opSubmitPriorityToRaw OpPrioHigh
1602

    
1603
opPrioSubmitValid :: FrozenSet Int
1604
opPrioSubmitValid = ConstantUtils.mkSet [opPrioLow, opPrioNormal, opPrioHigh]
1605

    
1606
opPrioDefault :: Int
1607
opPrioDefault = opPrioNormal
1608

    
1609
-- * Execution log types
1610

    
1611
elogMessage :: String
1612
elogMessage = Types.eLogTypeToRaw ELogMessage
1613

    
1614
elogRemoteImport :: String
1615
elogRemoteImport = Types.eLogTypeToRaw ELogRemoteImport
1616

    
1617
elogJqueueTest :: String
1618
elogJqueueTest = Types.eLogTypeToRaw ELogJqueueTest
1619

    
1620
-- * Confd
1621

    
1622
confdProtocolVersion :: Int
1623
confdProtocolVersion = ConstantUtils.confdProtocolVersion
1624

    
1625
-- Confd request type
1626

    
1627
confdReqPing :: Int
1628
confdReqPing = Types.confdRequestTypeToRaw ReqPing
1629

    
1630
confdReqNodeRoleByname :: Int
1631
confdReqNodeRoleByname = Types.confdRequestTypeToRaw ReqNodeRoleByName
1632

    
1633
confdReqNodePipByInstanceIp :: Int
1634
confdReqNodePipByInstanceIp = Types.confdRequestTypeToRaw ReqNodePipByInstPip
1635

    
1636
confdReqClusterMaster :: Int
1637
confdReqClusterMaster = Types.confdRequestTypeToRaw ReqClusterMaster
1638

    
1639
confdReqNodePipList :: Int
1640
confdReqNodePipList = Types.confdRequestTypeToRaw ReqNodePipList
1641

    
1642
confdReqMcPipList :: Int
1643
confdReqMcPipList = Types.confdRequestTypeToRaw ReqMcPipList
1644

    
1645
confdReqInstancesIpsList :: Int
1646
confdReqInstancesIpsList = Types.confdRequestTypeToRaw ReqInstIpsList
1647

    
1648
confdReqNodeDrbd :: Int
1649
confdReqNodeDrbd = Types.confdRequestTypeToRaw ReqNodeDrbd
1650

    
1651
confdReqNodeInstances :: Int
1652
confdReqNodeInstances = Types.confdRequestTypeToRaw ReqNodeInstances
1653

    
1654
confdReqs :: FrozenSet Int
1655
confdReqs =
1656
  ConstantUtils.mkSet .
1657
  map Types.confdRequestTypeToRaw $
1658
  [minBound..] \\ [ReqNodeInstances]
1659

    
1660
-- * Confd request type
1661

    
1662
confdReqfieldName :: Int
1663
confdReqfieldName = Types.confdReqFieldToRaw ReqFieldName
1664

    
1665
confdReqfieldIp :: Int
1666
confdReqfieldIp = Types.confdReqFieldToRaw ReqFieldIp
1667

    
1668
confdReqfieldMnodePip :: Int
1669
confdReqfieldMnodePip = Types.confdReqFieldToRaw ReqFieldMNodePip
1670

    
1671
-- * Confd repl status
1672

    
1673
confdReplStatusOk :: Int
1674
confdReplStatusOk = Types.confdReplyStatusToRaw ReplyStatusOk
1675

    
1676
confdReplStatusError :: Int
1677
confdReplStatusError = Types.confdReplyStatusToRaw ReplyStatusError
1678

    
1679
confdReplStatusNotimplemented :: Int
1680
confdReplStatusNotimplemented = Types.confdReplyStatusToRaw ReplyStatusNotImpl
1681

    
1682
confdReplStatuses :: FrozenSet Int
1683
confdReplStatuses =
1684
  ConstantUtils.mkSet $ map Types.confdReplyStatusToRaw [minBound..]
1685

    
1686
-- * Confd node role
1687

    
1688
confdNodeRoleMaster :: Int
1689
confdNodeRoleMaster = Types.confdNodeRoleToRaw NodeRoleMaster
1690

    
1691
confdNodeRoleCandidate :: Int
1692
confdNodeRoleCandidate = Types.confdNodeRoleToRaw NodeRoleCandidate
1693

    
1694
confdNodeRoleOffline :: Int
1695
confdNodeRoleOffline = Types.confdNodeRoleToRaw NodeRoleOffline
1696

    
1697
confdNodeRoleDrained :: Int
1698
confdNodeRoleDrained = Types.confdNodeRoleToRaw NodeRoleDrained
1699

    
1700
confdNodeRoleRegular :: Int
1701
confdNodeRoleRegular = Types.confdNodeRoleToRaw NodeRoleRegular
1702

    
1703
-- * A few common errors for confd
1704

    
1705
confdErrorUnknownEntry :: Int
1706
confdErrorUnknownEntry = Types.confdErrorTypeToRaw ConfdErrorUnknownEntry
1707

    
1708
confdErrorInternal :: Int
1709
confdErrorInternal = Types.confdErrorTypeToRaw ConfdErrorInternal
1710

    
1711
confdErrorArgument :: Int
1712
confdErrorArgument = Types.confdErrorTypeToRaw ConfdErrorArgument
1713

    
1714
-- * Confd request query fields
1715

    
1716
confdReqqLink :: String
1717
confdReqqLink = ConstantUtils.confdReqqLink
1718

    
1719
confdReqqIp :: String
1720
confdReqqIp = ConstantUtils.confdReqqIp
1721

    
1722
confdReqqIplist :: String
1723
confdReqqIplist = ConstantUtils.confdReqqIplist
1724

    
1725
confdReqqFields :: String
1726
confdReqqFields = ConstantUtils.confdReqqFields
1727

    
1728
-- | Each request is "salted" by the current timestamp.
1729
--
1730
-- This constant decides how many seconds of skew to accept.
1731
--
1732
-- TODO: make this a default and allow the value to be more
1733
-- configurable
1734
confdMaxClockSkew :: Int
1735
confdMaxClockSkew = 2 * nodeMaxClockSkew
1736

    
1737
-- | When we haven't reloaded the config for more than this amount of
1738
-- seconds, we force a test to see if inotify is betraying us. Using a
1739
-- prime number to ensure we get less chance of 'same wakeup' with
1740
-- other processes.
1741
confdConfigReloadTimeout :: Int
1742
confdConfigReloadTimeout = 17
1743

    
1744
-- | If we receive more than one update in this amount of
1745
-- microseconds, we move to polling every RATELIMIT seconds, rather
1746
-- than relying on inotify, to be able to serve more requests.
1747
confdConfigReloadRatelimit :: Int
1748
confdConfigReloadRatelimit = 250000
1749

    
1750
-- | Magic number prepended to all confd queries.
1751
--
1752
-- This allows us to distinguish different types of confd protocols
1753
-- and handle them. For example by changing this we can move the whole
1754
-- payload to be compressed, or move away from json.
1755
confdMagicFourcc :: String
1756
confdMagicFourcc = "plj0"
1757

    
1758
-- | By default a confd request is sent to the minimum between this
1759
-- number and all MCs. 6 was chosen because even in the case of a
1760
-- disastrous 50% response rate, we should have enough answers to be
1761
-- able to compare more than one.
1762
confdDefaultReqCoverage :: Int
1763
confdDefaultReqCoverage = 6
1764

    
1765
-- | Timeout in seconds to expire pending query request in the confd
1766
-- client library. We don't actually expect any answer more than 10
1767
-- seconds after we sent a request.
1768
confdClientExpireTimeout :: Int
1769
confdClientExpireTimeout = 10
1770

    
1771
-- * Possible values for NodeGroup.alloc_policy
1772

    
1773
allocPolicyLastResort :: String
1774
allocPolicyLastResort = Types.allocPolicyToRaw AllocLastResort
1775

    
1776
allocPolicyPreferred :: String
1777
allocPolicyPreferred = Types.allocPolicyToRaw AllocPreferred
1778

    
1779
allocPolicyUnallocable :: String
1780
allocPolicyUnallocable = Types.allocPolicyToRaw AllocUnallocable
1781

    
1782
validAllocPolicies :: [String]
1783
validAllocPolicies = map Types.allocPolicyToRaw [minBound..]
1784

    
1785
-- | Temporary external/shared storage parameters
1786
blockdevDriverManual :: String
1787
blockdevDriverManual = Types.blockDriverToRaw BlockDrvManual
1788

    
1789
-- | 'qemu-img' path, required for 'ovfconverter'
1790
qemuimgPath :: String
1791
qemuimgPath = AutoConf.qemuimgPath
1792

    
1793
-- | Whether htools was enabled at compilation time
1794
--
1795
-- FIXME: this should be moved next to the other enable constants,
1796
-- such as, 'enableConfd', and renamed to 'enableHtools'.
1797
htools :: Bool
1798
htools = AutoConf.htools
1799

    
1800
-- * Key files for SSH daemon
1801

    
1802
sshHostDsaPriv :: String
1803
sshHostDsaPriv = sshConfigDir ++ "/ssh_host_dsa_key"
1804

    
1805
sshHostDsaPub :: String
1806
sshHostDsaPub = sshHostDsaPriv ++ ".pub"
1807

    
1808
sshHostRsaPriv :: String
1809
sshHostRsaPriv = sshConfigDir ++ "/ssh_host_rsa_key"
1810

    
1811
sshHostRsaPub :: String
1812
sshHostRsaPub = sshHostRsaPriv ++ ".pub"
1813

    
1814
-- | Path generating random UUID
1815
randomUuidFile :: String
1816
randomUuidFile = ConstantUtils.randomUuidFile
1817

    
1818
-- * Auto-repair tag prefixes
1819

    
1820
autoRepairTagPrefix :: String
1821
autoRepairTagPrefix = "ganeti:watcher:autorepair:"
1822

    
1823
autoRepairTagEnabled :: String
1824
autoRepairTagEnabled = autoRepairTagPrefix
1825

    
1826
autoRepairTagPending :: String
1827
autoRepairTagPending = autoRepairTagPrefix ++ "pending:"
1828

    
1829
autoRepairTagResult :: String
1830
autoRepairTagResult = autoRepairTagPrefix ++ "result:"
1831

    
1832
autoRepairTagSuspended :: String
1833
autoRepairTagSuspended = autoRepairTagPrefix ++ "suspend:"
1834

    
1835
-- * Auto-repair levels
1836

    
1837
autoRepairFailover :: String
1838
autoRepairFailover = "failover"
1839

    
1840
autoRepairFixStorage :: String
1841
autoRepairFixStorage = "fix-storage"
1842

    
1843
autoRepairMigrate :: String
1844
autoRepairMigrate = "migrate"
1845

    
1846
autoRepairReinstall :: String
1847
autoRepairReinstall = "reinstall"
1848

    
1849
autoRepairAllTypes :: FrozenSet String
1850
autoRepairAllTypes =
1851
  ConstantUtils.mkSet [autoRepairFailover,
1852
                       autoRepairFixStorage,
1853
                       autoRepairMigrate,
1854
                       autoRepairReinstall]
1855

    
1856
-- * Auto-repair results
1857

    
1858
autoRepairEnoperm :: String
1859
autoRepairEnoperm = "enoperm"
1860

    
1861
autoRepairFailure :: String
1862
autoRepairFailure = "failure"
1863

    
1864
autoRepairSuccess :: String
1865
autoRepairSuccess = "success"
1866

    
1867
autoRepairAllResults :: FrozenSet String
1868
autoRepairAllResults =
1869
  ConstantUtils.mkSet [autoRepairEnoperm, autoRepairFailure, autoRepairSuccess]
1870

    
1871
-- | The version identifier for builtin data collectors
1872
builtinDataCollectorVersion :: String
1873
builtinDataCollectorVersion = "B"
1874

    
1875
-- | The reason trail opcode parameter name
1876
opcodeReason :: String
1877
opcodeReason = "reason"
1878

    
1879
diskstatsFile :: String
1880
diskstatsFile = "/proc/diskstats"
1881

    
1882
-- *  CPU load collector
1883

    
1884
statFile :: String
1885
statFile = "/proc/stat"
1886

    
1887
cpuavgloadBufferSize :: Int
1888
cpuavgloadBufferSize = 150
1889

    
1890
cpuavgloadWindowSize :: Int
1891
cpuavgloadWindowSize = 600
1892

    
1893
-- | Mond's variable for periodical data collection
1894
mondTimeInterval :: Int
1895
mondTimeInterval = 5
1896

    
1897
-- * Disk access modes
1898

    
1899
diskUserspace :: String
1900
diskUserspace = Types.diskAccessModeToRaw DiskUserspace
1901

    
1902
diskKernelspace :: String
1903
diskKernelspace = Types.diskAccessModeToRaw DiskKernelspace
1904

    
1905
diskValidAccessModes :: FrozenSet String
1906
diskValidAccessModes =
1907
  ConstantUtils.mkSet $ map Types.diskAccessModeToRaw [minBound..]
1908

    
1909
-- | Timeout for queue draining in upgrades
1910
upgradeQueueDrainTimeout :: Int
1911
upgradeQueueDrainTimeout = 36 * 60 * 60 -- 1.5 days
1912

    
1913
-- | Intervall at which the queue is polled during upgrades
1914
upgradeQueuePollInterval :: Int
1915
upgradeQueuePollInterval  = 10