Add type synonyms for the node/instance indices
[ganeti-local] / Ganeti / HTools / Loader.hs
index 442dbb3..1720bcb 100644 (file)
@@ -9,6 +9,7 @@ module Ganeti.HTools.Loader
     , checkData
     , assignIndices
     , lookupNode
+    , stripSuffix
     ) where
 
 import Data.List
@@ -21,13 +22,8 @@ import qualified Ganeti.HTools.Node as Node
 
 import Ganeti.HTools.Types
 
-
--- | Swap a list of @(a, b)@ into @(b, a)@
-swapPairs :: [(a, b)] -> [(b, a)]
-swapPairs = map (\ (a, b) -> (b, a))
-
 -- | Lookups a node into an assoc list
-lookupNode :: (Monad m) => NameAssoc -> String -> String -> m Int
+lookupNode :: (Monad m) => [(String, Ndx)] -> String -> String -> m Ndx
 lookupNode ktn inst node =
     case lookup node ktn of
       Nothing -> fail $ "Unknown node '" ++ node ++ "' for instance " ++ inst
@@ -41,9 +37,9 @@ assignIndices =
           . zip [0..]
 
 -- | For each instance, add its index to its primary and secondary nodes
-fixNodes :: [(Int, Node.Node)]
-         -> [(Int, Instance.Instance)]
-         -> [(Int, Node.Node)]
+fixNodes :: [(Ndx, Node.Node)]
+         -> [(Idx, Instance.Instance)]
+         -> [(Ndx, Node.Node)]
 fixNodes nl il =
     foldl' (\accu (idx, inst) ->
                 let
@@ -68,13 +64,10 @@ fixNodes nl il =
 
 -- | Compute the longest common suffix of a NameList list that
 -- | starts with a dot
-longestDomain :: NameList -> String
+longestDomain :: [String] -> String
 longestDomain [] = ""
-longestDomain ((_,x):xs) =
-    let
-        onlyStrings = snd $ unzip xs
-    in
-      foldr (\ suffix accu -> if all (isSuffixOf suffix) onlyStrings
+longestDomain (x:xs) =
+      foldr (\ suffix accu -> if all (isSuffixOf suffix) xs
                               then suffix
                               else accu)
       "" $ filter (isPrefixOf ".") (tails x)
@@ -85,34 +78,31 @@ stripSuffix sflen name = take ((length name) - sflen) name
 
 {-| Initializer function that loads the data from a node and list file
     and massages it into the correct format. -}
-mergeData :: ([(String, Int)], Node.AssocList,
-              [(String, Int)], Instance.AssocList) -- ^ Data from either
-                                                   -- Text.loadData
-                                                   -- or Rapi.loadData
-          -> Result (NodeList, InstanceList, String, NameList, NameList)
-mergeData (ktn, nl, kti, il) = do
+mergeData :: (Node.AssocList,
+              Instance.AssocList) -- ^ Data from either Text.loadData
+                                  -- or Rapi.loadData
+          -> Result (Node.List, Instance.List, String)
+mergeData (nl, il) = do
   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)
+      node_names = map Node.name $ Container.elems nl3
+      inst_names = map Instance.name $ Container.elems il3
+      common_suffix = longestDomain (node_names ++ inst_names)
       csl = length common_suffix
-      stn = map (\(x, y) -> (x, stripSuffix csl y)) xtn
-      sti = map (\(x, y) -> (x, stripSuffix csl y)) xti
-      snl = Container.map (\n -> setName n (stripSuffix csl $ name n)) nl3
-      sil = Container.map (\i -> setName i (stripSuffix csl $ name i)) il3
-  return (snl, sil, common_suffix, stn, sti)
+      snl = Container.map (\n -> setName n (stripSuffix csl $ nameOf n)) nl3
+      sil = Container.map (\i -> setName i (stripSuffix csl $ nameOf i)) il3
+  return (snl, sil, common_suffix)
 
 -- | Check cluster data for consistency
-checkData :: NodeList -> InstanceList -> NameList -> NameList
-          -> ([String], NodeList)
-checkData nl il ktn _ =
+checkData :: Node.List -> Instance.List
+          -> ([String], Node.List)
+checkData nl il =
     Container.mapAccum
         (\ msgs node ->
-             let nname = fromJust $ lookup (Node.idx node) ktn
+             let nname = Node.name node
                  nilst = map (flip Container.find $ il) (Node.plist node)
                  dilst = filter (not . Instance.running) nilst
                  adj_mem = sum . map Instance.mem $ dilst
@@ -135,7 +125,7 @@ checkData nl il ktn _ =
         ) [] nl
 
 -- | Compute the amount of memory used by primary instances on a node.
-nodeImem :: Node.Node -> InstanceList -> Int
+nodeImem :: Node.Node -> Instance.List -> Int
 nodeImem node il =
     let rfind = flip Container.find $ il
     in sum . map Instance.mem .
@@ -143,7 +133,7 @@ nodeImem node il =
 
 -- | Compute the amount of disk used by instances on a node (either primary
 -- or secondary).
-nodeIdsk :: Node.Node -> InstanceList -> Int
+nodeIdsk :: Node.Node -> Instance.List -> Int
 nodeIdsk node il =
     let rfind = flip Container.find $ il
     in sum . map Instance.dsk .