Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Loader.hs @ 55416810

History | View | Annotate | Download (12.4 kB)

1
{-| Generic data loader.
2

    
3
This module holds the common code for parsing the input data after it
4
has been loaded from external sources.
5

    
6
-}
7

    
8
{-
9

    
10
Copyright (C) 2009, 2010, 2011, 2012 Google Inc.
11

    
12
This program is free software; you can redistribute it and/or modify
13
it under the terms of the GNU General Public License as published by
14
the Free Software Foundation; either version 2 of the License, or
15
(at your option) any later version.
16

    
17
This program is distributed in the hope that it will be useful, but
18
WITHOUT ANY WARRANTY; without even the implied warranty of
19
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20
General Public License for more details.
21

    
22
You should have received a copy of the GNU General Public License
23
along with this program; if not, write to the Free Software
24
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25
02110-1301, USA.
26

    
27
-}
28

    
29
module Ganeti.HTools.Loader
30
  ( mergeData
31
  , checkData
32
  , assignIndices
33
  , lookupNode
34
  , lookupInstance
35
  , lookupGroup
36
  , commonSuffix
37
  , RqType(..)
38
  , Request(..)
39
  , ClusterData(..)
40
  , emptyCluster
41
  ) where
42

    
43
import Control.Monad
44
import Data.List
45
import qualified Data.Map as M
46
import Data.Maybe
47
import Text.Printf (printf)
48
import System.Time (ClockTime(..))
49

    
50
import qualified Ganeti.HTools.Container as Container
51
import qualified Ganeti.HTools.Instance as Instance
52
import qualified Ganeti.HTools.Node as Node
53
import qualified Ganeti.HTools.Group as Group
54
import qualified Ganeti.HTools.Cluster as Cluster
55

    
56
import Ganeti.BasicTypes
57
import qualified Ganeti.Constants as C
58
import Ganeti.HTools.Types
59
import Ganeti.Utils
60

    
61
-- * Constants
62

    
63
-- | The exclusion tag prefix.
64
exTagsPrefix :: String
65
exTagsPrefix = "htools:iextags:"
66

    
67
-- * Types
68

    
69
{-| The iallocator request type.
70

    
71
This type denotes what request we got from Ganeti and also holds
72
request-specific fields.
73

    
74
-}
75
data RqType
76
  = Allocate Instance.Instance Int           -- ^ A new instance allocation
77
  | Relocate Idx Int [Ndx]                   -- ^ Choose a new secondary node
78
  | NodeEvacuate [Idx] EvacMode              -- ^ node-evacuate mode
79
  | ChangeGroup [Gdx] [Idx]                  -- ^ Multi-relocate mode
80
  | MultiAllocate [(Instance.Instance, Int)] -- ^ Multi-allocate mode
81
    deriving (Show)
82

    
83
-- | A complete request, as received from Ganeti.
84
data Request = Request RqType ClusterData
85
               deriving (Show)
86

    
87
-- | The cluster state.
88
data ClusterData = ClusterData
89
  { cdGroups    :: Group.List    -- ^ The node group list
90
  , cdNodes     :: Node.List     -- ^ The node list
91
  , cdInstances :: Instance.List -- ^ The instance list
92
  , cdTags      :: [String]      -- ^ The cluster tags
93
  , cdIPolicy   :: IPolicy       -- ^ The cluster instance policy
94
  } deriving (Show, Eq)
95

    
96
-- | An empty cluster.
97
emptyCluster :: ClusterData
98
emptyCluster = ClusterData Container.empty Container.empty Container.empty []
99
                 defIPolicy
100

    
101
-- * Functions
102

    
103
-- | Lookups a node into an assoc list.
104
lookupNode :: (Monad m) => NameAssoc -> String -> String -> m Ndx
105
lookupNode ktn inst node =
106
  maybe (fail $ "Unknown node '" ++ node ++ "' for instance " ++ inst) return $
107
    M.lookup node ktn
108

    
109
-- | Lookups an instance into an assoc list.
110
lookupInstance :: (Monad m) => NameAssoc -> String -> m Idx
111
lookupInstance kti inst =
112
  maybe (fail $ "Unknown instance '" ++ inst ++ "'") return $ M.lookup inst kti
113

    
114
-- | Lookups a group into an assoc list.
115
lookupGroup :: (Monad m) => NameAssoc -> String -> String -> m Gdx
116
lookupGroup ktg nname gname =
117
  maybe (fail $ "Unknown group '" ++ gname ++ "' for node " ++ nname) return $
118
    M.lookup gname ktg
119

    
120
-- | Given a list of elements (and their names), assign indices to them.
121
assignIndices :: (Element a) =>
122
                 [(String, a)]
123
              -> (NameAssoc, Container.Container a)
124
assignIndices name_element =
125
  let (name_idx, idx_element) =
126
          unzip . map (\ (idx, (k, v)) -> ((k, idx), (idx, setIdx v idx)))
