Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Loader.hs @ 56c094b4

History | View | Annotate | Download (9 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 2a8e2dc9 Iustin Pop
Copyright (C) 2009, 2010, 2011 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 f4531f51 Iustin Pop
    , lookupGroup
36 3e4480e0 Iustin Pop
    , commonSuffix
37 19f38ee8 Iustin Pop
    , RqType(..)
38 19f38ee8 Iustin Pop
    , Request(..)
39 7b6e99b3 Iustin Pop
    , ClusterData(..)
40 7b6e99b3 Iustin Pop
    , emptyCluster
41 446d8827 Iustin Pop
    ) where
42 040afc35 Iustin Pop
43 e4c5beaf Iustin Pop
import Data.List
44 2d0ca2c5 Iustin Pop
import qualified Data.Map as M
45 446d8827 Iustin Pop
import Text.Printf (printf)
46 e4c5beaf Iustin Pop
47 e4c5beaf Iustin Pop
import qualified Ganeti.HTools.Container as Container
48 e4c5beaf Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
49 e4c5beaf Iustin Pop
import qualified Ganeti.HTools.Node as Node
50 a679e9dc Iustin Pop
import qualified Ganeti.HTools.Group as Group
51 e4c5beaf Iustin Pop
52 e4c5beaf Iustin Pop
import Ganeti.HTools.Types
53 e4c5beaf Iustin Pop
54 f5e67f55 Iustin Pop
-- * Constants
55 f5e67f55 Iustin Pop
56 f5e67f55 Iustin Pop
-- | The exclusion tag prefix
57 f5e67f55 Iustin Pop
exTagsPrefix :: String
58 f5e67f55 Iustin Pop
exTagsPrefix = "htools:iextags:"
59 f5e67f55 Iustin Pop
60 19f38ee8 Iustin Pop
-- * Types
61 19f38ee8 Iustin Pop
62 54365762 Iustin Pop
{-| The iallocator request type.
63 19f38ee8 Iustin Pop
64 19f38ee8 Iustin Pop
This type denotes what request we got from Ganeti and also holds
65 19f38ee8 Iustin Pop
request-specific fields.
66 19f38ee8 Iustin Pop
67 19f38ee8 Iustin Pop
-}
68 19f38ee8 Iustin Pop
data RqType
69 19f38ee8 Iustin Pop
    = Allocate Instance.Instance Int -- ^ A new instance allocation
70 19f38ee8 Iustin Pop
    | Relocate Idx Int [Ndx]         -- ^ Move an instance to a new
71 19f38ee8 Iustin Pop
                                     -- secondary node
72 54365762 Iustin Pop
    | Evacuate [Ndx]                 -- ^ Evacuate nodes
73 6bc39970 Iustin Pop
    deriving (Show, Read)
74 19f38ee8 Iustin Pop
75 19f38ee8 Iustin Pop
-- | A complete request, as received from Ganeti.
76 34c00528 Iustin Pop
data Request = Request RqType ClusterData
77 6bc39970 Iustin Pop
    deriving (Show, Read)
78 19f38ee8 Iustin Pop
79 7b6e99b3 Iustin Pop
-- | The cluster state.
80 7b6e99b3 Iustin Pop
data ClusterData = ClusterData
81 7b6e99b3 Iustin Pop
    { cdGroups    :: Group.List    -- ^ The node group list
82 7b6e99b3 Iustin Pop
    , cdNodes     :: Node.List     -- ^ The node list
83 7b6e99b3 Iustin Pop
    , cdInstances :: Instance.List -- ^ The instance list
84 7b6e99b3 Iustin Pop
    , cdTags      :: [String]      -- ^ The cluster tags
85 6bc39970 Iustin Pop
    } deriving (Show, Read)
86 7b6e99b3 Iustin Pop
87 7b6e99b3 Iustin Pop
-- | An empty cluster.
88 7b6e99b3 Iustin Pop
emptyCluster :: ClusterData
89 7b6e99b3 Iustin Pop
emptyCluster = ClusterData Container.empty Container.empty Container.empty []
90 7b6e99b3 Iustin Pop
91 19f38ee8 Iustin Pop
-- * Functions
92 19f38ee8 Iustin Pop
93 9188aeef Iustin Pop
-- | Lookups a node into an assoc list.
94 6ff78049 Iustin Pop
lookupNode :: (Monad m) => NameAssoc -> String -> String -> m Ndx
95 040afc35 Iustin Pop
lookupNode ktn inst node =
96 2d0ca2c5 Iustin Pop
    case M.lookup node ktn of
