Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Constants.hs @ fb0fa957

History | View | Annotate | Download (121.7 kB)

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

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

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

    
15
-}
16

    
17
{-
18

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

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

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

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

    
36
-}
37
module Ganeti.Constants where
38

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

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

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

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

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

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

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

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

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

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

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

    
86
-- ** Build-time constants
87

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
135
-- * Various versions
136

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

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

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

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

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

    
152
osApiV10 :: Int
153
osApiV10 = 10
154

    
155
osApiV15 :: Int
156
osApiV15 = 15
157

    
158
osApiV20 :: Int
159
osApiV20 = 20
160

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

    
164
exportVersion :: Int
165
exportVersion = 0
166

    
167
rapiVersion :: Int
168
rapiVersion = 2
169

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

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

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

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

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

    
189
-- * User separation
190

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
257
-- * Cpu pinning separators and constants
258

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

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

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

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

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

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

    
297
-- * Wipe
298

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

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

    
306
minWipeChunkPercent :: Int
307
minWipeChunkPercent = 10
308

    
309
-- * Directories
310

    
311
runDirsMode :: Int
312
runDirsMode = 0o775
313

    
314
secureDirMode :: Int
315
secureDirMode = 0o700
316

    
317
secureFileMode :: Int
318
secureFileMode = 0o600
319

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

    
323
-- * 'autoconf' enable/disable
324

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

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

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

    
334
-- * SSH constants
335

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

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

    
342
-- * Daemons
343

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

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

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

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

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

    
359
luxid :: String
360
luxid = Runtime.daemonName GanetiLuxid
361

    
362
rapi :: String
363
rapi = Runtime.daemonName GanetiRapi
364

    
365
kvmd :: String
366
kvmd = Runtime.daemonName GanetiKvmd
367

    
368
daemons :: FrozenSet String
369
daemons =
370
  ConstantUtils.mkSet [confd,
371
                       luxid,
372
                       masterd,
373
                       mond,
374
                       noded,
375
                       rapi]
376

    
377
defaultConfdPort :: Int
378
defaultConfdPort = 1814
379

    
380
defaultMondPort :: Int
381
defaultMondPort = 1815
382

    
383
defaultMetadPort :: Int
384
defaultMetadPort = 8080
385

    
386
defaultNodedPort :: Int
387
defaultNodedPort = 1811
388

    
389
defaultRapiPort :: Int
390
defaultRapiPort = 5080
391

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

    
403
firstDrbdPort :: Int
404
firstDrbdPort = 11000
405

    
406
lastDrbdPort :: Int
407
lastDrbdPort = 14999
408

    
409
daemonsLogbase :: Map String String
410
daemonsLogbase =
411
  Map.fromList
412
  [ (Runtime.daemonName d, Runtime.daemonLogBase d) | d <- [minBound..] ]
413

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

    
424
extraLogreasonAccess :: String
425
extraLogreasonAccess = Runtime.daemonsExtraLogbase GanetiMond AccessLog
426

    
427
extraLogreasonError :: String
428
extraLogreasonError = Runtime.daemonsExtraLogbase GanetiMond ErrorLog
429

    
430
devConsole :: String
431
devConsole = ConstantUtils.devConsole
432

    
433
procMounts :: String
434
procMounts = "/proc/mounts"
435

    
436
-- * Luxi (Local UniX Interface) related constants
437

    
438
luxiEom :: PythonChar
439
luxiEom = PythonChar '\x03'
440

    
441
-- | Environment variable for the luxi override socket
442
luxiOverride :: String
443
luxiOverride = "FORCE_LUXI_SOCKET"
444

    
445
luxiOverrideMaster :: String
446
luxiOverrideMaster = "master"
447

    
448
luxiOverrideQuery :: String
449
luxiOverrideQuery = "query"
450

    
451
luxiVersion :: Int
452
luxiVersion = configVersion
453

    
454
-- * Syslog
455

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

    
459
syslogNo :: String
460
syslogNo = Logging.syslogUsageToRaw SyslogNo
461

    
462
syslogYes :: String
463
syslogYes = Logging.syslogUsageToRaw SyslogYes
464

    
465
syslogOnly :: String
466
syslogOnly = Logging.syslogUsageToRaw SyslogOnly
467

    
468
syslogSocket :: String
469
syslogSocket = "/dev/log"
470

    
471
exportConfFile :: String
472
exportConfFile = "config.ini"
473

    
474
-- * Xen
475

    
476
xenBootloader :: String
477
xenBootloader = AutoConf.xenBootloader
478

    
479
xenCmdXl :: String
480
xenCmdXl = "xl"
481

    
482
xenCmdXm :: String
483
xenCmdXm = "xm"
484

    
485
xenInitrd :: String
486
xenInitrd = AutoConf.xenInitrd
487

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

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

    
496
-- * KVM and socat
497

    
498
kvmPath :: String
499
kvmPath = AutoConf.kvmPath
500

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

    
504
socatEscapeCode :: String
505
socatEscapeCode = "0x1d"
506

    
507
socatPath :: String
508
socatPath = AutoConf.socatPath
509

    
510
socatUseCompress :: Bool
511
socatUseCompress = AutoConf.socatUseCompress
512

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

    
516
-- * Console types
517

    
518
-- | Display a message for console access
519
consMessage :: String
520
consMessage = "msg"
521

    
522
-- | Console as SPICE server
523
consSpice :: String
524
consSpice = "spice"
525

    
526
-- | Console as SSH command
527
consSsh :: String
528
consSsh = "ssh"
529

    
530
-- | Console as VNC server
531
consVnc :: String
532
consVnc = "vnc"
533

    
534
consAll :: FrozenSet String
535
consAll = ConstantUtils.mkSet [consMessage, consSpice, consSsh, consVnc]
536

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

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

    
556
-- * X509
557

    
558
-- | commonName (CN) used in certificates
559
x509CertCn :: String
560
x509CertCn = "ganeti.example.com"
561

    
562
-- | Default validity of certificates in days
563
x509CertDefaultValidity :: Int
564
x509CertDefaultValidity = 365 * 5
565

    
566
x509CertSignatureHeader :: String
567
x509CertSignatureHeader = "X-Ganeti-Signature"
568

    
569
-- | Digest used to sign certificates ("openssl x509" uses SHA1 by default)
570
x509CertSignDigest :: String
571
x509CertSignDigest = "SHA1"
572

    
573
-- * Import/export daemon mode
574

    
575
iemExport :: String
576
iemExport = "export"
577

    
578
iemImport :: String
579
iemImport = "import"
580

    
581
-- * Import/export transport compression
582

    
583
iecGzip :: String
584
iecGzip = "gzip"
585

    
586
iecNone :: String
587
iecNone = "none"
588

    
589
iecAll :: [String]
590
iecAll = [iecGzip, iecNone]
591

    
592
ieCustomSize :: String
593
ieCustomSize = "fd"
594

    
595
-- * Import/export I/O
596

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

    
602
-- | Raw block device I/O using "dd"
603
ieioRawDisk :: String
604
ieioRawDisk = "raw"
605

    
606
-- | OS definition import/export script
607
ieioScript :: String
608
ieioScript = "script"
609

    
610
-- * Values
611

    
612
valueDefault :: String
613
valueDefault = "default"
614

    
615
valueAuto :: String
616
valueAuto = "auto"
617

    
618
valueGenerate :: String
619
valueGenerate = "generate"
620

    
621
valueNone :: String
622
valueNone = "none"
623

    
624
valueTrue :: String
625
valueTrue = "true"
626

    
627
valueFalse :: String
628
valueFalse = "false"
629

    
630
-- * Hooks
631

    
632
hooksNameCfgupdate :: String
633
hooksNameCfgupdate = "config-update"
634

    
635
hooksNameWatcher :: String
636
hooksNameWatcher = "watcher"
637

    
638
hooksPath :: String
639
hooksPath = "/sbin:/bin:/usr/sbin:/usr/bin"
640

    
641
hooksPhasePost :: String
642
hooksPhasePost = "post"
643

    
644
hooksPhasePre :: String
645
hooksPhasePre = "pre"
646

    
647
hooksVersion :: Int
648
hooksVersion = 2
649

    
650
-- * Hooks subject type (what object type does the LU deal with)
651

    
652
htypeCluster :: String
653
htypeCluster = "CLUSTER"
654

    
655
htypeGroup :: String
656
htypeGroup = "GROUP"
657

    
658
htypeInstance :: String
659
htypeInstance = "INSTANCE"
660

    
661
htypeNetwork :: String
662
htypeNetwork = "NETWORK"
663

    
664
htypeNode :: String
665
htypeNode = "NODE"
666

    
667
-- * Hkr
668

    
669
hkrSkip :: Int
670
hkrSkip = 0
671

    
672
hkrFail :: Int
673
hkrFail = 1
674

    
675
hkrSuccess :: Int
676
hkrSuccess = 2
677

    
678
-- * Storage types
679

    
680
stBlock :: String
681
stBlock = Types.storageTypeToRaw StorageBlock
682

    
683
stDiskless :: String
684
stDiskless = Types.storageTypeToRaw StorageDiskless
685

    
686
stExt :: String
687
stExt = Types.storageTypeToRaw StorageExt
688

    
689
stFile :: String
690
stFile = Types.storageTypeToRaw StorageFile
691

    
692
stSharedFile :: String
693
stSharedFile = Types.storageTypeToRaw StorageSharedFile
694

    
695
stLvmPv :: String
696
stLvmPv = Types.storageTypeToRaw StorageLvmPv
697

    
698
stLvmVg :: String
699
stLvmVg = Types.storageTypeToRaw StorageLvmVg
700

    
701
stRados :: String
702
stRados = Types.storageTypeToRaw StorageRados
703

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

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

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

    
717
-- * Storage fields
718
-- ** First two are valid in LU context only, not passed to backend
719

    
720
sfNode :: String
721
sfNode = "node"
722

    
723
sfType :: String
724
sfType = "type"
725

    
726
-- ** and the rest are valid in backend
727

    
728
sfAllocatable :: String
729
sfAllocatable = Types.storageFieldToRaw SFAllocatable
730

    
731
sfFree :: String
732
sfFree = Types.storageFieldToRaw SFFree
733

    
734
sfName :: String
735
sfName = Types.storageFieldToRaw SFName
736

    
737
sfSize :: String
738
sfSize = Types.storageFieldToRaw SFSize
739

    
740
sfUsed :: String
741
sfUsed = Types.storageFieldToRaw SFUsed
742

    
743
validStorageFields :: FrozenSet String
744
validStorageFields =
745
  ConstantUtils.mkSet $ map Types.storageFieldToRaw [minBound..] ++
746
                        [sfNode, sfType]
747

    
748
modifiableStorageFields :: Map String (FrozenSet String)
749
modifiableStorageFields =
750
  Map.fromList [(Types.storageTypeToRaw StorageLvmPv,
751
                 ConstantUtils.mkSet [sfAllocatable])]
752

    
753
-- * Storage operations
754

    
755
soFixConsistency :: String
756
soFixConsistency = "fix-consistency"
757

    
758
validStorageOperations :: Map String (FrozenSet String)
759
validStorageOperations =
760
  Map.fromList [(Types.storageTypeToRaw StorageLvmVg,
761
                 ConstantUtils.mkSet [soFixConsistency])]
762

    
763
-- * Volume fields
764

    
765
vfDev :: String
766
vfDev = "dev"
767

    
768
vfInstance :: String
769
vfInstance = "instance"
770

    
771
vfName :: String
772
vfName = "name"
773

    
774
vfNode :: String
775
vfNode = "node"
776

    
777
vfPhys :: String
778
vfPhys = "phys"
779

    
780
vfSize :: String
781
vfSize = "size"
782

    
783
vfVg :: String
784
vfVg = "vg"
785

    
786
-- * Local disk status
787

    
788
ldsFaulty :: Int
789
ldsFaulty = Types.localDiskStatusToRaw DiskStatusFaulty
790

    
791
ldsOkay :: Int
792
ldsOkay = Types.localDiskStatusToRaw DiskStatusOk
793

    
794
ldsUnknown :: Int
795
ldsUnknown = Types.localDiskStatusToRaw DiskStatusUnknown
796

    
797
ldsNames :: Map Int String
798
ldsNames =
799
  Map.fromList [ (Types.localDiskStatusToRaw ds,
800
                  localDiskStatusName ds) | ds <- [minBound..] ]
801

    
802
-- * Disk template types
803

    
804
dtDiskless :: String
805
dtDiskless = Types.diskTemplateToRaw DTDiskless
806

    
807
dtFile :: String
808
dtFile = Types.diskTemplateToRaw DTFile
809

    
810
dtSharedFile :: String
811
dtSharedFile = Types.diskTemplateToRaw DTSharedFile
812

    
813
dtPlain :: String
814
dtPlain = Types.diskTemplateToRaw DTPlain
815

    
816
dtBlock :: String
817
dtBlock = Types.diskTemplateToRaw DTBlock
818

    
819
dtDrbd8 :: String
820
dtDrbd8 = Types.diskTemplateToRaw DTDrbd8
821

    
822
dtRbd :: String
823
dtRbd = Types.diskTemplateToRaw DTRbd
824

    
825
dtExt :: String
826
dtExt = Types.diskTemplateToRaw DTExt
827

    
828
dtGluster :: String
829
dtGluster = Types.diskTemplateToRaw DTGluster
830

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

    
842
diskTemplates :: FrozenSet String
843
diskTemplates = ConstantUtils.mkSet $ map Types.diskTemplateToRaw [minBound..]
844

    
845
-- | Disk templates that are enabled by default
846
defaultEnabledDiskTemplates :: [String]
847
defaultEnabledDiskTemplates = map Types.diskTemplateToRaw [DTDrbd8, DTPlain]
848

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

    
864
-- | The set of network-mirrored disk templates
865
dtsIntMirror :: FrozenSet String
866
dtsIntMirror = ConstantUtils.mkSet [dtDrbd8]
867

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

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

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

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

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

    
898
-- | The set of disk templates that allow migrations
899
dtsMirrored :: FrozenSet String
900
dtsMirrored = dtsIntMirror `ConstantUtils.union` dtsExtMirror
901

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

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

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

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

    
926
dtsBlock :: FrozenSet String
927
dtsBlock =
928
  ConstantUtils.mkSet $
929
  map Types.diskTemplateToRaw [DTPlain, DTDrbd8, DTBlock, DTRbd, DTExt]
930

    
931
-- | The set of lvm-based disk templates
932
dtsLvm :: FrozenSet String
933
dtsLvm = diskTemplates `ConstantUtils.difference` dtsNotLvm
934

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

    
940
-- * Drbd
941

    
942
drbdHmacAlg :: String
943
drbdHmacAlg = "md5"
944

    
945
drbdDefaultNetProtocol :: String
946
drbdDefaultNetProtocol = "C"
947

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

    
951
drbdStatusFile :: String
952
drbdStatusFile = "/proc/drbd"
953

    
954
-- | Size of DRBD meta block device
955
drbdMetaSize :: Int
956
drbdMetaSize = 128
957

    
958
-- * Drbd barrier types
959

    
960
drbdBDiskBarriers :: String
961
drbdBDiskBarriers = "b"
962

    
963
drbdBDiskDrain :: String
964
drbdBDiskDrain = "d"
965

    
966
drbdBDiskFlush :: String
967
drbdBDiskFlush = "f"
968

    
969
drbdBNone :: String
970
drbdBNone = "n"
971

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

    
986
-- | Rbd tool command
987
rbdCmd :: String
988
rbdCmd = "rbd"
989

    
990
-- * File backend driver
991

    
992
fdBlktap :: String
993
fdBlktap = Types.fileDriverToRaw FileBlktap
994

    
995
fdBlktap2 :: String
996
fdBlktap2 = Types.fileDriverToRaw FileBlktap2
997

    
998
fdLoop :: String
999
fdLoop = Types.fileDriverToRaw FileLoop
1000

    
1001
fdDefault :: String
1002
fdDefault = fdLoop
1003

    
1004
fileDriver :: FrozenSet String
1005
fileDriver =
1006
  ConstantUtils.mkSet $
1007
  map Types.fileDriverToRaw [minBound..]
1008

    
1009
-- | The set of drbd-like disk types
1010
dtsDrbd :: FrozenSet String
1011
dtsDrbd = ConstantUtils.mkSet [Types.diskTemplateToRaw DTDrbd8]
1012

    
1013
-- * Disk access mode
1014

    
1015
diskRdonly :: String
1016
diskRdonly = Types.diskModeToRaw DiskRdOnly
1017

    
1018
diskRdwr :: String
1019
diskRdwr = Types.diskModeToRaw DiskRdWr
1020

    
1021
diskAccessSet :: FrozenSet String
1022
diskAccessSet = ConstantUtils.mkSet $ map Types.diskModeToRaw [minBound..]
1023

    
1024
-- * Disk replacement mode
1025

    
1026
replaceDiskAuto :: String
1027
replaceDiskAuto = Types.replaceDisksModeToRaw ReplaceAuto
1028

    
1029
replaceDiskChg :: String
1030
replaceDiskChg = Types.replaceDisksModeToRaw ReplaceNewSecondary
1031

    
1032
replaceDiskPri :: String
1033
replaceDiskPri = Types.replaceDisksModeToRaw ReplaceOnPrimary
1034

    
1035
replaceDiskSec :: String
1036
replaceDiskSec = Types.replaceDisksModeToRaw ReplaceOnSecondary
1037

    
1038
replaceModes :: FrozenSet String
1039
replaceModes =
1040
  ConstantUtils.mkSet $ map Types.replaceDisksModeToRaw [minBound..]
1041

    
1042
-- * Instance export mode
1043

    
1044
exportModeLocal :: String
1045
exportModeLocal = Types.exportModeToRaw ExportModeLocal
1046

    
1047
exportModeRemote :: String
1048
exportModeRemote = Types.exportModeToRaw ExportModeRemote
1049

    
1050
exportModes :: FrozenSet String
1051
exportModes = ConstantUtils.mkSet $ map Types.exportModeToRaw [minBound..]
1052

    
1053
-- * Instance creation modes
1054

    
1055
instanceCreate :: String
1056
instanceCreate = Types.instCreateModeToRaw InstCreate
1057

    
1058
instanceImport :: String
1059
instanceImport = Types.instCreateModeToRaw InstImport
1060

    
1061
instanceRemoteImport :: String
1062
instanceRemoteImport = Types.instCreateModeToRaw InstRemoteImport
1063

    
1064
instanceCreateModes :: FrozenSet String
1065
instanceCreateModes =
1066
  ConstantUtils.mkSet $ map Types.instCreateModeToRaw [minBound..]
