Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Loader.hs @ 9188aeef

History | View | Annotate | Download (5.5 kB)

1
{-| Loading data from external sources
2

    
3
This module holds the common code for loading the cluster state from external sources.
4

    
5
-}
6

    
7
module Ganeti.HTools.Loader
8
    ( mergeData
9
    , checkData
10
    , assignIndices
11
    , lookupNode
12
    , lookupInstance
13
    , stripSuffix
14
    ) where
15

    
16
import Data.List
17
import Data.Maybe (fromJust)
18
import Text.Printf (printf)
19

    
20
import qualified Ganeti.HTools.Container as Container
21
import qualified Ganeti.HTools.Instance as Instance
22
import qualified Ganeti.HTools.Node as Node
23

    
24
import Ganeti.HTools.Types
25

    
26
-- | Lookups a node into an assoc list.
27
lookupNode :: (Monad m) => [(String, Ndx)] -> String -> String -> m Ndx
28
lookupNode ktn inst node =
29
    case lookup node ktn of
30
      Nothing -> fail $ "Unknown node '" ++ node ++ "' for instance " ++ inst
31
      Just idx -> return idx
32

    
33
-- | Lookups an instance into an assoc list.
34
lookupInstance :: (Monad m) => [(String, Idx)] -> String -> m Idx
35
lookupInstance kti inst =
36
    case lookup inst kti of
37
      Nothing -> fail $ "Unknown instance '" ++ inst ++ "'"
38
      Just idx -> return idx
39

    
40
-- | Given a list of elements (and their names), assign indices to them.
41
assignIndices :: (Element a) =>
42
                 [(String, a)]
43
              -> (NameAssoc, [(Int, a)])
44
assignIndices =
45
    unzip . map (\ (idx, (k, v)) -> ((k, idx), (idx, setIdx v idx)))
46
          . zip [0..]
47

    
48
-- | For each instance, add its index to its primary and secondary nodes.
49
fixNodes :: [(Ndx, Node.Node)]
50
         -> [(Idx, Instance.Instance)]
51
         -> [(Ndx, Node.Node)]
52
fixNodes nl il =
53
    foldl' (\accu (idx, inst) ->
54
                let
55
                    assocEqual = (\ (i, _) (j, _) -> i == j)
56
                    pdx = Instance.pnode inst
57
                    sdx = Instance.snode inst
58
                    pold = fromJust $ lookup pdx accu
59
                    pnew = Node.setPri pold idx
60
                    ac1 = deleteBy assocEqual (pdx, pold) accu
61
                    ac2 = (pdx, pnew):ac1
62
                in
63
                  if sdx /= Node.noSecondary then
64
                      let
65
                          sold = fromJust $ lookup sdx accu
66
                          snew = Node.setSec sold idx
67
                          ac3 = deleteBy assocEqual (sdx, sold) ac2
68
                          ac4 = (sdx, snew):ac3
69
                      in ac4
70
                  else
71
                      ac2
72
           ) nl il
73

    
74
-- | Compute the longest common suffix of a list of strings that
75
-- | starts with a dot.
76
longestDomain :: [String] -> String
77
longestDomain [] = ""
78
longestDomain (x:xs) =
79
      foldr (\ suffix accu -> if all (isSuffixOf suffix) xs
80
                              then suffix
81
                              else accu)
82
      "" $ filter (isPrefixOf ".") (tails x)
83

    
84
-- | Remove tail suffix from a string.
85
stripSuffix :: Int -> String -> String
86
stripSuffix sflen name = take ((length name) - sflen) name
87

    
88
-- | Initializer function that loads the data from a node and instance
89
-- list and massages it into the correct format.
90
mergeData :: (Node.AssocList,
91
              Instance.AssocList) -- ^ Data from either Text.loadData
92
                                  -- or Rapi.loadData
93
          -> Result (Node.List, Instance.List, String)
94
mergeData (nl, il) = do
95
  let
96
      nl2 = fixNodes nl il
97
      il3 = Container.fromAssocList il
98
      nl3 = Container.fromAssocList
99
            (map (\ (k, v) -> (k, Node.buildPeers v il3)) nl2)
100
      node_names = map Node.name $ Container.elems nl3
101
      inst_names = map Instance.name $ Container.elems il3
102
      common_suffix = longestDomain (node_names ++ inst_names)
103
      csl = length common_suffix
104
      snl = Container.map (\n -> setName n (stripSuffix csl $ nameOf n)) nl3
105
      sil = Container.map (\i -> setName i (stripSuffix csl $ nameOf i)) il3
106
  return (snl, sil, common_suffix)
107

    
108
-- | Checks the cluster data for consistency.
109
checkData :: Node.List -> Instance.List
110
          -> ([String], Node.List)
111
checkData nl il =
112
    Container.mapAccum
113
        (\ msgs node ->
114
             let nname = Node.name node
115
                 nilst = map (flip Container.find $ il) (Node.plist node)
116
                 dilst = filter (not . Instance.running) nilst
117
                 adj_mem = sum . map Instance.mem $ dilst
118
                 delta_mem = (truncate $ Node.t_mem node)
119
                             - (Node.n_mem node)
120
                             - (Node.f_mem node)
121
                             - (nodeImem node il)
122
                             + adj_mem
123
                 delta_dsk = (truncate $ Node.t_dsk node)
124
                             - (Node.f_dsk node)
125
                             - (nodeIdsk node il)
126
                 newn = Node.setFmem (Node.setXmem node delta_mem)
127
                        (Node.f_mem node - adj_mem)
128
                 umsg1 = if delta_mem > 512 || delta_dsk > 1024
129
                         then [printf "node %s is missing %d MB ram \
130
                                     \and %d GB disk"
131
                                     nname delta_mem (delta_dsk `div` 1024)]
132
                         else []
133
             in (msgs ++ umsg1, newn)
134
        ) [] nl
135

    
136
-- | Compute the amount of memory used by primary instances on a node.
137
nodeImem :: Node.Node -> Instance.List -> Int
138
nodeImem node il =
139
    let rfind = flip Container.find $ il
140
    in sum . map Instance.mem .
141
       map rfind $ Node.plist node
142

    
143
-- | Compute the amount of disk used by instances on a node (either primary
144
-- or secondary).
145
nodeIdsk :: Node.Node -> Instance.List -> Int
146
nodeIdsk node il =
147
    let rfind = flip Container.find $ il
148
    in sum . map Instance.dsk .
149
       map rfind $ (Node.plist node) ++ (Node.slist node)