Make Query operators enforce strictness
[ganeti-local] / htools / Ganeti / HTools / Instance.hs
index 0f32080..b941df6 100644 (file)
@@ -31,9 +31,9 @@ module Ganeti.HTools.Instance
   , AssocList
   , List
   , create
-  , instanceRunning
-  , instanceOffline
-  , instanceNotOffline
+  , isRunning
+  , isOffline
+  , notOffline
   , instanceDown
   , usesSecMem
   , applyIfOnline
@@ -54,12 +54,14 @@ module Ganeti.HTools.Instance
   , requiredNodes
   , allNodes
   , usesLocalStorage
+  , mirrorType
   ) where
 
+import Ganeti.BasicTypes
 import qualified Ganeti.HTools.Types as T
 import qualified Ganeti.HTools.Container as Container
 
-import Ganeti.HTools.Utils
+import Ganeti.Utils
 
 -- * Type declarations
 
@@ -77,9 +79,11 @@ data Instance = Instance
   , util         :: T.DynUtil -- ^ Dynamic resource usage
   , movable      :: Bool      -- ^ Can and should the instance be moved?
   , autoBalance  :: Bool      -- ^ Is the instance auto-balanced?
-  , tags         :: [String]  -- ^ List of instance tags
   , diskTemplate :: T.DiskTemplate -- ^ The disk template of the instance
-  } deriving (Show, Read, Eq)
+  , spindleUse   :: Int       -- ^ The numbers of used spindles
+  , allTags      :: [String]  -- ^ List of all instance tags
+  , exclTags     :: [String]  -- ^ List of instance exclusion tags
+  } deriving (Show, Eq)
 
 instance T.Element Instance where
   nameOf   = name
@@ -89,36 +93,36 @@ instance T.Element Instance where
   allNames n = [name n, alias n]
 
 -- | Check if instance is running.
-instanceRunning :: Instance -> Bool
-instanceRunning (Instance {runSt = T.Running}) = True
-instanceRunning (Instance {runSt = T.ErrorUp}) = True
-instanceRunning _                              = False
+isRunning :: Instance -> Bool
+isRunning (Instance {runSt = T.Running}) = True
+isRunning (Instance {runSt = T.ErrorUp}) = True
+isRunning _                              = False
 
 -- | Check if instance is offline.
-instanceOffline :: Instance -> Bool
-instanceOffline (Instance {runSt = T.AdminOffline}) = True
-instanceOffline _                                   = False
+isOffline :: Instance -> Bool
+isOffline (Instance {runSt = T.StatusOffline}) = True
+isOffline _                                    = False
 
 
 -- | Helper to check if the instance is not offline.
-instanceNotOffline :: Instance -> Bool
-instanceNotOffline = not . instanceOffline
+notOffline :: Instance -> Bool
+notOffline = not . isOffline
 
 -- | Check if instance is down.
 instanceDown :: Instance -> Bool
-instanceDown inst | instanceRunning inst = False
-instanceDown inst | instanceOffline inst = False
-instanceDown _                           = True
+instanceDown inst | isRunning inst = False
+instanceDown inst | isOffline inst = False
+instanceDown _                     = True
 
 -- | Apply the function if the instance is online. Otherwise use
 -- the initial value
 applyIfOnline :: Instance -> (a -> a) -> a -> a
-applyIfOnline = applyIf . instanceNotOffline
+applyIfOnline = applyIf . notOffline
 
 -- | Helper for determining whether an instance's memory needs to be
 -- taken into account for secondary memory reservation.
 usesSecMem :: Instance -> Bool
-usesSecMem inst = instanceNotOffline inst && autoBalance inst
+usesSecMem inst = notOffline inst && autoBalance inst
 
 -- | Constant holding the local storage templates.
 --
@@ -137,7 +141,12 @@ localStorageTemplates = [ T.DTDrbd8, T.DTPlain ]
 -- instance. Further the movable state can be restricted more due to
 -- user choices, etc.
 movableDiskTemplates :: [T.DiskTemplate]
-movableDiskTemplates = [ T.DTDrbd8, T.DTBlock, T.DTSharedFile ]
+movableDiskTemplates =
+  [ T.DTDrbd8
+  , T.DTBlock
+  , T.DTSharedFile
+  , T.DTRbd
+  ]
 
 -- | A simple name for the int, instance association list.
 type AssocList = [(T.Idx, Instance)]
@@ -152,9 +161,10 @@ type List = Container.Container Instance
 -- Some parameters are not initialized by function, and must be set
 -- later (via 'setIdx' for example).
 create :: String -> Int -> Int -> Int -> T.InstanceStatus
-       -> [String] -> Bool -> T.Ndx -> T.Ndx -> T.DiskTemplate -> Instance
+       -> [String] -> Bool -> T.Ndx -> T.Ndx -> T.DiskTemplate -> Int
+       -> Instance
 create name_init mem_init dsk_init vcpus_init run_init tags_init
