Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Loader.hs @ f9fc7a63

History | View | Annotate | Download (5.5 kB)

1 040afc35 Iustin Pop
{-| Loading data from external sources
2 040afc35 Iustin Pop
3 040afc35 Iustin Pop
This module holds the common code for loading the cluster state from external sources.
4 040afc35 Iustin Pop
5 040afc35 Iustin Pop
-}
6 040afc35 Iustin Pop
7 040afc35 Iustin Pop
module Ganeti.HTools.Loader
8 446d8827 Iustin Pop
    ( mergeData
9 446d8827 Iustin Pop
    , checkData
10 446d8827 Iustin Pop
    , assignIndices
11 446d8827 Iustin Pop
    , lookupNode
12 5a1edeb6 Iustin Pop
    , lookupInstance
13 ed41c179 Iustin Pop
    , stripSuffix
14 446d8827 Iustin Pop
    ) where
15 040afc35 Iustin Pop
16 e4c5beaf Iustin Pop
import Data.List
17 446d8827 Iustin Pop
import Data.Maybe (fromJust)
18 446d8827 Iustin Pop
import Text.Printf (printf)
19 e4c5beaf Iustin Pop
20 e4c5beaf Iustin Pop
import qualified Ganeti.HTools.Container as Container
21 e4c5beaf Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
22 e4c5beaf Iustin Pop
import qualified Ganeti.HTools.Node as Node
23 e4c5beaf Iustin Pop
24 e4c5beaf Iustin Pop
import Ganeti.HTools.Types
25 e4c5beaf Iustin Pop
26 040afc35 Iustin Pop
-- | Lookups a node into an assoc list
27 608efcce Iustin Pop
lookupNode :: (Monad m) => [(String, Ndx)] -> String -> String -> m Ndx
28 040afc35 Iustin Pop
lookupNode ktn inst node =
29 040afc35 Iustin Pop
    case lookup node ktn of
30 040afc35 Iustin Pop
      Nothing -> fail $ "Unknown node '" ++ node ++ "' for instance " ++ inst
31 040afc35 Iustin Pop
      Just idx -> return idx
32 040afc35 Iustin Pop
33 5a1edeb6 Iustin Pop
-- | Lookups an instance into an assoc list
34 5a1edeb6 Iustin Pop
lookupInstance :: (Monad m) => [(String, Idx)] -> String -> m Idx
35 5a1edeb6 Iustin Pop
lookupInstance kti inst =
36 5a1edeb6 Iustin Pop
    case lookup inst kti of
37 5a1edeb6 Iustin Pop
      Nothing -> fail $ "Unknown instance '" ++ inst ++ "'"
38 5a1edeb6 Iustin Pop
      Just idx -> return idx
39 5a1edeb6 Iustin Pop
40 5a1edeb6 Iustin Pop
-- | Given a list of elements (and their names), assign indices to them
41 497e30a1 Iustin Pop
assignIndices :: (Element a) =>
42 497e30a1 Iustin Pop
                 [(String, a)]
43 040afc35 Iustin Pop
              -> (NameAssoc, [(Int, a)])
44 497e30a1 Iustin Pop
assignIndices =
45 497e30a1 Iustin Pop
    unzip . map (\ (idx, (k, v)) -> ((k, idx), (idx, setIdx v idx)))
46 040afc35 Iustin Pop
          . zip [0..]
47 e4c5beaf Iustin Pop
48 e4c5beaf Iustin Pop
-- | For each instance, add its index to its primary and secondary nodes
49 608efcce Iustin Pop
fixNodes :: [(Ndx, Node.Node)]
50 608efcce Iustin Pop
         -> [(Idx, Instance.Instance)]
51 608efcce Iustin Pop
         -> [(Ndx, Node.Node)]
52 e4c5beaf Iustin Pop
fixNodes nl il =
53 e4c5beaf Iustin Pop
    foldl' (\accu (idx, inst) ->
