Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Loader.hs @ f5ed8632

History | View | Annotate | Download (8.3 kB)

1 e8f89bb6 Iustin Pop
{-| Generic data loader
2 040afc35 Iustin Pop
3 e8f89bb6 Iustin Pop
This module holds the common code for parsing the input data after it
4 e8f89bb6 Iustin Pop
has been loaded from external sources.
5 040afc35 Iustin Pop
6 040afc35 Iustin Pop
-}
7 040afc35 Iustin Pop
8 e2fa2baf Iustin Pop
{-
9 e2fa2baf Iustin Pop
10 e2fa2baf Iustin Pop
Copyright (C) 2009 Google Inc.
11 e2fa2baf Iustin Pop
12 e2fa2baf Iustin Pop
This program is free software; you can redistribute it and/or modify
13 e2fa2baf Iustin Pop
it under the terms of the GNU General Public License as published by
14 e2fa2baf Iustin Pop
the Free Software Foundation; either version 2 of the License, or
15 e2fa2baf Iustin Pop
(at your option) any later version.
16 e2fa2baf Iustin Pop
17 e2fa2baf Iustin Pop
This program is distributed in the hope that it will be useful, but
18 e2fa2baf Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
19 e2fa2baf Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20 e2fa2baf Iustin Pop
General Public License for more details.
21 e2fa2baf Iustin Pop
22 e2fa2baf Iustin Pop
You should have received a copy of the GNU General Public License
23 e2fa2baf Iustin Pop
along with this program; if not, write to the Free Software
24 e2fa2baf Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25 e2fa2baf Iustin Pop
02110-1301, USA.
26 e2fa2baf Iustin Pop
27 e2fa2baf Iustin Pop
-}
28 e2fa2baf Iustin Pop
29 040afc35 Iustin Pop
module Ganeti.HTools.Loader
30 446d8827 Iustin Pop
    ( mergeData
31 446d8827 Iustin Pop
    , checkData
32 446d8827 Iustin Pop
    , assignIndices
33 446d8827 Iustin Pop
    , lookupNode
34 5a1edeb6 Iustin Pop
    , lookupInstance
35 3e4480e0 Iustin Pop
    , commonSuffix
36 19f38ee8 Iustin Pop
    , RqType(..)
37 19f38ee8 Iustin Pop
    , Request(..)
38 446d8827 Iustin Pop
    ) where
39 040afc35 Iustin Pop
40 78694255 Iustin Pop
import Data.Function (on)
41 e4c5beaf Iustin Pop
import Data.List
42 446d8827 Iustin Pop
import Data.Maybe (fromJust)
43 446d8827 Iustin Pop
import Text.Printf (printf)
44 e4c5beaf Iustin Pop
45 e4c5beaf Iustin Pop
import qualified Ganeti.HTools.Container as Container
46 e4c5beaf Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
47 e4c5beaf Iustin Pop
import qualified Ganeti.HTools.Node as Node
48 e4c5beaf Iustin Pop
49 e4c5beaf Iustin Pop
import Ganeti.HTools.Types
50 e4c5beaf Iustin Pop
51 f5e67f55 Iustin Pop
-- * Constants
52 f5e67f55 Iustin Pop
53 f5e67f55 Iustin Pop
-- | The exclusion tag prefix
54 f5e67f55 Iustin Pop
exTagsPrefix :: String
55 f5e67f55 Iustin Pop
exTagsPrefix = "htools:iextags:"
56 f5e67f55 Iustin Pop
57 19f38ee8 Iustin Pop
-- * Types
58 19f38ee8 Iustin Pop
59 54365762 Iustin Pop
{-| The iallocator request type.
60 19f38ee8 Iustin Pop
61 19f38ee8 Iustin Pop
This type denotes what request we got from Ganeti and also holds
62 19f38ee8 Iustin Pop
request-specific fields.
63 19f38ee8 Iustin Pop
64 19f38ee8 Iustin Pop
-}
65 19f38ee8 Iustin Pop
data RqType
66 19f38ee8 Iustin Pop
    = Allocate Instance.Instance Int -- ^ A new instance allocation
67 19f38ee8 Iustin Pop
    | Relocate Idx Int [Ndx]         -- ^ Move an instance to a new
68 19f38ee8 Iustin Pop
                                     -- secondary node
69 54365762 Iustin Pop
    | Evacuate [Ndx]                 -- ^ Evacuate nodes
70 19f38ee8 Iustin Pop
    deriving (Show)