97 040afc35 Iustin Pop
      Nothing -> fail $ "Unknown node '" ++ node ++ "' for instance " ++ inst
98 040afc35 Iustin Pop
      Just idx -> return idx
99 040afc35 Iustin Pop
100 9188aeef Iustin Pop
-- | Lookups an instance into an assoc list.
101 6ff78049 Iustin Pop
lookupInstance :: (Monad m) => NameAssoc -> String -> m Idx
102 5a1edeb6 Iustin Pop
lookupInstance kti inst =
103 2d0ca2c5 Iustin Pop
    case M.lookup inst kti of
104 5a1edeb6 Iustin Pop
      Nothing -> fail $ "Unknown instance '" ++ inst ++ "'"
105 5a1edeb6 Iustin Pop
      Just idx -> return idx
106 5a1edeb6 Iustin Pop
107 f4531f51 Iustin Pop
-- | Lookups a group into an assoc list.
108 f4531f51 Iustin Pop
lookupGroup :: (Monad m) => NameAssoc -> String -> String -> m Gdx
109 f4531f51 Iustin Pop
lookupGroup ktg nname gname =
110 f4531f51 Iustin Pop
    case M.lookup gname ktg of
111 f4531f51 Iustin Pop
      Nothing -> fail $ "Unknown group '" ++ gname ++ "' for node " ++ nname
112 f4531f51 Iustin Pop
      Just idx -> return idx
113 f4531f51 Iustin Pop
114 9188aeef Iustin Pop
-- | Given a list of elements (and their names), assign indices to them.
115 497e30a1 Iustin Pop
assignIndices :: (Element a) =>
116 497e30a1 Iustin Pop
                 [(String, a)]
117 99b63608 Iustin Pop
              -> (NameAssoc, Container.Container a)
118 2d0ca2c5 Iustin Pop
assignIndices nodes =
119 2d0ca2c5 Iustin Pop
  let (na, idx_node) =
120 2d0ca2c5 Iustin Pop
          unzip . map (\ (idx, (k, v)) -> ((k, idx), (idx, setIdx v idx)))
121 2d0ca2c5 Iustin Pop
          . zip [0..] $ nodes
122 cb0c77ff Iustin Pop
  in (M.fromList na, Container.fromList idx_node)
123 78694255 Iustin Pop
124 9188aeef Iustin Pop
-- | For each instance, add its index to its primary and secondary nodes.
125 99b63608 Iustin Pop
fixNodes :: Node.List
126 aa8d2e71 Iustin Pop
         -> Instance.Instance
127 99b63608 Iustin Pop
         -> Node.List
128 aa8d2e71 Iustin Pop
fixNodes accu inst =
129 d71d0a1d Iustin Pop
    let
130 2060348b Iustin Pop
        pdx = Instance.pNode inst
131 2060348b Iustin Pop
        sdx = Instance.sNode inst
132 99b63608 Iustin Pop
        pold = Container.find pdx accu
133 a488a217 Iustin Pop
        pnew = Node.setPri pold inst
134 99b63608 Iustin Pop
        ac2 = Container.add pdx pnew accu
135 d71d0a1d Iustin Pop
    in
136 d71d0a1d Iustin Pop
      if sdx /= Node.noSecondary
137 99b63608 Iustin Pop
      then let sold = Container.find sdx accu
138 a488a217 Iustin Pop
               snew = Node.setSec sold inst
139 99b63608 Iustin Pop
           in Container.add sdx snew ac2
140 d71d0a1d Iustin Pop
      else ac2
141 e4c5beaf Iustin Pop
142 0f15cc76 Iustin Pop
-- | Remove non-selected tags from the exclusion list
143 0f15cc76 Iustin Pop
filterExTags :: [String] -> Instance.Instance -> Instance.Instance
144 0f15cc76 Iustin Pop
filterExTags tl inst =
145 0f15cc76 Iustin Pop
    let old_tags = Instance.tags inst
146 5182e970 Iustin Pop
        new_tags = filter (\tag -> any (`isPrefixOf` tag) tl)
147 0f15cc76 Iustin Pop
                   old_tags
148 0f15cc76 Iustin Pop
    in inst { Instance.tags = new_tags }
