Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Loader.hs @ 7c14b50a

History | View | Annotate | Download (9.9 kB)

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