71 19f38ee8 Iustin Pop
72 19f38ee8 Iustin Pop
-- | A complete request, as received from Ganeti.
73 3e4480e0 Iustin Pop
data Request = Request RqType Node.List Instance.List [String]
74 19f38ee8 Iustin Pop
    deriving (Show)
75 19f38ee8 Iustin Pop
76 19f38ee8 Iustin Pop
-- * Functions
77 19f38ee8 Iustin Pop
78 9188aeef Iustin Pop
-- | Lookups a node into an assoc list.
79 608efcce Iustin Pop
lookupNode :: (Monad m) => [(String, Ndx)] -> String -> String -> m Ndx
80 040afc35 Iustin Pop
lookupNode ktn inst node =
81 040afc35 Iustin Pop
    case lookup node ktn of
82 040afc35 Iustin Pop
      Nothing -> fail $ "Unknown node '" ++ node ++ "' for instance " ++ inst
83 040afc35 Iustin Pop
      Just idx -> return idx
84 040afc35 Iustin Pop
85 9188aeef Iustin Pop
-- | Lookups an instance into an assoc list.
86 5a1edeb6 Iustin Pop
lookupInstance :: (Monad m) => [(String, Idx)] -> String -> m Idx
87 5a1edeb6 Iustin Pop
lookupInstance kti inst =
88 5a1edeb6 Iustin Pop
    case lookup inst kti of
89 5a1edeb6 Iustin Pop
      Nothing -> fail $ "Unknown instance '" ++ inst ++ "'"
90 5a1edeb6 Iustin Pop
      Just idx -> return idx
91 5a1edeb6 Iustin Pop
92 9188aeef Iustin Pop
-- | Given a list of elements (and their names), assign indices to them.
93 497e30a1 Iustin Pop
assignIndices :: (Element a) =>
94 497e30a1 Iustin Pop
                 [(String, a)]
95 040afc35 Iustin Pop
              -> (NameAssoc, [(Int, a)])
96 497e30a1 Iustin Pop
assignIndices =
97 497e30a1 Iustin Pop
    unzip . map (\ (idx, (k, v)) -> ((k, idx), (idx, setIdx v idx)))
98 040afc35 Iustin Pop
          . zip [0..]
99 e4c5beaf Iustin Pop
100 78694255 Iustin Pop
-- | Assoc element comparator
101 78694255 Iustin Pop
assocEqual :: (Eq a) => (a, b) -> (a, b) -> Bool
102 78694255 Iustin Pop
assocEqual = (==) `on` fst
103 78694255 Iustin Pop
104 9188aeef Iustin Pop
-- | For each instance, add its index to its primary and secondary nodes.
105 608efcce Iustin Pop
fixNodes :: [(Ndx, Node.Node)]
106 aa8d2e71 Iustin Pop
         -> Instance.Instance
107 608efcce Iustin Pop
         -> [(Ndx, Node.Node)]
108 aa8d2e71 Iustin Pop
fixNodes accu inst =
109 d71d0a1d Iustin Pop
    let
110 2060348b Iustin Pop
        pdx = Instance.pNode inst
111 2060348b Iustin Pop
        sdx = Instance.sNode inst
112 d71d0a1d Iustin Pop
        pold = fromJust $ lookup pdx accu
113 a488a217 Iustin Pop
        pnew = Node.setPri pold inst
114 d71d0a1d Iustin Pop
        ac1 = deleteBy assocEqual (pdx, pold) accu
115 a488a217 Iustin Pop
        ac2 = (pdx, pnew):ac1
116 d71d0a1d Iustin Pop
    in
117 d71d0a1d Iustin Pop
      if sdx /= Node.noSecondary
118 d71d0a1d Iustin Pop
      then let sold = fromJust $ lookup sdx accu
119 a488a217 Iustin Pop
               snew = Node.setSec sold inst
120 d71d0a1d Iustin Pop
               ac3 = deleteBy assocEqual (sdx, sold) ac2
121 d71d0a1d Iustin Pop
           in (sdx, snew):ac3
122 d71d0a1d Iustin Pop
      else ac2
123 e4c5beaf Iustin Pop
124 0f15cc76 Iustin Pop
-- | Remove non-selected tags from the exclusion list
125 0f15cc76 Iustin Pop
filterExTags :: [String] -> Instance.Instance -> Instance.Instance
126 0f15cc76 Iustin Pop
filterExTags tl inst =
127 0f15cc76 Iustin Pop
    let old_tags = Instance.tags inst
128 5182e970 Iustin Pop
        new_tags = filter (\tag -> any (`isPrefixOf` tag) tl)