149 0f15cc76 Iustin Pop
150 39f979b8 Iustin Pop
-- | Update the movable attribute
151 39f979b8 Iustin Pop
updateMovable :: [String] -> Instance.Instance -> Instance.Instance
152 39f979b8 Iustin Pop
updateMovable exinst inst =
153 39f979b8 Iustin Pop
    if Instance.sNode inst == Node.noSecondary ||
154 39f979b8 Iustin Pop
       Instance.name inst `elem` exinst
155 39f979b8 Iustin Pop
    then Instance.setMovable inst False
156 39f979b8 Iustin Pop
    else inst
157 39f979b8 Iustin Pop
158 f9fc7a63 Iustin Pop
-- | Compute the longest common suffix of a list of strings that
159 9188aeef Iustin Pop
-- | starts with a dot.
160 8472a321 Iustin Pop
longestDomain :: [String] -> String
161 e4c5beaf Iustin Pop
longestDomain [] = ""
162 8472a321 Iustin Pop
longestDomain (x:xs) =
163 8472a321 Iustin Pop
      foldr (\ suffix accu -> if all (isSuffixOf suffix) xs
164 e4c5beaf Iustin Pop
                              then suffix
165 e4c5beaf Iustin Pop
                              else accu)
166 e4c5beaf Iustin Pop
      "" $ filter (isPrefixOf ".") (tails x)
167 e4c5beaf Iustin Pop
168 f5e67f55 Iustin Pop
-- | Extracts the exclusion tags from the cluster configuration
169 f5e67f55 Iustin Pop
extractExTags :: [String] -> [String]
170 f5e67f55 Iustin Pop
extractExTags =
171 f5e67f55 Iustin Pop
    map (drop (length exTagsPrefix)) .
172 f5e67f55 Iustin Pop
    filter (isPrefixOf exTagsPrefix)
173 f5e67f55 Iustin Pop
174 381be58a Iustin Pop
-- | Extracts the common suffix from node\/instance names
175 3e4480e0 Iustin Pop
commonSuffix :: Node.List -> Instance.List -> String
176 3e4480e0 Iustin Pop
commonSuffix nl il =
177 3e4480e0 Iustin Pop
    let node_names = map Node.name $ Container.elems nl
178 3e4480e0 Iustin Pop
        inst_names = map Instance.name $ Container.elems il
179 3e4480e0 Iustin Pop
    in longestDomain (node_names ++ inst_names)
180 3e4480e0 Iustin Pop
181 9188aeef Iustin Pop
-- | Initializer function that loads the data from a node and instance
182 9188aeef Iustin Pop
-- list and massages it into the correct format.
183 aa8d2e71 Iustin Pop
mergeData :: [(String, DynUtil)]  -- ^ Instance utilisation data
184 0f15cc76 Iustin Pop
          -> [String]             -- ^ Exclusion tags
185 39f979b8 Iustin Pop
          -> [String]             -- ^ Untouchable instances
186 f4f6eb0b Iustin Pop
          -> ClusterData          -- ^ Data from backends
187 c0e31451 Iustin Pop
          -> Result ClusterData   -- ^ Fixed cluster data
188 f4f6eb0b Iustin Pop
mergeData um extags exinsts cdata@(ClusterData _ nl il2 tags) =
189 99b63608 Iustin Pop
  let il = Container.elems il2
190 a5f8dcdc Iustin Pop
      il3 = foldl' (\im (name, n_util) ->
191 a5f8dcdc Iustin Pop
                        case Container.findByName im name of
192 a5f8dcdc Iustin Pop
                          Nothing -> im -- skipping unknown instance
193 a5f8dcdc Iustin Pop
                          Just inst ->
194 a5f8dcdc Iustin Pop
                              let new_i = inst { Instance.util = n_util }
195 a5f8dcdc Iustin Pop
                              in Container.add (Instance.idx inst) new_i im
196 a5f8dcdc Iustin Pop
                   ) il2 um
197 f5e67f55 Iustin Pop
      allextags = extags ++ extractExTags tags
198 39f979b8 Iustin Pop
      il4 = Container.map (filterExTags allextags .
199 39f979b8 Iustin Pop
                           updateMovable exinsts) il3
200 0f15cc76 Iustin Pop
      nl2 = foldl' fixNodes nl (Container.elems il4)
