Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Loader.hs @ 903a7d46

History | View | Annotate | Download (6.7 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
{-
8

    
9
Copyright (C) 2009 Google Inc.
10

    
11
This program is free software; you can redistribute it and/or modify
12
it under the terms of the GNU General Public License as published by
13
the Free Software Foundation; either version 2 of the License, or
14
(at your option) any later version.
15

    
16
This program is distributed in the hope that it will be useful, but
17
WITHOUT ANY WARRANTY; without even the implied warranty of
18
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19
General Public License for more details.
20

    
21
You should have received a copy of the GNU General Public License
22
along with this program; if not, write to the Free Software
23
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
24
02110-1301, USA.
25

    
26
-}
27

    
28
module Ganeti.HTools.Loader
29
    ( mergeData
30
    , checkData
31
    , assignIndices
32
    , lookupNode
33
    , lookupInstance
34
    , stripSuffix
35
    , RqType(..)
36
    , Request(..)
37
    ) where
38

    
39
import Data.List
40
import Data.Maybe (fromJust)
41
import Text.Printf (printf)
42

    
43
import qualified Ganeti.HTools.Container as Container
44
import qualified Ganeti.HTools.Instance as Instance
45
import qualified Ganeti.HTools.Node as Node
46

    
47
import Ganeti.HTools.Types
48

    
49
-- * Types
50

    
51
{-| The request type.
52

    
53
This type denotes what request we got from Ganeti and also holds
54
request-specific fields.
55

    
56
-}
57
data RqType
58
    = Allocate Instance.Instance Int -- ^ A new instance allocation
59
    | Relocate Idx Int [Ndx]         -- ^ Move an instance to a new
60
                                     -- secondary node
61
    deriving (Show)
62

    
63
-- | A complete request, as received from Ganeti.
64
data Request = Request RqType Node.List Instance.List String
65
    deriving (Show)
66

    
67
-- * Functions
68

    
69
-- | Lookups a node into an assoc list.
70
lookupNode :: (Monad m) => [(String, Ndx)] -> String -> String -> m Ndx
71
lookupNode ktn inst node =
72
    case lookup node ktn of
73
      Nothing -> fail $ "Unknown node '" ++ node ++ "' for instance " ++ inst
74
      Just idx -> return idx
75

    
76
-- | Lookups an instance into an assoc list.
77
lookupInstance :: (Monad m) => [(String, Idx)] -> String -> m Idx
78
lookupInstance kti inst =
79
    case lookup inst kti of
80
      Nothing -> fail $ "Unknown instance '" ++ inst ++ "'"
81
      Just idx -> return idx
82

    
83
-- | Given a list of elements (and their names), assign indices to them.
84
assignIndices :: (Element a) =>
85
                 [(String, a)]
86
              -> (NameAssoc, [(Int, a)])
87
assignIndices =
88
    unzip . map (\ (idx, (k, v)) -> ((k, idx), (idx, setIdx v idx)))
89
          . zip [0..]
90

    
91
-- | For each instance, add its index to its primary and secondary nodes.
92
fixNodes :: [(Ndx, Node.Node)]
93
         -> [(Idx, Instance.Instance)]
94
         -> [(Ndx, Node.Node)]
95
fixNodes nl il =
96
    foldl' (\accu (idx, inst) ->
97
                let
98
                    assocEqual = (\ (i, _) (j, _) -> i == j)
99
                    pdx = Instance.pnode inst
100
                    sdx = Instance.snode inst
101
                    pold = fromJust $ lookup pdx accu
102
                    pnew = Node.setPri pold idx
103
                    ac1 = deleteBy assocEqual (pdx, pold) accu
104
                    ac2 = (pdx, pnew):ac1
105
                in
106
                  if sdx /= Node.noSecondary then
107
                      let
108
                          sold = fromJust $ lookup sdx accu
109
                          snew = Node.setSec sold idx
110
                          ac3 = deleteBy assocEqual (sdx, sold) ac2
111
                          ac4 = (sdx, snew):ac3
112
                      in ac4
113
                  else
114
                      ac2
115
           ) nl il
116

    
117
-- | Compute the longest common suffix of a list of strings that
118
-- | starts with a dot.
119
longestDomain :: [String] -> String
120
longestDomain [] = ""
121
longestDomain (x:xs) =
122
      foldr (\ suffix accu -> if all (isSuffixOf suffix) xs
123
                              then suffix
124
                              else accu)
125
      "" $ filter (isPrefixOf ".") (tails x)
126

    
127
-- | Remove tail suffix from a string.
128
stripSuffix :: Int -> String -> String
129
stripSuffix sflen name = take ((length name) - sflen) name
130

    
131
-- | Initializer function that loads the data from a node and instance
132
-- list and massages it into the correct format.
133
mergeData :: (Node.AssocList,
134
              Instance.AssocList) -- ^ Data from either Text.loadData
135
                                  -- or Rapi.loadData
136
          -> Result (Node.List, Instance.List, String)
137
mergeData (nl, il) = do
138
  let
139
      nl2 = fixNodes nl il
140
      il3 = Container.fromAssocList il
141
      nl3 = Container.fromAssocList
142
            (map (\ (k, v) -> (k, Node.buildPeers v il3)) nl2)
143
      node_names = map Node.name $ Container.elems nl3
144
      inst_names = map Instance.name $ Container.elems il3
145
      common_suffix = longestDomain (node_names ++ inst_names)
146
      csl = length common_suffix
147
      snl = Container.map (\n -> setName n (stripSuffix csl $ nameOf n)) nl3
148
      sil = Container.map (\i -> setName i (stripSuffix csl $ nameOf i)) il3
149
  return (snl, sil, common_suffix)
150

    
151
-- | Checks the cluster data for consistency.
152
checkData :: Node.List -> Instance.List
153
          -> ([String], Node.List)
154
checkData nl il =
155
    Container.mapAccum
156
        (\ msgs node ->
157
             let nname = Node.name node
158
                 nilst = map (flip Container.find $ il) (Node.plist node)
159
                 dilst = filter (not . Instance.running) nilst
160
                 adj_mem = sum . map Instance.mem $ dilst
161
                 delta_mem = (truncate $ Node.t_mem node)
162
                             - (Node.n_mem node)
163
                             - (Node.f_mem node)
164
                             - (nodeImem node il)
165
                             + adj_mem
166
                 delta_dsk = (truncate $ Node.t_dsk node)
167
                             - (Node.f_dsk node)
168
                             - (nodeIdsk node il)
169
                 newn = Node.setFmem (Node.setXmem node delta_mem)
170
                        (Node.f_mem node - adj_mem)
171
                 umsg1 = if delta_mem > 512 || delta_dsk > 1024
172
                         then [printf "node %s is missing %d MB ram \
173
                                     \and %d GB disk"
174
                                     nname delta_mem (delta_dsk `div` 1024)]
175
                         else []
176
             in (msgs ++ umsg1, newn)
177
        ) [] nl
178

    
179
-- | Compute the amount of memory used by primary instances on a node.
180
nodeImem :: Node.Node -> Instance.List -> Int
181
nodeImem node il =
182
    let rfind = flip Container.find $ il
183
    in sum . map Instance.mem .
184
       map rfind $ Node.plist node
185

    
186
-- | Compute the amount of disk used by instances on a node (either primary
187
-- or secondary).
188
nodeIdsk :: Node.Node -> Instance.List -> Int
189
nodeIdsk node il =
190
    let rfind = flip Container.find $ il
191
    in sum . map Instance.dsk .
192
       map rfind $ (Node.plist node) ++ (Node.slist node)