Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Loader.hs @ b513faa1

History | View | Annotate | Download (5.4 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
    ) where
13

    
14
import Data.List
15
import Data.Maybe (fromJust)
16
import Text.Printf (printf)
17

    
18
import qualified Ganeti.HTools.Container as Container
19
import qualified Ganeti.HTools.Instance as Instance
20
import qualified Ganeti.HTools.Node as Node
21

    
22
import Ganeti.HTools.Types
23

    
24

    
25
-- | Swap a list of @(a, b)@ into @(b, a)@
26
swapPairs :: [(a, b)] -> [(b, a)]
27
swapPairs = map (\ (a, b) -> (b, a))
28

    
29
-- | Lookups a node into an assoc list
30
lookupNode :: (Monad m) => NameAssoc -> String -> String -> m Int
31
lookupNode ktn inst node =
32
    case lookup node ktn of
33
      Nothing -> fail $ "Unknown node '" ++ node ++ "' for instance " ++ inst
34
      Just idx -> return idx
35

    
36
assignIndices :: (Element a) =>
37
                 [(String, a)]
38
              -> (NameAssoc, [(Int, a)])
39
assignIndices =
40
    unzip . map (\ (idx, (k, v)) -> ((k, idx), (idx, setIdx v idx)))
41
          . zip [0..]
42

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

    
69
-- | Compute the longest common suffix of a NameList list that
70
-- | starts with a dot
71
longestDomain :: NameList -> String
72
longestDomain [] = ""
73
longestDomain ((_,x):xs) =
74
    let
75
        onlyStrings = snd $ unzip xs
76
    in
77
      foldr (\ suffix accu -> if all (isSuffixOf suffix) onlyStrings
78
                              then suffix
79
                              else accu)
80
      "" $ filter (isPrefixOf ".") (tails x)
81

    
82
-- | Remove tails from the (Int, String) lists
83
stripSuffix :: String -> NameList -> NameList
84
stripSuffix suffix lst =
85
    let sflen = length suffix in
86
    map (\ (key, name) -> (key, take ((length name) - sflen) name)) lst
87

    
88
{-| Initializer function that loads the data from a node and list file
89
    and massages it into the correct format. -}
90
mergeData :: ([(String, Int)], Node.AssocList,
91
              [(String, Int)], Instance.AssocList) -- ^ Data from either
92
                                                   -- Text.loadData
93
                                                   -- or Rapi.loadData
94
          -> Result (NodeList, InstanceList, String, NameList, NameList)
95
mergeData (ktn, nl, kti, il) = do
96
  let
97
      nl2 = fixNodes nl il
98
      il3 = Container.fromAssocList il
99
      nl3 = Container.fromAssocList
100
            (map (\ (k, v) -> (k, Node.buildPeers v il3 (length nl2))) nl2)
101
      xtn = swapPairs ktn
102
      xti = swapPairs kti
103
      common_suffix = longestDomain (xti ++ xtn)
104
      stn = stripSuffix common_suffix xtn
105
      sti = stripSuffix common_suffix xti
106
  return (nl3, il3, common_suffix, stn, sti)
107

    
108
-- | Check cluster data for consistency
109
checkData :: NodeList -> InstanceList -> NameList -> NameList
110
          -> ([String], NodeList)
111
checkData nl il ktn _ =
112
    Container.mapAccum
113
        (\ msgs node ->
114
             let nname = fromJust $ lookup (Node.idx node) ktn
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 -> InstanceList -> 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 -> InstanceList -> 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)