1067

    
1068
-- * Remote import/export handshake message and version
1069

    
1070
rieHandshake :: String
1071
rieHandshake = "Hi, I'm Ganeti"
1072

    
1073
rieVersion :: Int
1074
rieVersion = 0
1075

    
1076
-- | Remote import/export certificate validity (seconds)
1077
rieCertValidity :: Int
1078
rieCertValidity = 24 * 60 * 60
1079

    
1080
-- | Export only: how long to wait per connection attempt (seconds)
1081
rieConnectAttemptTimeout :: Int
1082
rieConnectAttemptTimeout = 20
1083

    
1084
-- | Export only: number of attempts to connect
1085
rieConnectRetries :: Int
1086
rieConnectRetries = 10
1087

    
1088
-- | Overall timeout for establishing connection
1089
rieConnectTimeout :: Int
1090
rieConnectTimeout = 180
1091

    
1092
-- | Give child process up to 5 seconds to exit after sending a signal
1093
childLingerTimeout :: Double
1094
childLingerTimeout = 5.0
1095

    
1096
-- * Import/export config options
1097

    
1098
inisectBep :: String
1099
inisectBep = "backend"
1100

    
1101
inisectExp :: String
1102
inisectExp = "export"
1103

    
1104
inisectHyp :: String
1105
inisectHyp = "hypervisor"
1106

    
1107
inisectIns :: String
1108
inisectIns = "instance"
1109

    
1110
inisectOsp :: String
1111
inisectOsp = "os"
1112

    
1113
inisectOspPrivate :: String
1114
inisectOspPrivate = "os_private"
1115

    
1116
-- * Dynamic device modification
1117

    
1118
ddmAdd :: String
1119
ddmAdd = Types.ddmFullToRaw DdmFullAdd
1120

    
1121
ddmModify :: String
1122
ddmModify = Types.ddmFullToRaw DdmFullModify
1123

    
1124
ddmRemove :: String
1125
ddmRemove = Types.ddmFullToRaw DdmFullRemove
1126

    
1127
ddmsValues :: FrozenSet String
1128
ddmsValues = ConstantUtils.mkSet [ddmAdd, ddmRemove]
1129

    
1130
ddmsValuesWithModify :: FrozenSet String
1131
ddmsValuesWithModify = ConstantUtils.mkSet $ map Types.ddmFullToRaw [minBound..]
1132

    
1133
-- * Common exit codes
1134

    
1135
exitSuccess :: Int
1136
exitSuccess = 0
1137

    
1138
exitFailure :: Int
1139
exitFailure = ConstantUtils.exitFailure
1140

    
1141
exitNotcluster :: Int
1142
exitNotcluster = 5
1143

    
1144
exitNotmaster :: Int
1145
exitNotmaster = 11
1146

    
1147
exitNodesetupError :: Int
1148
exitNodesetupError = 12
1149

    
1150
-- | Need user confirmation
1151
exitConfirmation :: Int
1152
exitConfirmation = 13
1153

    
1154
-- | Exit code for query operations with unknown fields
1155
exitUnknownField :: Int
1156
exitUnknownField = 14
1157

    
1158
-- * Tags
1159

    
1160
tagCluster :: String
1161
tagCluster = Types.tagKindToRaw TagKindCluster
1162

    
1163
tagInstance :: String
1164
tagInstance = Types.tagKindToRaw TagKindInstance
1165

    
1166
tagNetwork :: String
1167
tagNetwork = Types.tagKindToRaw TagKindNetwork
1168

    
1169
tagNode :: String
1170
tagNode = Types.tagKindToRaw TagKindNode
1171

    
1172
tagNodegroup :: String
1173
tagNodegroup = Types.tagKindToRaw TagKindGroup
1174

    
1175
validTagTypes :: FrozenSet String
1176
validTagTypes = ConstantUtils.mkSet $ map Types.tagKindToRaw [minBound..]
1177

    
1178
maxTagLen :: Int
1179
maxTagLen = 128
1180

    
1181
maxTagsPerObj :: Int
1182
maxTagsPerObj = 4096
1183

    
1184
-- * Others
1185

    
1186
defaultBridge :: String
1187
defaultBridge = "xen-br0"
1188

    
1189
defaultOvs :: String
1190
defaultOvs = "switch1"
1191

    
1192
-- | 60 MiB/s, expressed in KiB/s
1193
classicDrbdSyncSpeed :: Int
1194
classicDrbdSyncSpeed = 60 * 1024
1195

    
1196
ip4AddressAny :: String
1197
ip4AddressAny = "0.0.0.0"
1198

    
1199
ip4AddressLocalhost :: String
1200
ip4AddressLocalhost = "127.0.0.1"
1201

    
1202
ip6AddressAny :: String
1203
ip6AddressAny = "::"
1204

    
1205
ip6AddressLocalhost :: String
1206
ip6AddressLocalhost = "::1"
1207

    
1208
ip4Version :: Int
1209
ip4Version = 4
1210

    
1211
ip6Version :: Int
1212
ip6Version = 6
1213

    
1214
validIpVersions :: FrozenSet Int
1215
validIpVersions = ConstantUtils.mkSet [ip4Version, ip6Version]
1216

    
1217
tcpPingTimeout :: Int
1218
tcpPingTimeout = 10
1219

    
1220
defaultVg :: String
1221
defaultVg = "xenvg"
1222

    
1223
defaultDrbdHelper :: String
1224
defaultDrbdHelper = "/bin/true"
1225

    
1226
minVgSize :: Int
1227
minVgSize = 20480
1228

    
1229
defaultMacPrefix :: String
1230
defaultMacPrefix = "aa:00:00"
1231

    
1232
-- | Default maximum instance wait time (seconds)
1233
defaultShutdownTimeout :: Int
1234
defaultShutdownTimeout = 120
1235

    
1236
-- | Node clock skew (seconds)
1237
nodeMaxClockSkew :: Int
1238
nodeMaxClockSkew = 150
1239

    
1240
-- | Time for an intra-cluster disk transfer to wait for a connection
1241
diskTransferConnectTimeout :: Int
1242
diskTransferConnectTimeout = 60
1243

    
1244
-- | Disk index separator
1245
diskSeparator :: String
1246
diskSeparator = AutoConf.diskSeparator
1247

    
1248
ipCommandPath :: String
1249
ipCommandPath = AutoConf.ipPath
1250

    
1251
-- | Key for job IDs in opcode result
1252
jobIdsKey :: String
1253
jobIdsKey = "jobs"
1254

    
1255
-- * Runparts results
1256

    
1257
runpartsErr :: Int
1258
runpartsErr = 2
1259

    
1260
runpartsRun :: Int
1261
runpartsRun = 1
1262

    
1263
runpartsSkip :: Int
1264
runpartsSkip = 0
1265

    
1266
runpartsStatus :: [Int]
1267
runpartsStatus = [runpartsErr, runpartsRun, runpartsSkip]
1268

    
1269
-- * RPC
1270

    
1271
rpcEncodingNone :: Int
1272
rpcEncodingNone = 0
1273

    
1274
rpcEncodingZlibBase64 :: Int
1275
rpcEncodingZlibBase64 = 1
1276

    
1277
-- * Timeout table
1278
--
1279
-- Various time constants for the timeout table
1280

    
1281
rpcTmoUrgent :: Int
1282
rpcTmoUrgent = Types.rpcTimeoutToRaw Urgent
1283

    
1284
rpcTmoFast :: Int
1285
rpcTmoFast = Types.rpcTimeoutToRaw Fast
1286

    
1287
rpcTmoNormal :: Int
1288
rpcTmoNormal = Types.rpcTimeoutToRaw Normal
1289

    
1290
rpcTmoSlow :: Int
1291
rpcTmoSlow = Types.rpcTimeoutToRaw Slow
1292

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

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

    
1305
-- | Timeout for connecting to nodes (seconds)
1306
rpcConnectTimeout :: Int
1307
rpcConnectTimeout = 5
1308

    
1309
-- OS
1310

    
1311
osScriptCreate :: String
1312
osScriptCreate = "create"
1313

    
1314
osScriptExport :: String
1315
osScriptExport = "export"
1316

    
1317
osScriptImport :: String
1318
osScriptImport = "import"
1319

    
1320
osScriptRename :: String
1321
osScriptRename = "rename"
1322

    
1323
osScriptVerify :: String
1324
osScriptVerify = "verify"
1325

    
1326
osScripts :: [String]
1327
osScripts = [osScriptCreate, osScriptExport, osScriptImport, osScriptRename,
1328
             osScriptVerify]
1329

    
1330
osApiFile :: String
1331
osApiFile = "ganeti_api_version"
1332

    
1333
osVariantsFile :: String
1334
osVariantsFile = "variants.list"
1335

    
1336
osParametersFile :: String
1337
osParametersFile = "parameters.list"
1338

    
1339
osValidateParameters :: String
1340
osValidateParameters = "parameters"
1341

    
1342
osValidateCalls :: FrozenSet String
1343
osValidateCalls = ConstantUtils.mkSet [osValidateParameters]
1344

    
1345
-- | External Storage (ES) related constants
1346

    
1347
esActionAttach :: String
1348
esActionAttach = "attach"
1349

    
1350
esActionCreate :: String
1351
esActionCreate = "create"
1352

    
1353
esActionDetach :: String
1354
esActionDetach = "detach"
1355

    
1356
esActionGrow :: String
1357
esActionGrow = "grow"
1358

    
1359
esActionRemove :: String
1360
esActionRemove = "remove"
1361

    
1362
esActionSetinfo :: String
1363
esActionSetinfo = "setinfo"
1364

    
1365
esActionVerify :: String
1366
esActionVerify = "verify"
1367

    
1368
esScriptCreate :: String
1369
esScriptCreate = esActionCreate
1370

    
1371
esScriptRemove :: String
1372
esScriptRemove = esActionRemove
1373

    
1374
esScriptGrow :: String
1375
esScriptGrow = esActionGrow
1376

    
1377
esScriptAttach :: String
1378
esScriptAttach = esActionAttach
1379

    
1380
esScriptDetach :: String
1381
esScriptDetach = esActionDetach
1382

    
1383
esScriptSetinfo :: String
1384
esScriptSetinfo = esActionSetinfo
1385

    
1386
esScriptVerify :: String
1387
esScriptVerify = esActionVerify
1388

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

    
1399
esParametersFile :: String
1400
esParametersFile = "parameters.list"
1401

    
1402
-- * Reboot types
1403

    
1404
instanceRebootSoft :: String
1405
instanceRebootSoft = Types.rebootTypeToRaw RebootSoft
1406

    
1407
instanceRebootHard :: String
1408
instanceRebootHard = Types.rebootTypeToRaw RebootHard
1409

    
1410
instanceRebootFull :: String
1411
instanceRebootFull = Types.rebootTypeToRaw RebootFull
1412

    
1413
rebootTypes :: FrozenSet String
1414
rebootTypes = ConstantUtils.mkSet $ map Types.rebootTypeToRaw [minBound..]
1415

    
1416
-- * Instance reboot behaviors
1417

    
1418
instanceRebootAllowed :: String
1419
instanceRebootAllowed = "reboot"
1420

    
1421
instanceRebootExit :: String
1422
instanceRebootExit = "exit"
1423

    
1424
rebootBehaviors :: [String]
1425
rebootBehaviors = [instanceRebootAllowed, instanceRebootExit]
1426

    
1427
-- * VTypes
1428

    
1429
vtypeBool :: VType
1430
vtypeBool = VTypeBool
1431

    
1432
vtypeInt :: VType
1433
vtypeInt = VTypeInt
1434

    
1435
vtypeMaybeString :: VType
1436
vtypeMaybeString = VTypeMaybeString
1437

    
1438
-- | Size in MiBs
1439
vtypeSize :: VType
1440
vtypeSize = VTypeSize
1441

    
1442
vtypeString :: VType
1443
vtypeString = VTypeString
1444

    
1445
enforceableTypes :: FrozenSet VType
1446
enforceableTypes = ConstantUtils.mkSet [minBound..]
1447

    
1448
-- | Constant representing that the user does not specify any IP version
1449
ifaceNoIpVersionSpecified :: Int
1450
ifaceNoIpVersionSpecified = 0
1451

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

    
1473
-- * HV parameter names (global namespace)
1474

    
1475
hvAcpi :: String
1476
hvAcpi = "acpi"
1477

    
1478
hvBlockdevPrefix :: String
1479
hvBlockdevPrefix = "blockdev_prefix"
1480

    
1481
hvBootloaderArgs :: String
1482
hvBootloaderArgs = "bootloader_args"
1483

    
1484
hvBootloaderPath :: String
1485
hvBootloaderPath = "bootloader_path"
1486

    
1487
hvBootOrder :: String
1488
hvBootOrder = "boot_order"
1489

    
1490
hvCdromImagePath :: String
1491
hvCdromImagePath = "cdrom_image_path"
1492

    
1493
hvCpuCap :: String
1494
hvCpuCap = "cpu_cap"
1495

    
1496
hvCpuCores :: String
1497
hvCpuCores = "cpu_cores"
1498

    
1499
hvCpuMask :: String
1500
hvCpuMask = "cpu_mask"
1501

    
1502
hvCpuSockets :: String
1503
hvCpuSockets = "cpu_sockets"
1504

    
1505
hvCpuThreads :: String
1506
hvCpuThreads = "cpu_threads"
1507

    
1508
hvCpuType :: String
1509
hvCpuType = "cpu_type"
1510

    
1511
hvCpuWeight :: String
1512
hvCpuWeight = "cpu_weight"
1513

    
1514
hvDeviceModel :: String
1515
hvDeviceModel = "device_model"
1516

    
1517
hvDiskCache :: String
1518
hvDiskCache = "disk_cache"
1519

    
1520
hvDiskType :: String
1521
hvDiskType = "disk_type"
1522

    
1523
hvInitrdPath :: String
1524
hvInitrdPath = "initrd_path"
1525

    
1526
hvInitScript :: String
1527
hvInitScript = "init_script"
1528

    
1529
hvKernelArgs :: String
1530
hvKernelArgs = "kernel_args"
1531

    
1532
hvKernelPath :: String
1533
hvKernelPath = "kernel_path"
1534

    
1535
hvKeymap :: String
1536
hvKeymap = "keymap"
1537

    
1538
hvKvmCdrom2ImagePath :: String
1539
hvKvmCdrom2ImagePath = "cdrom2_image_path"
1540

    
1541
hvKvmCdromDiskType :: String
1542
hvKvmCdromDiskType = "cdrom_disk_type"
1543

    
1544
hvKvmExtra :: String
1545
hvKvmExtra = "kvm_extra"
1546

    
1547
hvKvmFlag :: String
1548
hvKvmFlag = "kvm_flag"
1549

    
1550
hvKvmFloppyImagePath :: String
1551
hvKvmFloppyImagePath = "floppy_image_path"
1552

    
1553
hvKvmMachineVersion :: String
1554
hvKvmMachineVersion = "machine_version"
1555

    
1556
hvKvmPath :: String
1557
hvKvmPath = "kvm_path"
1558

    
1559
hvKvmSpiceAudioCompr :: String
1560
hvKvmSpiceAudioCompr = "spice_playback_compression"
1561

    
1562
hvKvmSpiceBind :: String
1563
hvKvmSpiceBind = "spice_bind"
1564

    
1565
hvKvmSpiceIpVersion :: String
1566
hvKvmSpiceIpVersion = "spice_ip_version"
1567

    
1568
hvKvmSpiceJpegImgCompr :: String
1569
hvKvmSpiceJpegImgCompr = "spice_jpeg_wan_compression"
1570

    
1571
hvKvmSpiceLosslessImgCompr :: String
1572
hvKvmSpiceLosslessImgCompr = "spice_image_compression"
1573

    
1574
hvKvmSpicePasswordFile :: String
1575
hvKvmSpicePasswordFile = "spice_password_file"
1576

    
1577
hvKvmSpiceStreamingVideoDetection :: String
1578
hvKvmSpiceStreamingVideoDetection = "spice_streaming_video"
1579

    
1580
hvKvmSpiceTlsCiphers :: String
1581
hvKvmSpiceTlsCiphers = "spice_tls_ciphers"
1582

    
1583
hvKvmSpiceUseTls :: String
1584
hvKvmSpiceUseTls = "spice_use_tls"
1585

    
1586
hvKvmSpiceUseVdagent :: String
1587
hvKvmSpiceUseVdagent = "spice_use_vdagent"
1588

    
1589
hvKvmSpiceZlibGlzImgCompr :: String
1590
hvKvmSpiceZlibGlzImgCompr = "spice_zlib_glz_wan_compression"
1591

    
1592
hvKvmUseChroot :: String
1593
hvKvmUseChroot = "use_chroot"
1594

    
1595
hvKvmUserShutdown :: String
1596
hvKvmUserShutdown = "user_shutdown"
1597

    
1598
hvMemPath :: String
1599
hvMemPath = "mem_path"
1600

    
1601
hvMigrationBandwidth :: String
1602
hvMigrationBandwidth = "migration_bandwidth"
1603

    
1604
hvMigrationDowntime :: String
1605
hvMigrationDowntime = "migration_downtime"
1606

    
1607
hvMigrationMode :: String
1608
hvMigrationMode = "migration_mode"
1609

    
1610
hvMigrationPort :: String
1611
hvMigrationPort = "migration_port"
1612

    
1613
hvNicType :: String
1614
hvNicType = "nic_type"
1615

    
1616
hvPae :: String
1617
hvPae = "pae"
1618

    
1619
hvPassthrough :: String
1620
hvPassthrough = "pci_pass"
1621

    
1622
hvRebootBehavior :: String
1623
hvRebootBehavior = "reboot_behavior"
1624

    
1625
hvRootPath :: String
1626
hvRootPath = "root_path"
1627

    
1628
hvSecurityDomain :: String
1629
hvSecurityDomain = "security_domain"
1630

    
1631
hvSecurityModel :: String
1632
hvSecurityModel = "security_model"
1633

    
1634
hvSerialConsole :: String
1635
hvSerialConsole = "serial_console"
1636

    
1637
hvSerialSpeed :: String
1638
hvSerialSpeed = "serial_speed"
1639

    
1640
hvSoundhw :: String
1641
hvSoundhw = "soundhw"
1642

    
1643
hvUsbDevices :: String
1644
hvUsbDevices = "usb_devices"
1645

    
1646
hvUsbMouse :: String
1647
hvUsbMouse = "usb_mouse"
1648

    
1649
hvUseBootloader :: String
1650
hvUseBootloader = "use_bootloader"
1651

    
1652
hvUseLocaltime :: String
1653
hvUseLocaltime = "use_localtime"
1654

    
1655
hvVga :: String
1656
hvVga = "vga"
1657

    
1658
hvVhostNet :: String
1659
hvVhostNet = "vhost_net"
1660

    
1661
hvVifScript :: String
1662
hvVifScript = "vif_script"
1663

    
1664
hvVifType :: String
1665
hvVifType = "vif_type"
1666

    
1667
hvViridian :: String
1668
hvViridian = "viridian"
1669

    
1670
hvVncBindAddress :: String
1671
hvVncBindAddress = "vnc_bind_address"
1672

    
1673
hvVncPasswordFile :: String
1674
hvVncPasswordFile = "vnc_password_file"
1675

    
1676
hvVncTls :: String
1677
hvVncTls = "vnc_tls"
1678

    
1679
hvVncX509 :: String
1680
hvVncX509 = "vnc_x509_path"
1681

    
1682
hvVncX509Verify :: String
1683
hvVncX509Verify = "vnc_x509_verify"
1684

    
1685
hvVnetHdr :: String
1686
hvVnetHdr = "vnet_hdr"
1687

    
1688
hvXenCmd :: String
1689
hvXenCmd = "xen_cmd"
1690

    
1691
hvXenCpuid :: String
1692
hvXenCpuid = "cpuid"
1693

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

    
1709
hvsParameters :: FrozenSet String
1710
hvsParameters = ConstantUtils.mkSet $ Map.keys hvsParameterTypes
1711

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

    
1789
-- * Migration statuses
1790

    
1791
hvMigrationActive :: String
1792
hvMigrationActive = "active"
1793

    
1794
hvMigrationCancelled :: String
1795
hvMigrationCancelled = "cancelled"
1796

    
1797
hvMigrationCompleted :: String
1798
hvMigrationCompleted = "completed"
1799

    
1800
hvMigrationFailed :: String
1801
hvMigrationFailed = "failed"
1802

    
1803
hvMigrationValidStatuses :: FrozenSet String
1804
hvMigrationValidStatuses =
1805
  ConstantUtils.mkSet [hvMigrationActive,
1806
                       hvMigrationCancelled,
1807
                       hvMigrationCompleted,
1808
                       hvMigrationFailed]