129 0f15cc76 Iustin Pop
                   old_tags
130 0f15cc76 Iustin Pop
    in inst { Instance.tags = new_tags }
131 0f15cc76 Iustin Pop
132 39f979b8 Iustin Pop
-- | Update the movable attribute
133 39f979b8 Iustin Pop
updateMovable :: [String] -> Instance.Instance -> Instance.Instance
134 39f979b8 Iustin Pop
updateMovable exinst inst =
135 39f979b8 Iustin Pop
    if Instance.sNode inst == Node.noSecondary ||
136 39f979b8 Iustin Pop
       Instance.name inst `elem` exinst
137 39f979b8 Iustin Pop
    then Instance.setMovable inst False
138 39f979b8 Iustin Pop
    else inst
139 39f979b8 Iustin Pop
140 f9fc7a63 Iustin Pop
-- | Compute the longest common suffix of a list of strings that
141 9188aeef Iustin Pop
-- | starts with a dot.
142 8472a321 Iustin Pop
longestDomain :: [String] -> String
143 e4c5beaf Iustin Pop
longestDomain [] = ""
144 8472a321 Iustin Pop
longestDomain (x:xs) =
145 8472a321 Iustin Pop
      foldr (\ suffix accu -> if all (isSuffixOf suffix) xs
146 e4c5beaf Iustin Pop
                              then suffix
147 e4c5beaf Iustin Pop
                              else accu)
148 e4c5beaf Iustin Pop
      "" $ filter (isPrefixOf ".") (tails x)
149 e4c5beaf Iustin Pop
150 f5e67f55 Iustin Pop
-- | Extracts the exclusion tags from the cluster configuration
151 f5e67f55 Iustin Pop
extractExTags :: [String] -> [String]
152 f5e67f55 Iustin Pop
extractExTags =
153 f5e67f55 Iustin Pop
    map (drop (length exTagsPrefix)) .
154 f5e67f55 Iustin Pop
    filter (isPrefixOf exTagsPrefix)
155 f5e67f55 Iustin Pop
156 381be58a Iustin Pop
-- | Extracts the common suffix from node\/instance names
157 3e4480e0 Iustin Pop
commonSuffix :: Node.List -> Instance.List -> String
158 3e4480e0 Iustin Pop
commonSuffix nl il =
159 3e4480e0 Iustin Pop
    let node_names = map Node.name $ Container.elems nl
160 3e4480e0 Iustin Pop
        inst_names = map Instance.name $ Container.elems il
161 3e4480e0 Iustin Pop
    in longestDomain (node_names ++ inst_names)
162 3e4480e0 Iustin Pop
163 9188aeef Iustin Pop
-- | Initializer function that loads the data from a node and instance
164 9188aeef Iustin Pop
-- list and massages it into the correct format.
165 aa8d2e71 Iustin Pop
mergeData :: [(String, DynUtil)]  -- ^ Instance utilisation data
166 0f15cc76 Iustin Pop
          -> [String]             -- ^ Exclusion tags
167 39f979b8 Iustin Pop
          -> [String]             -- ^ Untouchable instances
168 94e05c32 Iustin Pop
          -> (Node.AssocList, Instance.AssocList, [String])
169 94e05c32 Iustin Pop
          -- ^ Data from backends
170 3e4480e0 Iustin Pop
          -> Result (Node.List, Instance.List, [String])
171 39f979b8 Iustin Pop
mergeData um extags exinsts (nl, il, tags) =
172 aa8d2e71 Iustin Pop
  let il2 = Container.fromAssocList il
173 a5f8dcdc Iustin Pop
      il3 = foldl' (\im (name, n_util) ->
174 a5f8dcdc Iustin Pop
                        case Container.findByName im name of
175 a5f8dcdc Iustin Pop
                          Nothing -> im -- skipping unknown instance
176 a5f8dcdc Iustin Pop
                          Just inst ->
177 a5f8dcdc Iustin Pop
                              let new_i = inst { Instance.util = n_util }
178 a5f8dcdc Iustin Pop
                              in Container.add (Instance.idx inst) new_i im
179 a5f8dcdc Iustin Pop
                   ) il2 um
180 f5e67f55 Iustin Pop
      allextags = extags ++ extractExTags tags
181 39f979b8 Iustin Pop
      il4 = Container.map (filterExTags allextags .
182 39f979b8 Iustin Pop
                           updateMovable exinsts) il3
