Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Backend / IAlloc.hs @ c324da14

History | View | Annotate | Download (17.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.HTools.Nic as Nic
48
import qualified Ganeti.Constants as C
49
import Ganeti.HTools.CLI
50
import Ganeti.HTools.Loader
51
import Ganeti.HTools.Types
52
import Ganeti.JSON
53
import Ganeti.Utils
54

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

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

    
60
-- | Parse a NIC within an instance (in a creation request)
61
parseNic :: String -> JSRecord -> Result Nic.Nic
62
parseNic n a = do
63
  mac     <- maybeFromObj a "mac"
64
  ip      <- maybeFromObj a "ip"
65
  mode    <- maybeFromObj a "mode" >>= \m -> case m of
66
               Just "bridged" -> Ok $ Just Nic.Bridged
67
               Just "routed" -> Ok $ Just Nic.Routed
68
               Just "openvswitch" -> Ok $ Just Nic.OpenVSwitch
69
               Nothing -> Ok Nothing
70
               _ -> Bad $ "invalid NIC mode in instance " ++ n
71
  link    <- maybeFromObj a "link"
72
  bridge  <- maybeFromObj a "bridge"
73
  network <- maybeFromObj a "network"
74
  return (Nic.create mac ip mode link bridge network)
75

    
76
-- | Parse the basic specifications of an instance.
77
--
78
-- Instances in the cluster instance list and the instance in an
79
-- 'Allocate' request share some common properties, which are read by
80
-- this function.
81
parseBaseInstance :: String
82
                  -> JSRecord
83
                  -> Result (String, Instance.Instance)
84
parseBaseInstance n a = do
85
  let errorMessage = "invalid data for instance '" ++ n ++ "'"
86
  let extract x = tryFromObj errorMessage a x
87
  disk  <- extract "disk_space_total"
88
  disks <- extract "disks" >>= toArray >>= asObjectList >>=
89
           mapM (flip (tryFromObj errorMessage) "size" . fromJSObject)
90
  mem   <- extract "memory"
91
  vcpus <- extract "vcpus"
92
  tags  <- extract "tags"
93
  dt    <- extract "disk_template"
94
  su    <- extract "spindle_use"
95
  nics  <- extract "nics" >>= toArray >>= asObjectList >>=
96
           mapM (parseNic n . fromJSObject)
97
  return
98
    (n,
99
     Instance.create n mem disk disks vcpus Running tags True 0 0 dt su nics)
100

    
101
-- | Parses an instance as found in the cluster instance list.
102
parseInstance :: NameAssoc -- ^ The node name-to-index association list
103
              -> String    -- ^ The name of the instance
104
              -> JSRecord  -- ^ The JSON object
105
              -> Result (String, Instance.Instance)
106
parseInstance ktn n a = do
107
  base <- parseBaseInstance n a
108
  nodes <- fromObj a "nodes"
109
  (pnode, snodes) <-
110
    case nodes of
111
      [] -> Bad $ "empty node list for instance " ++ n
112
      x:xs -> readEitherString x >>= \x' -> return (x', xs)
113
  pidx <- lookupNode ktn n pnode
114
  sidx <- case snodes of
115
            [] -> return Node.noSecondary
116
            x:_ -> readEitherString x >>= lookupNode ktn n
117
  return (n, Instance.setBoth (snd base) pidx sidx)
118

    
119
-- | Parses a node as found in the cluster node list.
120
parseNode :: NameAssoc   -- ^ The group association
121
          -> String      -- ^ The node's name
122
          -> JSRecord    -- ^ The JSON object
123
          -> Result (String, Node.Node)
124
parseNode ktg n a = do
125
  let desc = "invalid data for node '" ++ n ++ "'"
126
      extract x = tryFromObj desc a x
127
  offline <- extract "offline"
128
  drained <- extract "drained"
129
  guuid   <- extract "group"
130
  vm_capable  <- annotateResult desc $ maybeFromObj a "vm_capable"
131
  let vm_capable' = fromMaybe True vm_capable
132
  gidx <- lookupGroup ktg n guuid
133
  node <- if offline || drained || not vm_capable'
134
            then return $ Node.create n 0 0 0 0 0 0 True 0 gidx False
135
            else do
136
              mtotal <- extract "total_memory"
137
              mnode  <- extract "reserved_memory"
138
              mfree  <- extract "free_memory"
139
              dtotal <- extract "total_disk"
140
              dfree  <- extract "free_disk"
141
              ctotal <- extract "total_cpus"
142
              ndparams <- extract "ndparams" >>= asJSObject
143
              spindles <- tryFromObj desc (fromJSObject ndparams)
144
                          "spindle_count"
145
              excl_stor <- tryFromObj desc (fromJSObject ndparams)
146
                           "exclusive_storage"
147
              return $ Node.create n mtotal mnode mfree
148
                     dtotal dfree ctotal False spindles gidx excl_stor
149
  return (n, node)
150

    
151
-- | Parses a group as found in the cluster group list.
152
parseGroup :: String     -- ^ The group UUID
153
           -> JSRecord   -- ^ The JSON object
154
           -> Result (String, Group.Group)
155
parseGroup u a = do
156
  let extract x = tryFromObj ("invalid data for group '" ++ u ++ "'") a x
157
  name <- extract "name"
158
  apol <- extract "alloc_policy"
159
  nets <- extract "networks"
160
  ipol <- extract "ipolicy"
161
  tags <- extract "tags"
162
  return (u, Group.create name u apol nets ipol tags)
163

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

    
252
-- | Formats the result into a valid IAllocator response message.
253
formatResponse :: Bool     -- ^ Whether the request was successful
254
               -> String   -- ^ Information text