127
          . zip [0..] $ name_element
128
  in (M.fromList name_idx, Container.fromList idx_element)
129

    
130
-- | For each instance, add its index to its primary and secondary nodes.
131
fixNodes :: Node.List
132
         -> Instance.Instance
133
         -> Node.List
134
fixNodes accu inst =
135
  let pdx = Instance.pNode inst
136
      sdx = Instance.sNode inst
137
      pold = Container.find pdx accu
138
      pnew = Node.setPri pold inst
139
      ac2 = Container.add pdx pnew accu
140
  in if sdx /= Node.noSecondary
141
       then let sold = Container.find sdx accu
142
                snew = Node.setSec sold inst
143
            in Container.add sdx snew ac2
144
       else ac2
145

    
146
-- | Set the node's policy to its group one. Note that this requires
147
-- the group to exist (should have been checked before), otherwise it
148
-- will abort with a runtime error.
149
setNodePolicy :: Group.List -> Node.Node -> Node.Node
150
setNodePolicy gl node =
151
  let grp = Container.find (Node.group node) gl
152
      gpol = Group.iPolicy grp
153
  in Node.setPolicy gpol node
154

    
155
-- | Update instance with exclusion tags list.
156
updateExclTags :: [String] -> Instance.Instance -> Instance.Instance
157
updateExclTags tl inst =
158
  let allTags = Instance.allTags inst
159
      exclTags = filter (\tag -> any (`isPrefixOf` tag) tl) allTags
160
  in inst { Instance.exclTags = exclTags }
161

    
162
-- | Update the movable attribute.
163
updateMovable :: [String]           -- ^ Selected instances (if not empty)
164
              -> [String]           -- ^ Excluded instances
165
              -> Instance.Instance  -- ^ Target Instance
166
              -> Instance.Instance  -- ^ Target Instance with updated attribute
167
updateMovable selinsts exinsts inst =
168
  if Instance.name inst `elem` exinsts ||
169
     not (null selinsts || Instance.name inst `elem` selinsts)
170
    then Instance.setMovable inst False
171
    else inst
172

    
173
-- | Disables moves for instances with a split group.
174
disableSplitMoves :: Node.List -> Instance.Instance -> Instance.Instance
175
disableSplitMoves nl inst =
176
  if not . isOk . Cluster.instanceGroup nl $ inst
177
    then Instance.setMovable inst False
178
    else inst
179

    
180
-- | Set the auto-repair policy for an instance.
181
setArPolicy :: [String]       -- ^ Cluster tags
182
            -> Group.List     -- ^ List of node groups
183
            -> Node.List      -- ^ List of nodes
184
            -> Instance.List  -- ^ List of instances
185
            -> Instance.List  -- ^ Updated list of instances
186
setArPolicy ctags gl nl il =
187
  let cpol = fromMaybe ArNotEnabled $ getArPolicy ctags
188
      gpols = Container.map (fromMaybe cpol . getArPolicy . Group.allTags) gl
189
      ipolfn = getArPolicy . Instance.allTags
190
      nlookup = flip Container.find nl . Instance.pNode
191
      glookup = flip Container.find gpols . Node.group . nlookup
192
      updateInstance inst = inst {
193
        Instance.arPolicy = fromMaybe (glookup inst) $ ipolfn inst }
194
  in
195
   Container.map updateInstance il
196

    
197
-- | Get the auto-repair policy from a list of tags.
198
--
199
-- This examines the ganeti:watcher:autorepair and
200
-- ganeti:watcher:autorepair:suspend tags to determine the policy. If none of
201
-- these tags are present, Nothing (and not ArNotEnabled) is returned.
202
getArPolicy :: [String] -> Maybe AutoRepairPolicy
203
getArPolicy tags =
204
  let enabled = mapMaybe (autoRepairTypeFromRaw <=<
205
                          chompPrefix C.autoRepairTagEnabled) tags
206
      suspended = mapMaybe (chompPrefix C.autoRepairTagSuspended) tags
207
      suspTime = if "" `elem` suspended
208
                   then Forever
209
                   else Until . flip TOD 0 . maximum $
210
                        mapMaybe (tryRead "auto-repair suspend time") suspended
211
  in
212
   case () of
213
     -- Note how we must return ArSuspended even if "enabled" is empty, so that
214
     -- node groups or instances can suspend repairs that were enabled at an
215
     -- upper scope (cluster or node group).
216
     _ | not $ null suspended -> Just $ ArSuspended suspTime
217
       | not $ null enabled   -> Just $ ArEnabled (minimum enabled)
218
       | otherwise            -> Nothing
219

    
220
-- | Compute the longest common suffix of a list of strings that
221
-- starts with a dot.
222
longestDomain :: [String] -> String
223
longestDomain [] = ""
224
longestDomain (x:xs) =
225
  foldr (\ suffix accu -> if all (isSuffixOf suffix) xs
226
                            then suffix
227
                            else accu)
