Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (11.9 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
    ) where
30

    
31
import Data.Either ()
32
import Data.Maybe (fromMaybe, isJust)
33
import Data.List
34
import Control.Monad
35
import Text.JSON (JSObject, JSValue(JSBool, JSString, JSArray),
36
                  makeObj, encodeStrict, decodeStrict,
37
                  fromJSObject, toJSString)
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
-- | Parse the basic specifications of an instance.
54
--
55
-- Instances in the cluster instance list and the instance in an
56
-- 'Allocate' request share some common properties, which are read by
57
-- this function.
58
parseBaseInstance :: String
59
                  -> JSRecord
60
                  -> Result (String, Instance.Instance)
61
parseBaseInstance n a = do
62
  let extract x = tryFromObj ("invalid data for instance '" ++ n ++ "'") a x
63
  disk  <- extract "disk_space_total"
64
  mem   <- extract "memory"
65
  vcpus <- extract "vcpus"
66
  tags  <- extract "tags"
67
  let running = "running"
68
  return (n, Instance.create n mem disk vcpus running tags True 0 0)
69

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

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

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

    
124
parseTargetGroups :: JSRecord      -- ^ The JSON object (request dict)
125
                  -> Group.List    -- ^ The existing groups
126
                  -> Result [Gdx]
127
parseTargetGroups req map_g = do
128
  group_uuids <- fromObjWithDefault req "target_groups" []
129
  mapM (liftM Group.idx . Container.findByName map_g) group_uuids
130

    
131
-- | Top-level parser.
132
parseData :: String         -- ^ The JSON message as received from Ganeti
133
          -> Result Request -- ^ A (possible valid) request
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
  cdata <- mergeData [] [] [] [] (ClusterData gl nl il ctags)
159
  let map_n = cdNodes cdata
160
      map_i = cdInstances cdata
161
      map_g = cdGroups cdata
162
  optype <- extrReq "type"
163
  rqtype <-
164
      case () of
165
        _ | optype == C.iallocatorModeAlloc ->
166
              do
167
                rname     <- extrReq "name"
168
                req_nodes <- extrReq "required_nodes"
169
                inew      <- parseBaseInstance rname request
170
                let io = snd inew
171
                return $ Allocate io req_nodes
172
          | optype == C.iallocatorModeReloc ->
173
              do
174
                rname     <- extrReq "name"
175
                ridx      <- lookupInstance kti rname
176
                req_nodes <- extrReq "required_nodes"
177
                ex_nodes  <- extrReq "relocate_from"
178
                ex_idex   <- mapM (Container.findByName map_n) ex_nodes
179
                return $ Relocate ridx req_nodes (map Node.idx ex_idex)
180
          | optype == C.iallocatorModeMevac ->
181
              do
182
                ex_names <- extrReq "evac_nodes"
183
                ex_nodes <- mapM (Container.findByName map_n) ex_names
184
                let ex_ndx = map Node.idx ex_nodes
185
                return $ Evacuate ex_ndx
186
          | optype == C.iallocatorModeMreloc ->
187
              do
188
                rl_names <- extrReq "instances"
189
                rl_insts <- mapM (Container.findByName map_i) rl_names
190
                let rl_idx = map Instance.idx rl_insts
191
                rl_mode <-
192
                   case extrReq "reloc_mode" of
193
                     Ok s | s == C.iallocatorMrelocKeep -> return KeepGroup
194
                          | s == C.iallocatorMrelocChange ->
195
                              do
196
                                tg_groups <- parseTargetGroups request map_g
197
                                return $ ChangeGroup tg_groups
198
                          | s == C.iallocatorMrelocAny -> return AnyGroup
199
                          | otherwise -> Bad $ "Invalid relocate mode " ++ s
200
                     Bad x -> Bad x
201
                return $ MultiReloc rl_idx rl_mode
202
          | optype == C.iallocatorModeNodeEvac ->
203
              do
204
                rl_names <- extrReq "instances"
205
                rl_insts <- mapM (Container.findByName map_i) rl_names
206
                let rl_idx = map Instance.idx rl_insts
207
                rl_mode <-
208
                   case extrReq "evac_mode" of
209
                     Ok s | s == C.iallocatorNevacAll -> return ChangeAll
210
                          | s == C.iallocatorNevacPri -> return ChangePrimary