183 0f15cc76 Iustin Pop
      nl2 = foldl' fixNodes nl (Container.elems il4)
184 ce0392e6 Iustin Pop
      nl3 = Container.fromAssocList
185 0f15cc76 Iustin Pop
            (map (\ (k, v) -> (k, Node.buildPeers v il4)) nl2)
186 ce0392e6 Iustin Pop
      node_names = map (Node.name . snd) nl
187 ce0392e6 Iustin Pop
      inst_names = map (Instance.name . snd) il
188 8472a321 Iustin Pop
      common_suffix = longestDomain (node_names ++ inst_names)
189 3e4480e0 Iustin Pop
      snl = Container.map (computeAlias common_suffix) nl3
190 3e4480e0 Iustin Pop
      sil = Container.map (computeAlias common_suffix) il4
191 c854092b Iustin Pop
      all_inst_names = concatMap allNames $ Container.elems sil
192 c854092b Iustin Pop
  in if not $ all (`elem` all_inst_names) exinsts
193 5ab2b771 Iustin Pop
     then Bad $ "Some of the excluded instances are unknown: " ++
194 c854092b Iustin Pop
          show (exinsts \\ all_inst_names)
195 3e4480e0 Iustin Pop
     else Ok (snl, sil, tags)
196 446d8827 Iustin Pop
197 9188aeef Iustin Pop
-- | Checks the cluster data for consistency.
198 262a08a2 Iustin Pop
checkData :: Node.List -> Instance.List
199 262a08a2 Iustin Pop
          -> ([String], Node.List)
200 dbd6700b Iustin Pop
checkData nl il =
201 446d8827 Iustin Pop
    Container.mapAccum
202 446d8827 Iustin Pop
        (\ msgs node ->
203 dbd6700b Iustin Pop
             let nname = Node.name node
204 5182e970 Iustin Pop
                 nilst = map (`Container.find` il) (Node.pList node)
205 446d8827 Iustin Pop
                 dilst = filter (not . Instance.running) nilst
206 446d8827 Iustin Pop
                 adj_mem = sum . map Instance.mem $ dilst
207 2060348b Iustin Pop
                 delta_mem = truncate (Node.tMem node)
208 2060348b Iustin Pop
                             - Node.nMem node
209 2060348b Iustin Pop
                             - Node.fMem node
210 9f6dcdea Iustin Pop
                             - nodeImem node il
211 446d8827 Iustin Pop
                             + adj_mem
212 2060348b Iustin Pop
                 delta_dsk = truncate (Node.tDsk node)
213 2060348b Iustin Pop
                             - Node.fDsk node
214 9f6dcdea Iustin Pop
                             - nodeIdsk node il
215 446d8827 Iustin Pop
                 newn = Node.setFmem (Node.setXmem node delta_mem)
216 2060348b Iustin Pop
                        (Node.fMem node - adj_mem)
217 9f6dcdea Iustin Pop
                 umsg1 = [printf "node %s is missing %d MB ram \
218 9f6dcdea Iustin Pop
                                 \and %d GB disk"
219 9f6dcdea Iustin Pop
                                 nname delta_mem (delta_dsk `div` 1024) |
220 9f6dcdea Iustin Pop
                                 delta_mem > 512 || delta_dsk > 1024]::[String]
221 446d8827 Iustin Pop
             in (msgs ++ umsg1, newn)
222 446d8827 Iustin Pop
        ) [] nl
223 446d8827 Iustin Pop
224 446d8827 Iustin Pop
-- | Compute the amount of memory used by primary instances on a node.
225 262a08a2 Iustin Pop
nodeImem :: Node.Node -> Instance.List -> Int
226 446d8827 Iustin Pop
nodeImem node il =
227 9f6dcdea Iustin Pop
    let rfind = flip Container.find il
228 9f6dcdea Iustin Pop
    in sum . map (Instance.mem . rfind)
229 2060348b Iustin Pop
           $ Node.pList node
230 446d8827 Iustin Pop
231 446d8827 Iustin Pop
-- | Compute the amount of disk used by instances on a node (either primary
232 446d8827 Iustin Pop
-- or secondary).
233 262a08a2 Iustin Pop
nodeIdsk :: Node.Node -> Instance.List -> Int
234 446d8827 Iustin Pop
nodeIdsk node il =
235 9f6dcdea Iustin Pop
    let rfind = flip Container.find il
236 9f6dcdea Iustin Pop
    in sum . map (Instance.dsk . rfind)
237 2060348b Iustin Pop
           $ Node.pList node ++ Node.sList node