255
               -> JSValue  -- ^ The JSON encoded result
256
               -> String   -- ^ The full JSON-formatted message
257
formatResponse success info result =
258
  let e_success = ("success", showJSON success)
259
      e_info = ("info", showJSON info)
260
      e_result = ("result", result)
261
  in encodeStrict $ makeObj [e_success, e_info, e_result]
262

    
263
-- | Flatten the log of a solution into a string.
264
describeSolution :: Cluster.AllocSolution -> String
265
describeSolution = intercalate ", " . Cluster.asLog
266

    
267
-- | Convert allocation/relocation results into the result format.
268
formatAllocate :: Instance.List -> Cluster.AllocSolution -> Result IAllocResult
269
formatAllocate il as = do
270
  let info = describeSolution as
271
  case Cluster.asSolution as of
272
    Nothing -> fail info
273
    Just (nl, inst, nodes, _) ->
274
      do
275
        let il' = Container.add (Instance.idx inst) inst il
276
        return (info, showJSON $ map Node.name nodes, nl, il')
277

    
278
-- | Convert multi allocation results into the result format.
279
formatMultiAlloc :: (Node.List, Instance.List, Cluster.AllocSolutionList)
280
                 -> Result IAllocResult
281
formatMultiAlloc (fin_nl, fin_il, ars) =
282
  let rars = reverse ars
283
      (allocated, failed) = partition (isJust . Cluster.asSolution . snd) rars
284
      aars = map (\(_, ar) ->
285
                     let (_, inst, nodes, _) = fromJust $ Cluster.asSolution ar
286
                         iname = Instance.name inst
287
                         nnames = map Node.name nodes
288
                     in (iname, nnames)) allocated
289
      fars = map (\(inst, ar) ->
290
                     let iname = Instance.name inst
291
                     in (iname, describeSolution ar)) failed
292
      info = show (length failed) ++ " instances failed to allocate and " ++
293
             show (length allocated) ++ " were allocated successfully"
294
  in return (info, showJSON (aars, fars), fin_nl, fin_il)
295

    
296
-- | Convert a node-evacuation/change group result.
297
formatNodeEvac :: Group.List
298
               -> Node.List
299
               -> Instance.List
300
               -> (Node.List, Instance.List, Cluster.EvacSolution)
301
               -> Result IAllocResult
302
formatNodeEvac gl nl il (fin_nl, fin_il, es) =
303
  let iname = Instance.name . flip Container.find il
304
      nname = Node.name . flip Container.find nl
305
      gname = Group.name . flip Container.find gl
306
      fes = map (\(idx, msg) -> (iname idx, msg)) $ Cluster.esFailed es
307
      mes = map (\(idx, gdx, ndxs) -> (iname idx, gname gdx, map nname ndxs))
308
            $ Cluster.esMoved es
309
      failed = length fes
310
      moved  = length mes
311
      info = show failed ++ " instances failed to move and " ++ show moved ++
312
             " were moved successfully"
313
  in Ok (info, showJSON (mes, fes, Cluster.esOpCodes es), fin_nl, fin_il)
314

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

    
381
processRelocate _ _ _ _ reqn _ =
382
  fail $ "Exchange " ++ show reqn ++ " nodes mode is not implemented"
383

    
384
formatRelocate :: (Node.List, Instance.List, [Ndx])
385
               -> Result IAllocResult
386
formatRelocate (nl, il, ndxs) =
387
  let nodes = map (`Container.find` nl) ndxs
388
      names = map Node.name nodes
389
  in Ok ("success", showJSON names, nl, il)
390

    
391
-- | Process a request and return new node lists.
392
processRequest :: Request -> Result IAllocResult
393
processRequest request =
394
  let Request rqtype (ClusterData gl nl il _ _) = request
395
  in case rqtype of
396
       Allocate xi reqn ->
397
         Cluster.tryMGAlloc gl nl il xi reqn >>= formatAllocate il
398
       Relocate idx reqn exnodes ->
399
         processRelocate gl nl il idx reqn exnodes >>= formatRelocate
400
       ChangeGroup gdxs idxs ->
401
         Cluster.tryChangeGroup gl nl il idxs gdxs >>=
402
                formatNodeEvac gl nl il
403
       NodeEvacuate xi mode ->
404
         Cluster.tryNodeEvac gl nl il mode xi >>=
405
                formatNodeEvac gl nl il
406
       MultiAllocate xies ->
407
         Cluster.allocList gl nl il xies [] >>= formatMultiAlloc
408

    
409
-- | Reads the request from the data file(s).
410
readRequest :: FilePath -> IO Request
411
readRequest fp = do
412
  now <- getClockTime
413
  input_data <- case fp of
414
                  "-" -> getContents
415
                  _   -> readFile fp
416
  case parseData now input_data of
417
    Bad err -> exitErr err
418
    Ok (fix_msgs, rq) -> maybeShowWarnings fix_msgs >> return rq
419

    
420
-- | Main iallocator pipeline.
421
runIAllocator :: Request -> (Maybe (Node.List, Instance.List), String)
422
runIAllocator request =
423
  let (ok, info, result, cdata) =
424
        case processRequest request of
425
          Ok (msg, r, nl, il) -> (True, "Request successful: " ++ msg, r,
426
                                  Just (nl, il))
427
          Bad msg -> (False, "Request failed: " ++ msg, JSArray [], Nothing)
428
      rstring = formatResponse ok info result
429
  in (cdata, rstring)
430

    
431
-- | Load the data from an iallocation request file
432
loadData :: FilePath -- ^ The path to the file
433
         -> IO (Result ClusterData)
434
loadData fp = do
435
  Request _ cdata <- readRequest fp
436
  return $ Ok cdata