54 e4c5beaf Iustin Pop
                let
55 e4c5beaf Iustin Pop
                    assocEqual = (\ (i, _) (j, _) -> i == j)
56 e4c5beaf Iustin Pop
                    pdx = Instance.pnode inst
57 e4c5beaf Iustin Pop
                    sdx = Instance.snode inst
58 e4c5beaf Iustin Pop
                    pold = fromJust $ lookup pdx accu
59 e4c5beaf Iustin Pop
                    pnew = Node.setPri pold idx
60 e4c5beaf Iustin Pop
                    ac1 = deleteBy assocEqual (pdx, pold) accu
61 e4c5beaf Iustin Pop
                    ac2 = (pdx, pnew):ac1
62 e4c5beaf Iustin Pop
                in
63 e4c5beaf Iustin Pop
                  if sdx /= Node.noSecondary then
64 e4c5beaf Iustin Pop
                      let
65 e4c5beaf Iustin Pop
                          sold = fromJust $ lookup sdx accu
66 e4c5beaf Iustin Pop
                          snew = Node.setSec sold idx
67 e4c5beaf Iustin Pop
                          ac3 = deleteBy assocEqual (sdx, sold) ac2
68 e4c5beaf Iustin Pop
                          ac4 = (sdx, snew):ac3
69 e4c5beaf Iustin Pop
                      in ac4
70 e4c5beaf Iustin Pop
                  else
71 e4c5beaf Iustin Pop
                      ac2
72 e4c5beaf Iustin Pop
           ) nl il
73 e4c5beaf Iustin Pop
74 f9fc7a63 Iustin Pop
-- | Compute the longest common suffix of a list of strings that
75 e4c5beaf Iustin Pop
-- | starts with a dot
76 8472a321 Iustin Pop
longestDomain :: [String] -> String
77 e4c5beaf Iustin Pop
longestDomain [] = ""
78 8472a321 Iustin Pop
longestDomain (x:xs) =
79 8472a321 Iustin Pop
      foldr (\ suffix accu -> if all (isSuffixOf suffix) xs
80 e4c5beaf Iustin Pop
                              then suffix
81 e4c5beaf Iustin Pop
                              else accu)
82 e4c5beaf Iustin Pop
      "" $ filter (isPrefixOf ".") (tails x)
83 e4c5beaf Iustin Pop
84 26b5d395 Iustin Pop
-- | Remove tail suffix from a string
85 26b5d395 Iustin Pop
stripSuffix :: Int -> String -> String
86 26b5d395 Iustin Pop
stripSuffix sflen name = take ((length name) - sflen) name
87 e4c5beaf Iustin Pop
88 e4c5beaf Iustin Pop
{-| Initializer function that loads the data from a node and list file
89 e4c5beaf Iustin Pop
    and massages it into the correct format. -}
90 e3a684c5 Iustin Pop
mergeData :: (Node.AssocList,
91 e3a684c5 Iustin Pop
              Instance.AssocList) -- ^ Data from either Text.loadData
92 e3a684c5 Iustin Pop
                                  -- or Rapi.loadData
93 262a08a2 Iustin Pop
          -> Result (Node.List, Instance.List, String)
94 e3a684c5 Iustin Pop
mergeData (nl, il) = do
95 e4c5beaf Iustin Pop
  let
96 e4c5beaf Iustin Pop
      nl2 = fixNodes nl il
97 e4c5beaf Iustin Pop
      il3 = Container.fromAssocList il
98 e4c5beaf Iustin Pop
      nl3 = Container.fromAssocList
99 e4c5beaf Iustin Pop
            (map (\ (k, v) -> (k, Node.buildPeers v il3 (length nl2))) nl2)
100 8472a321 Iustin Pop
      node_names = map Node.name $ Container.elems nl3
101 8472a321 Iustin Pop
      inst_names = map Instance.name $ Container.elems il3
