More code reorganizations
[ganeti-local] / Ganeti / HTools / Cluster.hs
index 77237f7..33d523c 100644 (file)
@@ -32,7 +32,6 @@ module Ganeti.HTools.Cluster
     , compCV
     , printStats
     -- * Loading functions
     , compCV
     , printStats
     -- * Loading functions
-    , loadData
     , checkData
     ) where
 
     , checkData
     ) where
 
@@ -45,12 +44,9 @@ import Control.Monad
 import qualified Ganeti.HTools.Container as Container
 import qualified Ganeti.HTools.Instance as Instance
 import qualified Ganeti.HTools.Node as Node
 import qualified Ganeti.HTools.Container as Container
 import qualified Ganeti.HTools.Instance as Instance
 import qualified Ganeti.HTools.Node as Node
+import Ganeti.HTools.Types
 import Ganeti.HTools.Utils
 
 import Ganeti.HTools.Utils
 
-type NodeList = Container.Container Node.Node
-type InstanceList = Container.Container Instance.Instance
--- | The type used to hold idx-to-name mappings
-type NameList = [(Int, String)]
 -- | A separate name for the cluster score type
 type Score = Double
 
 -- | A separate name for the cluster score type
 type Score = Double
 
@@ -475,8 +471,10 @@ checkMove nodes_idx ini_tbl victims =
         -- iterate over all instances, computing the best move
         best_tbl =
             foldl'
         -- iterate over all instances, computing the best move
         best_tbl =
             foldl'
-            (\ step_tbl elem -> compareTables step_tbl $
-                                checkInstanceMove nodes_idx ini_tbl elem)
+            (\ step_tbl elem ->
+                 if Instance.snode elem == Node.noSecondary then step_tbl
+                    else compareTables step_tbl $
+                         checkInstanceMove nodes_idx ini_tbl elem)
             ini_tbl victims
         Table _ _ _ best_plc = best_tbl
     in
             ini_tbl victims
         Table _ _ _ best_plc = best_tbl
     in
@@ -688,109 +686,6 @@ printStats nl =
 
 -- Loading functions
 
 
 -- Loading functions
 
-{- | Convert newline and delimiter-separated text.
-
-This function converts a text in tabular format as generated by
-@gnt-instance list@ and @gnt-node list@ to a list of objects using a
-supplied conversion function.
-
--}
-loadTabular :: (Monad m) => String -> ([String] -> m (String, a))
-            -> (a -> Int -> a) -> m ([(String, Int)], [(Int, a)])
-loadTabular text_data convert_fn set_fn = do
-  let lines_data = lines text_data
-      rows = map (sepSplit '|') lines_data
-  kerows <- mapM convert_fn rows
-  let idxrows = map (\ (idx, (k, v)) -> ((k, idx), (idx, set_fn v idx)))
-                (zip [0..] kerows)
-  return $ unzip idxrows
-
--- | For each instance, add its index to its primary and secondary nodes
-fixNodes :: [(Int, Node.Node)]
-         -> [(Int, Instance.Instance)]
-         -> [(Int, Node.Node)]
-fixNodes nl il =
-    foldl' (\accu (idx, inst) ->
-                let
-                    assocEqual = (\ (i, _) (j, _) -> i == j)
-                    pdx = Instance.pnode inst
-                    sdx = Instance.snode inst
-                    pold = fromJust $ lookup pdx accu
-                    sold = fromJust $ lookup sdx accu
-                    pnew = Node.setPri pold idx
-                    snew = Node.setSec sold idx
-                    ac1 = deleteBy assocEqual (pdx, pold) accu
-                    ac2 = deleteBy assocEqual (sdx, sold) ac1
-                    ac3 = (pdx, pnew):(sdx, snew):ac2
-                in ac3) nl il
-
--- | Compute the longest common suffix of a NameList list that
--- | starts with a dot
-longestDomain :: NameList -> String
-longestDomain [] = ""
-longestDomain ((_,x):xs) =
-    let
-        onlyStrings = snd $ unzip xs
-    in
-      foldr (\ suffix accu -> if all (isSuffixOf suffix) onlyStrings
-                              then suffix
-                              else accu)
-      "" $ filter (isPrefixOf ".") (tails x)
-
--- | Remove tails from the (Int, String) lists
-stripSuffix :: String -> NameList -> NameList
-stripSuffix suffix lst =
-    let sflen = length suffix in
-    map (\ (key, name) -> (key, take ((length name) - sflen) name)) lst
-
--- | Lookups a node into an assoc list
-lookupNode :: (Monad m) => String -> String -> [(String, Int)] -> m Int
-lookupNode node inst ktn =
-    case lookup node ktn of
-      Nothing -> fail $ "Unknown node " ++ node ++ " for instance " ++ inst
-      Just idx -> return idx
-
-{-| Initializer function that loads the data from a node and list file
-    and massages it into the correct format. -}
-loadData :: String -- ^ Node data in text format
-         -> String -- ^ Instance data in text format
-         -> Result (Container.Container Node.Node,
-                    Container.Container Instance.Instance,
-                    String, NameList, NameList)
-loadData ndata idata = do
-  {- node file: name t_mem n_mem f_mem t_disk f_disk -}
-  (ktn, nl) <- loadTabular ndata
-               (\ (name:tm:nm:fm:td:fd:fo:[]) ->
-                    return (name,
-                            if any (== "?") [tm,nm,fm,td,fd] || fo == "Y" then
-                                Node.create 0 0 0 0 0 True
-                            else
-                                Node.create (read tm) (read nm) (read fm)
-                                        (read td) (read fd) False
-                           ))
-               Node.setIdx
-      {- instance file: name mem disk status pnode snode -}
-  (kti, il) <- loadTabular idata
-                  (\ (name:mem:dsk:status:pnode:snode:[]) -> do
-                     pidx <- lookupNode pnode name ktn
-                     sidx <- lookupNode snode name ktn
-                     let newinst = Instance.create (read mem) (read dsk)
-                                   status pidx sidx
-                     return (name, newinst)
-                  )
-                  Instance.setIdx
-  let
-      nl2 = fixNodes nl il
-      il3 = Container.fromAssocList il
-      nl3 = Container.fromAssocList
-            (map (\ (k, v) -> (k, Node.buildPeers v il3 (length nl2))) nl2)
-      xtn = swapPairs ktn
-      xti = swapPairs kti
-      common_suffix = longestDomain (xti ++ xtn)
-      stn = stripSuffix common_suffix xtn
-      sti = stripSuffix common_suffix xti
-  return (nl3, il3, common_suffix, stn, sti)
-
 -- | Compute the amount of memory used by primary instances on a node.
 nodeImem :: Node.Node -> InstanceList -> Int
 nodeImem node il =
 -- | Compute the amount of memory used by primary instances on a node.
 nodeImem :: Node.Node -> InstanceList -> Int
 nodeImem node il =
@@ -806,7 +701,6 @@ nodeIdsk node il =
     in sum . map Instance.dsk .
        map rfind $ (Node.plist node) ++ (Node.slist node)
 
     in sum . map Instance.dsk .
        map rfind $ (Node.plist node) ++ (Node.slist node)
 
-
 -- | Check cluster data for consistency
 checkData :: NodeList -> InstanceList -> NameList -> NameList
           -> ([String], NodeList)
 -- | Check cluster data for consistency
 checkData :: NodeList -> InstanceList -> NameList -> NameList
           -> ([String], NodeList)