Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Loader.hs @ 0f15cc76

History | View | Annotate | Download (7.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 ed41c179 Iustin Pop
    , stripSuffix
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 19f38ee8 Iustin Pop
-- * Types
52 19f38ee8 Iustin Pop
53 19f38ee8 Iustin Pop
{-| The request type.
54 19f38ee8 Iustin Pop
55 19f38ee8 Iustin Pop
This type denotes what request we got from Ganeti and also holds
56 19f38ee8 Iustin Pop
request-specific fields.
57 19f38ee8 Iustin Pop
58 19f38ee8 Iustin Pop
-}
59 19f38ee8 Iustin Pop
data RqType
60 19f38ee8 Iustin Pop
    = Allocate Instance.Instance Int -- ^ A new instance allocation
61 19f38ee8 Iustin Pop
    | Relocate Idx Int [Ndx]         -- ^ Move an instance to a new
62 19f38ee8 Iustin Pop
                                     -- secondary node
63 19f38ee8 Iustin Pop
    deriving (Show)
64 19f38ee8 Iustin Pop
65 19f38ee8 Iustin Pop
-- | A complete request, as received from Ganeti.
66 19f38ee8 Iustin Pop
data Request = Request RqType Node.List Instance.List String
67 19f38ee8 Iustin Pop
    deriving (Show)
68 19f38ee8 Iustin Pop
69 19f38ee8 Iustin Pop
-- * Functions
70 19f38ee8 Iustin Pop
71 9188aeef Iustin Pop
-- | Lookups a node into an assoc list.
72 608efcce Iustin Pop
lookupNode :: (Monad m) => [(String, Ndx)] -> String -> String -> m Ndx
73 040afc35 Iustin Pop
lookupNode ktn inst node =
74 040afc35 Iustin Pop
    case lookup node ktn of
75 040afc35 Iustin Pop
      Nothing -> fail $ "Unknown node '" ++ node ++ "' for instance " ++ inst
76 040afc35 Iustin Pop
      Just idx -> return idx
77 040afc35 Iustin Pop
78 9188aeef Iustin Pop
-- | Lookups an instance into an assoc list.
79 5a1edeb6 Iustin Pop
lookupInstance :: (Monad m) => [(String, Idx)] -> String -> m Idx
80 5a1edeb6 Iustin Pop
lookupInstance kti inst =
81 5a1edeb6 Iustin Pop
    case lookup inst kti of
82 5a1edeb6 Iustin Pop
      Nothing -> fail $ "Unknown instance '" ++ inst ++ "'"
83 5a1edeb6 Iustin Pop
      Just idx -> return idx
84 5a1edeb6 Iustin Pop
85 9188aeef Iustin Pop
-- | Given a list of elements (and their names), assign indices to them.
86 497e30a1 Iustin Pop
assignIndices :: (Element a) =>
87 497e30a1 Iustin Pop
                 [(String, a)]
88 040afc35 Iustin Pop
              -> (NameAssoc, [(Int, a)])
89 497e30a1 Iustin Pop
assignIndices =
90 497e30a1 Iustin Pop
    unzip . map (\ (idx, (k, v)) -> ((k, idx), (idx, setIdx v idx)))
91 040afc35 Iustin Pop
          . zip [0..]
92 e4c5beaf Iustin Pop
93 78694255 Iustin Pop
-- | Assoc element comparator
94 78694255 Iustin Pop
assocEqual :: (Eq a) => (a, b) -> (a, b) -> Bool
95 78694255 Iustin Pop
assocEqual = (==) `on` fst
96 78694255 Iustin Pop
97 9188aeef Iustin Pop
-- | For each instance, add its index to its primary and secondary nodes.
98 608efcce Iustin Pop
fixNodes :: [(Ndx, Node.Node)]
99 aa8d2e71 Iustin Pop
         -> Instance.Instance
100 608efcce Iustin Pop
         -> [(Ndx, Node.Node)]
101 aa8d2e71 Iustin Pop
fixNodes accu inst =
102 d71d0a1d Iustin Pop
    let
103 2060348b Iustin Pop
        pdx = Instance.pNode inst
104 2060348b Iustin Pop
        sdx = Instance.sNode inst
105 d71d0a1d Iustin Pop
        pold = fromJust $ lookup pdx accu
106 a488a217 Iustin Pop
        pnew = Node.setPri pold inst
107 d71d0a1d Iustin Pop
        ac1 = deleteBy assocEqual (pdx, pold) accu
108 a488a217 Iustin Pop
        ac2 = (pdx, pnew):ac1
109 d71d0a1d Iustin Pop
    in
110 d71d0a1d Iustin Pop
      if sdx /= Node.noSecondary
111 d71d0a1d Iustin Pop
      then let sold = fromJust $ lookup sdx accu
112 a488a217 Iustin Pop
               snew = Node.setSec sold inst
113 d71d0a1d Iustin Pop
               ac3 = deleteBy assocEqual (sdx, sold) ac2
114 d71d0a1d Iustin Pop
           in (sdx, snew):ac3
115 d71d0a1d Iustin Pop
      else ac2
116 e4c5beaf Iustin Pop
117 0f15cc76 Iustin Pop
-- | Remove non-selected tags from the exclusion list
118 0f15cc76 Iustin Pop
filterExTags :: [String] -> Instance.Instance -> Instance.Instance
119 0f15cc76 Iustin Pop
filterExTags tl inst =
120 0f15cc76 Iustin Pop
    let old_tags = Instance.tags inst
121 0f15cc76 Iustin Pop
        new_tags = filter (\tag -> any (\extag -> isPrefixOf extag tag) tl)
122 0f15cc76 Iustin Pop
                   old_tags
123 0f15cc76 Iustin Pop
    in inst { Instance.tags = new_tags }
124 0f15cc76 Iustin Pop
125 f9fc7a63 Iustin Pop
-- | Compute the longest common suffix of a list of strings that
126 9188aeef Iustin Pop
-- | starts with a dot.
127 8472a321 Iustin Pop
longestDomain :: [String] -> String
128 e4c5beaf Iustin Pop
longestDomain [] = ""
129 8472a321 Iustin Pop
longestDomain (x:xs) =
130 8472a321 Iustin Pop
      foldr (\ suffix accu -> if all (isSuffixOf suffix) xs
131 e4c5beaf Iustin Pop
                              then suffix
132 e4c5beaf Iustin Pop
                              else accu)
133 e4c5beaf Iustin Pop
      "" $ filter (isPrefixOf ".") (tails x)
134 e4c5beaf Iustin Pop
135 9188aeef Iustin Pop
-- | Remove tail suffix from a string.
136 26b5d395 Iustin Pop
stripSuffix :: Int -> String -> String
137 9f6dcdea Iustin Pop
stripSuffix sflen name = take (length name - sflen) name
138 e4c5beaf Iustin Pop
139 9188aeef Iustin Pop
-- | Initializer function that loads the data from a node and instance
140 9188aeef Iustin Pop
-- list and massages it into the correct format.
141 aa8d2e71 Iustin Pop
mergeData :: [(String, DynUtil)]  -- ^ Instance utilisation data
142 0f15cc76 Iustin Pop
          -> [String]             -- ^ Exclusion tags
143 aa8d2e71 Iustin Pop
          -> (Node.AssocList,
144 e3a684c5 Iustin Pop
              Instance.AssocList) -- ^ Data from either Text.loadData
145 e3a684c5 Iustin Pop
                                  -- or Rapi.loadData
146 262a08a2 Iustin Pop
          -> Result (Node.List, Instance.List, String)
147 0f15cc76 Iustin Pop
mergeData um extags (nl, il) =
148 aa8d2e71 Iustin Pop
  let il2 = Container.fromAssocList il
149 a5f8dcdc Iustin Pop
      il3 = foldl' (\im (name, n_util) ->
150 a5f8dcdc Iustin Pop
                        case Container.findByName im name of
151 a5f8dcdc Iustin Pop
                          Nothing -> im -- skipping unknown instance
152 a5f8dcdc Iustin Pop
                          Just inst ->
153 a5f8dcdc Iustin Pop
                              let new_i = inst { Instance.util = n_util }
154 a5f8dcdc Iustin Pop
                              in Container.add (Instance.idx inst) new_i im
155 a5f8dcdc Iustin Pop
                   ) il2 um
