Hs2Py constants: add 'value*' and 'niccDefaults'
[ganeti-local] / src / Ganeti / ConstantUtils.hs
index b14ab7f..853cdeb 100644 (file)
@@ -28,17 +28,31 @@ Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
 -}
 module Ganeti.ConstantUtils where
 
+import Data.Char (ord)
 import Data.Set (Set)
-import qualified Data.Set as Set (fromList, toList)
+import qualified Data.Set as Set (difference, fromList, toList, union)
 
 import Ganeti.THH (PyValue(..))
 import Ganeti.PyValueInstances ()
 
+-- | PythonChar wraps a Python 'char'
+newtype PythonChar = PythonChar { unPythonChar :: Char }
+  deriving (Show)
+
+instance PyValue PythonChar where
+  showValue c = "chr(" ++ show (ord (unPythonChar c)) ++ ")"
+
+-- | 'PythonNone' wraps Python 'None'
+data PythonNone = PythonNone
+
+instance PyValue PythonNone where
+  showValue _ = "None"
+
 -- | FrozenSet wraps a Haskell 'Set'
 --
 -- See 'PyValue' instance for 'FrozenSet'.
 newtype FrozenSet a = FrozenSet { unFrozenSet :: Set a }
-  deriving (Eq, Show)
+  deriving (Eq, Ord, Show)
 
 -- | Converts a Haskell 'Set' into a Python 'frozenset'
 --
@@ -53,6 +67,15 @@ instance PyValue a => PyValue (FrozenSet a) where
 mkSet :: Ord a => [a] -> FrozenSet a
 mkSet = FrozenSet . Set.fromList
 
+toList :: FrozenSet a -> [a]
+toList = Set.toList . unFrozenSet
+
+union :: Ord a => FrozenSet a -> FrozenSet a -> FrozenSet a
+union x y = FrozenSet (unFrozenSet x `Set.union` unFrozenSet y)
+
+difference :: Ord a => FrozenSet a -> FrozenSet a -> FrozenSet a
+difference x y = FrozenSet (unFrozenSet x `Set.difference` unFrozenSet y)
+
 -- | 'Protocol' represents the protocols used by the daemons
 data Protocol = Tcp | Udp
   deriving (Show)
@@ -66,7 +89,7 @@ instance PyValue Protocol where
 
 -- | Failure exit code
 --
--- This is defined here and not in 'Ganeti.HsConstants' together with
+-- These are defined here and not in 'Ganeti.HsConstants' together with
 -- the other exit codes in order to avoid a circular dependency
 -- between 'Ganeti.HsConstants' and 'Ganeti.Runtime'
 exitFailure :: Int
@@ -88,11 +111,12 @@ devConsole = "/dev/console"
 randomUuidFile :: String
 randomUuidFile = "/proc/sys/kernel/random/uuid"
 
--- | Priority levels
+-- * Priority levels
 --
--- This is defined here and not in 'Ganeti.Types' order to avoid a GHC
--- stage restriction and because there is no suitable 'declareADT'
+-- This is defined here and not in 'Ganeti.Types' in order to avoid a
+-- GHC stage restriction and because there is no suitable 'declareADT'
 -- variant that handles integer values directly.
+
 priorityLow :: Int
 priorityLow = 10
 
@@ -107,3 +131,70 @@ priorityHigh = -10
 buildVersion :: Int -> Int -> Int -> Int
 buildVersion major minor revision =
   1000000 * major + 10000 * minor + 1 * revision
+
+-- | Confd protocol version
+--
+-- This is defined here in order to avoid a circular dependency
+-- between 'Ganeti.Confd.Types' and 'Ganeti.HsConstants'.
+confdProtocolVersion :: Int
+confdProtocolVersion = 1
+
+-- * Confd request query fields
+--
+-- These are defined here and not in 'Ganeti.Types' due to GHC stage
+-- restrictions concerning Template Haskell.  They are also not
+-- defined in 'Ganeti.HsConstants' in order to avoid a circular
+-- dependency between that module and 'Ganeti.Types'.
+
+confdReqqLink :: String
+confdReqqLink = "0"
+
+confdReqqIp :: String
+confdReqqIp = "1"
+
+confdReqqIplist :: String
+confdReqqIplist = "2"
+
+confdReqqFields :: String
+confdReqqFields = "3"
+
+-- * ISpec
+
+ispecMemSize :: String
+ispecMemSize = "memory-size"
+
+ispecCpuCount :: String
+ispecCpuCount = "cpu-count"
+
+ispecDiskCount :: String
+ispecDiskCount = "disk-count"
+
+ispecDiskSize :: String
+ispecDiskSize = "disk-size"
+
+ispecNicCount :: String
+ispecNicCount = "nic-count"
+
+ispecSpindleUse :: String
+ispecSpindleUse = "spindle-use"
+
+ispecsMinmax :: String
+ispecsMinmax = "minmax"
+
+ispecsStd :: String
+ispecsStd = "std"
+
+ipolicyDts :: String
+ipolicyDts = "disk-templates"
+
+ipolicyVcpuRatio :: String
+ipolicyVcpuRatio = "vcpu-ratio"
+
+ipolicySpindleRatio :: String
+ipolicySpindleRatio = "spindle-ratio"
+
+ipolicyDefaultsVcpuRatio :: Double
+ipolicyDefaultsVcpuRatio = 4.0
+
+ipolicyDefaultsSpindleRatio :: Double
+ipolicyDefaultsSpindleRatio = 32.0