211
                          | s == C.iallocatorNevacSec -> return ChangeSecondary
212
                          | otherwise -> Bad $ "Invalid evacuate mode " ++ s
213
                     Bad x -> Bad x
214
                return $ NodeEvacuate rl_idx rl_mode
215

    
216
          | otherwise -> fail ("Invalid request type '" ++ optype ++ "'")
217
  return $ Request rqtype cdata
218

    
219
-- | Format the result
220
formatRVal :: RqType -> [Node.AllocElement] -> JSValue
221
formatRVal _ [] = JSArray []
222

    
223
formatRVal (Evacuate _) elems =
224
    let sols = map (\(_, inst, nl, _) -> Instance.name inst : map Node.name nl)
225
               elems
226
        jsols = map (JSArray . map (JSString . toJSString)) sols
227
    in JSArray jsols
228

    
229
formatRVal _ elems =
230
    let (_, _, nodes, _) = head elems
231
        nodes' = map Node.name nodes
232
    in JSArray $ map (JSString . toJSString) nodes'
233

    
234
-- | Formats the response into a valid IAllocator response message.
235
formatResponse :: Bool     -- ^ Whether the request was successful
236
               -> String   -- ^ Information text
237
               -> RqType   -- ^ Request type
238
               -> [Node.AllocElement] -- ^ The resulting allocations
239
               -> String   -- ^ The JSON-formatted message
240
formatResponse success info rq elems =
241
    let
242
        e_success = ("success", JSBool success)
243
        e_info = ("info", JSString . toJSString $ info)
244
        e_result = ("result", formatRVal rq elems)
245
    in encodeStrict $ makeObj [e_success, e_info, e_result]
246

    
247
processResults :: (Monad m) =>
248
                  RqType -> Cluster.AllocSolution
249
               -> m Cluster.AllocSolution
250
processResults _ (Cluster.AllocSolution { Cluster.asSolutions = [],
251
                                          Cluster.asLog = msgs }) =
252
  fail $ intercalate ", " msgs
253

    
254
processResults (Evacuate _) as = return as
255

    
256
processResults _ as =
257
    case Cluster.asSolutions as of
258
      _:[] -> return as
259
      _ -> fail "Internal error: multiple allocation solutions"
260

    
261
-- | Process a request and return new node lists
262
processRequest :: Request
263
               -> Result Cluster.AllocSolution
264
processRequest request =
265
  let Request rqtype (ClusterData gl nl il _) = request
266
  in case rqtype of
267
       Allocate xi reqn -> Cluster.tryMGAlloc gl nl il xi reqn
268
       Relocate idx reqn exnodes -> Cluster.tryMGReloc gl nl il
269
                                    idx reqn exnodes
270
       Evacuate exnodes -> Cluster.tryMGEvac gl nl il exnodes
271
       MultiReloc _ _ -> fail "multi-reloc not handled"
272
       NodeEvacuate _ _ -> fail "node-evacuate not handled"
273

    
274
-- | Reads the request from the data file(s)
275
readRequest :: Options -> [String] -> IO Request
276
readRequest opts args = do
277
  when (null args) $ do
278
         hPutStrLn stderr "Error: this program needs an input file."
279
         exitWith $ ExitFailure 1
280

    
281
  input_data <- readFile (head args)
282
  r1 <- case parseData input_data of
283
          Bad err -> do
284
            hPutStrLn stderr $ "Error: " ++ err
285
            exitWith $ ExitFailure 1
286
          Ok rq -> return rq
287
  (if isJust (optDataFile opts) ||  (not . null . optNodeSim) opts
288
   then do
289
     cdata <- loadExternalData opts
290
     let Request rqt _ = r1
291
     return $ Request rqt cdata
292
   else return r1)
293

    
294
-- | Main iallocator pipeline.
295
runIAllocator :: Request -> String
296
runIAllocator request =
297
  let Request rq _ = request
298
      sols = processRequest request >>= processResults rq
299
      (ok, info, rn) =
300
          case sols of
301
            Ok as -> (True, "Request successful: " ++
302
                            intercalate ", " (Cluster.asLog as),
303
                      Cluster.asSolutions as)
304
            Bad s -> (False, "Request failed: " ++ s, [])
305
      resp = formatResponse ok info rq rn
306
  in resp