156 0f15cc76 Iustin Pop
      il4 = Container.map (filterExTags extags) il3
157 0f15cc76 Iustin Pop
      nl2 = foldl' fixNodes nl (Container.elems il4)
158 ce0392e6 Iustin Pop
      nl3 = Container.fromAssocList
159 0f15cc76 Iustin Pop
            (map (\ (k, v) -> (k, Node.buildPeers v il4)) nl2)
160 ce0392e6 Iustin Pop
      node_names = map (Node.name . snd) nl
161 ce0392e6 Iustin Pop
      inst_names = map (Instance.name . snd) il
162 8472a321 Iustin Pop
      common_suffix = longestDomain (node_names ++ inst_names)
163 26b5d395 Iustin Pop
      csl = length common_suffix
164 262a08a2 Iustin Pop
      snl = Container.map (\n -> setName n (stripSuffix csl $ nameOf n)) nl3
165 0f15cc76 Iustin Pop
      sil = Container.map (\i -> setName i (stripSuffix csl $ nameOf i)) il4
166 ce0392e6 Iustin Pop
  in Ok (snl, sil, common_suffix)
167 446d8827 Iustin Pop
168 9188aeef Iustin Pop
-- | Checks the cluster data for consistency.
169 262a08a2 Iustin Pop
checkData :: Node.List -> Instance.List
170 262a08a2 Iustin Pop
          -> ([String], Node.List)