1809

    
1810
hvMigrationFailedStatuses :: FrozenSet String
1811
hvMigrationFailedStatuses =
1812
  ConstantUtils.mkSet [hvMigrationFailed, hvMigrationCancelled]
1813

    
1814
-- | KVM-specific statuses
1815
--
1816
-- FIXME: this constant seems unnecessary
1817
hvKvmMigrationValidStatuses :: FrozenSet String
1818
hvKvmMigrationValidStatuses = hvMigrationValidStatuses
1819

    
1820
-- | Node info keys
1821
hvNodeinfoKeyVersion :: String
1822
hvNodeinfoKeyVersion = "hv_version"
1823

    
1824
-- * Hypervisor state
1825

    
1826
hvstCpuNode :: String
1827
hvstCpuNode = "cpu_node"
1828

    
1829
hvstCpuTotal :: String
1830
hvstCpuTotal = "cpu_total"
1831

    
1832
hvstMemoryHv :: String
1833
hvstMemoryHv = "mem_hv"
1834

    
1835
hvstMemoryNode :: String
1836
hvstMemoryNode = "mem_node"
1837

    
1838
hvstMemoryTotal :: String
1839
hvstMemoryTotal = "mem_total"
1840

    
1841
hvstsParameters :: FrozenSet String
1842
hvstsParameters =
1843
  ConstantUtils.mkSet [hvstCpuNode,
1844
                       hvstCpuTotal,
1845
                       hvstMemoryHv,
1846
                       hvstMemoryNode,
1847
                       hvstMemoryTotal]
1848

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

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

    
1866
-- * Disk state
1867

    
1868
dsDiskOverhead :: String
1869
dsDiskOverhead = "disk_overhead"
1870

    
1871
dsDiskReserved :: String
1872
dsDiskReserved = "disk_reserved"
1873

    
1874
dsDiskTotal :: String
1875
dsDiskTotal = "disk_total"
1876

    
1877
dsDefaults :: Map String Int
1878
dsDefaults =
1879
  Map.fromList
1880
  [(dsDiskTotal, 0),
1881
   (dsDiskReserved, 0),
1882
   (dsDiskOverhead, 0)]
1883

    
1884
dssParameterTypes :: Map String VType
1885
dssParameterTypes =
1886
  Map.fromList [(dsDiskTotal, VTypeInt),
1887
                (dsDiskReserved, VTypeInt),
1888
                (dsDiskOverhead, VTypeInt)]
1889

    
1890
dssParameters :: FrozenSet String
1891
dssParameters =
1892
  ConstantUtils.mkSet [dsDiskTotal, dsDiskReserved, dsDiskOverhead]
1893

    
1894
dsValidTypes :: FrozenSet String
1895
dsValidTypes = ConstantUtils.mkSet [Types.diskTemplateToRaw DTPlain]
1896

    
1897
-- Backend parameter names
1898

    
1899
beAlwaysFailover :: String
1900
beAlwaysFailover = "always_failover"
1901

    
1902
beAutoBalance :: String
1903
beAutoBalance = "auto_balance"
1904

    
1905
beMaxmem :: String
1906
beMaxmem = "maxmem"
1907

    
1908
-- | Deprecated and replaced by max and min mem
1909
beMemory :: String
1910
beMemory = "memory"
1911

    
1912
beMinmem :: String
1913
beMinmem = "minmem"
1914

    
1915
beSpindleUse :: String
1916
beSpindleUse = "spindle_use"
1917

    
1918
beVcpus :: String
1919
beVcpus = "vcpus"
1920

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

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

    
1937
besParameterCompat :: Map String VType
1938
besParameterCompat = Map.insert beMemory VTypeSize besParameterTypes
1939

    
1940
besParameters :: FrozenSet String
1941
besParameters =
1942
  ConstantUtils.mkSet [beAlwaysFailover,
1943
                       beAutoBalance,
1944
                       beMaxmem,
1945
                       beMinmem,
1946
                       beSpindleUse,
1947
                       beVcpus]
1948

    
1949
-- | Instance specs
1950
--
1951
-- FIXME: these should be associated with 'Ganeti.HTools.Types.ISpec'
1952

    
1953
ispecMemSize :: String
1954
ispecMemSize = ConstantUtils.ispecMemSize
1955

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

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

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

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

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

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

    
1981
ispecsParameters :: FrozenSet String
1982
ispecsParameters =
1983
  ConstantUtils.mkSet [ConstantUtils.ispecCpuCount,
1984
                       ConstantUtils.ispecDiskCount,
1985
                       ConstantUtils.ispecDiskSize,
1986
                       ConstantUtils.ispecMemSize,
1987
                       ConstantUtils.ispecNicCount,
1988
                       ConstantUtils.ispecSpindleUse]
1989

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

    
1993
ispecsMax :: String
1994
ispecsMax = "max"
1995

    
1996
ispecsMin :: String
1997
ispecsMin = "min"
1998

    
1999
ispecsStd :: String
2000
ispecsStd = ConstantUtils.ispecsStd
2001

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

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

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

    
2011
ispecsMinmaxKeys :: FrozenSet String
2012
ispecsMinmaxKeys = ConstantUtils.mkSet [ispecsMax, ispecsMin]
2013

    
2014
ipolicyParameters :: FrozenSet String
2015
ipolicyParameters =
2016
  ConstantUtils.mkSet [ConstantUtils.ipolicyVcpuRatio,
2017
                       ConstantUtils.ipolicySpindleRatio]
2018

    
2019
ipolicyAllKeys :: FrozenSet String
2020
ipolicyAllKeys =
2021
  ConstantUtils.union ipolicyParameters $
2022
  ConstantUtils.mkSet [ConstantUtils.ipolicyDts,
2023
                       ConstantUtils.ispecsMinmax,
2024
                       ispecsStd]
2025

    
2026
-- | Node parameter names
2027

    
2028
ndExclusiveStorage :: String
2029
ndExclusiveStorage = "exclusive_storage"
2030

    
2031
ndOobProgram :: String
2032
ndOobProgram = "oob_program"
2033

    
2034
ndSpindleCount :: String
2035
ndSpindleCount = "spindle_count"
2036

    
2037
ndOvs :: String
2038
ndOvs = "ovs"
2039

    
2040
ndOvsLink :: String
2041
ndOvsLink = "ovs_link"
2042

    
2043
ndOvsName :: String
2044
ndOvsName = "ovs_name"
2045

    
2046
ndSshPort :: String
2047
ndSshPort = "ssh_port"
2048

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

    
2060
ndsParameters :: FrozenSet String
2061
ndsParameters = ConstantUtils.mkSet (Map.keys ndsParameterTypes)
2062

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

    
2073
-- * Logical Disks parameters
2074

    
2075
ldpAccess :: String
2076
ldpAccess = "access"
2077

    
2078
ldpBarriers :: String
2079
ldpBarriers = "disabled-barriers"
2080

    
2081
ldpDefaultMetavg :: String
2082
ldpDefaultMetavg = "default-metavg"
2083

    
2084
ldpDelayTarget :: String
2085
ldpDelayTarget = "c-delay-target"
2086

    
2087
ldpDiskCustom :: String
2088
ldpDiskCustom = "disk-custom"
2089

    
2090
ldpDynamicResync :: String
2091
ldpDynamicResync = "dynamic-resync"
2092

    
2093
ldpFillTarget :: String
2094
ldpFillTarget = "c-fill-target"
2095

    
2096
ldpMaxRate :: String
2097
ldpMaxRate = "c-max-rate"
2098

    
2099
ldpMinRate :: String
2100
ldpMinRate = "c-min-rate"
2101

    
2102
ldpNetCustom :: String
2103
ldpNetCustom = "net-custom"
2104

    
2105
ldpNoMetaFlush :: String
2106
ldpNoMetaFlush = "disable-meta-flush"
2107

    
2108
ldpPlanAhead :: String
2109
ldpPlanAhead = "c-plan-ahead"
2110

    
2111
ldpPool :: String
2112
ldpPool = "pool"
2113

    
2114
ldpProtocol :: String
2115
ldpProtocol = "protocol"
2116

    
2117
ldpResyncRate :: String
2118
ldpResyncRate = "resync-rate"
2119

    
2120
ldpStripes :: String
2121
ldpStripes = "stripes"
2122

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

    
2143
diskLdParameters :: FrozenSet String
2144
diskLdParameters = ConstantUtils.mkSet (Map.keys diskLdTypes)
2145

    
2146
-- * Disk template parameters
2147
--
2148
-- Disk template parameters can be set/changed by the user via
2149
-- gnt-cluster and gnt-group)
2150

    
2151
drbdResyncRate :: String
2152
drbdResyncRate = "resync-rate"
2153

    
2154
drbdDataStripes :: String
2155
drbdDataStripes = "data-stripes"
2156

    
2157
drbdMetaStripes :: String
2158
drbdMetaStripes = "meta-stripes"
2159

    
2160
drbdDiskBarriers :: String
2161
drbdDiskBarriers = "disk-barriers"
2162

    
2163
drbdMetaBarriers :: String
2164
drbdMetaBarriers = "meta-barriers"
2165

    
2166
drbdDefaultMetavg :: String
2167
drbdDefaultMetavg = "metavg"
2168

    
2169
drbdDiskCustom :: String
2170
drbdDiskCustom = "disk-custom"
2171

    
2172
drbdNetCustom :: String
2173
drbdNetCustom = "net-custom"
2174

    
2175
drbdProtocol :: String
2176
drbdProtocol = "protocol"
2177

    
2178
drbdDynamicResync :: String
2179
drbdDynamicResync = "dynamic-resync"
2180

    
2181
drbdPlanAhead :: String
2182
drbdPlanAhead = "c-plan-ahead"
2183

    
2184
drbdFillTarget :: String
2185
drbdFillTarget = "c-fill-target"
2186

    
2187
drbdDelayTarget :: String
2188
drbdDelayTarget = "c-delay-target"
2189

    
2190
drbdMaxRate :: String
2191
drbdMaxRate = "c-max-rate"
2192

    
2193
drbdMinRate :: String
2194
drbdMinRate = "c-min-rate"
2195

    
2196
lvStripes :: String
2197
lvStripes = "stripes"
2198

    
2199
rbdAccess :: String
2200
rbdAccess = "access"
2201

    
2202
rbdPool :: String
2203
rbdPool = "pool"
2204

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

    
2230
diskDtParameters :: FrozenSet String
2231
diskDtParameters = ConstantUtils.mkSet (Map.keys diskDtTypes)
2232

    
2233
-- * Dynamic disk parameters
2234

    
2235
ddpLocalIp :: String
2236
ddpLocalIp = "local-ip"
2237

    
2238
ddpRemoteIp :: String
2239
ddpRemoteIp = "remote-ip"
2240

    
2241
ddpPort :: String
2242
ddpPort = "port"
2243

    
2244
ddpLocalMinor :: String
2245
ddpLocalMinor = "local-minor"
2246

    
2247
ddpRemoteMinor :: String
2248
ddpRemoteMinor = "remote-minor"
2249

    
2250
-- * OOB supported commands
2251

    
2252
oobPowerOn :: String
2253
oobPowerOn = Types.oobCommandToRaw OobPowerOn
2254

    
2255
oobPowerOff :: String
2256
oobPowerOff = Types.oobCommandToRaw OobPowerOff
2257

    
2258
oobPowerCycle :: String
2259
oobPowerCycle = Types.oobCommandToRaw OobPowerCycle
2260

    
2261
oobPowerStatus :: String
2262
oobPowerStatus = Types.oobCommandToRaw OobPowerStatus
2263

    
2264
oobHealth :: String
2265
oobHealth = Types.oobCommandToRaw OobHealth
2266

    
2267
oobCommands :: FrozenSet String
2268
oobCommands = ConstantUtils.mkSet $ map Types.oobCommandToRaw [minBound..]
2269

    
2270
oobPowerStatusPowered :: String
2271
oobPowerStatusPowered = "powered"
2272

    
2273
-- | 60 seconds
2274
oobTimeout :: Int
2275
oobTimeout = 60
2276

    
2277
-- | 2 seconds
2278
oobPowerDelay :: Double
2279
oobPowerDelay = 2.0
2280

    
2281
oobStatusCritical :: String
2282
oobStatusCritical = Types.oobStatusToRaw OobStatusCritical
2283

    
2284
oobStatusOk :: String
2285
oobStatusOk = Types.oobStatusToRaw OobStatusOk
2286

    
2287
oobStatusUnknown :: String
2288
oobStatusUnknown = Types.oobStatusToRaw OobStatusUnknown
2289

    
2290
oobStatusWarning :: String
2291
oobStatusWarning = Types.oobStatusToRaw OobStatusWarning
2292

    
2293
oobStatuses :: FrozenSet String
2294
oobStatuses = ConstantUtils.mkSet $ map Types.oobStatusToRaw [minBound..]
2295

    
2296
-- | Instance Parameters Profile
2297
ppDefault :: String
2298
ppDefault = "default"
2299

    
2300
-- * nic* constants are used inside the ganeti config
2301

    
2302
nicLink :: String
2303
nicLink = "link"
2304

    
2305
nicMode :: String
2306
nicMode = "mode"
2307

    
2308
nicVlan :: String
2309
nicVlan = "vlan"
2310

    
2311
nicsParameterTypes :: Map String VType
2312
nicsParameterTypes =
2313
  Map.fromList [(nicMode, vtypeString),
2314
                (nicLink, vtypeString),
2315
                (nicVlan, vtypeString)]
2316

    
2317
nicsParameters :: FrozenSet String
2318
nicsParameters = ConstantUtils.mkSet (Map.keys nicsParameterTypes)
2319

    
2320
nicModeBridged :: String
2321
nicModeBridged = Types.nICModeToRaw NMBridged
2322

    
2323
nicModeRouted :: String
2324
nicModeRouted = Types.nICModeToRaw NMRouted
2325

    
2326
nicModeOvs :: String
2327
nicModeOvs = Types.nICModeToRaw NMOvs
2328

    
2329
nicIpPool :: String
2330
nicIpPool = Types.nICModeToRaw NMPool
2331

    
2332
nicValidModes :: FrozenSet String
2333
nicValidModes = ConstantUtils.mkSet $ map Types.nICModeToRaw [minBound..]
2334

    
2335
releaseAction :: String
2336
releaseAction = "release"
2337

    
2338
reserveAction :: String
2339
reserveAction = "reserve"
2340

    
2341
-- * idisk* constants are used in opcodes, to create/change disks
2342

    
2343
idiskAdopt :: String
2344
idiskAdopt = "adopt"
2345

    
2346
idiskMetavg :: String
2347
idiskMetavg = "metavg"
2348

    
2349
idiskMode :: String
2350
idiskMode = "mode"
2351

    
2352
idiskName :: String
2353
idiskName = "name"
2354

    
2355
idiskSize :: String
2356
idiskSize = "size"
2357

    
2358
idiskSpindles :: String
2359
idiskSpindles = "spindles"
2360

    
2361
idiskVg :: String
2362
idiskVg = "vg"
2363

    
2364
idiskProvider :: String
2365
idiskProvider = "provider"
2366

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

    
2378
idiskParams :: FrozenSet String
2379
idiskParams = ConstantUtils.mkSet (Map.keys idiskParamsTypes)
2380

    
2381
modifiableIdiskParamsTypes :: Map String VType
2382
modifiableIdiskParamsTypes =
2383
  Map.fromList [(idiskMode, VTypeString),
2384
                (idiskName, VTypeString)]
2385

    
2386
modifiableIdiskParams :: FrozenSet String
2387
modifiableIdiskParams =
2388
  ConstantUtils.mkSet (Map.keys modifiableIdiskParamsTypes)
2389

    
2390
-- * inic* constants are used in opcodes, to create/change nics
2391

    
2392
inicBridge :: String
2393
inicBridge = "bridge"
2394

    
2395
inicIp :: String
2396
inicIp = "ip"
2397

    
2398
inicLink :: String
2399
inicLink = "link"
2400

    
2401
inicMac :: String
2402
inicMac = "mac"
2403

    
2404
inicMode :: String
2405
inicMode = "mode"
2406

    
2407
inicName :: String
2408
inicName = "name"
2409

    
2410
inicNetwork :: String
2411
inicNetwork = "network"
2412

    
2413
inicVlan :: String
2414
inicVlan = "vlan"
2415

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

    
2427
inicParams :: FrozenSet String
2428
inicParams = ConstantUtils.mkSet (Map.keys inicParamsTypes)
2429

    
2430
-- * Hypervisor constants
2431

    
2432
htXenPvm :: String
2433
htXenPvm = Types.hypervisorToRaw XenPvm
2434

    
2435
htFake :: String
2436
htFake = Types.hypervisorToRaw Fake
2437

    
2438
htXenHvm :: String
2439
htXenHvm = Types.hypervisorToRaw XenHvm
2440

    
2441
htKvm :: String
2442
htKvm = Types.hypervisorToRaw Kvm
2443

    
2444
htChroot :: String
2445
htChroot = Types.hypervisorToRaw Chroot
2446

    
2447
htLxc :: String
2448
htLxc = Types.hypervisorToRaw Lxc
2449

    
2450
hyperTypes :: FrozenSet String
2451
hyperTypes = ConstantUtils.mkSet $ map Types.hypervisorToRaw [minBound..]
2452

    
2453
htsReqPort :: FrozenSet String
2454
htsReqPort = ConstantUtils.mkSet [htXenHvm, htKvm]
2455

    
2456
vncBasePort :: Int
2457
vncBasePort = 5900
2458

    
2459
vncDefaultBindAddress :: String
2460
vncDefaultBindAddress = ip4AddressAny
2461

    
2462
-- * NIC types
2463

    
2464
htNicE1000 :: String
2465
htNicE1000 = "e1000"
2466

    
2467
htNicI82551 :: String
2468
htNicI82551 = "i82551"
2469

    
2470
htNicI8259er :: String
2471
htNicI8259er = "i82559er"
2472

    
2473
htNicI85557b :: String
2474
htNicI85557b = "i82557b"
2475

    
2476
htNicNe2kIsa :: String
2477
htNicNe2kIsa = "ne2k_isa"
2478

    
2479
htNicNe2kPci :: String
2480
htNicNe2kPci = "ne2k_pci"
2481

    
2482
htNicParavirtual :: String
2483
htNicParavirtual = "paravirtual"
2484

    
2485
htNicPcnet :: String
2486
htNicPcnet = "pcnet"
2487

    
2488
htNicRtl8139 :: String
2489
htNicRtl8139 = "rtl8139"
2490

    
2491
htHvmValidNicTypes :: FrozenSet String
2492
htHvmValidNicTypes =
2493
  ConstantUtils.mkSet [htNicE1000,
2494
                       htNicNe2kIsa,
2495
                       htNicNe2kPci,
2496
                       htNicParavirtual,
2497
                       htNicRtl8139]
