Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Loader.hs @ 29a30533

History | View | Annotate | Download (10.4 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 d6eec019 Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012 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 ebf38064 Iustin Pop
  ( mergeData
31 ebf38064 Iustin Pop
  , checkData
32 ebf38064 Iustin Pop
  , assignIndices
33 ebf38064 Iustin Pop
  , lookupNode
34 ebf38064 Iustin Pop
  , lookupInstance
35 ebf38064 Iustin Pop
  , lookupGroup
36 ebf38064 Iustin Pop
  , commonSuffix
37 ebf38064 Iustin Pop
  , RqType(..)
38 ebf38064 Iustin Pop
  , Request(..)
39 ebf38064 Iustin Pop
  , ClusterData(..)
40 ebf38064 Iustin Pop
  , emptyCluster
41 ebf38064 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 a7e1fd89 Iustin Pop
import qualified Ganeti.HTools.Cluster as Cluster
52 e4c5beaf Iustin Pop
53 2fc5653f Iustin Pop
import Ganeti.BasicTypes
54 e4c5beaf Iustin Pop
import Ganeti.HTools.Types
55 26d62e4c Iustin Pop
import Ganeti.Utils
56 e4c5beaf Iustin Pop
57 f5e67f55 Iustin Pop
-- * Constants
58 f5e67f55 Iustin Pop
59 525bfb36 Iustin Pop
-- | The exclusion tag prefix.
60 f5e67f55 Iustin Pop
exTagsPrefix :: String
61 f5e67f55 Iustin Pop
exTagsPrefix = "htools:iextags:"
62 f5e67f55 Iustin Pop
63 19f38ee8 Iustin Pop
-- * Types
64 19f38ee8 Iustin Pop
65 54365762 Iustin Pop
{-| The iallocator request type.
66 19f38ee8 Iustin Pop
67 19f38ee8 Iustin Pop
This type denotes what request we got from Ganeti and also holds
68 19f38ee8 Iustin Pop
request-specific fields.
69 19f38ee8 Iustin Pop
70 19f38ee8 Iustin Pop
-}
71 19f38ee8 Iustin Pop
data RqType
72 2a9aff11 René Nussbaumer
  = Allocate Instance.Instance Int           -- ^ A new instance allocation
73 2a9aff11 René Nussbaumer
  | Relocate Idx Int [Ndx]                   -- ^ Choose a new secondary node
74 2a9aff11 René Nussbaumer
  | NodeEvacuate [Idx] EvacMode              -- ^ node-evacuate mode
75 2a9aff11 René Nussbaumer
  | ChangeGroup [Gdx] [Idx]                  -- ^ Multi-relocate mode
76 2a9aff11 René Nussbaumer
  | MultiAllocate [(Instance.Instance, Int)] -- ^ Multi-allocate mode
77 6bc39970 Iustin Pop
    deriving (Show, Read)
78 19f38ee8 Iustin Pop
79 19f38ee8 Iustin Pop
-- | A complete request, as received from Ganeti.
80 34c00528 Iustin Pop
data Request = Request RqType ClusterData
81 ebf38064 Iustin Pop
               deriving (Show, Read)
82 19f38ee8 Iustin Pop
83 7b6e99b3 Iustin Pop
-- | The cluster state.
84 7b6e99b3 Iustin Pop
data ClusterData = ClusterData
85 ebf38064 Iustin Pop
  { cdGroups    :: Group.List    -- ^ The node group list
86 ebf38064 Iustin Pop
  , cdNodes     :: Node.List     -- ^ The node list
87 ebf38064 Iustin Pop
  , cdInstances :: Instance.List -- ^ The instance list
88 ebf38064 Iustin Pop
  , cdTags      :: [String]      -- ^ The cluster tags
89 71375ef7 Iustin Pop
  , cdIPolicy   :: IPolicy       -- ^ The cluster instance policy
90 dce9bbb3 Iustin Pop
  } deriving (Show, Read, Eq)
91 7b6e99b3 Iustin Pop
92 7b6e99b3 Iustin Pop
-- | An empty cluster.
93 7b6e99b3 Iustin Pop
emptyCluster :: ClusterData
94 7b6e99b3 Iustin Pop
emptyCluster = ClusterData Container.empty Container.empty Container.empty []
95 71375ef7 Iustin Pop
                 defIPolicy
96 7b6e99b3 Iustin Pop
97 19f38ee8 Iustin Pop
-- * Functions
98 19f38ee8 Iustin Pop
99 9188aeef Iustin Pop
-- | Lookups a node into an assoc list.
100 6ff78049 Iustin Pop
lookupNode :: (Monad m) => NameAssoc -> String -> String -> m Ndx
101 040afc35 Iustin Pop
lookupNode ktn inst node =
102 76ae2e5b Iustin Pop
  maybe (fail $ "Unknown node '" ++ node ++ "' for instance " ++ inst) return $
103 76ae2e5b Iustin Pop
    M.lookup node ktn
104 040afc35 Iustin Pop
105 9188aeef Iustin Pop
-- | Lookups an instance into an assoc list.
106 6ff78049 Iustin Pop
lookupInstance :: (Monad m) => NameAssoc -> String -> m Idx
107 5a1edeb6 Iustin Pop
lookupInstance kti inst =
108 76ae2e5b Iustin Pop
  maybe (fail $ "Unknown instance '" ++ inst ++ "'") return $ M.lookup inst kti
109 5a1edeb6 Iustin Pop
110 f4531f51 Iustin Pop
-- | Lookups a group into an assoc list.
111 f4531f51 Iustin Pop
lookupGroup :: (Monad m) => NameAssoc -> String -> String -> m Gdx
112 f4531f51 Iustin Pop
lookupGroup ktg nname gname =
113 76ae2e5b Iustin Pop
  maybe (fail $ "Unknown group '" ++ gname ++ "' for node " ++ nname) return $
114 76ae2e5b Iustin Pop
    M.lookup gname ktg
115 f4531f51 Iustin Pop
116 9188aeef Iustin Pop
-- | Given a list of elements (and their names), assign indices to them.
117 497e30a1 Iustin Pop
assignIndices :: (Element a) =>
118 497e30a1 Iustin Pop
                 [(String, a)]
119 99b63608 Iustin Pop
              -> (NameAssoc, Container.Container a)
120 2d0ca2c5 Iustin Pop
assignIndices nodes =
121 2d0ca2c5 Iustin Pop
  let (na, idx_node) =
122 2d0ca2c5 Iustin Pop
          unzip . map (\ (idx, (k, v)) -> ((k, idx), (idx, setIdx v idx)))
123 2d0ca2c5 Iustin Pop
          . zip [0..] $ nodes
124 cb0c77ff Iustin Pop
  in (M.fromList na, Container.fromList idx_node)
125 78694255 Iustin Pop
126 9188aeef Iustin Pop
-- | For each instance, add its index to its primary and secondary nodes.
127 99b63608 Iustin Pop
fixNodes :: Node.List
128 aa8d2e71 Iustin Pop
         -> Instance.Instance
129 99b63608 Iustin Pop
         -> Node.List
130 aa8d2e71 Iustin Pop
fixNodes accu inst =
131 ebf38064 Iustin Pop
  let pdx = Instance.pNode inst
132 ebf38064 Iustin Pop
      sdx = Instance.sNode inst
133 ebf38064 Iustin Pop
      pold = Container.find pdx accu
134 ebf38064 Iustin Pop
      pnew = Node.setPri pold inst
135 ebf38064 Iustin Pop
      ac2 = Container.add pdx pnew accu
136 ebf38064 Iustin Pop
  in if sdx /= Node.noSecondary
137 ebf38064 Iustin Pop
       then let sold = Container.find sdx accu
138 ebf38064 Iustin Pop
                snew = Node.setSec sold inst
139 ebf38064 Iustin Pop
            in Container.add sdx snew ac2
140 ebf38064 Iustin Pop
       else ac2
141 e4c5beaf Iustin Pop
142 d6eec019 Iustin Pop
-- | Set the node's policy to its group one. Note that this requires
143 d6eec019 Iustin Pop
-- the group to exist (should have been checked before), otherwise it
144 d6eec019 Iustin Pop
-- will abort with a runtime error.
145 d6eec019 Iustin Pop
setNodePolicy :: Group.List -> Node.Node -> Node.Node
146 d6eec019 Iustin Pop
setNodePolicy gl node =
147 d6eec019 Iustin Pop
  let grp = Container.find (Node.group node) gl
148 d6eec019 Iustin Pop
      gpol = Group.iPolicy grp
149 d6eec019 Iustin Pop
  in Node.setPolicy gpol node
150 d6eec019 Iustin Pop
151 2f907bad Dato Simó
-- | Update instance with exclusion tags list.
152 2f907bad Dato Simó
updateExclTags :: [String] -> Instance.Instance -> Instance.Instance
153 2f907bad Dato Simó
updateExclTags tl inst =
154 2f907bad Dato Simó
  let allTags = Instance.allTags inst
155 2f907bad Dato Simó
      exclTags = filter (\tag -> any (`isPrefixOf` tag) tl) allTags
156 2f907bad Dato Simó
  in inst { Instance.exclTags = exclTags }
157 0f15cc76 Iustin Pop
158 525bfb36 Iustin Pop
-- | Update the movable attribute.
159 c6ccc073 Guido Trotter
updateMovable :: [String]           -- ^ Selected instances (if not empty)
160 c6ccc073 Guido Trotter
              -> [String]           -- ^ Excluded instances
161 c6ccc073 Guido Trotter
              -> Instance.Instance  -- ^ Target Instance
162 c6ccc073 Guido Trotter
              -> Instance.Instance  -- ^ Target Instance with updated attribute
163 c6ccc073 Guido Trotter
updateMovable selinsts exinsts inst =
164 a7667ba6 Iustin Pop
  if Instance.name inst `elem` exinsts ||
165 ebf38064 Iustin Pop
     not (null selinsts || Instance.name inst `elem` selinsts)
166 39f979b8 Iustin Pop
    then Instance.setMovable inst False
167 39f979b8 Iustin Pop
    else inst
168 39f979b8 Iustin Pop
169 a7e1fd89 Iustin Pop
-- | Disables moves for instances with a split group.
170 a7e1fd89 Iustin Pop
disableSplitMoves :: Node.List -> Instance.Instance -> Instance.Instance
171 a7e1fd89 Iustin Pop
disableSplitMoves nl inst =
172 a7e1fd89 Iustin Pop
  if not . isOk . Cluster.instanceGroup nl $ inst
173 a7e1fd89 Iustin Pop
    then Instance.setMovable inst False
174 a7e1fd89 Iustin Pop
    else inst
175 a7e1fd89 Iustin Pop
176 f9fc7a63 Iustin Pop
-- | Compute the longest common suffix of a list of strings that
177 525bfb36 Iustin Pop
-- starts with a dot.
178 8472a321 Iustin Pop
longestDomain :: [String] -> String
179 e4c5beaf Iustin Pop
longestDomain [] = ""
180 8472a321 Iustin Pop
longestDomain (x:xs) =
181 ebf38064 Iustin Pop
  foldr (\ suffix accu -> if all (isSuffixOf suffix) xs
182 ebf38064 Iustin Pop
                            then suffix
183 ebf38064 Iustin Pop
                            else accu)
184 ebf38064 Iustin Pop
          "" $ filter (isPrefixOf ".") (tails x)
185 e4c5beaf Iustin Pop
186 525bfb36 Iustin Pop
-- | Extracts the exclusion tags from the cluster configuration.
187 f5e67f55 Iustin Pop
extractExTags :: [String] -> [String]
188 f5e67f55 Iustin Pop
extractExTags =
189 ebf38064 Iustin Pop
  map (drop (length exTagsPrefix)) .
190 ebf38064 Iustin Pop
  filter (isPrefixOf exTagsPrefix)
191 f5e67f55 Iustin Pop
192 525bfb36 Iustin Pop
-- | Extracts the common suffix from node\/instance names.
193 3e4480e0 Iustin Pop
commonSuffix :: Node.List -> Instance.List -> String
194 3e4480e0 Iustin Pop
commonSuffix nl il =
195 ebf38064 Iustin Pop
  let node_names = map Node.name $ Container.elems nl
196 ebf38064 Iustin Pop
      inst_names = map Instance.name $ Container.elems il
197 ebf38064 Iustin Pop
  in longestDomain (node_names ++ inst_names)
198 3e4480e0 Iustin Pop
199 9188aeef Iustin Pop
-- | Initializer function that loads the data from a node and instance
200 9188aeef Iustin Pop
-- list and massages it into the correct format.
201 aa8d2e71 Iustin Pop
mergeData :: [(String, DynUtil)]  -- ^ Instance utilisation data
202 0f15cc76 Iustin Pop
          -> [String]             -- ^ Exclusion tags
203 2d1708e0 Guido Trotter
          -> [String]             -- ^ Selected instances (if not empty)
204 2d1708e0 Guido Trotter
          -> [String]             -- ^ Excluded instances
205 f4f6eb0b Iustin Pop
          -> ClusterData          -- ^ Data from backends
206 c0e31451 Iustin Pop
          -> Result ClusterData   -- ^ Fixed cluster data
207 d6eec019 Iustin Pop
mergeData um extags selinsts exinsts cdata@(ClusterData gl nl il2 tags _) =
208 99b63608 Iustin Pop
  let il = Container.elems il2
209 a5f8dcdc Iustin Pop
      il3 = foldl' (\im (name, n_util) ->
210 a5f8dcdc Iustin Pop
                        case Container.findByName im name of
211 a5f8dcdc Iustin Pop
                          Nothing -> im -- skipping unknown instance
212 a5f8dcdc Iustin Pop
                          Just inst ->
213 a5f8dcdc Iustin Pop
                              let new_i = inst { Instance.util = n_util }
214 a5f8dcdc Iustin Pop
                              in Container.add (Instance.idx inst) new_i im
215 a5f8dcdc Iustin Pop
                   ) il2 um
216 f5e67f55 Iustin Pop
      allextags = extags ++ extractExTags tags
217 424ec11d Guido Trotter
      inst_names = map Instance.name il
218 424ec11d Guido Trotter
      selinst_lkp = map (lookupName inst_names) selinsts
219 424ec11d Guido Trotter
      exinst_lkp = map (lookupName inst_names) exinsts
220 424ec11d Guido Trotter
      lkp_unknown = filter (not . goodLookupResult) (selinst_lkp ++ exinst_lkp)
221 424ec11d Guido Trotter
      selinst_names = map lrContent selinst_lkp
222 424ec11d Guido Trotter
      exinst_names = map lrContent exinst_lkp
223 99b63608 Iustin Pop
      node_names = map Node.name (Container.elems nl)
224 8472a321 Iustin Pop
      common_suffix = longestDomain (node_names ++ inst_names)
225 cdbab531 Iustin Pop
      il4 = Container.map (computeAlias common_suffix .
226 2f907bad Dato Simó
                           updateExclTags allextags .
227 cdbab531 Iustin Pop
                           updateMovable selinst_names exinst_names) il3
228 cdbab531 Iustin Pop
      nl2 = foldl' fixNodes nl (Container.elems il4)
229 d6eec019 Iustin Pop
      nl3 = Container.map (setNodePolicy gl .
230 d6eec019 Iustin Pop
                           computeAlias common_suffix .
231 cdbab531 Iustin Pop
                           (`Node.buildPeers` il4)) nl2
232 a7e1fd89 Iustin Pop
      il5 = Container.map (disableSplitMoves nl3) il4
233 424ec11d Guido Trotter
  in if' (null lkp_unknown)
234 a7e1fd89 Iustin Pop
         (Ok cdata { cdNodes = nl3, cdInstances = il5 })
235 424ec11d Guido Trotter
         (Bad $ "Unknown instance(s): " ++ show(map lrContent lkp_unknown))
236 446d8827 Iustin Pop
237 9188aeef Iustin Pop
-- | Checks the cluster data for consistency.
238 262a08a2 Iustin Pop
checkData :: Node.List -> Instance.List
239 262a08a2 Iustin Pop
          -> ([String], Node.List)
240 dbd6700b Iustin Pop
checkData nl il =
241 446d8827 Iustin Pop
    Container.mapAccum
242 446d8827 Iustin Pop
        (\ msgs node ->
243 dbd6700b Iustin Pop
             let nname = Node.name node
244 5182e970 Iustin Pop
                 nilst = map (`Container.find` il) (Node.pList node)
245 61bbbed7 Agata Murawska
                 dilst = filter Instance.instanceDown nilst
246 446d8827 Iustin Pop
                 adj_mem = sum . map Instance.mem $ dilst
247 2060348b Iustin Pop
                 delta_mem = truncate (Node.tMem node)
248 2060348b Iustin Pop
                             - Node.nMem node
249 2060348b Iustin Pop
                             - Node.fMem node
250 9f6dcdea Iustin Pop
                             - nodeImem node il
251 446d8827 Iustin Pop
                             + adj_mem
252 2060348b Iustin Pop
                 delta_dsk = truncate (Node.tDsk node)
253 2060348b Iustin Pop
                             - Node.fDsk node
254 9f6dcdea Iustin Pop
                             - nodeIdsk node il
255 446d8827 Iustin Pop
                 newn = Node.setFmem (Node.setXmem node delta_mem)
256 2060348b Iustin Pop
                        (Node.fMem node - adj_mem)
257 bdd8c739 Iustin Pop
                 umsg1 =
258 bdd8c739 Iustin Pop
                   if delta_mem > 512 || delta_dsk > 1024
259 3603605a Iustin Pop
                      then printf "node %s is missing %d MB ram \
260 3603605a Iustin Pop
                                  \and %d GB disk"
261 3603605a Iustin Pop
                                  nname delta_mem (delta_dsk `div` 1024):msgs
262 bdd8c739 Iustin Pop
                      else msgs
263 bdd8c739 Iustin Pop
             in (umsg1, newn)
264 446d8827 Iustin Pop
        ) [] nl
265 446d8827 Iustin Pop
266 446d8827 Iustin Pop
-- | Compute the amount of memory used by primary instances on a node.
267 262a08a2 Iustin Pop
nodeImem :: Node.Node -> Instance.List -> Int
268 446d8827 Iustin Pop
nodeImem node il =
269 ebf38064 Iustin Pop
  let rfind = flip Container.find il
270 ebf38064 Iustin Pop
      il' = map rfind $ Node.pList node
271 7959cbb9 Iustin Pop
      oil' = filter Instance.notOffline il'
272 ebf38064 Iustin Pop
  in sum . map Instance.mem $ oil'
273 61bbbed7 Agata Murawska
274 446d8827 Iustin Pop
275 446d8827 Iustin Pop
-- | Compute the amount of disk used by instances on a node (either primary
276 446d8827 Iustin Pop
-- or secondary).
277 262a08a2 Iustin Pop
nodeIdsk :: Node.Node -> Instance.List -> Int
278 446d8827 Iustin Pop
nodeIdsk node il =
279 ebf38064 Iustin Pop
  let rfind = flip Container.find il
280 ebf38064 Iustin Pop
  in sum . map (Instance.dsk . rfind)
281 ebf38064 Iustin Pop
       $ Node.pList node ++ Node.sList node