Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / IAlloc.hs @ c3f8cb12

History | View | Annotate | Download (13.8 kB)

1
{-| Implementation of the iallocator interface.
2

    
3
-}
4

    
5
{-
6

    
7
Copyright (C) 2009, 2010, 2011, 2012 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)
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.JSON
50
import Ganeti.HTools.Types
51

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
326
-- | Reads the request from the data file(s).
327
readRequest :: FilePath -> IO Request
328
readRequest fp = do
329
  input_data <- readFile fp
330
  case parseData input_data of
331
    Bad err -> do
332
      hPutStrLn stderr $ "Error: " ++ err
333
      exitWith $ ExitFailure 1
334
    Ok (fix_msgs, rq) -> maybeShowWarnings fix_msgs >> return rq
335

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