Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Loader.hs @ fbe5fcf6

History | View | Annotate | Download (12.4 kB)

1
{-| Generic data loader.
2

    
3
This module holds the common code for parsing the input data after it
4
has been loaded from external sources.
5

    
6
-}
7

    
8
{-
9

    
10
Copyright (C) 2009, 2010, 2011 Google Inc.
11

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

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

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

    
27
-}
28

    
29
module Ganeti.HTools.Loader
30
    ( mergeData
31
    , checkData
32
    , assignIndices
33
    , lookupNode
34
    , lookupInstance
35
    , lookupGroup
36
    , commonSuffix
37
    , RqType(..)
38
    , Request(..)
39
    , ClusterData(..)
40
    , emptyCluster
41
    , compareNameComponent
42
    , prefixMatch
43
    , LookupResult(..)
44
    , MatchPriority(..)
45
    ) where
46

    
47
import Data.List
48
import Data.Function
49
import qualified Data.Map as M
50
import Text.Printf (printf)
51

    
52
import qualified Ganeti.HTools.Container as Container
53
import qualified Ganeti.HTools.Instance as Instance
54
import qualified Ganeti.HTools.Node as Node
55
import qualified Ganeti.HTools.Group as Group
56

    
57
import Ganeti.HTools.Types
58
import Ganeti.HTools.Utils
59

    
60
-- * Constants
61

    
62
-- | The exclusion tag prefix.
63
exTagsPrefix :: String
64
exTagsPrefix = "htools:iextags:"
65

    
66
-- * Types
67

    
68
{-| The iallocator request type.
69

    
70
This type denotes what request we got from Ganeti and also holds
71
request-specific fields.
72

    
73
-}
74
data RqType
75
    = Allocate Instance.Instance Int -- ^ A new instance allocation
76
    | NodeEvacuate [Idx] EvacMode    -- ^ node-evacuate mode
77
    | ChangeGroup [Gdx] [Idx]        -- ^ Multi-relocate mode
78
    deriving (Show, Read)
79

    
80
-- | A complete request, as received from Ganeti.
81
data Request = Request RqType ClusterData
82
    deriving (Show, Read)
83

    
84
-- | The cluster state.
85
data ClusterData = ClusterData
86
    { cdGroups    :: Group.List    -- ^ The node group list
87
    , cdNodes     :: Node.List     -- ^ The node list
88
    , cdInstances :: Instance.List -- ^ The instance list
89
    , cdTags      :: [String]      -- ^ The cluster tags
90
    } deriving (Show, Read)
91

    
92
-- | The priority of a match in a lookup result.
93
data MatchPriority = ExactMatch
94
                   | MultipleMatch
95
                   | PartialMatch
96
                   | FailMatch
97
                   deriving (Show, Read, Enum, Eq, Ord)
98

    
99
-- | The result of a name lookup in a list.
100
data LookupResult = LookupResult
101
    { lrMatchPriority :: MatchPriority -- ^ The result type
102
    -- | Matching value (for ExactMatch, PartialMatch), Lookup string otherwise
103
    , lrContent :: String
104
    } deriving (Show, Read)
105

    
106
-- | Lookup results have an absolute preference ordering.
107
instance Eq LookupResult where
108
  (==) = (==) `on` lrMatchPriority
109

    
110
instance Ord LookupResult where
111
  compare = compare `on` lrMatchPriority
112

    
113
-- | An empty cluster.
114
emptyCluster :: ClusterData
115
emptyCluster = ClusterData Container.empty Container.empty Container.empty []
116

    
117
-- * Functions
118

    
119
-- | Lookups a node into an assoc list.
120
lookupNode :: (Monad m) => NameAssoc -> String -> String -> m Ndx
121
lookupNode ktn inst node =
122
    case M.lookup node ktn of
123
      Nothing -> fail $ "Unknown node '" ++ node ++ "' for instance " ++ inst
124
      Just idx -> return idx
125

    
126
-- | Lookups an instance into an assoc list.
127
lookupInstance :: (Monad m) => NameAssoc -> String -> m Idx
128
lookupInstance kti inst =
129
    case M.lookup inst kti of
130
      Nothing -> fail $ "Unknown instance '" ++ inst ++ "'"
131
      Just idx -> return idx
132

    
133
-- | Lookups a group into an assoc list.
134
lookupGroup :: (Monad m) => NameAssoc -> String -> String -> m Gdx
135
lookupGroup ktg nname gname =
136
    case M.lookup gname ktg of
137
      Nothing -> fail $ "Unknown group '" ++ gname ++ "' for node " ++ nname
138
      Just idx -> return idx