2498

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

    
2511
-- * Vif types
2512

    
2513
-- | Default vif type in xen-hvm
2514
htHvmVifIoemu :: String
2515
htHvmVifIoemu = "ioemu"
2516

    
2517
htHvmVifVif :: String
2518
htHvmVifVif = "vif"
2519

    
2520
htHvmValidVifTypes :: FrozenSet String
2521
htHvmValidVifTypes = ConstantUtils.mkSet [htHvmVifIoemu, htHvmVifVif]
2522

    
2523
-- * Disk types
2524

    
2525
htDiskIde :: String
2526
htDiskIde = "ide"
2527

    
2528
htDiskIoemu :: String
2529
htDiskIoemu = "ioemu"
2530

    
2531
htDiskMtd :: String
2532
htDiskMtd = "mtd"
2533

    
2534
htDiskParavirtual :: String
2535
htDiskParavirtual = "paravirtual"
2536

    
2537
htDiskPflash :: String
2538
htDiskPflash = "pflash"
2539

    
2540
htDiskScsi :: String
2541
htDiskScsi = "scsi"
2542

    
2543
htDiskSd :: String
2544
htDiskSd = "sd"
2545

    
2546
htHvmValidDiskTypes :: FrozenSet String
2547
htHvmValidDiskTypes = ConstantUtils.mkSet [htDiskIoemu, htDiskParavirtual]
2548

    
2549
htKvmValidDiskTypes :: FrozenSet String
2550
htKvmValidDiskTypes =
2551
  ConstantUtils.mkSet [htDiskIde,
2552
                       htDiskMtd,
2553
                       htDiskParavirtual,
2554
                       htDiskPflash,
2555
                       htDiskScsi,
2556
                       htDiskSd]
2557

    
2558
htCacheDefault :: String
2559
htCacheDefault = "default"
2560

    
2561
htCacheNone :: String
2562
htCacheNone = "none"
2563

    
2564
htCacheWback :: String
2565
htCacheWback = "writeback"
2566

    
2567
htCacheWthrough :: String
2568
htCacheWthrough = "writethrough"
2569

    
2570
htValidCacheTypes :: FrozenSet String
2571
htValidCacheTypes =
2572
  ConstantUtils.mkSet [htCacheDefault,
2573
                       htCacheNone,
2574
                       htCacheWback,
2575
                       htCacheWthrough]
2576

    
2577
-- * Mouse types
2578

    
2579
htMouseMouse :: String
2580
htMouseMouse = "mouse"
2581

    
2582
htMouseTablet :: String
2583
htMouseTablet = "tablet"
2584

    
2585
htKvmValidMouseTypes :: FrozenSet String
2586
htKvmValidMouseTypes = ConstantUtils.mkSet [htMouseMouse, htMouseTablet]
2587

    
2588
-- * Boot order
2589

    
2590
htBoCdrom :: String
2591
htBoCdrom = "cdrom"
2592

    
2593
htBoDisk :: String
2594
htBoDisk = "disk"
2595

    
2596
htBoFloppy :: String
2597
htBoFloppy = "floppy"
2598

    
2599
htBoNetwork :: String
2600
htBoNetwork = "network"
2601

    
2602
htKvmValidBoTypes :: FrozenSet String
2603
htKvmValidBoTypes =
2604
  ConstantUtils.mkSet [htBoCdrom, htBoDisk, htBoFloppy, htBoNetwork]
2605

    
2606
-- * SPICE lossless image compression options
2607

    
2608
htKvmSpiceLosslessImgComprAutoGlz :: String
2609
htKvmSpiceLosslessImgComprAutoGlz = "auto_glz"
2610

    
2611
htKvmSpiceLosslessImgComprAutoLz :: String
2612
htKvmSpiceLosslessImgComprAutoLz = "auto_lz"
2613

    
2614
htKvmSpiceLosslessImgComprGlz :: String
2615
htKvmSpiceLosslessImgComprGlz = "glz"
2616

    
2617
htKvmSpiceLosslessImgComprLz :: String
2618
htKvmSpiceLosslessImgComprLz = "lz"
2619

    
2620
htKvmSpiceLosslessImgComprOff :: String
2621
htKvmSpiceLosslessImgComprOff = "off"
2622

    
2623
htKvmSpiceLosslessImgComprQuic :: String
2624
htKvmSpiceLosslessImgComprQuic = "quic"
2625

    
2626
htKvmSpiceValidLosslessImgComprOptions :: FrozenSet String
2627
htKvmSpiceValidLosslessImgComprOptions =
2628
  ConstantUtils.mkSet [htKvmSpiceLosslessImgComprAutoGlz,
2629
                       htKvmSpiceLosslessImgComprAutoLz,
2630
                       htKvmSpiceLosslessImgComprGlz,
2631
                       htKvmSpiceLosslessImgComprLz,
2632
                       htKvmSpiceLosslessImgComprOff,
2633
                       htKvmSpiceLosslessImgComprQuic]
2634

    
2635
htKvmSpiceLossyImgComprAlways :: String
2636
htKvmSpiceLossyImgComprAlways = "always"
2637

    
2638
htKvmSpiceLossyImgComprAuto :: String
2639
htKvmSpiceLossyImgComprAuto = "auto"
2640

    
2641
htKvmSpiceLossyImgComprNever :: String
2642
htKvmSpiceLossyImgComprNever = "never"
2643

    
2644
htKvmSpiceValidLossyImgComprOptions :: FrozenSet String
2645
htKvmSpiceValidLossyImgComprOptions =
2646
  ConstantUtils.mkSet [htKvmSpiceLossyImgComprAlways,
2647
                       htKvmSpiceLossyImgComprAuto,
2648
                       htKvmSpiceLossyImgComprNever]
2649

    
2650
-- * SPICE video stream detection
2651

    
2652
htKvmSpiceVideoStreamDetectionAll :: String
2653
htKvmSpiceVideoStreamDetectionAll = "all"
2654

    
2655
htKvmSpiceVideoStreamDetectionFilter :: String
2656
htKvmSpiceVideoStreamDetectionFilter = "filter"
2657

    
2658
htKvmSpiceVideoStreamDetectionOff :: String
2659
htKvmSpiceVideoStreamDetectionOff = "off"
2660

    
2661
htKvmSpiceValidVideoStreamDetectionOptions :: FrozenSet String
2662
htKvmSpiceValidVideoStreamDetectionOptions =
2663
  ConstantUtils.mkSet [htKvmSpiceVideoStreamDetectionAll,
2664
                       htKvmSpiceVideoStreamDetectionFilter,
2665
                       htKvmSpiceVideoStreamDetectionOff]
2666

    
2667
-- * Security models
2668

    
2669
htSmNone :: String
2670
htSmNone = "none"
2671

    
2672
htSmPool :: String
2673
htSmPool = "pool"
2674

    
2675
htSmUser :: String
2676
htSmUser = "user"
2677

    
2678
htKvmValidSmTypes :: FrozenSet String
2679
htKvmValidSmTypes = ConstantUtils.mkSet [htSmNone, htSmPool, htSmUser]
2680

    
2681
-- * Kvm flag values
2682

    
2683
htKvmDisabled :: String
2684
htKvmDisabled = "disabled"
2685

    
2686
htKvmEnabled :: String
2687
htKvmEnabled = "enabled"
2688

    
2689
htKvmFlagValues :: FrozenSet String
2690
htKvmFlagValues = ConstantUtils.mkSet [htKvmDisabled, htKvmEnabled]
2691

    
2692
-- * Migration type
2693

    
2694
htMigrationLive :: String
2695
htMigrationLive = Types.migrationModeToRaw MigrationLive
2696

    
2697
htMigrationNonlive :: String
2698
htMigrationNonlive = Types.migrationModeToRaw MigrationNonLive
2699

    
2700
htMigrationModes :: FrozenSet String
2701
htMigrationModes =
2702
  ConstantUtils.mkSet $ map Types.migrationModeToRaw [minBound..]
2703

    
2704
-- * Cluster verify steps
2705

    
2706
verifyNplusoneMem :: String
2707
verifyNplusoneMem = Types.verifyOptionalChecksToRaw VerifyNPlusOneMem
2708

    
2709
verifyOptionalChecks :: FrozenSet String
2710
verifyOptionalChecks =
2711
  ConstantUtils.mkSet $ map Types.verifyOptionalChecksToRaw [minBound..]
2712

    
2713
-- * Cluster Verify error classes
2714

    
2715
cvTcluster :: String
2716
cvTcluster = "cluster"
2717

    
2718
cvTgroup :: String
2719
cvTgroup = "group"
2720

    
2721
cvTnode :: String
2722
cvTnode = "node"
2723

    
2724
cvTinstance :: String
2725
cvTinstance = "instance"
2726

    
2727
-- * Cluster Verify error levels
2728

    
2729
cvWarning :: String
2730
cvWarning = "WARNING"
2731

    
2732
cvError :: String
2733
cvError = "ERROR"
2734

    
2735
-- * Cluster Verify error codes and documentation
2736

    
2737
cvEclustercert :: (String, String, String)
2738
cvEclustercert =
2739
  ("cluster",
2740
   Types.cVErrorCodeToRaw CvECLUSTERCERT,
2741
   "Cluster certificate files verification failure")
2742

    
2743
cvEclusterclientcert :: (String, String, String)
2744
cvEclusterclientcert =
2745
  ("cluster",
2746
   Types.cVErrorCodeToRaw CvECLUSTERCLIENTCERT,
2747
   "Cluster client certificate files verification failure")
2748

    
2749
cvEclustercfg :: (String, String, String)
2750
cvEclustercfg =
2751
  ("cluster",
2752
   Types.cVErrorCodeToRaw CvECLUSTERCFG,
2753
   "Cluster configuration verification failure")
2754

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

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

    
2767
cvEclusterfilecheck :: (String, String, String)
2768
cvEclusterfilecheck =
2769
  ("cluster",
2770
   Types.cVErrorCodeToRaw CvECLUSTERFILECHECK,
2771
   "Cluster configuration verification failure")
2772

    
2773
cvEgroupdifferentpvsize :: (String, String, String)
2774
cvEgroupdifferentpvsize =
2775
  ("group",
2776
   Types.cVErrorCodeToRaw CvEGROUPDIFFERENTPVSIZE,
2777
   "PVs in the group have different sizes")
2778

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

    
2785
cvEinstancedown :: (String, String, String)
2786
cvEinstancedown =
2787
  ("instance",
2788
   Types.cVErrorCodeToRaw CvEINSTANCEDOWN,
2789
   "Instance not running on its primary node")
2790

    
2791
cvEinstancefaultydisk :: (String, String, String)
2792
cvEinstancefaultydisk =
2793
  ("instance",
2794
   Types.cVErrorCodeToRaw CvEINSTANCEFAULTYDISK,
2795
   "Impossible to retrieve status for a disk")
2796

    
2797
cvEinstancelayout :: (String, String, String)
2798
cvEinstancelayout =
2799
  ("instance",
2800
   Types.cVErrorCodeToRaw CvEINSTANCELAYOUT,
2801
   "Instance has multiple secondary nodes")
2802

    
2803
cvEinstancemissingcfgparameter :: (String, String, String)
2804
cvEinstancemissingcfgparameter =
2805
  ("instance",
2806
   Types.cVErrorCodeToRaw CvEINSTANCEMISSINGCFGPARAMETER,
2807
   "A configuration parameter for an instance is missing")
2808

    
2809
cvEinstancemissingdisk :: (String, String, String)
2810
cvEinstancemissingdisk =
2811
  ("instance",
2812
   Types.cVErrorCodeToRaw CvEINSTANCEMISSINGDISK,
2813
   "Missing volume on an instance")
2814

    
2815
cvEinstancepolicy :: (String, String, String)
2816
cvEinstancepolicy =
2817
  ("instance",
2818
   Types.cVErrorCodeToRaw CvEINSTANCEPOLICY,
2819
   "Instance does not meet policy")
2820

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

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

    
2833
cvEinstancewrongnode :: (String, String, String)
2834
cvEinstancewrongnode =
2835
  ("instance",
2836
   Types.cVErrorCodeToRaw CvEINSTANCEWRONGNODE,
2837
   "Instance running on the wrong node")
2838

    
2839
cvEnodedrbd :: (String, String, String)
2840
cvEnodedrbd =
2841
  ("node",
2842
   Types.cVErrorCodeToRaw CvENODEDRBD,
2843
   "Error parsing the DRBD status file")
2844

    
2845
cvEnodedrbdhelper :: (String, String, String)
2846
cvEnodedrbdhelper =
2847
  ("node",
2848
   Types.cVErrorCodeToRaw CvENODEDRBDHELPER,
2849
   "Error caused by the DRBD helper")
2850

    
2851
cvEnodedrbdversion :: (String, String, String)
2852
cvEnodedrbdversion =
2853
  ("node",
2854
   Types.cVErrorCodeToRaw CvENODEDRBDVERSION,
2855
   "DRBD version mismatch within a node group")
2856

    
2857
cvEnodefilecheck :: (String, String, String)
2858
cvEnodefilecheck =
2859
  ("node",
2860
   Types.cVErrorCodeToRaw CvENODEFILECHECK,
2861
   "Error retrieving the checksum of the node files")
2862

    
2863
cvEnodefilestoragepaths :: (String, String, String)
2864
cvEnodefilestoragepaths =
2865
  ("node",
2866
   Types.cVErrorCodeToRaw CvENODEFILESTORAGEPATHS,
2867
   "Detected bad file storage paths")
2868

    
2869
cvEnodefilestoragepathunusable :: (String, String, String)
2870
cvEnodefilestoragepathunusable =
2871
  ("node",
2872
   Types.cVErrorCodeToRaw CvENODEFILESTORAGEPATHUNUSABLE,
2873
   "File storage path unusable")
2874

    
2875
cvEnodehooks :: (String, String, String)
2876
cvEnodehooks =
2877
  ("node",
2878
   Types.cVErrorCodeToRaw CvENODEHOOKS,
2879
   "Communication failure in hooks execution")
2880

    
2881
cvEnodehv :: (String, String, String)
2882
cvEnodehv =
2883
  ("node",
2884
   Types.cVErrorCodeToRaw CvENODEHV,
2885
   "Hypervisor parameters verification failure")
2886

    
2887
cvEnodelvm :: (String, String, String)
2888
cvEnodelvm =
2889
  ("node",
2890
   Types.cVErrorCodeToRaw CvENODELVM,
2891
   "LVM-related node error")
2892

    
2893
cvEnoden1 :: (String, String, String)
2894
cvEnoden1 =
2895
  ("node",
2896
   Types.cVErrorCodeToRaw CvENODEN1,
2897
   "Not enough memory to accommodate instance failovers")
2898

    
2899
cvEnodenet :: (String, String, String)
2900
cvEnodenet =
2901
  ("node",
2902
   Types.cVErrorCodeToRaw CvENODENET,
2903
   "Network-related node error")
2904

    
2905
cvEnodeoobpath :: (String, String, String)
2906
cvEnodeoobpath =
2907
  ("node",
2908
   Types.cVErrorCodeToRaw CvENODEOOBPATH,
2909
   "Invalid Out Of Band path")
2910

    
2911
cvEnodeorphaninstance :: (String, String, String)
2912
cvEnodeorphaninstance =
2913
  ("node",
2914
   Types.cVErrorCodeToRaw CvENODEORPHANINSTANCE,
2915
   "Unknown intance running on a node")
2916

    
2917
cvEnodeorphanlv :: (String, String, String)
2918
cvEnodeorphanlv =
2919
  ("node",
2920
   Types.cVErrorCodeToRaw CvENODEORPHANLV,
2921
   "Unknown LVM logical volume")
2922

    
2923
cvEnodeos :: (String, String, String)
2924
cvEnodeos =
2925
  ("node",
2926
   Types.cVErrorCodeToRaw CvENODEOS,
2927
   "OS-related node error")
2928

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

    
2935
cvEnodesetup :: (String, String, String)
2936
cvEnodesetup =
2937
  ("node",
2938
   Types.cVErrorCodeToRaw CvENODESETUP,
2939
   "Node setup error")
2940

    
2941
cvEnodesharedfilestoragepathunusable :: (String, String, String)
2942
cvEnodesharedfilestoragepathunusable =
2943
  ("node",
2944
   Types.cVErrorCodeToRaw CvENODESHAREDFILESTORAGEPATHUNUSABLE,
2945
   "Shared file storage path unusable")
2946

    
2947
cvEnodessh :: (String, String, String)
2948
cvEnodessh =
2949
  ("node",
2950
   Types.cVErrorCodeToRaw CvENODESSH,
2951
   "SSH-related node error")
2952

    
2953
cvEnodetime :: (String, String, String)
2954
cvEnodetime =
2955
  ("node",
2956
   Types.cVErrorCodeToRaw CvENODETIME,
2957
   "Node returned invalid time")
2958

    
2959
cvEnodeuserscripts :: (String, String, String)
2960
cvEnodeuserscripts =
2961
  ("node",
2962
   Types.cVErrorCodeToRaw CvENODEUSERSCRIPTS,
2963
   "User scripts not present or not executable")
2964

    
2965
cvEnodeversion :: (String, String, String)
2966
cvEnodeversion =
2967
  ("node",
2968
   Types.cVErrorCodeToRaw CvENODEVERSION,
2969
   "Protocol version mismatch or Ganeti version mismatch")
2970

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

    
3013
cvAllEcodesStrings :: FrozenSet String
3014
cvAllEcodesStrings =
3015
  ConstantUtils.mkSet $ map Types.cVErrorCodeToRaw [minBound..]
