Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Loader.hs @ 19f38ee8

History | View | Annotate | Download (6 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
    , RqType(..)
15
    , Request(..)
16
    ) where
17

    
18
import Data.List
19
import Data.Maybe (fromJust)
20
import Text.Printf (printf)
21

    
22
import qualified Ganeti.HTools.Container as Container
23
import qualified Ganeti.HTools.Instance as Instance
24
import qualified Ganeti.HTools.Node as Node
25

    
26
import Ganeti.HTools.Types
27

    
28
-- * Types
29

    
30
{-| The request type.
31

    
32
This type denotes what request we got from Ganeti and also holds
33
request-specific fields.
34

    
35
-}
36
data RqType
37
    = Allocate Instance.Instance Int -- ^ A new instance allocation
38
    | Relocate Idx Int [Ndx]         -- ^ Move an instance to a new
39
                                     -- secondary node
40
    deriving (Show)
41

    
42
-- | A complete request, as received from Ganeti.
43
data Request = Request RqType Node.List Instance.List String
44
    deriving (Show)
45

    
46
-- * Functions
47

    
48
-- | Lookups a node into an assoc list.
49
lookupNode :: (Monad m) => [(String, Ndx)] -> String -> String -> m Ndx
50
lookupNode ktn inst node =
51
    case lookup node ktn of
52
      Nothing -> fail $ "Unknown node '" ++ node ++ "' for instance " ++ inst
53
      Just idx -> return idx
54

    
55
-- | Lookups an instance into an assoc list.
56
lookupInstance :: (Monad m) => [(String, Idx)] -> String -> m Idx
57
lookupInstance kti inst =
58
    case lookup inst kti of
59
      Nothing -> fail $ "Unknown instance '" ++ inst ++ "'"
60
      Just idx -> return idx
61

    
62
-- | Given a list of elements (and their names), assign indices to them.
63
assignIndices :: (Element a) =>
64
                 [(String, a)]
65
              -> (NameAssoc, [(Int, a)])
66
assignIndices =
67
    unzip . map (\ (idx, (k, v)) -> ((k, idx), (idx, setIdx v idx)))
68
          . zip [0..]
69

    
70
-- | For each instance, add its index to its primary and secondary nodes.
71
fixNodes :: [(Ndx, Node.Node)]
72
         -> [(Idx, Instance.Instance)]
73
         -> [(Ndx, Node.Node)]
74
fixNodes nl il =
75
    foldl' (\accu (idx, inst) ->
76
                let
77
                    assocEqual = (\ (i, _) (j, _) -> i == j)
78
                    pdx = Instance.pnode inst
79
                    sdx = Instance.snode inst
80
                    pold = fromJust $ lookup pdx accu
81
                    pnew = Node.setPri pold idx
82
                    ac1 = deleteBy assocEqual (pdx, pold) accu
83
                    ac2 = (pdx, pnew):ac1
84
                in
85
                  if sdx /= Node.noSecondary then
86
                      let
87
                          sold = fromJust $ lookup sdx accu
88
                          snew = Node.setSec sold idx
89
                          ac3 = deleteBy assocEqual (sdx, sold) ac2
90
                          ac4 = (sdx, snew):ac3
91
                      in ac4
92
                  else
93
                      ac2
94
           ) nl il
95

    
96
-- | Compute the longest common suffix of a list of strings that
97
-- | starts with a dot.
98
longestDomain :: [String] -> String
99
longestDomain [] = ""
100
longestDomain (x:xs) =
101
      foldr (\ suffix accu -> if all (isSuffixOf suffix) xs
102
                              then suffix
103
                              else accu)
104
      "" $ filter (isPrefixOf ".") (tails x)
105

    
106
-- | Remove tail suffix from a string.
107
stripSuffix :: Int -> String -> String
108
stripSuffix sflen name = take ((length name) - sflen) name
109

    
110
-- | Initializer function that loads the data from a node and instance
111
-- list and massages it into the correct format.
112
mergeData :: (Node.AssocList,
113
              Instance.AssocList) -- ^ Data from either Text.loadData
114
                                  -- or Rapi.loadData
115
          -> Result (Node.List, Instance.List, String)
116
mergeData (nl, il) = do
117
  let
118
      nl2 = fixNodes nl il
119
      il3 = Container.fromAssocList il
120
      nl3 = Container.fromAssocList
121
            (map (\ (k, v) -> (k, Node.buildPeers v il3)) nl2)
122
      node_names = map Node.name $ Container.elems nl3
123
      inst_names = map Instance.name $ Container.elems il3
124
      common_suffix = longestDomain (node_names ++ inst_names)
125
      csl = length common_suffix
126
      snl = Container.map (\n -> setName n (stripSuffix csl $ nameOf n)) nl3
127
      sil = Container.map (\i -> setName i (stripSuffix csl $ nameOf i)) il3
128
  return (snl, sil, common_suffix)
129

    
130
-- | Checks the cluster data for consistency.
131
checkData :: Node.List -> Instance.List
132
          -> ([String], Node.List)
133
checkData nl il =
134
    Container.mapAccum
135
        (\ msgs node ->
136
             let nname = Node.name node
137
                 nilst = map (flip Container.find $ il) (Node.plist node)
138
                 dilst = filter (not . Instance.running) nilst
139
                 adj_mem = sum . map Instance.mem $ dilst
140
                 delta_mem = (truncate $ Node.t_mem node)
141
                             - (Node.n_mem node)
142
                             - (Node.f_mem node)
143
                             - (nodeImem node il)
144
                             + adj_mem
145
                 delta_dsk = (truncate $ Node.t_dsk node)
146
                             - (Node.f_dsk node)
147
                             - (nodeIdsk node il)
148
                 newn = Node.setFmem (Node.setXmem node delta_mem)
149
                        (Node.f_mem node - adj_mem)
150
                 umsg1 = if delta_mem > 512 || delta_dsk > 1024
151
                         then [printf "node %s is missing %d MB ram \
152
                                     \and %d GB disk"
153
                                     nname delta_mem (delta_dsk `div` 1024)]
154
                         else []
155
             in (msgs ++ umsg1, newn)
156
        ) [] nl
157

    
158
-- | Compute the amount of memory used by primary instances on a node.
159
nodeImem :: Node.Node -> Instance.List -> Int
160
nodeImem node il =
161
    let rfind = flip Container.find $ il
162
    in sum . map Instance.mem .
163
       map rfind $ Node.plist node
164

    
165
-- | Compute the amount of disk used by instances on a node (either primary
166
-- or secondary).
167
nodeIdsk :: Node.Node -> Instance.List -> Int
168
nodeIdsk node il =
169
    let rfind = flip Container.find $ il
170
    in sum . map Instance.dsk .
171
       map rfind $ (Node.plist node) ++ (Node.slist node)