139

    
140
-- | Check for prefix matches in names.
141
-- Implemented in Ganeti core utils.text.MatchNameComponent
142
-- as the regexp r"^%s(\..*)?$" % re.escape(key)
143
prefixMatch :: String  -- ^ Lookup
144
            -> String  -- ^ Full name
145
            -> Bool    -- ^ Whether there is a prefix match
146
prefixMatch lkp = isPrefixOf (lkp ++ ".")
147

    
148
-- | Is the lookup priority a "good" one?
149
goodMatchPriority :: MatchPriority -> Bool
150
goodMatchPriority ExactMatch = True
151
goodMatchPriority PartialMatch = True
152
goodMatchPriority _ = False
153

    
154
-- | Is the lookup result an actual match?
155
goodLookupResult :: LookupResult -> Bool
156
goodLookupResult = goodMatchPriority . lrMatchPriority
157

    
158
-- | Compares a canonical name and a lookup string.
159
compareNameComponent :: String        -- ^ Canonical (target) name
160
                     -> String        -- ^ Partial (lookup) name
161
                     -> LookupResult  -- ^ Result of the lookup
162
compareNameComponent cnl lkp =
163
  select (LookupResult FailMatch lkp)
164
  [ (cnl == lkp          , LookupResult ExactMatch cnl)
165
  , (prefixMatch lkp cnl , LookupResult PartialMatch cnl)
166
  ]
167

    
168
-- | Lookup a string and choose the best result.
169
chooseLookupResult :: String       -- ^ Lookup key
170
                   -> String       -- ^ String to compare to the lookup key
171
                   -> LookupResult -- ^ Previous result
172
                   -> LookupResult -- ^ New result
173
chooseLookupResult lkp cstr old =
174
  -- default: use class order to pick the minimum result
175
  select (min new old)
176
  -- special cases:
177
  -- short circuit if the new result is an exact match
178
  [ ((lrMatchPriority new) == ExactMatch, new)
179
  -- if both are partial matches generate a multiple match
180
  , (partial2, LookupResult MultipleMatch lkp)
181
  ] where new = compareNameComponent cstr lkp
182
          partial2 = all ((PartialMatch==) . lrMatchPriority) [old, new]
183

    
184
-- | Find the canonical name for a lookup string in a list of names.
185
lookupName :: [String]      -- ^ List of keys
186
           -> String        -- ^ Lookup string
187
           -> LookupResult  -- ^ Result of the lookup
188
lookupName l s = foldr (chooseLookupResult s)
189
                       (LookupResult FailMatch s) l
190

    
191
-- | Given a list of elements (and their names), assign indices to them.
192
assignIndices :: (Element a) =>
193
                 [(String, a)]
194
              -> (NameAssoc, Container.Container a)
195
assignIndices nodes =
196
  let (na, idx_node) =
197
          unzip . map (\ (idx, (k, v)) -> ((k, idx), (idx, setIdx v idx)))
198
          . zip [0..] $ nodes
199
  in (M.fromList na, Container.fromList idx_node)
200

    
201
-- | For each instance, add its index to its primary and secondary nodes.
202
fixNodes :: Node.List
203
         -> Instance.Instance
204
         -> Node.List
205
fixNodes accu inst =
206
    let
207
        pdx = Instance.pNode inst
208
        sdx = Instance.sNode inst
209
        pold = Container.find pdx accu
210
        pnew = Node.setPri pold inst
211
        ac2 = Container.add pdx pnew accu
212
    in
213
      if sdx /= Node.noSecondary
214
      then let sold = Container.find sdx accu
215
               snew = Node.setSec sold inst
216
           in Container.add sdx snew ac2
217
      else ac2
218

    
219
-- | Remove non-selected tags from the exclusion list.
220
filterExTags :: [String] -> Instance.Instance -> Instance.Instance
221
filterExTags tl inst =
222
    let old_tags = Instance.tags inst
223
        new_tags = filter (\tag -> any (`isPrefixOf` tag) tl)
224
                   old_tags
225
    in inst { Instance.tags = new_tags }
226

    
227
-- | Update the movable attribute.
228
updateMovable :: [String]           -- ^ Selected instances (if not empty)
229
              -> [String]           -- ^ Excluded instances
230
              -> Instance.Instance  -- ^ Target Instance
231
              -> Instance.Instance  -- ^ Target Instance with updated attribute
232
updateMovable selinsts exinsts inst =
233
    if Instance.sNode inst == Node.noSecondary ||
234
       Instance.name inst `elem` exinsts ||
235
       not (null selinsts || Instance.name inst `elem` selinsts)
236
    then Instance.setMovable inst False
237
    else inst
238

    
239
-- | Compute the longest common suffix of a list of strings that
240
-- starts with a dot.
241
longestDomain :: [String] -> String
242
longestDomain [] = ""
243
longestDomain (x:xs) =
244
      foldr (\ suffix accu -> if all (isSuffixOf suffix) xs
245
                              then suffix
246
                              else accu)