3016

    
3017
-- * Node verify constants
3018

    
3019
nvBridges :: String
3020
nvBridges = "bridges"
3021

    
3022
nvClientCert :: String
3023
nvClientCert = "client-cert"
3024

    
3025
nvDrbdhelper :: String
3026
nvDrbdhelper = "drbd-helper"
3027

    
3028
nvDrbdversion :: String
3029
nvDrbdversion = "drbd-version"
3030

    
3031
nvDrbdlist :: String
3032
nvDrbdlist = "drbd-list"
3033

    
3034
nvExclusivepvs :: String
3035
nvExclusivepvs = "exclusive-pvs"
3036

    
3037
nvFilelist :: String
3038
nvFilelist = "filelist"
3039

    
3040
nvAcceptedStoragePaths :: String
3041
nvAcceptedStoragePaths = "allowed-file-storage-paths"
3042

    
3043
nvFileStoragePath :: String
3044
nvFileStoragePath = "file-storage-path"
3045

    
3046
nvSharedFileStoragePath :: String
3047
nvSharedFileStoragePath = "shared-file-storage-path"
3048

    
3049
nvHvinfo :: String
3050
nvHvinfo = "hvinfo"
3051

    
3052
nvHvparams :: String
3053
nvHvparams = "hvparms"
3054

    
3055
nvHypervisor :: String
3056
nvHypervisor = "hypervisor"
3057

    
3058
nvInstancelist :: String
3059
nvInstancelist = "instancelist"
3060

    
3061
nvLvlist :: String
3062
nvLvlist = "lvlist"
3063

    
3064
nvMasterip :: String
3065
nvMasterip = "master-ip"
3066

    
3067
nvNodelist :: String
3068
nvNodelist = "nodelist"
3069

    
3070
nvNodenettest :: String
3071
nvNodenettest = "node-net-test"
3072

    
3073
nvNodesetup :: String
3074
nvNodesetup = "nodesetup"
3075

    
3076
nvOobPaths :: String
3077
nvOobPaths = "oob-paths"
3078

    
3079
nvOslist :: String
3080
nvOslist = "oslist"
3081

    
3082
nvPvlist :: String
3083
nvPvlist = "pvlist"
3084

    
3085
nvTime :: String
3086
nvTime = "time"
3087

    
3088
nvUserscripts :: String
3089
nvUserscripts = "user-scripts"
3090

    
3091
nvVersion :: String
3092
nvVersion = "version"
3093

    
3094
nvVglist :: String
3095
nvVglist = "vglist"
3096

    
3097
nvVmnodes :: String
3098
nvVmnodes = "vmnodes"
3099

    
3100
-- * Instance status
3101

    
3102
inststAdmindown :: String
3103
inststAdmindown = Types.instanceStatusToRaw StatusDown
3104

    
3105
inststAdminoffline :: String
3106
inststAdminoffline = Types.instanceStatusToRaw StatusOffline
3107

    
3108
inststErrordown :: String
3109
inststErrordown = Types.instanceStatusToRaw ErrorDown
3110

    
3111
inststErrorup :: String
3112
inststErrorup = Types.instanceStatusToRaw ErrorUp
3113

    
3114
inststNodedown :: String
3115
inststNodedown = Types.instanceStatusToRaw NodeDown
3116

    
3117
inststNodeoffline :: String
3118
inststNodeoffline = Types.instanceStatusToRaw NodeOffline
3119

    
3120
inststRunning :: String
3121
inststRunning = Types.instanceStatusToRaw Running
3122

    
3123
inststUserdown :: String
3124
inststUserdown = Types.instanceStatusToRaw UserDown
3125

    
3126
inststWrongnode :: String
3127
inststWrongnode = Types.instanceStatusToRaw WrongNode
3128

    
3129
inststAll :: FrozenSet String
3130
inststAll = ConstantUtils.mkSet $ map Types.instanceStatusToRaw [minBound..]
3131

    
3132
-- * Admin states
3133

    
3134
adminstDown :: String
3135
adminstDown = Types.adminStateToRaw AdminDown
3136

    
3137
adminstOffline :: String
3138
adminstOffline = Types.adminStateToRaw AdminOffline
3139

    
3140
adminstUp :: String
3141
adminstUp = Types.adminStateToRaw AdminUp
3142

    
3143
adminstAll :: FrozenSet String
3144
adminstAll = ConstantUtils.mkSet $ map Types.adminStateToRaw [minBound..]
3145

    
3146
-- * Node roles
3147

    
3148
nrDrained :: String
3149
nrDrained = Types.nodeRoleToRaw NRDrained
3150

    
3151
nrMaster :: String
3152
nrMaster = Types.nodeRoleToRaw NRMaster
3153

    
3154
nrMcandidate :: String
3155
nrMcandidate = Types.nodeRoleToRaw NRCandidate
3156

    
3157
nrOffline :: String
3158
nrOffline = Types.nodeRoleToRaw NROffline
3159

    
3160
nrRegular :: String
3161
nrRegular = Types.nodeRoleToRaw NRRegular
3162

    
3163
nrAll :: FrozenSet String
3164
nrAll = ConstantUtils.mkSet $ map Types.nodeRoleToRaw [minBound..]
3165

    
3166
-- * SSL certificate check constants (in days)
3167

    
3168
sslCertExpirationError :: Int
3169
sslCertExpirationError = 7
3170

    
3171
sslCertExpirationWarn :: Int
3172
sslCertExpirationWarn = 30
3173

    
3174
-- * Allocator framework constants
3175

    
3176
iallocatorVersion :: Int
3177
iallocatorVersion = 2
3178

    
3179
iallocatorDirIn :: String
3180
iallocatorDirIn = Types.iAllocatorTestDirToRaw IAllocatorDirIn
3181

    
3182
iallocatorDirOut :: String
3183
iallocatorDirOut = Types.iAllocatorTestDirToRaw IAllocatorDirOut
3184

    
3185
validIallocatorDirections :: FrozenSet String
3186
validIallocatorDirections =
3187
  ConstantUtils.mkSet $ map Types.iAllocatorTestDirToRaw [minBound..]
3188

    
3189
iallocatorModeAlloc :: String
3190
iallocatorModeAlloc = Types.iAllocatorModeToRaw IAllocatorAlloc
3191

    
3192
iallocatorModeChgGroup :: String
3193
iallocatorModeChgGroup = Types.iAllocatorModeToRaw IAllocatorChangeGroup
3194

    
3195
iallocatorModeMultiAlloc :: String
3196
iallocatorModeMultiAlloc = Types.iAllocatorModeToRaw IAllocatorMultiAlloc
3197

    
3198
iallocatorModeNodeEvac :: String
3199
iallocatorModeNodeEvac = Types.iAllocatorModeToRaw IAllocatorNodeEvac
3200

    
3201
iallocatorModeReloc :: String
3202
iallocatorModeReloc = Types.iAllocatorModeToRaw IAllocatorReloc
3203

    
3204
validIallocatorModes :: FrozenSet String
3205
validIallocatorModes =
3206
  ConstantUtils.mkSet $ map Types.iAllocatorModeToRaw [minBound..]
3207

    
3208
iallocatorSearchPath :: [String]
3209
iallocatorSearchPath = AutoConf.iallocatorSearchPath
3210

    
3211
defaultIallocatorShortcut :: String
3212
defaultIallocatorShortcut = "."
3213

    
3214
-- * Node evacuation
3215

    
3216
nodeEvacPri :: String
3217
nodeEvacPri = Types.evacModeToRaw ChangePrimary
3218

    
3219
nodeEvacSec :: String
3220
nodeEvacSec = Types.evacModeToRaw ChangeSecondary
3221

    
3222
nodeEvacAll :: String
3223
nodeEvacAll = Types.evacModeToRaw ChangeAll
3224

    
3225
nodeEvacModes :: FrozenSet String
3226
nodeEvacModes = ConstantUtils.mkSet $ map Types.evacModeToRaw [minBound..]
3227

    
3228
-- * Job queue
3229

    
3230
jobQueueVersion :: Int
3231
jobQueueVersion = 1
3232

    
3233
jobQueueSizeHardLimit :: Int
3234
jobQueueSizeHardLimit = 5000
3235

    
3236
jobQueueFilesPerms :: Int
3237
jobQueueFilesPerms = 0o640
3238

    
3239
-- * Unchanged job return
3240

    
3241
jobNotchanged :: String
3242
jobNotchanged = "nochange"
3243

    
3244
-- * Job status
3245

    
3246
jobStatusQueued :: String
3247
jobStatusQueued = Types.jobStatusToRaw JOB_STATUS_QUEUED
3248

    
3249
jobStatusWaiting :: String
3250
jobStatusWaiting = Types.jobStatusToRaw JOB_STATUS_WAITING
3251

    
3252
jobStatusCanceling :: String
3253
jobStatusCanceling = Types.jobStatusToRaw JOB_STATUS_CANCELING
3254

    
3255
jobStatusRunning :: String
3256
jobStatusRunning = Types.jobStatusToRaw JOB_STATUS_RUNNING
3257

    
3258
jobStatusCanceled :: String
3259
jobStatusCanceled = Types.jobStatusToRaw JOB_STATUS_CANCELED
3260

    
3261
jobStatusSuccess :: String
3262
jobStatusSuccess = Types.jobStatusToRaw JOB_STATUS_SUCCESS
3263

    
3264
jobStatusError :: String
3265
jobStatusError = Types.jobStatusToRaw JOB_STATUS_ERROR
3266

    
3267
jobsPending :: FrozenSet String
3268
jobsPending =
3269
  ConstantUtils.mkSet [jobStatusQueued, jobStatusWaiting, jobStatusCanceling]
3270

    
3271
jobsFinalized :: FrozenSet String
3272
jobsFinalized =
3273
  ConstantUtils.mkSet $ map Types.finalizedJobStatusToRaw [minBound..]
3274

    
3275
jobStatusAll :: FrozenSet String
3276
jobStatusAll = ConstantUtils.mkSet $ map Types.jobStatusToRaw [minBound..]
3277

    
3278
-- * OpCode status
3279

    
3280
-- ** Not yet finalized opcodes
3281

    
3282
opStatusCanceling :: String
3283
opStatusCanceling = "canceling"
3284

    
3285
opStatusQueued :: String
3286
opStatusQueued = "queued"
3287

    
3288
opStatusRunning :: String
3289
opStatusRunning = "running"
3290

    
3291
opStatusWaiting :: String
3292
opStatusWaiting = "waiting"
3293

    
3294
-- ** Finalized opcodes
3295

    
3296
opStatusCanceled :: String
3297
opStatusCanceled = "canceled"
3298

    
3299
opStatusError :: String
3300
opStatusError = "error"
3301

    
3302
opStatusSuccess :: String
3303
opStatusSuccess = "success"
3304

    
3305
opsFinalized :: FrozenSet String
3306
opsFinalized =
3307
  ConstantUtils.mkSet [opStatusCanceled, opStatusError, opStatusSuccess]
3308

    
3309
-- * OpCode priority
3310

    
3311
opPrioLowest :: Int
3312
opPrioLowest = 19
3313

    
3314
opPrioHighest :: Int
3315
opPrioHighest = -20
3316

    
3317
opPrioLow :: Int
3318
opPrioLow = Types.opSubmitPriorityToRaw OpPrioLow
3319

    
3320
opPrioNormal :: Int
3321
opPrioNormal = Types.opSubmitPriorityToRaw OpPrioNormal
3322

    
3323
opPrioHigh :: Int
3324
opPrioHigh = Types.opSubmitPriorityToRaw OpPrioHigh
3325

    
3326
opPrioSubmitValid :: FrozenSet Int
3327
opPrioSubmitValid = ConstantUtils.mkSet [opPrioLow, opPrioNormal, opPrioHigh]
3328

    
3329
opPrioDefault :: Int
3330
opPrioDefault = opPrioNormal
3331

    
3332
-- * Lock recalculate mode
3333

    
3334
locksAppend :: String
3335
locksAppend = "append"
3336

    
3337
locksReplace :: String
3338
locksReplace = "replace"
3339

    
3340
-- * Lock timeout
3341
--
3342
-- The lock timeout (sum) before we transition into blocking acquire
3343
-- (this can still be reset by priority change).  Computed as max time
3344
-- (10 hours) before we should actually go into blocking acquire,
3345
-- given that we start from the default priority level.
3346

    
3347
lockAttemptsMaxwait :: Double
3348
lockAttemptsMaxwait = 15.0
3349

    
3350
lockAttemptsMinwait :: Double
3351
lockAttemptsMinwait = 1.0
3352

    
3353
lockAttemptsTimeout :: Int
3354
lockAttemptsTimeout = (10 * 3600) `div` (opPrioDefault - opPrioHighest)
3355

    
3356
-- * Execution log types
3357

    
3358
elogMessage :: String
3359
elogMessage = Types.eLogTypeToRaw ELogMessage
3360

    
3361
elogRemoteImport :: String
3362
elogRemoteImport = Types.eLogTypeToRaw ELogRemoteImport
3363

    
3364
elogJqueueTest :: String
3365
elogJqueueTest = Types.eLogTypeToRaw ELogJqueueTest
3366

    
3367
-- * /etc/hosts modification
3368

    
3369
etcHostsAdd :: String
3370
etcHostsAdd = "add"
3371

    
3372
etcHostsRemove :: String
3373
etcHostsRemove = "remove"
3374

    
3375
-- * Job queue test
3376

    
3377
jqtMsgprefix :: String
3378
jqtMsgprefix = "TESTMSG="
3379

    
3380
jqtExec :: String
3381
jqtExec = "exec"
3382

    
3383
jqtExpandnames :: String
3384
jqtExpandnames = "expandnames"
3385

    
3386
jqtLogmsg :: String
3387
jqtLogmsg = "logmsg"
3388

    
3389
jqtStartmsg :: String
3390
jqtStartmsg = "startmsg"
3391

    
3392
jqtAll :: FrozenSet String
3393
jqtAll = ConstantUtils.mkSet [jqtExec, jqtExpandnames, jqtLogmsg, jqtStartmsg]
3394

    
3395
-- * Query resources
3396

    
3397
qrCluster :: String
3398
qrCluster = "cluster"
3399

    
3400
qrExport :: String
3401
qrExport = "export"
3402

    
3403
qrExtstorage :: String
3404
qrExtstorage = "extstorage"
3405

    
3406
qrGroup :: String
3407
qrGroup = "group"
3408

    
3409
qrInstance :: String
3410
qrInstance = "instance"
3411

    
3412
qrJob :: String
3413
qrJob = "job"
3414

    
3415
qrLock :: String
3416
qrLock = "lock"
3417

    
3418
qrNetwork :: String
3419
qrNetwork = "network"
3420

    
3421
qrNode :: String
3422
qrNode = "node"
3423

    
3424
qrOs :: String
3425
qrOs = "os"
3426

    
3427
-- | List of resources which can be queried using 'Ganeti.OpCodes.OpQuery'
3428
qrViaOp :: FrozenSet String
3429
qrViaOp =
3430
  ConstantUtils.mkSet [qrCluster,
3431
                       qrOs,
3432
                       qrExtstorage]
3433

    
3434
-- | List of resources which can be queried using Local UniX Interface
3435
qrViaLuxi :: FrozenSet String
3436
qrViaLuxi = ConstantUtils.mkSet [qrGroup,
3437
                                 qrExport,
3438
                                 qrInstance,
3439
                                 qrJob,
3440
                                 qrLock,
3441
                                 qrNetwork,
3442
                                 qrNode]
3443

    
3444
-- | List of resources which can be queried using RAPI
3445
qrViaRapi :: FrozenSet String
3446
qrViaRapi = qrViaLuxi
3447

    
3448
-- | List of resources which can be queried via RAPI including PUT requests
3449
qrViaRapiPut :: FrozenSet String
3450
qrViaRapiPut = ConstantUtils.mkSet [qrLock, qrJob]
3451

    
3452
-- * Query field types
3453

    
3454
qftBool :: String
3455
qftBool = "bool"
3456

    
3457
qftNumber :: String
3458
qftNumber = "number"
3459

    
3460
qftOther :: String
3461
qftOther = "other"
3462

    
3463
qftText :: String
3464
qftText = "text"
3465

    
3466
qftTimestamp :: String
3467
qftTimestamp = "timestamp"
3468

    
3469
qftUnit :: String
3470
qftUnit = "unit"
3471

    
3472
qftUnknown :: String
3473
qftUnknown = "unknown"
3474

    
3475
qftAll :: FrozenSet String
3476
qftAll =
3477
  ConstantUtils.mkSet [qftBool,
3478
                       qftNumber,
3479
                       qftOther,
3480
                       qftText,
3481
                       qftTimestamp,
3482
                       qftUnit,
3483
                       qftUnknown]
3484

    
3485
-- * Query result field status
3486
--
3487
-- Don't change or reuse values as they're used by clients.
3488
--
3489
-- FIXME: link with 'Ganeti.Query.Language.ResultStatus'
3490

    
3491
-- | No data (e.g. RPC error), can be used instead of 'rsOffline'
3492
rsNodata :: Int
3493
rsNodata = 2
3494

    
3495
rsNormal :: Int
3496
rsNormal = 0
3497

    
3498
-- | Resource marked offline
3499
rsOffline :: Int
3500
rsOffline = 4
3501

    
3502
-- | Value unavailable/unsupported for item; if this field is
3503
-- supported but we cannot get the data for the moment, 'rsNodata' or
3504
-- 'rsOffline' should be used
3505
rsUnavail :: Int
3506
rsUnavail = 3
3507

    
3508
rsUnknown :: Int
3509
rsUnknown = 1
3510

    
3511
rsAll :: FrozenSet Int
3512
rsAll =
3513
  ConstantUtils.mkSet [rsNodata,
3514
                       rsNormal,
3515
                       rsOffline,
3516
                       rsUnavail,
3517
                       rsUnknown]
3518

    
3519
-- | Special field cases and their verbose/terse formatting
3520
rssDescription :: Map Int (String, String)
3521
rssDescription =
3522
  Map.fromList [(rsUnknown, ("(unknown)", "??")),
3523
                (rsNodata, ("(nodata)", "?")),
3524
                (rsOffline, ("(offline)", "*")),
3525
                (rsUnavail, ("(unavail)", "-"))]