201 2a8e2dc9 Iustin Pop
      nl3 = Container.map (flip Node.buildPeers il4) nl2
202 99b63608 Iustin Pop
      node_names = map Node.name (Container.elems nl)
203 99b63608 Iustin Pop
      inst_names = map Instance.name il
204 8472a321 Iustin Pop
      common_suffix = longestDomain (node_names ++ inst_names)
205 3e4480e0 Iustin Pop
      snl = Container.map (computeAlias common_suffix) nl3
206 3e4480e0 Iustin Pop
      sil = Container.map (computeAlias common_suffix) il4
207 c854092b Iustin Pop
      all_inst_names = concatMap allNames $ Container.elems sil
208 c854092b Iustin Pop
  in if not $ all (`elem` all_inst_names) exinsts
209 5ab2b771 Iustin Pop
     then Bad $ "Some of the excluded instances are unknown: " ++
210 c854092b Iustin Pop
          show (exinsts \\ all_inst_names)
211 f4f6eb0b Iustin Pop
     else Ok cdata { cdNodes = snl, cdInstances = sil }
212 446d8827 Iustin Pop
213 9188aeef Iustin Pop
-- | Checks the cluster data for consistency.
214 262a08a2 Iustin Pop
checkData :: Node.List -> Instance.List
215 262a08a2 Iustin Pop
          -> ([String], Node.List)
216 dbd6700b Iustin Pop
checkData nl il =
217 446d8827 Iustin Pop
    Container.mapAccum
218 446d8827 Iustin Pop
        (\ msgs node ->
219 dbd6700b Iustin Pop
             let nname = Node.name node
220 5182e970 Iustin Pop
                 nilst = map (`Container.find` il) (Node.pList node)
221 446d8827 Iustin Pop
                 dilst = filter (not . Instance.running) nilst
222 446d8827 Iustin Pop
                 adj_mem = sum . map Instance.mem $ dilst
223 2060348b Iustin Pop
                 delta_mem = truncate (Node.tMem node)
224 2060348b Iustin Pop
                             - Node.nMem node
225 2060348b Iustin Pop
                             - Node.fMem node
226 9f6dcdea Iustin Pop
                             - nodeImem node il
227 446d8827 Iustin Pop
                             + adj_mem
228 2060348b Iustin Pop
                 delta_dsk = truncate (Node.tDsk node)
229 2060348b Iustin Pop
                             - Node.fDsk node
230 9f6dcdea Iustin Pop
                             - nodeIdsk node il
231 446d8827 Iustin Pop
                 newn = Node.setFmem (Node.setXmem node delta_mem)
232 2060348b Iustin Pop
                        (Node.fMem node - adj_mem)
233 9f6dcdea Iustin Pop
                 umsg1 = [printf "node %s is missing %d MB ram \
234 9f6dcdea Iustin Pop
                                 \and %d GB disk"
235 9f6dcdea Iustin Pop
                                 nname delta_mem (delta_dsk `div` 1024) |
236 9f6dcdea Iustin Pop
                                 delta_mem > 512 || delta_dsk > 1024]::[String]
237 446d8827 Iustin Pop
             in (msgs ++ umsg1, newn)
238 446d8827 Iustin Pop
        ) [] nl
239 446d8827 Iustin Pop
240 446d8827 Iustin Pop
-- | Compute the amount of memory used by primary instances on a node.
241 262a08a2 Iustin Pop
nodeImem :: Node.Node -> Instance.List -> Int
242 446d8827 Iustin Pop
nodeImem node il =
243 9f6dcdea Iustin Pop
    let rfind = flip Container.find il
244 9f6dcdea Iustin Pop
    in sum . map (Instance.mem . rfind)
245 2060348b Iustin Pop
           $ Node.pList node
246 446d8827 Iustin Pop
247 446d8827 Iustin Pop
-- | Compute the amount of disk used by instances on a node (either primary
248 446d8827 Iustin Pop
-- or secondary).
249 262a08a2 Iustin Pop
nodeIdsk :: Node.Node -> Instance.List -> Int
250 446d8827 Iustin Pop
nodeIdsk node il =
251 9f6dcdea Iustin Pop
    let rfind = flip Container.find il
252 9f6dcdea Iustin Pop
    in sum . map (Instance.dsk . rfind)
253 2060348b Iustin Pop
           $ Node.pList node ++ Node.sList node