247
      "" $ filter (isPrefixOf ".") (tails x)
248

    
249
-- | Extracts the exclusion tags from the cluster configuration.
250
extractExTags :: [String] -> [String]
251
extractExTags =
252
    map (drop (length exTagsPrefix)) .
253
    filter (isPrefixOf exTagsPrefix)
254

    
255
-- | Extracts the common suffix from node\/instance names.
256
commonSuffix :: Node.List -> Instance.List -> String
257
commonSuffix nl il =
258
    let node_names = map Node.name $ Container.elems nl
259
        inst_names = map Instance.name $ Container.elems il
260
    in longestDomain (node_names ++ inst_names)
261

    
262
-- | Initializer function that loads the data from a node and instance
263
-- list and massages it into the correct format.
264
mergeData :: [(String, DynUtil)]  -- ^ Instance utilisation data
265
          -> [String]             -- ^ Exclusion tags
266
          -> [String]             -- ^ Selected instances (if not empty)
267
          -> [String]             -- ^ Excluded instances
268
          -> ClusterData          -- ^ Data from backends
269
          -> Result ClusterData   -- ^ Fixed cluster data
270
mergeData um extags selinsts exinsts cdata@(ClusterData _ nl il2 tags) =
271
  let il = Container.elems il2
272
      il3 = foldl' (\im (name, n_util) ->
273
                        case Container.findByName im name of
274
                          Nothing -> im -- skipping unknown instance
275
                          Just inst ->
276
                              let new_i = inst { Instance.util = n_util }
277
                              in Container.add (Instance.idx inst) new_i im
278
                   ) il2 um
279
      allextags = extags ++ extractExTags tags
280
      inst_names = map Instance.name il
281
      selinst_lkp = map (lookupName inst_names) selinsts
282
      exinst_lkp = map (lookupName inst_names) exinsts
283
      lkp_unknown = filter (not . goodLookupResult) (selinst_lkp ++ exinst_lkp)
284
      selinst_names = map lrContent selinst_lkp
285
      exinst_names = map lrContent exinst_lkp
286
      il4 = Container.map (filterExTags allextags .
287
                           updateMovable selinst_names exinst_names) il3
288
      nl2 = foldl' fixNodes nl (Container.elems il4)
289
      nl3 = Container.map (flip Node.buildPeers il4) nl2
290
      node_names = map Node.name (Container.elems nl)
291
      common_suffix = longestDomain (node_names ++ inst_names)
292
      snl = Container.map (computeAlias common_suffix) nl3
293
      sil = Container.map (computeAlias common_suffix) il4
294
  in if' (null lkp_unknown)
295
         (Ok cdata { cdNodes = snl, cdInstances = sil })
296
         (Bad $ "Unknown instance(s): " ++ show(map lrContent lkp_unknown))
297

    
298
-- | Checks the cluster data for consistency.
299
checkData :: Node.List -> Instance.List
300
          -> ([String], Node.List)
301
checkData nl il =
302
    Container.mapAccum
303
        (\ msgs node ->
304
             let nname = Node.name node
305
                 nilst = map (`Container.find` il) (Node.pList node)
306
                 dilst = filter (not . Instance.running) nilst
307
                 adj_mem = sum . map Instance.mem $ dilst
308
                 delta_mem = truncate (Node.tMem node)
309
                             - Node.nMem node
310
                             - Node.fMem node
311
                             - nodeImem node il
312
                             + adj_mem
313
                 delta_dsk = truncate (Node.tDsk node)
314
                             - Node.fDsk node
315
                             - nodeIdsk node il
316
                 newn = Node.setFmem (Node.setXmem node delta_mem)
317
                        (Node.fMem node - adj_mem)
318
                 umsg1 = [printf "node %s is missing %d MB ram \
319
                                 \and %d GB disk"
320
                                 nname delta_mem (delta_dsk `div` 1024) |
321
                                 delta_mem > 512 || delta_dsk > 1024]::[String]
322
             in (msgs ++ umsg1, newn)
323
        ) [] nl
324

    
325
-- | Compute the amount of memory used by primary instances on a node.
326
nodeImem :: Node.Node -> Instance.List -> Int
327
nodeImem node il =
328
    let rfind = flip Container.find il
329
    in sum . map (Instance.mem . rfind)
330
           $ Node.pList node
331

    
332
-- | Compute the amount of disk used by instances on a node (either primary
333
-- or secondary).
334
nodeIdsk :: Node.Node -> Instance.List -> Int
335
nodeIdsk node il =
336
    let rfind = flip Container.find il
337
    in sum . map (Instance.dsk . rfind)
338
           $ Node.pList node ++ Node.sList node