3526

    
3527
-- * Max dynamic devices
3528

    
3529
maxDisks :: Int
3530
maxDisks = Types.maxDisks
3531

    
3532
maxNics :: Int
3533
maxNics = Types.maxNics
3534

    
3535
-- | SSCONF file prefix
3536
ssconfFileprefix :: String
3537
ssconfFileprefix = "ssconf_"
3538

    
3539
-- * SSCONF keys
3540

    
3541
ssClusterName :: String
3542
ssClusterName = "cluster_name"
3543

    
3544
ssClusterTags :: String
3545
ssClusterTags = "cluster_tags"
3546

    
3547
ssFileStorageDir :: String
3548
ssFileStorageDir = "file_storage_dir"
3549

    
3550
ssSharedFileStorageDir :: String
3551
ssSharedFileStorageDir = "shared_file_storage_dir"
3552

    
3553
ssGlusterStorageDir :: String
3554
ssGlusterStorageDir = "gluster_storage_dir"
3555

    
3556
ssMasterCandidates :: String
3557
ssMasterCandidates = "master_candidates"
3558

    
3559
ssMasterCandidatesIps :: String
3560
ssMasterCandidatesIps = "master_candidates_ips"
3561

    
3562
ssMasterCandidatesCerts :: String
3563
ssMasterCandidatesCerts = "master_candidates_certs"
3564

    
3565
ssMasterIp :: String
3566
ssMasterIp = "master_ip"
3567

    
3568
ssMasterNetdev :: String
3569
ssMasterNetdev = "master_netdev"
3570

    
3571
ssMasterNetmask :: String
3572
ssMasterNetmask = "master_netmask"
3573

    
3574
ssMasterNode :: String
3575
ssMasterNode = "master_node"
3576

    
3577
ssNodeList :: String
3578
ssNodeList = "node_list"
3579

    
3580
ssNodePrimaryIps :: String
3581
ssNodePrimaryIps = "node_primary_ips"
3582

    
3583
ssNodeSecondaryIps :: String
3584
ssNodeSecondaryIps = "node_secondary_ips"
3585

    
3586
ssOfflineNodes :: String
3587
ssOfflineNodes = "offline_nodes"
3588

    
3589
ssOnlineNodes :: String
3590
ssOnlineNodes = "online_nodes"
3591

    
3592
ssPrimaryIpFamily :: String
3593
ssPrimaryIpFamily = "primary_ip_family"
3594

    
3595
ssInstanceList :: String
3596
ssInstanceList = "instance_list"
3597

    
3598
ssReleaseVersion :: String
3599
ssReleaseVersion = "release_version"
3600

    
3601
ssHypervisorList :: String
3602
ssHypervisorList = "hypervisor_list"
3603

    
3604
ssMaintainNodeHealth :: String
3605
ssMaintainNodeHealth = "maintain_node_health"
3606

    
3607
ssUidPool :: String
3608
ssUidPool = "uid_pool"
3609

    
3610
ssNodegroups :: String
3611
ssNodegroups = "nodegroups"
3612

    
3613
ssNetworks :: String
3614
ssNetworks = "networks"
3615

    
3616
-- | This is not a complete SSCONF key, but the prefix for the
3617
-- hypervisor keys
3618
ssHvparamsPref :: String
3619
ssHvparamsPref = "hvparams_"
3620

    
3621
-- * Hvparams keys
3622

    
3623
ssHvparamsXenChroot :: String
3624
ssHvparamsXenChroot = ssHvparamsPref ++ htChroot
3625

    
3626
ssHvparamsXenFake :: String
3627
ssHvparamsXenFake = ssHvparamsPref ++ htFake
3628

    
3629
ssHvparamsXenHvm :: String
3630
ssHvparamsXenHvm = ssHvparamsPref ++ htXenHvm
3631

    
3632
ssHvparamsXenKvm :: String
3633
ssHvparamsXenKvm = ssHvparamsPref ++ htKvm
3634

    
3635
ssHvparamsXenLxc :: String
3636
ssHvparamsXenLxc = ssHvparamsPref ++ htLxc
3637

    
3638
ssHvparamsXenPvm :: String
3639
ssHvparamsXenPvm = ssHvparamsPref ++ htXenPvm
3640

    
3641
validSsHvparamsKeys :: FrozenSet String
3642
validSsHvparamsKeys =
3643
  ConstantUtils.mkSet [ssHvparamsXenChroot,
3644
                       ssHvparamsXenLxc,
3645
                       ssHvparamsXenFake,
3646
                       ssHvparamsXenHvm,
3647
                       ssHvparamsXenKvm,
3648
                       ssHvparamsXenPvm]
3649

    
3650
ssFilePerms :: Int
3651
ssFilePerms = 0o444
3652

    
3653
-- | Cluster wide default parameters
3654
defaultEnabledHypervisor :: String
3655
defaultEnabledHypervisor = htXenPvm
3656

    
3657
hvcDefaults :: Map Hypervisor (Map String PyValueEx)
3658
hvcDefaults =
3659
  Map.fromList
3660
  [ (XenPvm, Map.fromList
3661
             [ (hvUseBootloader,  PyValueEx False)
3662
             , (hvBootloaderPath, PyValueEx xenBootloader)
3663
             , (hvBootloaderArgs, PyValueEx "")
3664
             , (hvKernelPath,     PyValueEx xenKernel)
3665
             , (hvInitrdPath,     PyValueEx "")
3666
             , (hvRootPath,       PyValueEx "/dev/xvda1")
3667
             , (hvKernelArgs,     PyValueEx "ro")
3668
             , (hvMigrationPort,  PyValueEx (8002 :: Int))
3669
             , (hvMigrationMode,  PyValueEx htMigrationLive)
3670
             , (hvBlockdevPrefix, PyValueEx "sd")
3671
             , (hvRebootBehavior, PyValueEx instanceRebootAllowed)
3672
             , (hvCpuMask,        PyValueEx cpuPinningAll)
3673
             , (hvCpuCap,         PyValueEx (0 :: Int))
3674
             , (hvCpuWeight,      PyValueEx (256 :: Int))
3675
             , (hvVifScript,      PyValueEx "")
3676
             , (hvXenCmd,         PyValueEx xenCmdXm)
3677
             , (hvXenCpuid,       PyValueEx "")
3678
             , (hvSoundhw,        PyValueEx "")
3679
             ])
3680
  , (XenHvm, Map.fromList
3681
             [ (hvBootOrder,      PyValueEx "cd")
3682
             , (hvCdromImagePath, PyValueEx "")
3683
             , (hvNicType,        PyValueEx htNicRtl8139)
3684
             , (hvDiskType,       PyValueEx htDiskParavirtual)
3685
             , (hvVncBindAddress, PyValueEx ip4AddressAny)
3686
             , (hvAcpi,           PyValueEx True)
3687
             , (hvPae,            PyValueEx True)
3688
             , (hvKernelPath,     PyValueEx "/usr/lib/xen/boot/hvmloader")
3689
             , (hvDeviceModel,    PyValueEx "/usr/lib/xen/bin/qemu-dm")
3690
             , (hvMigrationPort,  PyValueEx (8002 :: Int))
3691
             , (hvMigrationMode,  PyValueEx htMigrationNonlive)
3692
             , (hvUseLocaltime,   PyValueEx False)
3693
             , (hvBlockdevPrefix, PyValueEx "hd")
3694
             , (hvPassthrough,    PyValueEx "")
3695
             , (hvRebootBehavior, PyValueEx instanceRebootAllowed)
3696
             , (hvCpuMask,        PyValueEx cpuPinningAll)
3697
             , (hvCpuCap,         PyValueEx (0 :: Int))
3698
             , (hvCpuWeight,      PyValueEx (256 :: Int))
3699
             , (hvVifType,        PyValueEx htHvmVifIoemu)
3700
             , (hvVifScript,      PyValueEx "")
3701
             , (hvViridian,       PyValueEx False)
3702
             , (hvXenCmd,         PyValueEx xenCmdXm)
3703
             , (hvXenCpuid,       PyValueEx "")
3704
             , (hvSoundhw,        PyValueEx "")
3705
             ])
3706
  , (Kvm, Map.fromList
3707
          [ (hvKvmPath,                         PyValueEx kvmPath)
3708
          , (hvKernelPath,                      PyValueEx kvmKernel)
3709
          , (hvInitrdPath,                      PyValueEx "")
3710
          , (hvKernelArgs,                      PyValueEx "ro")
3711
          , (hvRootPath,                        PyValueEx "/dev/vda1")
3712
          , (hvAcpi,                            PyValueEx True)
3713
          , (hvSerialConsole,                   PyValueEx True)
3714
          , (hvSerialSpeed,                     PyValueEx (38400 :: Int))
3715
          , (hvVncBindAddress,                  PyValueEx "")
3716
          , (hvVncTls,                          PyValueEx False)
3717
          , (hvVncX509,                         PyValueEx "")
3718
          , (hvVncX509Verify,                   PyValueEx False)
3719
          , (hvVncPasswordFile,                 PyValueEx "")
3720
          , (hvKvmSpiceBind,                    PyValueEx "")
3721
          , (hvKvmSpiceIpVersion,           PyValueEx ifaceNoIpVersionSpecified)
3722
          , (hvKvmSpicePasswordFile,            PyValueEx "")
3723
          , (hvKvmSpiceLosslessImgCompr,        PyValueEx "")
3724
          , (hvKvmSpiceJpegImgCompr,            PyValueEx "")
3725
          , (hvKvmSpiceZlibGlzImgCompr,         PyValueEx "")
3726
          , (hvKvmSpiceStreamingVideoDetection, PyValueEx "")
3727
          , (hvKvmSpiceAudioCompr,              PyValueEx True)
3728
          , (hvKvmSpiceUseTls,                  PyValueEx False)
3729
          , (hvKvmSpiceTlsCiphers,              PyValueEx opensslCiphers)
3730
          , (hvKvmSpiceUseVdagent,              PyValueEx True)
3731
          , (hvKvmFloppyImagePath,              PyValueEx "")
3732
          , (hvCdromImagePath,                  PyValueEx "")
3733
          , (hvKvmCdrom2ImagePath,              PyValueEx "")
3734
          , (hvBootOrder,                       PyValueEx htBoDisk)
3735
          , (hvNicType,                         PyValueEx htNicParavirtual)
3736
          , (hvDiskType,                        PyValueEx htDiskParavirtual)
3737
          , (hvKvmCdromDiskType,                PyValueEx "")
3738
          , (hvUsbMouse,                        PyValueEx "")
3739
          , (hvKeymap,                          PyValueEx "")
3740
          , (hvMigrationPort,                   PyValueEx (8102 :: Int))
3741
          , (hvMigrationBandwidth,              PyValueEx (32 :: Int))
3742
          , (hvMigrationDowntime,               PyValueEx (30 :: Int))
3743
          , (hvMigrationMode,                   PyValueEx htMigrationLive)
3744
          , (hvUseLocaltime,                    PyValueEx False)
3745
          , (hvDiskCache,                       PyValueEx htCacheDefault)
3746
          , (hvSecurityModel,                   PyValueEx htSmNone)
3747
          , (hvSecurityDomain,                  PyValueEx "")
3748
          , (hvKvmFlag,                         PyValueEx "")
3749
          , (hvVhostNet,                        PyValueEx False)
3750
          , (hvKvmUseChroot,                    PyValueEx False)
3751
          , (hvKvmUserShutdown,                 PyValueEx False)
3752
          , (hvMemPath,                         PyValueEx "")
3753
          , (hvRebootBehavior,                  PyValueEx instanceRebootAllowed)
3754
          , (hvCpuMask,                         PyValueEx cpuPinningAll)
3755
          , (hvCpuType,                         PyValueEx "")
3756
          , (hvCpuCores,                        PyValueEx (0 :: Int))
3757
          , (hvCpuThreads,                      PyValueEx (0 :: Int))
3758
          , (hvCpuSockets,                      PyValueEx (0 :: Int))
3759
          , (hvSoundhw,                         PyValueEx "")
3760
          , (hvUsbDevices,                      PyValueEx "")
3761
          , (hvVga,                             PyValueEx "")
3762
          , (hvKvmExtra,                        PyValueEx "")
3763
          , (hvKvmMachineVersion,               PyValueEx "")
3764
          , (hvVnetHdr,                         PyValueEx True)])
3765
  , (Fake, Map.fromList [(hvMigrationMode, PyValueEx htMigrationLive)])
3766
  , (Chroot, Map.fromList [(hvInitScript, PyValueEx "/ganeti-chroot")])
3767
  , (Lxc, Map.fromList [(hvCpuMask, PyValueEx "")])
3768
  ]
3769

    
3770
hvcGlobals :: FrozenSet String
3771
hvcGlobals =
3772
  ConstantUtils.mkSet [hvMigrationBandwidth,
3773
                       hvMigrationMode,
3774
                       hvMigrationPort,
3775
                       hvXenCmd]
3776

    
3777
becDefaults :: Map String PyValueEx
3778
becDefaults =
3779
  Map.fromList
3780
  [ (beMinmem, PyValueEx (128 :: Int))
3781
  , (beMaxmem, PyValueEx (128 :: Int))
3782
  , (beVcpus, PyValueEx (1 :: Int))
3783
  , (beAutoBalance, PyValueEx True)
3784
  , (beAlwaysFailover, PyValueEx False)
3785
  , (beSpindleUse, PyValueEx (1 :: Int))
3786
  ]
3787

    
3788
ndcDefaults :: Map String PyValueEx
3789
ndcDefaults =
3790
  Map.fromList
3791
  [ (ndOobProgram,       PyValueEx "")
3792
  , (ndSpindleCount,     PyValueEx (1 :: Int))
3793
  , (ndExclusiveStorage, PyValueEx False)
3794
  , (ndOvs,              PyValueEx False)
3795
  , (ndOvsName,          PyValueEx defaultOvs)
3796
  , (ndOvsLink,          PyValueEx "")
3797
  , (ndSshPort,          PyValueEx (22 :: Int))
3798
  ]
3799

    
3800
ndcGlobals :: FrozenSet String
3801
ndcGlobals = ConstantUtils.mkSet [ndExclusiveStorage]
3802

    
3803
-- | Default delay target measured in sectors
3804
defaultDelayTarget :: Int
3805
defaultDelayTarget = 1
3806

    
3807
defaultDiskCustom :: String
3808
defaultDiskCustom = ""
3809

    
3810
defaultDiskResync :: Bool
3811
defaultDiskResync = False
3812

    
3813
-- | Default fill target measured in sectors
3814
defaultFillTarget :: Int
3815
defaultFillTarget = 0
3816

    
3817
-- | Default mininum rate measured in KiB/s
3818
defaultMinRate :: Int
3819
defaultMinRate = 4 * 1024
3820

    
3821
defaultNetCustom :: String
3822
defaultNetCustom = ""
3823

    
3824
-- | Default plan ahead measured in sectors
3825
--
3826
-- The default values for the DRBD dynamic resync speed algorithm are
3827
-- taken from the drbsetup 8.3.11 man page, except for c-plan-ahead
3828
-- (that we don't need to set to 0, because we have a separate option
3829
-- to enable it) and for c-max-rate, that we cap to the default value
3830
-- for the static resync rate.
3831
defaultPlanAhead :: Int
3832
defaultPlanAhead = 20
3833

    
3834
defaultRbdPool :: String
3835
defaultRbdPool = "rbd"
3836

    
3837
diskLdDefaults :: Map DiskTemplate (Map String PyValueEx)
3838
diskLdDefaults =
3839
  Map.fromList
3840
  [ (DTBlock, Map.empty)
3841
  , (DTDrbd8, Map.fromList
3842
              [ (ldpBarriers,      PyValueEx drbdBarriers)
3843
              , (ldpDefaultMetavg, PyValueEx defaultVg)
3844
              , (ldpDelayTarget,   PyValueEx defaultDelayTarget)
3845
              , (ldpDiskCustom,    PyValueEx defaultDiskCustom)
3846
              , (ldpDynamicResync, PyValueEx defaultDiskResync)
3847
              , (ldpFillTarget,    PyValueEx defaultFillTarget)
3848
              , (ldpMaxRate,       PyValueEx classicDrbdSyncSpeed)
3849
              , (ldpMinRate,       PyValueEx defaultMinRate)
3850
              , (ldpNetCustom,     PyValueEx defaultNetCustom)
3851
              , (ldpNoMetaFlush,   PyValueEx drbdNoMetaFlush)
3852
              , (ldpPlanAhead,     PyValueEx defaultPlanAhead)
3853
              , (ldpProtocol,      PyValueEx drbdDefaultNetProtocol)
3854
              , (ldpResyncRate,    PyValueEx classicDrbdSyncSpeed)
3855
              ])
3856
  , (DTExt, Map.empty)
3857
  , (DTFile, Map.empty)
3858
  , (DTPlain, Map.fromList [(ldpStripes, PyValueEx lvmStripecount)])
3859
  , (DTRbd, Map.fromList
3860
            [ (ldpPool, PyValueEx defaultRbdPool)
3861
            , (ldpAccess, PyValueEx diskKernelspace)
3862
            ])
3863
  , (DTSharedFile, Map.empty)
3864
  , (DTGluster, Map.fromList
3865
                [ (rbdAccess, PyValueEx diskKernelspace)
3866
                , (glusterHost, PyValueEx glusterHostDefault)
3867
                , (glusterVolume, PyValueEx glusterVolumeDefault)
3868
                , (glusterPort, PyValueEx glusterPortDefault)
3869
                ])
3870
  ]
3871

    
3872
diskDtDefaults :: Map DiskTemplate (Map String PyValueEx)
3873
diskDtDefaults =
3874
  Map.fromList
3875
  [ (DTBlock,      Map.empty)
3876
  , (DTDiskless,   Map.empty)
3877
  , (DTDrbd8,      Map.fromList
3878
                   [ (drbdDataStripes,   PyValueEx lvmStripecount)
3879
                   , (drbdDefaultMetavg, PyValueEx defaultVg)
3880
                   , (drbdDelayTarget,   PyValueEx defaultDelayTarget)
3881
                   , (drbdDiskBarriers,  PyValueEx drbdBarriers)
3882
                   , (drbdDiskCustom,    PyValueEx defaultDiskCustom)
3883
                   , (drbdDynamicResync, PyValueEx defaultDiskResync)
3884
                   , (drbdFillTarget,    PyValueEx defaultFillTarget)
3885
                   , (drbdMaxRate,       PyValueEx classicDrbdSyncSpeed)
3886
                   , (drbdMetaBarriers,  PyValueEx drbdNoMetaFlush)
3887
                   , (drbdMetaStripes,   PyValueEx lvmStripecount)
3888
                   , (drbdMinRate,       PyValueEx defaultMinRate)
3889
                   , (drbdNetCustom,     PyValueEx defaultNetCustom)
3890
                   , (drbdPlanAhead,     PyValueEx defaultPlanAhead)
3891
                   , (drbdProtocol,      PyValueEx drbdDefaultNetProtocol)
3892
                   , (drbdResyncRate,    PyValueEx classicDrbdSyncSpeed)
3893
                   ])
3894
  , (DTExt,        Map.empty)
3895
  , (DTFile,       Map.empty)
3896
  , (DTPlain,      Map.fromList [(lvStripes, PyValueEx lvmStripecount)])
3897
  , (DTRbd,        Map.fromList
3898
                   [ (rbdPool, PyValueEx defaultRbdPool)
3899
                   , (rbdAccess, PyValueEx diskKernelspace)
3900
                   ])
3901
  , (DTSharedFile, Map.empty)
3902
  , (DTGluster, Map.fromList
3903
                [ (rbdAccess, PyValueEx diskKernelspace)
3904
                , (glusterHost, PyValueEx glusterHostDefault)
3905
                , (glusterVolume, PyValueEx glusterVolumeDefault)
3906
                , (glusterPort, PyValueEx glusterPortDefault)
3907
                ])
3908
  ]
