Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / IAlloc.hs @ 3603605a

History | View | Annotate | Download (14 kB)

1
{-| Implementation of the iallocator interface.
2

    
3
-}
4

    
5
{-
6

    
7
Copyright (C) 2009, 2010, 2011 Google Inc.
8

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

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

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

    
24
-}
25

    
26
module Ganeti.HTools.IAlloc
27
  ( readRequest
28
  , runIAllocator
29
  , processRelocate
30
  ) where
31

    
32
import Data.Either ()
33
import Data.Maybe (fromMaybe, isJust)
34
import Data.List
35
import Control.Monad
36
import Text.JSON (JSObject, JSValue(JSArray),
37
                  makeObj, encodeStrict, decodeStrict, fromJSObject, showJSON)
38
import System.Exit
39
import System.IO
40

    
41
import qualified Ganeti.HTools.Cluster as Cluster
42
import qualified Ganeti.HTools.Container as Container
43
import qualified Ganeti.HTools.Group as Group
44
import qualified Ganeti.HTools.Node as Node
45
import qualified Ganeti.HTools.Instance as Instance
46
import qualified Ganeti.Constants as C
47
import Ganeti.HTools.CLI
48
import Ganeti.HTools.Loader
49
import Ganeti.HTools.ExtLoader (loadExternalData)
50
import Ganeti.HTools.Utils
51
import Ganeti.HTools.Types
52

    
53
{-# ANN module "HLint: ignore Eta reduce" #-}
54

    
55
-- | Type alias for the result of an IAllocator call.
56
type IAllocResult = (String, JSValue, Node.List, Instance.List)
57

    
58
-- | Parse the basic specifications of an instance.
59
--
60
-- Instances in the cluster instance list and the instance in an
61
-- 'Allocate' request share some common properties, which are read by
62
-- this function.
63
parseBaseInstance :: String
64
                  -> JSRecord
65
                  -> Result (String, Instance.Instance)
66
parseBaseInstance n a = do
67
  let extract x = tryFromObj ("invalid data for instance '" ++ n ++ "'") a x
68
  disk  <- extract "disk_space_total"
69
  mem   <- extract "memory"
70
  vcpus <- extract "vcpus"
71
  tags  <- extract "tags"
72
  dt    <- extract "disk_template"
73
  return (n, Instance.create n mem disk vcpus Running tags True 0 0 dt)
74

    
75
-- | Parses an instance as found in the cluster instance list.
76
parseInstance :: NameAssoc -- ^ The node name-to-index association list
77
              -> String    -- ^ The name of the instance
78
              -> JSRecord  -- ^ The JSON object
79
              -> Result (String, Instance.Instance)
80
parseInstance ktn n a = do
81
  base <- parseBaseInstance n a
82
  nodes <- fromObj a "nodes"
83
  pnode <- if null nodes
84
           then Bad $ "empty node list for instance " ++ n
85
           else readEitherString $ head nodes
86
  pidx <- lookupNode ktn n pnode
87
  let snodes = tail nodes
88
  sidx <- if null snodes
89
            then return Node.noSecondary
90
            else readEitherString (head snodes) >>= lookupNode ktn n
91
  return (n, Instance.setBoth (snd base) pidx sidx)
92

    
93
-- | Parses a node as found in the cluster node list.
94
parseNode :: NameAssoc   -- ^ The group association
95
          -> String      -- ^ The node's name
96
          -> JSRecord    -- ^ The JSON object
97
          -> Result (String, Node.Node)
98
parseNode ktg n a = do
99
  let desc = "invalid data for node '" ++ n ++ "'"
100
      extract x = tryFromObj desc a x
101
  offline <- extract "offline"
102
  drained <- extract "drained"
103
  guuid   <- extract "group"
104
  vm_capable  <- annotateResult desc $ maybeFromObj a "vm_capable"
105
  let vm_capable' = fromMaybe True vm_capable
106
  gidx <- lookupGroup ktg n guuid
107
  node <- if offline || drained || not vm_capable'
108
            then return $ Node.create n 0 0 0 0 0 0 True gidx
109
            else do
110
              mtotal <- extract "total_memory"
111
              mnode  <- extract "reserved_memory"
112
              mfree  <- extract "free_memory"
113
              dtotal <- extract "total_disk"
114
              dfree  <- extract "free_disk"
115
              ctotal <- extract "total_cpus"
116
              return $ Node.create n mtotal mnode mfree
117
                     dtotal dfree ctotal False gidx
118
  return (n, node)
119

    
120
-- | Parses a group as found in the cluster group list.
121
parseGroup :: String     -- ^ The group UUID
122
           -> JSRecord   -- ^ The JSON object
123
           -> Result (String, Group.Group)
124
parseGroup u a = do
125
  let extract x = tryFromObj ("invalid data for group '" ++ u ++ "'") a x
126
  name <- extract "name"
127
  apol <- extract "alloc_policy"
128
  return (u, Group.create name u apol)
129

    
130
-- | Top-level parser.
131
--
132
-- The result is a tuple of eventual warning messages and the parsed
133
-- request; if parsing the input data fails, we'll return a 'Bad'
134
-- value.
135
parseData :: String -- ^ The JSON message as received from Ganeti
136
          -> Result ([String], Request) -- ^ Result tuple
137
parseData body = do
138
  decoded <- fromJResult "Parsing input IAllocator message" (decodeStrict body)
139
  let obj = fromJSObject decoded
140
      extrObj x = tryFromObj "invalid iallocator message" obj x
141
  -- request parser
142
  request <- liftM fromJSObject (extrObj "request")
143
  let extrReq x = tryFromObj "invalid request dict" request x
144
  -- existing group parsing
145
  glist <- liftM fromJSObject (extrObj "nodegroups")
146
  gobj <- mapM (\(x, y) -> asJSObject y >>= parseGroup x . fromJSObject) glist
147
  let (ktg, gl) = assignIndices gobj
148
  -- existing node parsing
149
  nlist <- liftM fromJSObject (extrObj "nodes")
150
  nobj <- mapM (\(x,y) ->
151
                    asJSObject y >>= parseNode ktg x . fromJSObject) nlist
152
  let (ktn, nl) = assignIndices nobj
153
  -- existing instance parsing
154
  ilist <- extrObj "instances"
155
  let idata = fromJSObject ilist
156
  iobj <- mapM (\(x,y) ->
157
                    asJSObject y >>= parseInstance ktn x . fromJSObject) idata
158
  let (kti, il) = assignIndices iobj
159
  -- cluster tags
160
  ctags <- extrObj "cluster_tags"
161
  cdata1 <- mergeData [] [] [] [] (ClusterData gl nl il ctags)
162
  let (msgs, fix_nl) = checkData (cdNodes cdata1) (cdInstances cdata1)
163
      cdata = cdata1 { cdNodes = fix_nl }
164
      map_n = cdNodes cdata
165
      map_i = cdInstances cdata
166
      map_g = cdGroups cdata
167
  optype <- extrReq "type"
168
  rqtype <-
169
    case () of
170
      _ | optype == C.iallocatorModeAlloc ->
171
            do
172
              rname     <- extrReq "name"
173
              req_nodes <- extrReq "required_nodes"
174
              inew      <- parseBaseInstance rname request
175
              let io = snd inew
176
              return $ Allocate io req_nodes
177
        | optype == C.iallocatorModeReloc ->
178
            do
179
              rname     <- extrReq "name"
180
              ridx      <- lookupInstance kti rname
181
              req_nodes <- extrReq "required_nodes"
182
              ex_nodes  <- extrReq "relocate_from"
183
              ex_idex   <- mapM (Container.findByName map_n) ex_nodes
184
              return $ Relocate ridx req_nodes (map Node.idx ex_idex)
185
        | optype == C.iallocatorModeChgGroup ->
186
            do
187
              rl_names <- extrReq "instances"
188
              rl_insts <- mapM (liftM Instance.idx .
189
                                Container.findByName map_i) rl_names
190
              gr_uuids <- extrReq "target_groups"
191
              gr_idxes <- mapM (liftM Group.idx .
192
                                Container.findByName map_g) gr_uuids
193
              return $ ChangeGroup rl_insts gr_idxes
194
        | optype == C.iallocatorModeNodeEvac ->
195
            do
196
              rl_names <- extrReq "instances"
197
              rl_insts <- mapM (Container.findByName map_i) rl_names
198
              let rl_idx = map Instance.idx rl_insts
199
              rl_mode <- extrReq "evac_mode"
200
              return $ NodeEvacuate rl_idx rl_mode
201

    
202
        | otherwise -> fail ("Invalid request type '" ++ optype ++ "'")
203
  return (msgs, Request rqtype cdata)
204

    
205
-- | Formats the result into a valid IAllocator response message.
206
formatResponse :: Bool     -- ^ Whether the request was successful
207
               -> String   -- ^ Information text
208
               -> JSValue  -- ^ The JSON encoded result
209
               -> String   -- ^ The full JSON-formatted message
210
formatResponse success info result =
211
  let e_success = ("success", showJSON success)
212
      e_info = ("info", showJSON info)
213
      e_result = ("result", result)
214
  in encodeStrict $ makeObj [e_success, e_info, e_result]
215

    
216
-- | Flatten the log of a solution into a string.
217
describeSolution :: Cluster.AllocSolution -> String
218
describeSolution = intercalate ", " . Cluster.asLog
219

    
220
-- | Convert allocation/relocation results into the result format.
221
formatAllocate :: Instance.List -> Cluster.AllocSolution -> Result IAllocResult
222
formatAllocate il as = do
223
  let info = describeSolution as
224
  case Cluster.asSolution as of
225
    Nothing -> fail info
226
    Just (nl, inst, nodes, _) ->
227
      do
228
        let il' = Container.add (Instance.idx inst) inst il
229
        return (info, showJSON $ map Node.name nodes, nl, il')
230

    
231
-- | Convert a node-evacuation/change group result.
232
formatNodeEvac :: Group.List
233
               -> Node.List
234
               -> Instance.List
235
               -> (Node.List, Instance.List, Cluster.EvacSolution)
236
               -> Result IAllocResult
237
formatNodeEvac gl nl il (fin_nl, fin_il, es) =
238
  let iname = Instance.name . flip Container.find il
239
      nname = Node.name . flip Container.find nl
240
      gname = Group.name . flip Container.find gl
241
      fes = map (\(idx, msg) -> (iname idx, msg)) $ Cluster.esFailed es
242
      mes = map (\(idx, gdx, ndxs) -> (iname idx, gname gdx, map nname ndxs))
243
            $ Cluster.esMoved es
244
      failed = length fes
245
      moved  = length mes
246
      info = show failed ++ " instances failed to move and " ++ show moved ++
247
             " were moved successfully"
248
  in Ok (info, showJSON (mes, fes, Cluster.esOpCodes es), fin_nl, fin_il)
249

    
250
-- | Runs relocate for a single instance.
251
--
252
-- This is wrapper over the 'Cluster.tryNodeEvac' function that is run
253
-- with a single instance (ours), and further it checks that the
254
-- result it got (in the nodes field) is actually consistent, as
255
-- tryNodeEvac is designed to output primarily an opcode list, not a
256
-- node list.
257
processRelocate :: Group.List      -- ^ The group list
258
                -> Node.List       -- ^ The node list
259
                -> Instance.List   -- ^ The instance list
260
                -> Idx             -- ^ The index of the instance to move
261
                -> Int             -- ^ The number of nodes required
262
                -> [Ndx]           -- ^ Nodes which should not be used
263
                -> Result (Node.List, Instance.List, [Ndx]) -- ^ Solution list
264
processRelocate gl nl il idx 1 exndx = do
265
  let orig = Container.find idx il
266
      sorig = Instance.sNode orig
267
  when (exndx /= [sorig]) $
268
       -- FIXME: we can't use the excluded nodes here; the logic is
269
       -- already _but only partially_ implemented in tryNodeEvac...
270
       fail $ "Unsupported request: excluded nodes not equal to\
271
              \ instance's secondary node (" ++ show sorig ++ " versus " ++
272
              show exndx ++ ")"
273
  (nl', il', esol) <- Cluster.tryNodeEvac gl nl il ChangeSecondary [idx]
274
  nodes <- case lookup idx (Cluster.esFailed esol) of
275
             Just msg -> fail msg
276
             Nothing ->
277
                 case lookup idx (map (\(a, _, b) -> (a, b))
278
                                  (Cluster.esMoved esol)) of
279
                   Nothing ->
280
                       fail "Internal error: lost instance idx during move"
281
                   Just n -> return n
282
  let inst = Container.find idx il'
283
      pnode = Instance.pNode inst
284
      snode = Instance.sNode inst
285
  when (snode == sorig) $
286
       fail "Internal error: instance didn't change secondary node?!"
287
  when (snode == pnode) $
288
       fail "Internal error: selected primary as new secondary?!"
289

    
290
  nodes' <- if nodes == [pnode, snode]
291
            then return [snode] -- only the new secondary is needed
292
            else fail $ "Internal error: inconsistent node list (" ++
293
                 show nodes ++ ") versus instance nodes (" ++ show pnode ++
294
                 "," ++ show snode ++ ")"
295
  return (nl', il', nodes')
296

    
297
processRelocate _ _ _ _ reqn _ =
298
  fail $ "Exchange " ++ show reqn ++ " nodes mode is not implemented"
299

    
300
formatRelocate :: (Node.List, Instance.List, [Ndx])
301
               -> Result IAllocResult
302
formatRelocate (nl, il, ndxs) =
303
  let nodes = map (`Container.find` nl) ndxs
304
      names = map Node.name nodes
305
  in Ok ("success", showJSON names, nl, il)
306

    
307
-- | Process a request and return new node lists.
308
processRequest :: Request -> Result IAllocResult
309
processRequest request =
310
  let Request rqtype (ClusterData gl nl il _) = request
311
  in case rqtype of
312
       Allocate xi reqn ->
313
         Cluster.tryMGAlloc gl nl il xi reqn >>= formatAllocate il
314
       Relocate idx reqn exnodes ->
315
         processRelocate gl nl il idx reqn exnodes >>= formatRelocate
316
       ChangeGroup gdxs idxs ->
317
         Cluster.tryChangeGroup gl nl il idxs gdxs >>=
318
                formatNodeEvac gl nl il
319
       NodeEvacuate xi mode ->
320
         Cluster.tryNodeEvac gl nl il mode xi >>=
321
                formatNodeEvac gl nl il
322

    
323
-- | Reads the request from the data file(s).
324
readRequest :: Options -> [String] -> IO Request
325
readRequest opts args = do
326
  when (null args) $ do
327
    hPutStrLn stderr "Error: this program needs an input file."
328
    exitWith $ ExitFailure 1
329

    
330
  input_data <- readFile (head args)
331
  r1 <- case parseData input_data of
332
          Bad err -> do
333
            hPutStrLn stderr $ "Error: " ++ err
334
            exitWith $ ExitFailure 1
335
          Ok (fix_msgs, rq) -> maybeShowWarnings fix_msgs >> return rq
336
  if isJust (optDataFile opts) ||  (not . null . optNodeSim) opts
337
    then do
338
      cdata <- loadExternalData opts
339
      let Request rqt _ = r1
340
      return $ Request rqt cdata
341
    else return r1
342

    
343
-- | Main iallocator pipeline.
344
runIAllocator :: Request -> (Maybe (Node.List, Instance.List), String)
345
runIAllocator request =
346
  let (ok, info, result, cdata) =
347
        case processRequest request of
348
          Ok (msg, r, nl, il) -> (True, "Request successful: " ++ msg, r,
349
                                  Just (nl, il))
350
          Bad msg -> (False, "Request failed: " ++ msg, JSArray [], Nothing)
351
      rstring = formatResponse ok info result
352
  in (cdata, rstring)