228
          "" $ filter (isPrefixOf ".") (tails x)
229

    
230
-- | Extracts the exclusion tags from the cluster configuration.
231
extractExTags :: [String] -> [String]
232
extractExTags = filter (not . null) . mapMaybe (chompPrefix exTagsPrefix)
233

    
234
-- | Extracts the common suffix from node\/instance names.
235
commonSuffix :: Node.List -> Instance.List -> String
236
commonSuffix nl il =
237
  let node_names = map Node.name $ Container.elems nl
238
      inst_names = map Instance.name $ Container.elems il
239
  in longestDomain (node_names ++ inst_names)
240

    
241
-- | Initializer function that loads the data from a node and instance
242
-- list and massages it into the correct format.
243
mergeData :: [(String, DynUtil)]  -- ^ Instance utilisation data
244
          -> [String]             -- ^ Exclusion tags
245
          -> [String]             -- ^ Selected instances (if not empty)
246
          -> [String]             -- ^ Excluded instances
247
          -> ClusterData          -- ^ Data from backends
248
          -> Result ClusterData   -- ^ Fixed cluster data
249
mergeData um extags selinsts exinsts cdata@(ClusterData gl nl il ctags _) =
250
  let il2 = setArPolicy ctags gl nl il
251
      il3 = foldl' (\im (name, n_util) ->
252
                        case Container.findByName im name of
253
                          Nothing -> im -- skipping unknown instance
254
                          Just inst ->
255
                              let new_i = inst { Instance.util = n_util }
256
                              in Container.add (Instance.idx inst) new_i im
257
                   ) il2 um
258
      allextags = extags ++ extractExTags ctags
259
      inst_names = map Instance.name $ Container.elems il3
260
      selinst_lkp = map (lookupName inst_names) selinsts
261
      exinst_lkp = map (lookupName inst_names) exinsts
262
      lkp_unknown = filter (not . goodLookupResult) (selinst_lkp ++ exinst_lkp)
263
      selinst_names = map lrContent selinst_lkp
264
      exinst_names = map lrContent exinst_lkp
265
      node_names = map Node.name (Container.elems nl)
266
      common_suffix = longestDomain (node_names ++ inst_names)
267
      il4 = Container.map (computeAlias common_suffix .
268
                           updateExclTags allextags .
269
                           updateMovable selinst_names exinst_names) il3
270
      nl2 = foldl' fixNodes nl (Container.elems il4)
271
      nl3 = Container.map (setNodePolicy gl .
272
                           computeAlias common_suffix .
273
                           (`Node.buildPeers` il4)) nl2
274
      il5 = Container.map (disableSplitMoves nl3) il4
275
  in if' (null lkp_unknown)
276
         (Ok cdata { cdNodes = nl3, cdInstances = il5 })
277
         (Bad $ "Unknown instance(s): " ++ show(map lrContent lkp_unknown))
278

    
279
-- | Checks the cluster data for consistency.
280
checkData :: Node.List -> Instance.List
281
          -> ([String], Node.List)
282
checkData nl il =
283
    Container.mapAccum
284
        (\ msgs node ->
285
             let nname = Node.name node
286
                 nilst = map (`Container.find` il) (Node.pList node)
287
                 dilst = filter Instance.instanceDown nilst
288
                 adj_mem = sum . map Instance.mem $ dilst
289
                 delta_mem = truncate (Node.tMem node)
290
                             - Node.nMem node
291
                             - Node.fMem node
292
                             - nodeImem node il
293
                             + adj_mem
294
                 delta_dsk = truncate (Node.tDsk node)
295
                             - Node.fDsk node
296
                             - nodeIdsk node il
297
                 newn = Node.setFmem (Node.setXmem node delta_mem)
298
                        (Node.fMem node - adj_mem)
299
                 umsg1 =
300
                   if delta_mem > 512 || delta_dsk > 1024
301
                      then printf "node %s is missing %d MB ram \
302
                                  \and %d GB disk"
303
                                  nname delta_mem (delta_dsk `div` 1024):msgs
304
                      else msgs
305
             in (umsg1, newn)
306
        ) [] nl
307

    
308
-- | Compute the amount of memory used by primary instances on a node.
309
nodeImem :: Node.Node -> Instance.List -> Int
310
nodeImem node il =
311
  let rfind = flip Container.find il
312
      il' = map rfind $ Node.pList node
313
      oil' = filter Instance.notOffline il'
314
  in sum . map Instance.mem $ oil'
315

    
316

    
317
-- | Compute the amount of disk used by instances on a node (either primary
318
-- or secondary).
319
nodeIdsk :: Node.Node -> Instance.List -> Int
320
nodeIdsk node il =
321
  let rfind = flip Container.find il
322
  in sum . map (Instance.dsk . rfind)
323
       $ Node.pList node ++ Node.sList node