171 dbd6700b Iustin Pop
checkData nl il =
172 446d8827 Iustin Pop
    Container.mapAccum
173 446d8827 Iustin Pop
        (\ msgs node ->
174 dbd6700b Iustin Pop
             let nname = Node.name node
175 2060348b Iustin Pop
                 nilst = map (flip Container.find il) (Node.pList node)
176 446d8827 Iustin Pop
                 dilst = filter (not . Instance.running) nilst
177 446d8827 Iustin Pop
                 adj_mem = sum . map Instance.mem $ dilst
178 2060348b Iustin Pop
                 delta_mem = truncate (Node.tMem node)
179 2060348b Iustin Pop
                             - Node.nMem node
180 2060348b Iustin Pop
                             - Node.fMem node
181 9f6dcdea Iustin Pop
                             - nodeImem node il
182 446d8827 Iustin Pop
                             + adj_mem
183 2060348b Iustin Pop
                 delta_dsk = truncate (Node.tDsk node)
184 2060348b Iustin Pop
                             - Node.fDsk node
185 9f6dcdea Iustin Pop
                             - nodeIdsk node il
186 446d8827 Iustin Pop
                 newn = Node.setFmem (Node.setXmem node delta_mem)
187 2060348b Iustin Pop
                        (Node.fMem node - adj_mem)
188 9f6dcdea Iustin Pop
                 umsg1 = [printf "node %s is missing %d MB ram \
189 9f6dcdea Iustin Pop
                                 \and %d GB disk"
190 9f6dcdea Iustin Pop
                                 nname delta_mem (delta_dsk `div` 1024) |
191 9f6dcdea Iustin Pop
                                 delta_mem > 512 || delta_dsk > 1024]::[String]
192 446d8827 Iustin Pop
             in (msgs ++ umsg1, newn)
193 446d8827 Iustin Pop
        ) [] nl
194 446d8827 Iustin Pop
195 446d8827 Iustin Pop
-- | Compute the amount of memory used by primary instances on a node.
196 262a08a2 Iustin Pop
nodeImem :: Node.Node -> Instance.List -> Int
197 446d8827 Iustin Pop
nodeImem node il =
198 9f6dcdea Iustin Pop
    let rfind = flip Container.find il
199 9f6dcdea Iustin Pop
    in sum . map (Instance.mem . rfind)
200 2060348b Iustin Pop
           $ Node.pList node
201 446d8827 Iustin Pop
202 446d8827 Iustin Pop
-- | Compute the amount of disk used by instances on a node (either primary
203 446d8827 Iustin Pop
-- or secondary).
204 262a08a2 Iustin Pop
nodeIdsk :: Node.Node -> Instance.List -> Int
205 446d8827 Iustin Pop
nodeIdsk node il =
206 9f6dcdea Iustin Pop
    let rfind = flip Container.find il
207 9f6dcdea Iustin Pop
    in sum . map (Instance.dsk . rfind)
208 2060348b Iustin Pop
           $ Node.pList node ++ Node.sList node