Implement cpu/disk limits in instance moves
[ganeti-local] / Ganeti / HTools / Node.hs
index 3ecf685..c9df51b 100644 (file)
@@ -4,27 +4,59 @@
     updated value.
 -}
 
+{-
+
+Copyright (C) 2009 Google Inc.
+
+This program is free software; you can redistribute it and/or modify
+it under the terms of the GNU General Public License as published by
+the Free Software Foundation; either version 2 of the License, or
+(at your option) any later version.
+
+This program is distributed in the hope that it will be useful, but
+WITHOUT ANY WARRANTY; without even the implied warranty of
+MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
+General Public License for more details.
+
+You should have received a copy of the GNU General Public License
+along with this program; if not, write to the Free Software
+Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
+02110-1301, USA.
+
+-}
+
 module Ganeti.HTools.Node
-    (
-      Node(failN1, idx, t_mem, n_mem, f_mem, t_dsk, f_dsk,
-           p_mem, p_dsk, p_rem,
+    ( Node(failN1, name, idx, t_mem, n_mem, f_mem, r_mem,
+           t_dsk, f_dsk,
+           t_cpu, u_cpu,
+           p_mem, p_dsk, p_rem, p_cpu,
+           m_dsk, m_cpu,
            plist, slist, offline)
+    , List
     -- * Constructor
     , create
     -- ** Finalization after data loading
     , buildPeers
     , setIdx
+    , setName
     , setOffline
     , setXmem
+    , setFmem
+    , setPri
+    , setSec
+    , setMdsk
+    , setMcpu
+    , addCpus
     -- * Instance (re)location
     , removePri
     , removeSec
     , addPri
     , addSec
-    , setPri
-    , setSec
     -- * Formatting
     , list
+    -- * Misc stuff
+    , AssocList
+    , noSecondary
     ) where
 
 import Data.List
@@ -34,44 +66,78 @@ import qualified Ganeti.HTools.Container as Container
 import qualified Ganeti.HTools.Instance as Instance
 import qualified Ganeti.HTools.PeerMap as PeerMap
 
-import Ganeti.HTools.Utils
-
-data Node = Node { t_mem :: Double -- ^ total memory (MiB)
-                 , n_mem :: Int    -- ^ node memory (MiB)
-                 , f_mem :: Int    -- ^ free memory (MiB)
-                 , x_mem :: Int    -- ^ unaccounted memory (MiB)
-                 , t_dsk :: Double -- ^ total disk space (MiB)
-                 , f_dsk :: Int    -- ^ free disk space (MiB)
-                 , plist :: [Int]  -- ^ list of primary instance indices
-                 , slist :: [Int]  -- ^ list of secondary instance indices
-                 , idx :: Int      -- ^ internal index for book-keeping
-                 , peers :: PeerMap.PeerMap -- ^ pnode to instance mapping
-                 , failN1:: Bool   -- ^ whether the node has failed n1
-                 , r_mem :: Int    -- ^ maximum memory needed for
+import qualified Ganeti.HTools.Types as T
+
+-- * Type declarations
+
+-- | The node type.
+data Node = Node { name  :: String -- ^ The node name
+                 , t_mem :: Double -- ^ Total memory (MiB)
+                 , n_mem :: Int    -- ^ Node memory (MiB)
+                 , f_mem :: Int    -- ^ Free memory (MiB)
+                 , x_mem :: Int    -- ^ Unaccounted memory (MiB)
+                 , t_dsk :: Double -- ^ Total disk space (MiB)
+                 , f_dsk :: Int    -- ^ Free disk space (MiB)
+                 , t_cpu :: Double -- ^ Total CPU count
+                 , u_cpu :: Int    -- ^ Used VCPU count
+                 , plist :: [T.Idx]-- ^ List of primary instance indices
+                 , slist :: [T.Idx]-- ^ List of secondary instance indices
+                 , idx :: T.Ndx    -- ^ Internal index for book-keeping
+                 , peers :: PeerMap.PeerMap -- ^ Pnode to instance mapping
+                 , failN1:: Bool   -- ^ Whether the node has failed n1
+                 , r_mem :: Int    -- ^ Maximum memory needed for
                                    -- failover by primaries of this node
-                 , p_mem :: Double -- ^ percent of free memory
-                 , p_dsk :: Double -- ^ percent of free disk
-                 , p_rem :: Double -- ^ percent of reserved memory
-                 , offline :: Bool -- ^ whether the node should not be used
+                 , p_mem :: Double -- ^ Percent of free memory
+                 , p_dsk :: Double -- ^ Percent of free disk
+                 , p_rem :: Double -- ^ Percent of reserved memory
+                 , p_cpu :: Double -- ^ Ratio of virtual to physical CPUs
+                 , m_dsk :: Double -- ^ Minimum free disk ratio
+                 , m_cpu :: Double -- ^ Max ratio of virt-to-phys CPUs
+                 , offline :: Bool -- ^ Whether the node should not be used
                                    -- for allocations and skipped from
                                    -- score computations
   } deriving (Show)
 
-{- | Create a new node.
+instance T.Element Node where
+    nameOf = name
+    idxOf = idx
+    setName = setName
+    setIdx = setIdx
 
-The index and the peers maps are empty, and will be need to be update
-later via the 'setIdx' and 'buildPeers' functions.
+-- | A simple name for the int, node association list.
+type AssocList = [(T.Ndx, Node)]
 
--}
-create :: Double -> Int -> Int -> Double -> Int -> Node
-create mem_t_init mem_n_init mem_f_init dsk_t_init dsk_f_init =
+-- | A simple name for a node map.
+type List = Container.Container Node
+
+-- | Constant node index for a non-moveable instance.
+noSecondary :: T.Ndx
+noSecondary = -1
+
+-- | No limit value
+noLimit :: Double
+noLimit = -1
+
+-- * Initialization functions
+
+-- | Create a new node.
+--
+-- The index and the peers maps are empty, and will be need to be
+-- update later via the 'setIdx' and 'buildPeers' functions.
+create :: String -> Double -> Int -> Int -> Double
+       -> Int -> Double -> Bool -> Node
+create name_init mem_t_init mem_n_init mem_f_init
+       dsk_t_init dsk_f_init cpu_t_init offline_init =
     Node
     {
+      name  = name_init,
       t_mem = mem_t_init,
       n_mem = mem_n_init,
       f_mem = mem_f_init,
       t_dsk = dsk_t_init,
       f_dsk = dsk_f_init,
+      t_cpu = cpu_t_init,
+      u_cpu = 0,
       plist = [],
       slist = [],
       failN1 = True,
@@ -81,49 +147,98 @@ create mem_t_init mem_n_init mem_f_init dsk_t_init dsk_f_init =
       p_mem = (fromIntegral mem_f_init) / mem_t_init,
       p_dsk = (fromIntegral dsk_f_init) / dsk_t_init,
       p_rem = 0,
-      offline = False,
-      x_mem = 0
+      p_cpu = 0,
+      offline = offline_init,
+      x_mem = 0,
+      m_dsk = noLimit,
+      m_cpu = noLimit
     }
 
 -- | Changes the index.
+--
 -- This is used only during the building of the data structures.
-setIdx :: Node -> Int -> Node
+setIdx :: Node -> T.Ndx -> Node
 setIdx t i = t {idx = i}
 
--- | Sets the offline attribute
+-- | Changes the name.
+--
+-- This is used only during the building of the data structures.
+setName :: Node -> String -> Node
+setName t s = t {name = s}
+
+-- | Sets the offline attribute.
 setOffline :: Node -> Bool -> Node
 setOffline t val = t { offline = val }
 
--- | Sets the unnaccounted memory
+-- | Sets the unnaccounted memory.
 setXmem :: Node -> Int -> Node
 setXmem t val = t { x_mem = val }
 
--- | Given the rmem, free memory and disk, computes the failn1 status.
-computeFailN1 :: Int -> Int -> Int -> Bool
-computeFailN1 new_rmem new_mem new_dsk =
-    new_mem <= new_rmem || new_dsk <= 0
+-- | Sets the max disk usage ratio
+setMdsk :: Node -> Double -> Node
+setMdsk t val = t { m_dsk = val }
 
--- | Given the new free memory and disk, fail if any of them is below zero.
-failHealth :: Int -> Int -> Bool
-failHealth new_mem new_dsk = new_mem <= 0 || new_dsk <= 0
+-- | Sets the max cpu usage ratio
+setMcpu :: Node -> Double -> Node
+setMcpu t val = t { m_cpu = val }
 
 -- | Computes the maximum reserved memory for peers from a peer map.
 computeMaxRes :: PeerMap.PeerMap -> PeerMap.Elem
 computeMaxRes new_peers = PeerMap.maxElem new_peers
 
 -- | Builds the peer map for a given node.
-buildPeers :: Node -> Container.Container Instance.Instance -> Int -> Node
-buildPeers t il num_nodes =
+buildPeers :: Node -> Instance.List -> Node
+buildPeers t il =
     let mdata = map
                 (\i_idx -> let inst = Container.find i_idx il
                            in (Instance.pnode inst, Instance.mem inst))
                 (slist t)
-        pmap = PeerMap.accumArray (+) 0 (0, num_nodes - 1) mdata
+        pmap = PeerMap.accumArray (+) mdata
         new_rmem = computeMaxRes pmap
         new_failN1 = computeFailN1 new_rmem (f_mem t) (f_dsk t)
         new_prem = (fromIntegral new_rmem) / (t_mem t)
     in t {peers=pmap, failN1 = new_failN1, r_mem = new_rmem, p_rem = new_prem}
 
+-- | Assigns an instance to a node as primary without other updates.
+setPri :: Node -> T.Idx -> Node
+setPri t idx = t { plist = idx:(plist t) }
+
+-- | Assigns an instance to a node as secondary without other updates.
+setSec :: Node -> T.Idx -> Node
+setSec t idx = t { slist = idx:(slist t) }
+
+-- | Add primary cpus to a node
+addCpus :: Node -> Int -> Node
+addCpus t count =
+    let new_count = (u_cpu t) + count
+    in t { u_cpu = new_count, p_cpu = (fromIntegral new_count) / (t_cpu t) }
+
+-- * Update functions
+
+-- | Sets the free memory.
+setFmem :: Node -> Int -> Node
+setFmem t new_mem =
+    let new_n1 = computeFailN1 (r_mem t) new_mem (f_dsk t)
+        new_mp = (fromIntegral new_mem) / (t_mem t)
+    in
+      t { f_mem = new_mem, failN1 = new_n1, p_mem = new_mp }
+
+-- | Given the rmem, free memory and disk, computes the failn1 status.
+computeFailN1 :: Int -> Int -> Int -> Bool
+computeFailN1 new_rmem new_mem new_dsk =
+    new_mem <= new_rmem || new_dsk <= 0
+
+-- | Given the new free memory and disk, fail if any of them is below zero.
+failHealth :: Int -> Int -> Bool
+failHealth new_mem new_dsk = new_mem <= 0 || new_dsk <= 0
+
+-- | Given new limits, check if any of them are overtaken
+failLimits :: Node -> Double -> Double -> Bool
+failLimits t new_dsk new_cpu =
+    let l_dsk = m_dsk t
+        l_cpu = m_cpu t
+    in (l_dsk > new_dsk) || (l_cpu >= 0 && l_cpu < new_cpu)
+
 -- | Removes a primary instance.
 removePri :: Node -> Instance.Instance -> Node
 removePri t inst =
@@ -134,8 +249,11 @@ removePri t inst =
         new_mp = (fromIntegral new_mem) / (t_mem t)
         new_dp = (fromIntegral new_dsk) / (t_dsk t)
         new_failn1 = computeFailN1 (r_mem t) new_mem new_dsk
+        new_ucpu = (u_cpu t) - (Instance.vcpus inst)
+        new_rcpu = (fromIntegral new_ucpu) / (t_cpu t)
     in t {plist = new_plist, f_mem = new_mem, f_dsk = new_dsk,
-          failN1 = new_failn1, p_mem = new_mp, p_dsk = new_dp}
+          failN1 = new_failn1, p_mem = new_mp, p_dsk = new_dp,
+          u_cpu = new_ucpu, p_cpu = new_rcpu}
 
 -- | Removes a secondary instance.
 removeSec :: Node -> Instance.Instance -> Node
@@ -166,19 +284,25 @@ addPri t inst =
     let iname = Instance.idx inst
         new_mem = f_mem t - Instance.mem inst
         new_dsk = f_dsk t - Instance.dsk inst
-        new_failn1 = computeFailN1 (r_mem t) new_mem new_dsk in
-      if (failHealth new_mem new_dsk) || (new_failn1 && not (failN1 t)) then
+        new_failn1 = computeFailN1 (r_mem t) new_mem new_dsk
+        new_ucpu = (u_cpu t) + (Instance.vcpus inst)
+        new_pcpu = (fromIntegral new_ucpu) / (t_cpu t)
+        new_dp = (fromIntegral new_dsk) / (t_dsk t)
+    in
+      if (failHealth new_mem new_dsk) || (new_failn1 && not (failN1 t)) ||
+         (failLimits t new_dp new_pcpu)
+      then
         Nothing
       else
         let new_plist = iname:(plist t)
             new_mp = (fromIntegral new_mem) / (t_mem t)
-            new_dp = (fromIntegral new_dsk) / (t_dsk t)
         in
         Just t {plist = new_plist, f_mem = new_mem, f_dsk = new_dsk,
-                failN1 = new_failn1, p_mem = new_mp, p_dsk = new_dp}
+                failN1 = new_failn1, p_mem = new_mp, p_dsk = new_dp,
+                u_cpu = new_ucpu, p_cpu = new_pcpu}
 
 -- | Adds a secondary instance.
-addSec :: Node -> Instance.Instance -> Int -> Maybe Node
+addSec :: Node -> Instance.Instance -> T.Ndx -> Maybe Node
 addSec t inst pdx =
     let iname = Instance.idx inst
         old_peers = peers t
@@ -188,39 +312,46 @@ addSec t inst pdx =
         new_peers = PeerMap.add pdx new_peem old_peers
         new_rmem = max (r_mem t) new_peem
         new_prem = (fromIntegral new_rmem) / (t_mem t)
-        new_failn1 = computeFailN1 new_rmem old_mem new_dsk in
-    if (failHealth old_mem new_dsk) || (new_failn1 && not (failN1 t)) then
-        Nothing
-    else
-        let new_slist = iname:(slist t)
-            new_dp = (fromIntegral new_dsk) / (t_dsk t)
-        in
-        Just t {slist = new_slist, f_dsk = new_dsk,
-                peers = new_peers, failN1 = new_failn1,
-                r_mem = new_rmem, p_dsk = new_dp,
-                p_rem = new_prem}
-
--- | Add a primary instance to a node without other updates
-setPri :: Node -> Int -> Node
-setPri t idx = t { plist = idx:(plist t) }
+        new_failn1 = computeFailN1 new_rmem old_mem new_dsk
+        new_dp = (fromIntegral new_dsk) / (t_dsk t)
+    in if (failHealth old_mem new_dsk) || (new_failn1 && not (failN1 t)) ||
+          (failLimits t new_dp noLimit)
+       then
+           Nothing
+       else
+           let new_slist = iname:(slist t)
+           in
+             Just t {slist = new_slist, f_dsk = new_dsk,
+                     peers = new_peers, failN1 = new_failn1,
+                     r_mem = new_rmem, p_dsk = new_dp,
+                     p_rem = new_prem}
 
--- | Add a secondary instance to a node without other updates
-setSec :: Node -> Int -> Node
-setSec t idx = t { slist = idx:(slist t) }
+-- * Display functions
 
 -- | String converter for the node list functionality.
-list :: Int -> String -> Node -> String
-list mname n t =
-    let pl = plist t
-        sl = slist t
+list :: Int -> Node -> String
+list mname t =
+    let pl = length $ plist t
+        sl = length $ slist t
         mp = p_mem t
         dp = p_dsk t
+        cp = p_cpu t
         off = offline t
         fn = failN1 t
+        tmem = t_mem t
+        nmem = n_mem t
+        xmem = x_mem t
+        fmem = f_mem t
+        imem = (truncate tmem) - nmem - xmem - fmem
     in
-      printf " %c %-*s %5.0f %5d %5d %5d %5.0f %5d %3d %3d %.5f %.5f"
+      if off
+         then printf " - %-*s %57s %3d %3d"
+              mname (name t) "" pl sl
+         else
+             printf " %c %-*s %5.0f %5d %5d %5d %5d %5d %5.0f %5d\
+                    \ %4.0f %4d %3d %3d %6.4f %6.4f %5.2f"
                  (if off then '-' else if fn then '*' else ' ')
-                 mname n (t_mem t) (n_mem t) (f_mem t) (r_mem t)
+                 mname (name t) tmem nmem imem xmem fmem (r_mem t)
                  ((t_dsk t) / 1024) ((f_dsk t) `div` 1024)
-                 (length pl) (length sl)
-                 mp dp
+                 (t_cpu t) (u_cpu t)
+                 pl sl mp dp cp