Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / IAlloc.hs @ 7dd14211

History | View | Annotate | Download (14.1 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 (exitWith, ExitCode(..))
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
-- | Type alias for the result of an IAllocator call.
54
type IAllocResult = (String, JSValue, Node.List, Instance.List)
55

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

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

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

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

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

    
199
          | otherwise -> fail ("Invalid request type '" ++ optype ++ "'")
200
  return (msgs, Request rqtype cdata)
201

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

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

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

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

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

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

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

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

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

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

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

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