Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Backend / IAlloc.hs @ 241cea1e

History | View | Annotate | Download (16.9 kB)

1
{-| Implementation of the iallocator interface.
2

    
3
-}
4

    
5
{-
6

    
7
Copyright (C) 2009, 2010, 2011, 2012, 2013 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.Backend.IAlloc
27
  ( readRequest
28
  , runIAllocator
29
  , processRelocate
30
  , loadData
31
  ) where
32

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

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

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

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

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

    
80
-- | Parses an instance as found in the cluster instance list.
81
parseInstance :: NameAssoc -- ^ The node name-to-index association list
82
              -> String    -- ^ The name of the instance
83
              -> JSRecord  -- ^ The JSON object
84
              -> Result (String, Instance.Instance)
85
parseInstance ktn n a = do
86
  base <- parseBaseInstance n a
87
  nodes <- fromObj a "nodes"
88
  (pnode, snodes) <-
89
    case nodes of
90
      [] -> Bad $ "empty node list for instance " ++ n
91
      x:xs -> readEitherString x >>= \x' -> return (x', xs)
92
  pidx <- lookupNode ktn n pnode
93
  sidx <- case snodes of
94
            [] -> return Node.noSecondary
95
            x:_ -> readEitherString x >>= lookupNode ktn n
96
  return (n, Instance.setBoth (snd base) pidx sidx)
97

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

    
128
-- | Parses a group as found in the cluster group list.
129
parseGroup :: String     -- ^ The group UUID
130
           -> JSRecord   -- ^ The JSON object
131
           -> Result (String, Group.Group)
132
parseGroup u a = do
133
  let extract x = tryFromObj ("invalid data for group '" ++ u ++ "'") a x
134
  name <- extract "name"
135
  apol <- extract "alloc_policy"
136
  ipol <- extract "ipolicy"
137
  tags <- extract "tags"
138
  return (u, Group.create name u apol ipol tags)
139

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

    
228
-- | Formats the result into a valid IAllocator response message.
229
formatResponse :: Bool     -- ^ Whether the request was successful
230
               -> String   -- ^ Information text
231
               -> JSValue  -- ^ The JSON encoded result
232
               -> String   -- ^ The full JSON-formatted message
233
formatResponse success info result =
234
  let e_success = ("success", showJSON success)
235
      e_info = ("info", showJSON info)
236
      e_result = ("result", result)
237
  in encodeStrict $ makeObj [e_success, e_info, e_result]
238

    
239
-- | Flatten the log of a solution into a string.
240
describeSolution :: Cluster.AllocSolution -> String
241
describeSolution = intercalate ", " . Cluster.asLog
242

    
243
-- | Convert allocation/relocation results into the result format.
244
formatAllocate :: Instance.List -> Cluster.AllocSolution -> Result IAllocResult
245
formatAllocate il as = do
246
  let info = describeSolution as
247
  case Cluster.asSolution as of
248
    Nothing -> fail info
249
    Just (nl, inst, nodes, _) ->
250
      do
251
        let il' = Container.add (Instance.idx inst) inst il
