Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Loader.hs @ 09ab9fb2

History | View | Annotate | Download (13 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
  , setMaster
34
  , lookupNode
35
  , lookupInstance
36
  , lookupGroup
37
  , commonSuffix
38
  , RqType(..)
39
  , Request(..)
40
  , ClusterData(..)
41
  , emptyCluster
42
  ) where
43

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

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

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

    
62
-- * Constants
63

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

    
68
-- * Types
69

    
70
{-| The iallocator request type.
71

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

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

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

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

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

    
102
-- * Functions
103

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

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

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

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

    
131
-- | Given am indexed node list, and the name of the master, mark it as such. 
132
setMaster :: (Monad m) => NameAssoc -> Node.List -> String -> m Node.List
133
setMaster node_names node_idx master = do
134
  kmaster <- maybe (fail $ "Master node " ++ master ++ " unknown") return $
135
             M.lookup master node_names
136
  let mnode = Container.find kmaster node_idx
137
  return $ Container.add kmaster (Node.setMaster mnode True) node_idx
138

    
139
-- | For each instance, add its index to its primary and secondary nodes.
140
fixNodes :: Node.List
141
         -> Instance.Instance
142
         -> Node.List
143
fixNodes accu inst =
144
  let pdx = Instance.pNode inst
145
      sdx = Instance.sNode inst
146
      pold = Container.find pdx accu
147
      pnew = Node.setPri pold inst
148
      ac2 = Container.add pdx pnew accu
149
  in if sdx /= Node.noSecondary
150
       then let sold = Container.find sdx accu
151
                snew = Node.setSec sold inst
152
            in Container.add sdx snew ac2
153
       else ac2
154

    
155
-- | Set the node's policy to its group one. Note that this requires
156
-- the group to exist (should have been checked before), otherwise it
157
-- will abort with a runtime error.
158
setNodePolicy :: Group.List -> Node.Node -> Node.Node
159
setNodePolicy gl node =
160
  let grp = Container.find (Node.group node) gl
161
      gpol = Group.iPolicy grp
162
  in Node.setPolicy gpol node
163

    
164
-- | Update instance with exclusion tags list.
165
updateExclTags :: [String] -> Instance.Instance -> Instance.Instance
166
updateExclTags tl inst =
167
  let allTags = Instance.allTags inst
168
      exclTags = filter (\tag -> any (`isPrefixOf` tag) tl) allTags
169
  in inst { Instance.exclTags = exclTags }
170

    
171
-- | Update the movable attribute.
172
updateMovable :: [String]           -- ^ Selected instances (if not empty)
173
              -> [String]           -- ^ Excluded instances
174
              -> Instance.Instance  -- ^ Target Instance
175
              -> Instance.Instance  -- ^ Target Instance with updated attribute
176
updateMovable selinsts exinsts inst =
177
  if Instance.name inst `elem` exinsts ||
178
     not (null selinsts || Instance.name inst `elem` selinsts)
179
    then Instance.setMovable inst False
180
    else inst
181

    
182
-- | Disables moves for instances with a split group.
183
disableSplitMoves :: Node.List -> Instance.Instance -> Instance.Instance
184
disableSplitMoves nl inst =
185
  if not . isOk . Cluster.instanceGroup nl $ inst
186
    then Instance.setMovable inst False
187
    else inst
188

    
189
-- | Set the auto-repair policy for an instance.
190
setArPolicy :: [String]       -- ^ Cluster tags
191
            -> Group.List     -- ^ List of node groups
192
            -> Node.List      -- ^ List of nodes
193
            -> Instance.List  -- ^ List of instances
194
            -> ClockTime      -- ^ Current timestamp, to evaluate ArSuspended
195
            -> Instance.List  -- ^ Updated list of instances
196
setArPolicy ctags gl nl il time =
197
  let getArPolicy' = flip getArPolicy time
198
      cpol = fromMaybe ArNotEnabled $ getArPolicy' ctags
199
      gpols = Container.map (fromMaybe cpol . getArPolicy' . Group.allTags) gl
200
      ipolfn = getArPolicy' . Instance.allTags
201
      nlookup = flip Container.find nl . Instance.pNode
202
      glookup = flip Container.find gpols . Node.group . nlookup
203
      updateInstance inst = inst {
204
        Instance.arPolicy = fromMaybe (glookup inst) $ ipolfn inst }
205
  in
206
   Container.map updateInstance il
207

    
208
-- | Get the auto-repair policy from a list of tags.
209
--
210
-- This examines the ganeti:watcher:autorepair and
211
-- ganeti:watcher:autorepair:suspend tags to determine the policy. If none of
212
-- these tags are present, Nothing (and not ArNotEnabled) is returned.
213
getArPolicy :: [String] -> ClockTime -> Maybe AutoRepairPolicy
214
getArPolicy tags time =
215
  let enabled = mapMaybe (autoRepairTypeFromRaw <=<
216
                          chompPrefix C.autoRepairTagEnabled) tags
217
      suspended = mapMaybe (chompPrefix C.autoRepairTagSuspended) tags
218
      futureTs = filter (> time) . map (flip TOD 0) $
219
                   mapMaybe (tryRead "auto-repair suspend time") suspended
220
  in
221
   case () of
222
     -- Note how we must return ArSuspended even if "enabled" is empty, so that
223
     -- node groups or instances can suspend repairs that were enabled at an
224
     -- upper scope (cluster or node group).
225
     _ | "" `elem` suspended -> Just $ ArSuspended Forever
226
       | not $ null futureTs -> Just . ArSuspended . Until . maximum $ futureTs
227
       | not $ null enabled  -> Just $ ArEnabled (minimum enabled)
228
       | otherwise           -> Nothing
229

    
230
-- | Compute the longest common suffix of a list of strings that
231
-- starts with a dot.
232
longestDomain :: [String] -> String
233
longestDomain [] = ""
234
longestDomain (x:xs) =
235
  foldr (\ suffix accu -> if all (isSuffixOf suffix) xs
236
                            then suffix
237
                            else accu)
238
          "" $ filter (isPrefixOf ".") (tails x)
239

    
240
-- | Extracts the exclusion tags from the cluster configuration.
241
extractExTags :: [String] -> [String]
242
extractExTags = filter (not . null) . mapMaybe (chompPrefix exTagsPrefix)
243

    
244
-- | Extracts the common suffix from node\/instance names.
245
commonSuffix :: Node.List -> Instance.List -> String
246
commonSuffix nl il =
247
  let node_names = map Node.name $ Container.elems nl
248
      inst_names = map Instance.name $ Container.elems il
249
  in longestDomain (node_names ++ inst_names)
250

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

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

    
319
-- | Compute the amount of memory used by primary instances on a node.
320
nodeImem :: Node.Node -> Instance.List -> Int
321
nodeImem node il =
322
  let rfind = flip Container.find il
323
      il' = map rfind $ Node.pList node
324
      oil' = filter Instance.notOffline il'
325
  in sum . map Instance.mem $ oil'
326

    
327

    
328
-- | Compute the amount of disk used by instances on a node (either primary
329
-- or secondary).
330
nodeIdsk :: Node.Node -> Instance.List -> Int
331
nodeIdsk node il =
332
  let rfind = flip Container.find il
333
  in sum . map (Instance.dsk . rfind)
334
       $ Node.pList node ++ Node.sList node