102 8472a321 Iustin Pop
      common_suffix = longestDomain (node_names ++ inst_names)
103 26b5d395 Iustin Pop
      csl = length common_suffix
104 262a08a2 Iustin Pop
      snl = Container.map (\n -> setName n (stripSuffix csl $ nameOf n)) nl3
105 262a08a2 Iustin Pop
      sil = Container.map (\i -> setName i (stripSuffix csl $ nameOf i)) il3
106 8472a321 Iustin Pop
  return (snl, sil, common_suffix)
107 446d8827 Iustin Pop
108 446d8827 Iustin Pop
-- | Check cluster data for consistency
109 262a08a2 Iustin Pop
checkData :: Node.List -> Instance.List
110 262a08a2 Iustin Pop
          -> ([String], Node.List)
111 dbd6700b Iustin Pop
checkData nl il =
112 446d8827 Iustin Pop
    Container.mapAccum
113 446d8827 Iustin Pop
        (\ msgs node ->
114 dbd6700b Iustin Pop
             let nname = Node.name node
115 446d8827 Iustin Pop
                 nilst = map (flip Container.find $ il) (Node.plist node)
116 446d8827 Iustin Pop
                 dilst = filter (not . Instance.running) nilst
117 446d8827 Iustin Pop
                 adj_mem = sum . map Instance.mem $ dilst
118 446d8827 Iustin Pop
                 delta_mem = (truncate $ Node.t_mem node)
119 446d8827 Iustin Pop
                             - (Node.n_mem node)
120 446d8827 Iustin Pop
                             - (Node.f_mem node)
121 446d8827 Iustin Pop
                             - (nodeImem node il)
122 446d8827 Iustin Pop
                             + adj_mem
123 446d8827 Iustin Pop
                 delta_dsk = (truncate $ Node.t_dsk node)
124 446d8827 Iustin Pop
                             - (Node.f_dsk node)
125 446d8827 Iustin Pop
                             - (nodeIdsk node il)
126 446d8827 Iustin Pop
                 newn = Node.setFmem (Node.setXmem node delta_mem)
127 446d8827 Iustin Pop
                        (Node.f_mem node - adj_mem)
128 446d8827 Iustin Pop
                 umsg1 = if delta_mem > 512 || delta_dsk > 1024
129 446d8827 Iustin Pop
                         then [printf "node %s is missing %d MB ram \
130 446d8827 Iustin Pop
                                     \and %d GB disk"
131 446d8827 Iustin Pop
                                     nname delta_mem (delta_dsk `div` 1024)]
132 446d8827 Iustin Pop
                         else []
133 446d8827 Iustin Pop
             in (msgs ++ umsg1, newn)
134 446d8827 Iustin Pop
        ) [] nl
135 446d8827 Iustin Pop
136 446d8827 Iustin Pop
-- | Compute the amount of memory used by primary instances on a node.
137 262a08a2 Iustin Pop
nodeImem :: Node.Node -> Instance.List -> Int
138 446d8827 Iustin Pop
nodeImem node il =
139 446d8827 Iustin Pop
    let rfind = flip Container.find $ il
140 446d8827 Iustin Pop
    in sum . map Instance.mem .
141 446d8827 Iustin Pop
       map rfind $ Node.plist node
142 446d8827 Iustin Pop
143 446d8827 Iustin Pop
-- | Compute the amount of disk used by instances on a node (either primary
144 446d8827 Iustin Pop
-- or secondary).
145 262a08a2 Iustin Pop
nodeIdsk :: Node.Node -> Instance.List -> Int
146 446d8827 Iustin Pop
nodeIdsk node il =
147 446d8827 Iustin Pop
    let rfind = flip Container.find $ il
148 446d8827 Iustin Pop
    in sum . map Instance.dsk .
149 446d8827 Iustin Pop
       map rfind $ (Node.plist node) ++ (Node.slist node)