3909

    
3910
niccDefaults :: Map String PyValueEx
3911
niccDefaults =
3912
  Map.fromList
3913
  [ (nicMode, PyValueEx nicModeBridged)
3914
  , (nicLink, PyValueEx defaultBridge)
3915
  , (nicVlan, PyValueEx "")
3916
  ]
3917

    
3918
-- | All of the following values are quite arbitrary - there are no
3919
-- "good" defaults, these must be customised per-site
3920
ispecsMinmaxDefaults :: Map String (Map String Int)
3921
ispecsMinmaxDefaults =
3922
  Map.fromList
3923
  [(ispecsMin,
3924
    Map.fromList
3925
    [(ConstantUtils.ispecMemSize, Types.iSpecMemorySize Types.defMinISpec),
3926
     (ConstantUtils.ispecCpuCount, Types.iSpecCpuCount Types.defMinISpec),
3927
     (ConstantUtils.ispecDiskCount, Types.iSpecDiskCount Types.defMinISpec),
3928
     (ConstantUtils.ispecDiskSize, Types.iSpecDiskSize Types.defMinISpec),
3929
     (ConstantUtils.ispecNicCount, Types.iSpecNicCount Types.defMinISpec),
3930
     (ConstantUtils.ispecSpindleUse, Types.iSpecSpindleUse Types.defMinISpec)]),
3931
   (ispecsMax,
3932
    Map.fromList
3933
    [(ConstantUtils.ispecMemSize, Types.iSpecMemorySize Types.defMaxISpec),
3934
     (ConstantUtils.ispecCpuCount, Types.iSpecCpuCount Types.defMaxISpec),
3935
     (ConstantUtils.ispecDiskCount, Types.iSpecDiskCount Types.defMaxISpec),
3936
     (ConstantUtils.ispecDiskSize, Types.iSpecDiskSize Types.defMaxISpec),
3937
     (ConstantUtils.ispecNicCount, Types.iSpecNicCount Types.defMaxISpec),
3938
     (ConstantUtils.ispecSpindleUse, Types.iSpecSpindleUse Types.defMaxISpec)])]
3939

    
3940
ipolicyDefaults :: Map String PyValueEx
3941
ipolicyDefaults =
3942
  Map.fromList
3943
  [ (ispecsMinmax,        PyValueEx [ispecsMinmaxDefaults])
3944
  , (ispecsStd,           PyValueEx (Map.fromList
3945
                                     [ (ispecMemSize,    128)
3946
                                     , (ispecCpuCount,   1)
3947
                                     , (ispecDiskCount,  1)
3948
                                     , (ispecDiskSize,   1024)
3949
                                     , (ispecNicCount,   1)
3950
                                     , (ispecSpindleUse, 1)
3951
                                     ] :: Map String Int))
3952
  , (ipolicyDts,          PyValueEx (ConstantUtils.toList diskTemplates))
3953
  , (ipolicyVcpuRatio,    PyValueEx (4.0 :: Double))
3954
  , (ipolicySpindleRatio, PyValueEx (32.0 :: Double))
3955
  ]
3956

    
3957
masterPoolSizeDefault :: Int
3958
masterPoolSizeDefault = 10
3959

    
3960
-- * Exclusive storage
3961

    
3962
-- | Error margin used to compare physical disks
3963
partMargin :: Double
3964
partMargin = 0.01
3965

    
3966
-- | Space reserved when creating instance disks
3967
partReserved :: Double
3968
partReserved = 0.02
3969

    
3970
-- * Luxid job scheduling
3971

    
3972
-- | Time intervall in seconds for polling updates on the job queue. This
3973
-- intervall is only relevant if the number of running jobs reaches the maximal
3974
-- allowed number, as otherwise new jobs will be started immediately anyway.
3975
-- Also, as jobs are watched via inotify, scheduling usually works independent
3976
-- of polling. Therefore we chose a sufficiently large interval, in the order of
3977
-- 5 minutes. As with the interval for reloading the configuration, we chose a
3978
-- prime number to avoid accidental 'same wakeup' with other processes.
3979
luxidJobqueuePollInterval :: Int
3980
luxidJobqueuePollInterval = 307
3981

    
3982
-- | The default value for the maximal number of jobs to be running at the same
3983
-- time. Once the maximal number is reached, new jobs will just be queued and
3984
-- only started, once some of the other jobs have finished.
3985
luxidMaximalRunningJobsDefault :: Int
3986
luxidMaximalRunningJobsDefault = 20
3987

    
3988
-- * Confd
3989

    
3990
confdProtocolVersion :: Int
3991
confdProtocolVersion = ConstantUtils.confdProtocolVersion
3992

    
3993
-- Confd request type
3994

    
3995
confdReqPing :: Int
3996
confdReqPing = Types.confdRequestTypeToRaw ReqPing
3997

    
3998
confdReqNodeRoleByname :: Int
3999
confdReqNodeRoleByname = Types.confdRequestTypeToRaw ReqNodeRoleByName
4000

    
4001
confdReqNodePipByInstanceIp :: Int
4002
confdReqNodePipByInstanceIp = Types.confdRequestTypeToRaw ReqNodePipByInstPip
4003

    
4004
confdReqClusterMaster :: Int
4005
confdReqClusterMaster = Types.confdRequestTypeToRaw ReqClusterMaster
4006

    
4007
confdReqNodePipList :: Int
4008
confdReqNodePipList = Types.confdRequestTypeToRaw ReqNodePipList
4009

    
4010
confdReqMcPipList :: Int
4011
confdReqMcPipList = Types.confdRequestTypeToRaw ReqMcPipList
4012

    
4013
confdReqInstancesIpsList :: Int
4014
confdReqInstancesIpsList = Types.confdRequestTypeToRaw ReqInstIpsList
4015

    
4016
confdReqNodeDrbd :: Int
4017
confdReqNodeDrbd = Types.confdRequestTypeToRaw ReqNodeDrbd
4018

    
4019
confdReqNodeInstances :: Int
4020
confdReqNodeInstances = Types.confdRequestTypeToRaw ReqNodeInstances
4021

    
4022
confdReqs :: FrozenSet Int
4023
confdReqs =
4024
  ConstantUtils.mkSet .
4025
  map Types.confdRequestTypeToRaw $
4026
  [minBound..] \\ [ReqNodeInstances]
4027

    
4028
-- * Confd request type
4029

    
4030
confdReqfieldName :: Int
4031
confdReqfieldName = Types.confdReqFieldToRaw ReqFieldName
4032

    
4033
confdReqfieldIp :: Int
4034
confdReqfieldIp = Types.confdReqFieldToRaw ReqFieldIp
4035

    
4036
confdReqfieldMnodePip :: Int
4037
confdReqfieldMnodePip = Types.confdReqFieldToRaw ReqFieldMNodePip
4038

    
4039
-- * Confd repl status
4040

    
4041
confdReplStatusOk :: Int
4042
confdReplStatusOk = Types.confdReplyStatusToRaw ReplyStatusOk
4043

    
4044
confdReplStatusError :: Int
4045
confdReplStatusError = Types.confdReplyStatusToRaw ReplyStatusError
4046

    
4047
confdReplStatusNotimplemented :: Int
4048
confdReplStatusNotimplemented = Types.confdReplyStatusToRaw ReplyStatusNotImpl
4049

    
4050
confdReplStatuses :: FrozenSet Int
4051
confdReplStatuses =
4052
  ConstantUtils.mkSet $ map Types.confdReplyStatusToRaw [minBound..]
