Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / ConstantUtils.hs @ 72e18df1

History | View | Annotate | Download (2.9 kB)

1
{-| ConstantUtils contains the helper functions for constants
2

    
3
This module cannot be merged with 'Ganeti.Utils' because it would
4
create a circular dependency if imported, for example, from
5
'Ganeti.Constants'.
6

    
7
-}
8

    
9
{-
10

    
11
Copyright (C) 2013 Google Inc.
12

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

    
18
This program is distributed in the hope that it will be useful, but
19
WITHOUT ANY WARRANTY; without even the implied warranty of
20
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
21
General Public License for more details.
22

    
23
You should have received a copy of the GNU General Public License
24
along with this program; if not, write to the Free Software
25
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
26
02110-1301, USA.
27

    
28
-}
29
module Ganeti.ConstantUtils where
30

    
31
import Data.Set (Set)
32
import qualified Data.Set as Set (fromList, toList)
33

    
34
import Ganeti.THH (PyValue(..))
35
import Ganeti.PyValueInstances ()
36

    
37
-- | FrozenSet wraps a Haskell 'Set'
38
--
39
-- See 'PyValue' instance for 'FrozenSet'.
40
newtype FrozenSet a = FrozenSet { unFrozenSet :: Set a }
41
  deriving (Eq, Show)
42

    
43
-- | Converts a Haskell 'Set' into a Python 'frozenset'
44
--
45
-- This instance was supposed to be for 'Set' instead of 'FrozenSet'.
46
-- However, 'ghc-6.12.1' seems to be crashing with 'segmentation
47
-- fault' due to the presence of more than one instance of 'Set',
48
-- namely, this one and the one in 'Ganeti.OpCodes'.  For this reason,
49
-- we wrap 'Set' into 'FrozenSet'.
50
instance PyValue a => PyValue (FrozenSet a) where
51
  showValue s = "frozenset(" ++ showValue (Set.toList (unFrozenSet s)) ++ ")"
52

    
53
mkSet :: Ord a => [a] -> FrozenSet a
54
mkSet = FrozenSet . Set.fromList
55

    
56
-- | 'Protocol' represents the protocols used by the daemons
57
data Protocol = Tcp | Udp
58
  deriving (Show)
59

    
60
-- | 'PyValue' instance of 'Protocol'
61
--
62
-- This instance is used by the Haskell to Python constants
63
instance PyValue Protocol where
64
  showValue Tcp = "\"tcp\""
65
  showValue Udp = "\"udp\""
66

    
67
-- | Failure exit code
68
--
69
-- This is defined here and not in 'Ganeti.HsConstants' together with
70
-- the other exit codes in order to avoid a circular dependency
71
-- between 'Ganeti.HsConstants' and 'Ganeti.Runtime'
72
exitFailure :: Int
73
exitFailure = 1
74

    
75
-- | Console device
76
--
77
-- This is defined here and not in 'Ganeti.HsConstants' order to avoid
78
-- a circular dependency between 'Ganeti.HsConstants' and
79
-- 'Ganeti.Logging'
80
devConsole :: String
81
devConsole = "/dev/console"
82

    
83
-- | Priority levels
84
--
85
-- This is defined here and not in 'Ganeti.Types' order to avoid a GHC
86
-- stage restriction and because there is no suitable 'declareADT'
87
-- variant that handles integer values directly.
88
priorityLow :: Int
89
priorityLow = 10
90

    
91
priorityNormal :: Int
92
priorityNormal = 0
93

    
94
priorityHigh :: Int
95
priorityHigh = -10