-       auto_balance_init pn sn dt =
+       auto_balance_init pn sn dt su =
   Instance { name = name_init
            , alias = name_init
            , mem = mem_init
@@ -165,10 +175,12 @@ create name_init mem_init dsk_init vcpus_init run_init tags_init
            , sNode = sn
            , idx = -1
            , util = T.baseUtil
-           , tags = tags_init
            , movable = supportsMoves dt
            , autoBalance = auto_balance_init
            , diskTemplate = dt
+           , spindleUse = su
+           , allTags = tags_init
+           , exclTags = []
            }
 
 -- | Changes the index.
@@ -224,20 +236,20 @@ setMovable t m = t { movable = m }
 
 -- | Try to shrink the instance based on the reason why we can't
 -- allocate it.
-shrinkByType :: Instance -> T.FailMode -> T.Result Instance
+shrinkByType :: Instance -> T.FailMode -> Result Instance
 shrinkByType inst T.FailMem = let v = mem inst - T.unitMem
                               in if v < T.unitMem
-                                 then T.Bad "out of memory"
-                                 else T.Ok inst { mem = v }
+                                 then Bad "out of memory"
+                                 else Ok inst { mem = v }
 shrinkByType inst T.FailDisk = let v = dsk inst - T.unitDsk
                                in if v < T.unitDsk
-                                  then T.Bad "out of disk"
-                                  else T.Ok inst { dsk = v }
+                                  then Bad "out of disk"
+                                  else Ok inst { dsk = v }
 shrinkByType inst T.FailCPU = let v = vcpus inst - T.unitCpu
                               in if v < T.unitCpu
-                                 then T.Bad "out of vcpus"
-                                 else T.Ok inst { vcpus = v }
-shrinkByType _ f = T.Bad $ "Unhandled failure mode " ++ show f
+                                 then Bad "out of vcpus"
+                                 else Ok inst { vcpus = v }
+shrinkByType _ f = Bad $ "Unhandled failure mode " ++ show f
 
 -- | Return the spec of an instance.
 specOf :: Instance -> T.RSpec
@@ -245,31 +257,31 @@ specOf Instance { mem = m, dsk = d, vcpus = c } =
   T.RSpec { T.rspecCpu = c, T.rspecMem = m, T.rspecDsk = d }
 
 -- | Checks if an instance is smaller than a given spec. Returns
--- OpGood for a correct spec, otherwise OpFail one of the possible
+-- OpGood for a correct spec, otherwise Bad one of the possible
 -- failure modes.
 instBelowISpec :: Instance -> T.ISpec -> T.OpResult ()
 instBelowISpec inst ispec
-  | mem inst > T.iSpecMemorySize ispec = T.OpFail T.FailMem
-  | dsk inst > T.iSpecDiskSize ispec   = T.OpFail T.FailDisk
-  | vcpus inst > T.iSpecCpuCount ispec = T.OpFail T.FailCPU
-  | otherwise = T.OpGood ()
+  | mem inst > T.iSpecMemorySize ispec = Bad T.FailMem
+  | dsk inst > T.iSpecDiskSize ispec   = Bad T.FailDisk
+  | vcpus inst > T.iSpecCpuCount ispec = Bad T.FailCPU
+  | otherwise = Ok ()
 
 -- | Checks if an instance is bigger than a given spec.
 instAboveISpec :: Instance -> T.ISpec -> T.OpResult ()
 instAboveISpec inst ispec
-  | mem inst < T.iSpecMemorySize ispec = T.OpFail T.FailMem
-  | dsk inst < T.iSpecDiskSize ispec   = T.OpFail T.FailDisk
-  | vcpus inst < T.iSpecCpuCount ispec = T.OpFail T.FailCPU
-  | otherwise = T.OpGood ()
+  | mem inst < T.iSpecMemorySize ispec = Bad T.FailMem
+  | dsk inst < T.iSpecDiskSize ispec   = Bad T.FailDisk
+  | vcpus inst < T.iSpecCpuCount ispec = Bad T.FailCPU
+  | otherwise = Ok ()
 
 -- | Checks if an instance matches a policy.
 instMatchesPolicy :: Instance -> T.IPolicy -> T.OpResult ()
 instMatchesPolicy inst ipol = do
   instAboveISpec inst (T.iPolicyMinSpec ipol)
   instBelowISpec inst (T.iPolicyMaxSpec ipol)
-  if (diskTemplate inst `elem` T.iPolicyDiskTemplates ipol)
-    then T.OpGood ()
-    else T.OpFail T.FailDisk
+  if diskTemplate inst `elem` T.iPolicyDiskTemplates ipol
+    then Ok ()
+    else Bad T.FailDisk
 
 -- | Checks whether the instance uses a secondary node.
 --
@@ -296,3 +308,7 @@ usesLocalStorage = (`elem` localStorageTemplates) . diskTemplate
 -- | Checks whether a given disk template supported moves.
 supportsMoves :: T.DiskTemplate -> Bool
 supportsMoves = (`elem` movableDiskTemplates)
+
+-- | A simple wrapper over 'T.templateMirrorType'.
+mirrorType :: Instance -> T.MirrorType
+mirrorType = T.templateMirrorType . diskTemplate