Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / IAlloc.hs @ 8b5a517a

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.JSON
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
  ipol <- extract "ipolicy"
129
  return (u, Group.create name u apol ipol)
130

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

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

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

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

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

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

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

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

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

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

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

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

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

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