4053

    
4054
-- * Confd node role
4055

    
4056
confdNodeRoleMaster :: Int
4057
confdNodeRoleMaster = Types.confdNodeRoleToRaw NodeRoleMaster
4058

    
4059
confdNodeRoleCandidate :: Int
4060
confdNodeRoleCandidate = Types.confdNodeRoleToRaw NodeRoleCandidate
4061

    
4062
confdNodeRoleOffline :: Int
4063
confdNodeRoleOffline = Types.confdNodeRoleToRaw NodeRoleOffline
4064

    
4065
confdNodeRoleDrained :: Int
4066
confdNodeRoleDrained = Types.confdNodeRoleToRaw NodeRoleDrained
4067

    
4068
confdNodeRoleRegular :: Int
4069
confdNodeRoleRegular = Types.confdNodeRoleToRaw NodeRoleRegular
4070

    
4071
-- * A few common errors for confd
4072

    
4073
confdErrorUnknownEntry :: Int
4074
confdErrorUnknownEntry = Types.confdErrorTypeToRaw ConfdErrorUnknownEntry
4075

    
4076
confdErrorInternal :: Int
4077
confdErrorInternal = Types.confdErrorTypeToRaw ConfdErrorInternal
4078

    
4079
confdErrorArgument :: Int
4080
confdErrorArgument = Types.confdErrorTypeToRaw ConfdErrorArgument
4081

    
4082
-- * Confd request query fields
4083

    
4084
confdReqqLink :: String
4085
confdReqqLink = ConstantUtils.confdReqqLink
4086

    
4087
confdReqqIp :: String
4088
confdReqqIp = ConstantUtils.confdReqqIp
4089

    
4090
confdReqqIplist :: String
4091
confdReqqIplist = ConstantUtils.confdReqqIplist
4092

    
4093
confdReqqFields :: String
4094
confdReqqFields = ConstantUtils.confdReqqFields
4095

    
4096
-- | Each request is "salted" by the current timestamp.
4097
--
4098
-- This constant decides how many seconds of skew to accept.
4099
--
4100
-- TODO: make this a default and allow the value to be more
4101
-- configurable
4102
confdMaxClockSkew :: Int
4103
confdMaxClockSkew = 2 * nodeMaxClockSkew
4104

    
4105
-- | When we haven't reloaded the config for more than this amount of
4106
-- seconds, we force a test to see if inotify is betraying us. Using a
4107
-- prime number to ensure we get less chance of 'same wakeup' with
4108
-- other processes.
4109
confdConfigReloadTimeout :: Int
4110
confdConfigReloadTimeout = 17
4111

    
4112
-- | If we receive more than one update in this amount of
4113
-- microseconds, we move to polling every RATELIMIT seconds, rather
4114
-- than relying on inotify, to be able to serve more requests.
4115
confdConfigReloadRatelimit :: Int
4116
confdConfigReloadRatelimit = 250000
4117

    
4118
-- | Magic number prepended to all confd queries.
4119
--
4120
-- This allows us to distinguish different types of confd protocols
4121
-- and handle them. For example by changing this we can move the whole
4122
-- payload to be compressed, or move away from json.
4123
confdMagicFourcc :: String
4124
confdMagicFourcc = "plj0"
4125

    
4126
-- | By default a confd request is sent to the minimum between this
4127
-- number and all MCs. 6 was chosen because even in the case of a
4128
-- disastrous 50% response rate, we should have enough answers to be
4129
-- able to compare more than one.
4130
confdDefaultReqCoverage :: Int
4131
confdDefaultReqCoverage = 6
4132

    
4133
-- | Timeout in seconds to expire pending query request in the confd
4134
-- client library. We don't actually expect any answer more than 10
4135
-- seconds after we sent a request.
4136
confdClientExpireTimeout :: Int
4137
confdClientExpireTimeout = 10
4138

    
4139
-- | Maximum UDP datagram size.
4140
--
4141
-- On IPv4: 64K - 20 (ip header size) - 8 (udp header size) = 65507
4142
-- On IPv6: 64K - 40 (ip6 header size) - 8 (udp header size) = 65487
4143
--   (assuming we can't use jumbo frames)
4144
-- We just set this to 60K, which should be enough
4145
maxUdpDataSize :: Int
4146
maxUdpDataSize = 61440
4147

    
4148
-- * User-id pool minimum/maximum acceptable user-ids
4149

    
4150
uidpoolUidMin :: Int
4151
uidpoolUidMin = 0
4152

    
4153
-- | Assuming 32 bit user-ids
4154
uidpoolUidMax :: Integer
4155
uidpoolUidMax = 2 ^ 32 - 1
4156

    
4157
-- | Name or path of the pgrep command
4158
pgrep :: String
4159
pgrep = "pgrep"
4160

    
4161
-- | Name of the node group that gets created at cluster init or
4162
-- upgrade
4163
initialNodeGroupName :: String
4164
initialNodeGroupName = "default"
4165

    
4166
-- * Possible values for NodeGroup.alloc_policy
4167

    
4168
allocPolicyLastResort :: String
4169
allocPolicyLastResort = Types.allocPolicyToRaw AllocLastResort
4170

    
4171
allocPolicyPreferred :: String
4172
allocPolicyPreferred = Types.allocPolicyToRaw AllocPreferred
4173

    
4174
allocPolicyUnallocable :: String
4175
allocPolicyUnallocable = Types.allocPolicyToRaw AllocUnallocable
4176

    
4177
validAllocPolicies :: [String]
4178
validAllocPolicies = map Types.allocPolicyToRaw [minBound..]
4179

    
4180
-- | Temporary external/shared storage parameters
4181
blockdevDriverManual :: String
4182
blockdevDriverManual = Types.blockDriverToRaw BlockDrvManual
4183

    
4184
-- | 'qemu-img' path, required for 'ovfconverter'
4185
qemuimgPath :: String
4186
qemuimgPath = AutoConf.qemuimgPath
4187

    
4188
-- | The hail iallocator
4189
iallocHail :: String
4190
iallocHail = "hail"
4191

    
4192
-- * Fake opcodes for functions that have hooks attached to them via
4193
-- backend.RunLocalHooks
4194

    
4195
fakeOpMasterTurndown :: String
4196
fakeOpMasterTurndown = "OP_CLUSTER_IP_TURNDOWN"
4197

    
4198
fakeOpMasterTurnup :: String
4199
fakeOpMasterTurnup = "OP_CLUSTER_IP_TURNUP"
4200

    
4201

    
4202
-- * Crypto Types
4203
-- Types of cryptographic tokens used in node communication
4204

    
4205
cryptoTypeSslDigest :: String
4206
cryptoTypeSslDigest = "ssl"
4207

    
4208
cryptoTypeSsh :: String
4209
cryptoTypeSsh = "ssh"
4210

    
4211
-- So far only ssl keys are used in the context of this constant
4212
cryptoTypes :: FrozenSet String
4213
cryptoTypes = ConstantUtils.mkSet [cryptoTypeSslDigest]
4214

    
4215
-- * Crypto Actions
4216
-- Actions that can be performed on crypto tokens
4217

    
4218
cryptoActionGet :: String
4219
cryptoActionGet = "get"
4220

    
4221
-- This is 'create and get'
4222
cryptoActionCreate :: String
4223
cryptoActionCreate = "create"
4224

    
4225
cryptoActions :: FrozenSet String
4226
cryptoActions = ConstantUtils.mkSet [cryptoActionGet, cryptoActionCreate]
4227

    
4228
-- * Options for CryptoActions
4229

    
4230
-- Filename of the certificate
4231
cryptoOptionCertFile :: String
4232
cryptoOptionCertFile = "cert_file"
4233

    
4234
-- * SSH key types
4235

    
4236
sshkDsa :: String
4237
sshkDsa = "dsa"
4238

    
4239
sshkRsa :: String
4240
sshkRsa = "rsa"
4241

    
4242
sshkAll :: FrozenSet String
4243
sshkAll = ConstantUtils.mkSet [sshkRsa, sshkDsa]
4244

    
4245
-- * SSH authorized key types
4246

    
4247
sshakDss :: String
4248
sshakDss = "ssh-dss"
4249

    
4250
sshakRsa :: String
4251
sshakRsa = "ssh-rsa"
4252

    
4253
sshakAll :: FrozenSet String
4254
sshakAll = ConstantUtils.mkSet [sshakDss, sshakRsa]
4255

    
4256
-- * SSH setup
4257

    
4258
sshsClusterName :: String
4259
sshsClusterName = "cluster_name"
4260

    
4261
sshsSshHostKey :: String
4262
sshsSshHostKey = "ssh_host_key"
4263

    
4264
sshsSshRootKey :: String
4265
sshsSshRootKey = "ssh_root_key"
4266

    
4267
sshsNodeDaemonCertificate :: String
4268
sshsNodeDaemonCertificate = "node_daemon_certificate"
4269

    
4270
-- * Key files for SSH daemon
4271

    
4272
sshHostDsaPriv :: String
4273
sshHostDsaPriv = sshConfigDir ++ "/ssh_host_dsa_key"
4274

    
4275
sshHostDsaPub :: String
4276
sshHostDsaPub = sshHostDsaPriv ++ ".pub"
4277

    
4278
sshHostRsaPriv :: String
4279
sshHostRsaPriv = sshConfigDir ++ "/ssh_host_rsa_key"
4280

    
4281
sshHostRsaPub :: String
4282
sshHostRsaPub = sshHostRsaPriv ++ ".pub"
4283

    
4284
sshDaemonKeyfiles :: Map String (String, String)
4285
sshDaemonKeyfiles =
4286
  Map.fromList [ (sshkRsa, (sshHostRsaPriv, sshHostRsaPub))
4287
               , (sshkDsa, (sshHostDsaPriv, sshHostDsaPub))
4288
               ]
4289

    
4290
-- * Node daemon setup
4291

    
4292
ndsClusterName :: String
4293
ndsClusterName = "cluster_name"
4294

    
4295
ndsNodeDaemonCertificate :: String
4296
ndsNodeDaemonCertificate = "node_daemon_certificate"
4297

    
4298
ndsSsconf :: String
4299
ndsSsconf = "ssconf"
4300

    
4301
ndsStartNodeDaemon :: String
4302
ndsStartNodeDaemon = "start_node_daemon"
4303

    
4304
-- * VCluster related constants
4305

    
4306
vClusterEtcHosts :: String
4307
vClusterEtcHosts = "/etc/hosts"
4308

    
4309
vClusterVirtPathPrefix :: String
4310
vClusterVirtPathPrefix = "/###-VIRTUAL-PATH-###,"
4311

    
4312
vClusterRootdirEnvname :: String
4313
vClusterRootdirEnvname = "GANETI_ROOTDIR"
4314

    
4315
vClusterHostnameEnvname :: String
4316
vClusterHostnameEnvname = "GANETI_HOSTNAME"
4317

    
4318
vClusterVpathWhitelist :: FrozenSet String
4319
vClusterVpathWhitelist = ConstantUtils.mkSet [ vClusterEtcHosts ]
4320

    
4321
-- * The source reasons for the execution of an OpCode
4322

    
4323
opcodeReasonSrcClient :: String
4324
opcodeReasonSrcClient = "gnt:client"
4325

    
4326
opcodeReasonSrcNoded :: String
4327
opcodeReasonSrcNoded = "gnt:daemon:noded"
4328

    
4329
opcodeReasonSrcOpcode :: String
4330
opcodeReasonSrcOpcode = "gnt:opcode"
4331

    
4332
opcodeReasonSrcRlib2 :: String
4333
opcodeReasonSrcRlib2 = "gnt:library:rlib2"
4334

    
4335
opcodeReasonSrcUser :: String
4336
opcodeReasonSrcUser = "gnt:user"
4337

    
4338
opcodeReasonSources :: FrozenSet String
4339
opcodeReasonSources =
4340
  ConstantUtils.mkSet [opcodeReasonSrcClient,
4341
                       opcodeReasonSrcNoded,
4342
                       opcodeReasonSrcOpcode,
4343
                       opcodeReasonSrcRlib2,
4344
                       opcodeReasonSrcUser]
4345

    
4346
-- | Path generating random UUID
4347
randomUuidFile :: String
4348
randomUuidFile = ConstantUtils.randomUuidFile
4349

    
4350
-- * Auto-repair tag prefixes
4351

    
4352
autoRepairTagPrefix :: String
4353
autoRepairTagPrefix = "ganeti:watcher:autorepair:"
4354

    
4355
autoRepairTagEnabled :: String
4356
autoRepairTagEnabled = autoRepairTagPrefix
4357

    
4358
autoRepairTagPending :: String
4359
autoRepairTagPending = autoRepairTagPrefix ++ "pending:"
4360

    
4361
autoRepairTagResult :: String
4362
autoRepairTagResult = autoRepairTagPrefix ++ "result:"
4363

    
4364
autoRepairTagSuspended :: String
4365
autoRepairTagSuspended = autoRepairTagPrefix ++ "suspend:"
4366

    
4367
-- * Auto-repair levels
4368

    
4369
autoRepairFailover :: String
4370
autoRepairFailover = Types.autoRepairTypeToRaw ArFailover
4371

    
4372
autoRepairFixStorage :: String
4373
autoRepairFixStorage = Types.autoRepairTypeToRaw ArFixStorage
4374

    
4375
autoRepairMigrate :: String
4376
autoRepairMigrate = Types.autoRepairTypeToRaw ArMigrate
4377

    
4378
autoRepairReinstall :: String
4379
autoRepairReinstall = Types.autoRepairTypeToRaw ArReinstall
4380

    
4381
autoRepairAllTypes :: FrozenSet String
4382
autoRepairAllTypes =
4383
  ConstantUtils.mkSet [autoRepairFailover,
4384
                       autoRepairFixStorage,
4385
                       autoRepairMigrate,
4386
                       autoRepairReinstall]
4387

    
4388
-- * Auto-repair results
4389

    
4390
autoRepairEnoperm :: String
4391
autoRepairEnoperm = Types.autoRepairResultToRaw ArEnoperm
4392

    
4393
autoRepairFailure :: String
4394
autoRepairFailure = Types.autoRepairResultToRaw ArFailure
4395

    
4396
autoRepairSuccess :: String
4397
autoRepairSuccess = Types.autoRepairResultToRaw ArSuccess
4398

    
4399
autoRepairAllResults :: FrozenSet String
4400
autoRepairAllResults =
4401
  ConstantUtils.mkSet [autoRepairEnoperm, autoRepairFailure, autoRepairSuccess]
4402

    
4403
-- | The version identifier for builtin data collectors
4404
builtinDataCollectorVersion :: String
4405
builtinDataCollectorVersion = "B"
4406

    
4407
-- | The reason trail opcode parameter name
4408
opcodeReason :: String
4409
opcodeReason = "reason"
4410

    
4411
diskstatsFile :: String
4412
diskstatsFile = "/proc/diskstats"
4413

    
4414
-- *  CPU load collector
4415

    
4416
statFile :: String
4417
statFile = "/proc/stat"
4418

    
4419
cpuavgloadBufferSize :: Int
4420
cpuavgloadBufferSize = 150
4421

    
4422
cpuavgloadWindowSize :: Int
4423
cpuavgloadWindowSize = 600
4424

    
4425
-- * Monitoring daemon
4426

    
4427
-- | Mond's variable for periodical data collection
4428
mondTimeInterval :: Int
4429
mondTimeInterval = 5
4430

    
4431
-- | Mond's latest API version
4432
mondLatestApiVersion :: Int
4433
mondLatestApiVersion = 1
4434

    
4435
-- * Disk access modes
4436

    
4437
diskUserspace :: String
4438
diskUserspace = Types.diskAccessModeToRaw DiskUserspace
4439

    
4440
diskKernelspace :: String
4441
diskKernelspace = Types.diskAccessModeToRaw DiskKernelspace
4442

    
4443
diskValidAccessModes :: FrozenSet String
4444
diskValidAccessModes =
4445
  ConstantUtils.mkSet $ map Types.diskAccessModeToRaw [minBound..]
4446

    
4447
-- | Timeout for queue draining in upgrades
4448
upgradeQueueDrainTimeout :: Int
4449
upgradeQueueDrainTimeout = 36 * 60 * 60 -- 1.5 days
4450

    
4451
-- | Intervall at which the queue is polled during upgrades
4452
upgradeQueuePollInterval :: Int
4453
upgradeQueuePollInterval  = 10
4454

    
4455
-- * Hotplug Actions
4456

    
4457
hotplugActionAdd :: String
4458
hotplugActionAdd = Types.hotplugActionToRaw HAAdd
4459

    
4460
hotplugActionRemove :: String
4461
hotplugActionRemove = Types.hotplugActionToRaw HARemove
4462

    
4463
hotplugActionModify :: String
4464
hotplugActionModify = Types.hotplugActionToRaw HAMod
4465

    
4466
hotplugAllActions :: FrozenSet String
4467
hotplugAllActions =
4468
  ConstantUtils.mkSet $ map Types.hotplugActionToRaw [minBound..]
4469

    
4470
-- * Hotplug Device Targets
4471

    
4472
hotplugTargetNic :: String
4473
hotplugTargetNic = Types.hotplugTargetToRaw HTNic
4474

    
4475
hotplugTargetDisk :: String
4476
hotplugTargetDisk = Types.hotplugTargetToRaw HTDisk
4477

    
4478
hotplugAllTargets :: FrozenSet String
4479
hotplugAllTargets =
4480
  ConstantUtils.mkSet $ map Types.hotplugTargetToRaw [minBound..]
4481

    
4482
-- | Timeout for disk removal (seconds)
4483
diskRemoveRetryTimeout :: Int
4484
diskRemoveRetryTimeout = 30
4485

    
4486
-- | Interval between disk removal retries (seconds)
4487
diskRemoveRetryInterval :: Int
4488
diskRemoveRetryInterval  = 3
4489

    
4490
-- * UUID regex
4491

    
4492
uuidRegex :: String
4493
uuidRegex = "^[a-f0-9]{8}-[a-f0-9]{4}-[a-f0-9]{4}-[a-f0-9]{4}-[a-f0-9]{12}$"
4494

    
4495
-- * Luxi constants
4496

    
4497
luxiSocketPerms :: Int
4498
luxiSocketPerms = 0o660
4499

    
4500
luxiKeyMethod :: String
4501
luxiKeyMethod = "method"
4502

    
4503
luxiKeyArgs :: String
4504
luxiKeyArgs = "args"
4505

    
4506
luxiKeySuccess :: String
4507
luxiKeySuccess = "success"
4508

    
4509
luxiKeyResult :: String
4510
luxiKeyResult = "result"
4511

    
4512
luxiKeyVersion :: String
4513
luxiKeyVersion = "version"
4514

    
4515
luxiReqSubmitJob :: String
4516
luxiReqSubmitJob = "SubmitJob"
4517

    
4518
luxiReqSubmitJobToDrainedQueue :: String
4519
luxiReqSubmitJobToDrainedQueue = "SubmitJobToDrainedQueue"
4520

    
4521
luxiReqSubmitManyJobs :: String
4522
luxiReqSubmitManyJobs = "SubmitManyJobs"
4523

    
4524
luxiReqWaitForJobChange :: String
4525
luxiReqWaitForJobChange = "WaitForJobChange"
4526

    
4527
luxiReqPickupJob :: String
4528
luxiReqPickupJob = "PickupJob"
4529

    
4530
luxiReqCancelJob :: String
4531
luxiReqCancelJob = "CancelJob"
4532

    
4533
luxiReqArchiveJob :: String
4534
luxiReqArchiveJob = "ArchiveJob"
4535

    
4536
luxiReqChangeJobPriority :: String
4537
luxiReqChangeJobPriority = "ChangeJobPriority"
4538

    
4539
luxiReqAutoArchiveJobs :: String
4540
luxiReqAutoArchiveJobs = "AutoArchiveJobs"
4541

    
4542
luxiReqQuery :: String
4543
luxiReqQuery = "Query"
4544

    
4545
luxiReqQueryFields :: String
4546
luxiReqQueryFields = "QueryFields"
4547

    
4548
luxiReqQueryJobs :: String
4549
luxiReqQueryJobs = "QueryJobs"
4550

    
4551
luxiReqQueryInstances :: String
4552
luxiReqQueryInstances = "QueryInstances"
4553

    
4554
luxiReqQueryNodes :: String
4555
luxiReqQueryNodes = "QueryNodes"
4556

    
4557
luxiReqQueryGroups :: String
4558
luxiReqQueryGroups = "QueryGroups"
4559

    
4560
luxiReqQueryNetworks :: String
4561
luxiReqQueryNetworks = "QueryNetworks"
4562

    
4563
luxiReqQueryExports :: String
4564
luxiReqQueryExports = "QueryExports"
4565

    
4566
luxiReqQueryConfigValues :: String
4567
luxiReqQueryConfigValues = "QueryConfigValues"
4568

    
4569
luxiReqQueryClusterInfo :: String
4570
luxiReqQueryClusterInfo = "QueryClusterInfo"
4571

    
4572
luxiReqQueryTags :: String
4573
luxiReqQueryTags = "QueryTags"
4574

    
4575
luxiReqSetDrainFlag :: String
4576
luxiReqSetDrainFlag = "SetDrainFlag"
4577

    
4578
luxiReqSetWatcherPause :: String
4579
luxiReqSetWatcherPause = "SetWatcherPause"
4580

    
4581
luxiReqAll :: FrozenSet String
4582
luxiReqAll =
4583
  ConstantUtils.mkSet
4584
  [ luxiReqArchiveJob
4585
  , luxiReqAutoArchiveJobs
4586
  , luxiReqCancelJob
4587
  , luxiReqChangeJobPriority
4588
  , luxiReqQuery
4589
  , luxiReqQueryClusterInfo
4590
  , luxiReqQueryConfigValues
4591
  , luxiReqQueryExports
4592
  , luxiReqQueryFields
4593
  , luxiReqQueryGroups
4594
  , luxiReqQueryInstances
4595
  , luxiReqQueryJobs
4596
  , luxiReqQueryNodes
4597
  , luxiReqQueryNetworks
4598
  , luxiReqQueryTags
4599
  , luxiReqSetDrainFlag
4600
  , luxiReqSetWatcherPause
4601
  , luxiReqSubmitJob
4602
  , luxiReqSubmitJobToDrainedQueue
4603
  , luxiReqSubmitManyJobs
4604
  , luxiReqWaitForJobChange
4605
  , luxiReqPickupJob
4606
  ]
4607

    
4608
luxiDefCtmo :: Int
4609
luxiDefCtmo = 10
4610

    
4611
luxiDefRwto :: Int
4612
luxiDefRwto = 60
4613

    
4614
-- | 'WaitForJobChange' timeout
4615
luxiWfjcTimeout :: Int
4616
luxiWfjcTimeout = (luxiDefRwto - 1) `div` 2
4617

    
4618
-- * Query language constants
4619

    
4620
-- ** Logic operators with one or more operands, each of which is a
4621
-- filter on its own
4622

    
4623
qlangOpAnd :: String
4624
qlangOpAnd = "&"
4625

    
4626
qlangOpOr :: String
4627
qlangOpOr = "|"
4628

    
4629
-- ** Unary operators with exactly one operand
4630

    
4631
qlangOpNot :: String
4632
qlangOpNot = "!"
4633

    
4634
qlangOpTrue :: String
4635
qlangOpTrue = "?"
4636

    
4637
-- ** Binary operators with exactly two operands, the field name and
4638
-- an operator-specific value
4639

    
4640
qlangOpContains :: String
4641
qlangOpContains = "=[]"
4642

    
4643
qlangOpEqual :: String
4644
qlangOpEqual = "="
4645

    
4646
qlangOpGe :: String
4647
qlangOpGe = ">="
4648

    
4649
qlangOpGt :: String
4650
qlangOpGt = ">"
4651

    
4652
qlangOpLe :: String
4653
qlangOpLe = "<="
4654

    
4655
qlangOpLt :: String
4656
qlangOpLt = "<"
4657

    
4658
qlangOpNotEqual :: String
4659
qlangOpNotEqual = "!="
4660

    
4661
qlangOpRegexp :: String
4662
qlangOpRegexp = "=~"
4663

    
4664
-- | Characters used for detecting user-written filters (see
4665
-- L{_CheckFilter})
4666

    
4667
qlangFilterDetectionChars :: FrozenSet String
4668
qlangFilterDetectionChars =
4669
  ConstantUtils.mkSet ["!", " ", "\"", "\'",
4670
                       ")", "(", "\x0b", "\n",
4671
                       "\r", "\x0c", "/", "<",
4672
                       "\t", ">", "=", "\\", "~"]
4673

    
4674
-- | Characters used to detect globbing filters
4675
qlangGlobDetectionChars :: FrozenSet String
4676
qlangGlobDetectionChars = ConstantUtils.mkSet ["*", "?"]
4677

    
4678
-- * Error related constants
4679
--
4680
-- 'OpPrereqError' failure types
4681

    
4682
-- | Environment error (e.g. node disk error)
4683
errorsEcodeEnviron :: String
4684
errorsEcodeEnviron = "environment_error"
4685

    
4686
-- | Entity already exists
4687
errorsEcodeExists :: String
4688
errorsEcodeExists = "already_exists"
4689

    
4690
-- | Internal cluster error
4691
errorsEcodeFault :: String
4692
errorsEcodeFault = "internal_error"
4693

    
4694
-- | Wrong arguments (at syntax level)
4695
errorsEcodeInval :: String
4696
errorsEcodeInval = "wrong_input"
4697

    
4698
-- | Entity not found
4699
errorsEcodeNoent :: String
4700
errorsEcodeNoent = "unknown_entity"
4701

    
4702
-- | Not enough resources (iallocator failure, disk space, memory, etc)
4703
errorsEcodeNores :: String
4704
errorsEcodeNores = "insufficient_resources"
4705

    
4706
-- | Resource not unique (e.g. MAC or IP duplication)
4707
errorsEcodeNotunique :: String
4708
errorsEcodeNotunique = "resource_not_unique"
4709

    
4710
-- | Resolver errors
4711
errorsEcodeResolver :: String
4712
errorsEcodeResolver = "resolver_error"
4713

    
4714
-- | Wrong entity state
4715
errorsEcodeState :: String
4716
errorsEcodeState = "wrong_state"
4717

    
4718
-- | Temporarily out of resources; operation can be tried again
4719
errorsEcodeTempNores :: String
4720
errorsEcodeTempNores = "temp_insufficient_resources"
4721

    
4722
errorsEcodeAll :: FrozenSet String
4723
errorsEcodeAll =
4724
  ConstantUtils.mkSet [ errorsEcodeNores
4725
                      , errorsEcodeExists
4726
                      , errorsEcodeState
4727
                      , errorsEcodeNotunique
4728
                      , errorsEcodeTempNores
4729
                      , errorsEcodeNoent
4730
                      , errorsEcodeFault
4731
                      , errorsEcodeResolver
4732
                      , errorsEcodeInval
4733
                      , errorsEcodeEnviron
4734
                      ]
4735

    
4736
-- * Jstore related constants
4737

    
4738
jstoreJobsPerArchiveDirectory :: Int
4739
jstoreJobsPerArchiveDirectory = 10000
4740

    
4741
-- * Gluster settings
4742

    
4743
-- | Name of the Gluster host setting
4744
glusterHost :: String
4745
glusterHost = "host"
4746

    
4747
-- | Default value of the Gluster host setting
4748
glusterHostDefault :: String
4749
glusterHostDefault = "127.0.0.1"
4750

    
4751
-- | Name of the Gluster volume setting
4752
glusterVolume :: String
4753
glusterVolume = "volume"
4754

    
4755
-- | Default value of the Gluster volume setting
4756
glusterVolumeDefault :: String
4757
glusterVolumeDefault = "gv0"
4758

    
4759
-- | Name of the Gluster port setting
4760
glusterPort :: String
4761
glusterPort = "port"
4762

    
4763
-- | Default value of the Gluster port setting
4764
glusterPortDefault :: Int
4765
glusterPortDefault = 24007
4766

    
4767
-- * Instance communication
4768
--
4769
-- The instance communication attaches an additional NIC, named
4770
-- @instanceCommunicationNicPrefix@:@instanceName@ and prefixed by
4771
-- @instanceCommunicationMacPrefix@, to the instances that have
4772
-- instance communication enabled.  This NIC is part of the network
4773
-- @instanceCommunicationNetworkName@, which is in turn created by
4774
-- 'gnt-network'.  This network is defined as
4775
-- @instanceCommunicationNetwork4@ for IPv4 and
4776
-- @instanceCommunicationNetwork6@ for IPv6.
4777

    
4778
instanceCommunicationDoc :: String
4779
instanceCommunicationDoc =
4780
  "Enable or disable the communication mechanism for an instance"
4781

    
4782
instanceCommunicationMacPrefix :: String
4783
instanceCommunicationMacPrefix = "52:54:00"
4784

    
4785
-- | The instance communication network is a link-local IPv4/IPv6
4786
-- network because the communication is meant to be exclusive between
4787
-- the host and the guest and not routed outside the node.
4788
instanceCommunicationNetwork4 :: String
4789
instanceCommunicationNetwork4 = "169.254.0.0/16"
4790

    
4791
-- | See 'instanceCommunicationNetwork4'.
4792
instanceCommunicationNetwork6 :: String
4793
instanceCommunicationNetwork6 = "fe80::/10"
4794

    
4795
instanceCommunicationNetworkLink :: String
4796
instanceCommunicationNetworkLink = "communication_rt"
4797

    
4798
instanceCommunicationNicPrefix :: String
4799
instanceCommunicationNicPrefix = "ganeti:communication:"
4800

    
4801
-- | Parameters that should be protected
4802
--
4803
-- Python does not have a type system and can't automatically infer what should
4804
-- be the resulting type of a JSON request. As a result, it must rely on this
4805
-- list of parameter names to protect values correctly.
4806
--
4807
-- Names ending in _cluster will be treated as dicts of dicts of private values.
4808
-- Otherwise they are considered dicts of private values.
4809
privateParametersBlacklist :: [String]
4810
privateParametersBlacklist = [ "osparams_private"
4811
                             , "osparams_secret"
4812
                             , "osparams_private_cluster"
4813
                             ]
4814

    
4815
-- | Warn the user that the logging level is too low for production use.
4816
debugModeConfidentialityWarning :: String
4817
debugModeConfidentialityWarning =
4818
  "ALERT: %s started in debug mode.\n\
4819
  \ Private and secret parameters WILL be logged!\n"