252
        return (info, showJSON $ map Node.name nodes, nl, il')
253

    
254
-- | Convert multi allocation results into the result format.
255
formatMultiAlloc :: (Node.List, Instance.List, Cluster.AllocSolutionList)
256
                 -> Result IAllocResult
257
formatMultiAlloc (fin_nl, fin_il, ars) =
258
  let rars = reverse ars
259
      (allocated, failed) = partition (isJust . Cluster.asSolution . snd) rars
260
      aars = map (\(_, ar) ->
261
                     let (_, inst, nodes, _) = fromJust $ Cluster.asSolution ar
262
                         iname = Instance.name inst
263
                         nnames = map Node.name nodes
264
                     in (iname, nnames)) allocated
265
      fars = map (\(inst, ar) ->
266
                     let iname = Instance.name inst
267
                     in (iname, describeSolution ar)) failed
268
      info = show (length failed) ++ " instances failed to allocate and " ++
269
             show (length allocated) ++ " were allocated successfully"
270
  in return (info, showJSON (aars, fars), fin_nl, fin_il)
271

    
272
-- | Convert a node-evacuation/change group result.
273
formatNodeEvac :: Group.List
274
               -> Node.List
275
               -> Instance.List
276
               -> (Node.List, Instance.List, Cluster.EvacSolution)
277
               -> Result IAllocResult
278
formatNodeEvac gl nl il (fin_nl, fin_il, es) =
279
  let iname = Instance.name . flip Container.find il
280
      nname = Node.name . flip Container.find nl
281
      gname = Group.name . flip Container.find gl
282
      fes = map (\(idx, msg) -> (iname idx, msg)) $ Cluster.esFailed es
283
      mes = map (\(idx, gdx, ndxs) -> (iname idx, gname gdx, map nname ndxs))
284
            $ Cluster.esMoved es
285
      failed = length fes
286
      moved  = length mes
287
      info = show failed ++ " instances failed to move and " ++ show moved ++
288
             " were moved successfully"
289
  in Ok (info, showJSON (mes, fes, Cluster.esOpCodes es), fin_nl, fin_il)
290

    
291
-- | Runs relocate for a single instance.
292
--
293
-- This is wrapper over the 'Cluster.tryNodeEvac' function that is run
294
-- with a single instance (ours), and further it checks that the
295
-- result it got (in the nodes field) is actually consistent, as
296
-- tryNodeEvac is designed to output primarily an opcode list, not a
297
-- node list.
298
processRelocate :: Group.List      -- ^ The group list
299
                -> Node.List       -- ^ The node list
300
                -> Instance.List   -- ^ The instance list
301
                -> Idx             -- ^ The index of the instance to move
302
                -> Int             -- ^ The number of nodes required
303
                -> [Ndx]           -- ^ Nodes which should not be used
304
                -> Result (Node.List, Instance.List, [Ndx]) -- ^ Solution list
305
processRelocate gl nl il idx 1 exndx = do
306
  let orig = Container.find idx il
307
      sorig = Instance.sNode orig
308
      porig = Instance.pNode orig
309
      mir_type = Instance.mirrorType orig
310
  (exp_node, node_type, reloc_type) <-
311
    case mir_type of
312
      MirrorNone -> fail "Can't relocate non-mirrored instances"
313
      MirrorInternal -> return (sorig, "secondary", ChangeSecondary)
314
      MirrorExternal -> return (porig, "primary", ChangePrimary)
315
  when (exndx /= [exp_node]) .
316
       -- FIXME: we can't use the excluded nodes here; the logic is
317
       -- already _but only partially_ implemented in tryNodeEvac...
318
       fail $ "Unsupported request: excluded nodes not equal to\
319
              \ instance's " ++  node_type ++ "(" ++ show exp_node
320
              ++ " versus " ++ show exndx ++ ")"
321
  (nl', il', esol) <- Cluster.tryNodeEvac gl nl il reloc_type [idx]
322
  nodes <- case lookup idx (Cluster.esFailed esol) of
323
             Just msg -> fail msg
324
             Nothing ->
325
                 case lookup idx (map (\(a, _, b) -> (a, b))
326
                                  (Cluster.esMoved esol)) of
327
                   Nothing ->
328
                       fail "Internal error: lost instance idx during move"
329
                   Just n -> return n
330
  let inst = Container.find idx il'
331
      pnode = Instance.pNode inst
332
      snode = Instance.sNode inst
333
  nodes' <-
334
    case mir_type of
335
      MirrorNone -> fail "Internal error: mirror type none after relocation?!"
336
      MirrorInternal ->
337
        do
338
          when (snode == sorig) $
339
               fail "Internal error: instance didn't change secondary node?!"
340
          when (snode == pnode) $
341
               fail "Internal error: selected primary as new secondary?!"
342
          if nodes == [pnode, snode]
343
            then return [snode] -- only the new secondary is needed
344
            else fail $ "Internal error: inconsistent node list (" ++
345
                 show nodes ++ ") versus instance nodes (" ++ show pnode ++
346
                 "," ++ show snode ++ ")"
347
      MirrorExternal ->
348
        do
349
          when (pnode == porig) $
350
               fail "Internal error: instance didn't change primary node?!"
351
          if nodes == [pnode]
352
            then return nodes
353
            else fail $ "Internal error: inconsistent node list (" ++
354
                 show nodes ++ ") versus instance node (" ++ show pnode ++ ")"
355
  return (nl', il', nodes')
356

    
357
processRelocate _ _ _ _ reqn _ =
358
  fail $ "Exchange " ++ show reqn ++ " nodes mode is not implemented"
359

    
360
formatRelocate :: (Node.List, Instance.List, [Ndx])
361
               -> Result IAllocResult
362
formatRelocate (nl, il, ndxs) =
363
  let nodes = map (`Container.find` nl) ndxs
364
      names = map Node.name nodes
365
  in Ok ("success", showJSON names, nl, il)
366

    
367
-- | Process a request and return new node lists.
368
processRequest :: Request -> Result IAllocResult
369
processRequest request =
370
  let Request rqtype (ClusterData gl nl il _ _) = request
371
  in case rqtype of
372
       Allocate xi reqn ->
373
         Cluster.tryMGAlloc gl nl il xi reqn >>= formatAllocate il
374
       Relocate idx reqn exnodes ->
375
         processRelocate gl nl il idx reqn exnodes >>= formatRelocate
376
       ChangeGroup gdxs idxs ->
377
         Cluster.tryChangeGroup gl nl il idxs gdxs >>=
378
                formatNodeEvac gl nl il
379
       NodeEvacuate xi mode ->
380
         Cluster.tryNodeEvac gl nl il mode xi >>=
381
                formatNodeEvac gl nl il
382
       MultiAllocate xies ->
383
         Cluster.allocList gl nl il xies [] >>= formatMultiAlloc
384

    
385
-- | Reads the request from the data file(s).
386
readRequest :: FilePath -> IO Request
387
readRequest fp = do
388
  now <- getClockTime
389
  input_data <- case fp of
390
                  "-" -> getContents
391
                  _   -> readFile fp
392
  case parseData now input_data of
393
    Bad err -> exitErr err
394
    Ok (fix_msgs, rq) -> maybeShowWarnings fix_msgs >> return rq
395

    
396
-- | Main iallocator pipeline.
397
runIAllocator :: Request -> (Maybe (Node.List, Instance.List), String)
398
runIAllocator request =
399
  let (ok, info, result, cdata) =
400
        case processRequest request of
401
          Ok (msg, r, nl, il) -> (True, "Request successful: " ++ msg, r,
402
                                  Just (nl, il))
403
          Bad msg -> (False, "Request failed: " ++ msg, JSArray [], Nothing)
404
      rstring = formatResponse ok info result
405
  in (cdata, rstring)
406

    
407
-- | Load the data from an iallocation request file
408
loadData :: FilePath -- ^ The path to the file
409
         -> IO (Result ClusterData)
410
loadData fp = do
411
  Request _ cdata <- readRequest fp
412
  return $ Ok cdata