Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (11.8 kB)

1 43643696 Iustin Pop
{-| Implementation of the iallocator interface.
2 43643696 Iustin Pop
3 43643696 Iustin Pop
-}
4 43643696 Iustin Pop
5 e2fa2baf Iustin Pop
{-
6 e2fa2baf Iustin Pop
7 e8230242 Iustin Pop
Copyright (C) 2009, 2010, 2011 Google Inc.
8 e2fa2baf Iustin Pop
9 e2fa2baf Iustin Pop
This program is free software; you can redistribute it and/or modify
10 e2fa2baf Iustin Pop
it under the terms of the GNU General Public License as published by
11 e2fa2baf Iustin Pop
the Free Software Foundation; either version 2 of the License, or
12 e2fa2baf Iustin Pop
(at your option) any later version.
13 e2fa2baf Iustin Pop
14 e2fa2baf Iustin Pop
This program is distributed in the hope that it will be useful, but
15 e2fa2baf Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
16 e2fa2baf Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17 e2fa2baf Iustin Pop
General Public License for more details.
18 e2fa2baf Iustin Pop
19 e2fa2baf Iustin Pop
You should have received a copy of the GNU General Public License
20 e2fa2baf Iustin Pop
along with this program; if not, write to the Free Software
21 e2fa2baf Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22 e2fa2baf Iustin Pop
02110-1301, USA.
23 e2fa2baf Iustin Pop
24 e2fa2baf Iustin Pop
-}
25 e2fa2baf Iustin Pop
26 43643696 Iustin Pop
module Ganeti.HTools.IAlloc
27 00152519 Iustin Pop
    ( readRequest
28 00152519 Iustin Pop
    , runIAllocator
29 43643696 Iustin Pop
    ) where
30 43643696 Iustin Pop
31 43643696 Iustin Pop
import Data.Either ()
32 00152519 Iustin Pop
import Data.Maybe (fromMaybe, isJust)
33 cabce2f4 Iustin Pop
import Data.List
34 43643696 Iustin Pop
import Control.Monad
35 34c5a24a Iustin Pop
import Text.JSON (JSObject, JSValue(JSArray),
36 34c5a24a Iustin Pop
                  makeObj, encodeStrict, decodeStrict, fromJSObject, showJSON)
37 cabce2f4 Iustin Pop
import System (exitWith, ExitCode(..))
38 cabce2f4 Iustin Pop
import System.IO
39 cabce2f4 Iustin Pop
40 cabce2f4 Iustin Pop
import qualified Ganeti.HTools.Cluster as Cluster
41 262a08a2 Iustin Pop
import qualified Ganeti.HTools.Container as Container
42 a679e9dc Iustin Pop
import qualified Ganeti.HTools.Group as Group
43 942403e6 Iustin Pop
import qualified Ganeti.HTools.Node as Node
44 942403e6 Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
45 df5227dc Iustin Pop
import qualified Ganeti.Constants as C
46 cabce2f4 Iustin Pop
import Ganeti.HTools.CLI
47 e4c5beaf Iustin Pop
import Ganeti.HTools.Loader
48 cabce2f4 Iustin Pop
import Ganeti.HTools.ExtLoader (loadExternalData)
49 e4c5beaf Iustin Pop
import Ganeti.HTools.Utils
50 e4c5beaf Iustin Pop
import Ganeti.HTools.Types
51 43643696 Iustin Pop
52 7c14b50a Iustin Pop
-- | Type alias for the result of an IAllocator call.
53 7c14b50a Iustin Pop
type IAllocResult = (String, JSValue)
54 7c14b50a Iustin Pop
55 9188aeef Iustin Pop
-- | Parse the basic specifications of an instance.
56 9188aeef Iustin Pop
--
57 9188aeef Iustin Pop
-- Instances in the cluster instance list and the instance in an
58 9188aeef Iustin Pop
-- 'Allocate' request share some common properties, which are read by
59 9188aeef Iustin Pop
-- this function.
60 e4c5beaf Iustin Pop
parseBaseInstance :: String
61 28f19313 Iustin Pop
                  -> JSRecord
62 e4c5beaf Iustin Pop
                  -> Result (String, Instance.Instance)
63 e4c5beaf Iustin Pop
parseBaseInstance n a = do
64 e8230242 Iustin Pop
  let extract x = tryFromObj ("invalid data for instance '" ++ n ++ "'") a x
65 e8230242 Iustin Pop
  disk  <- extract "disk_space_total"
66 e8230242 Iustin Pop
  mem   <- extract "memory"
67 e8230242 Iustin Pop
  vcpus <- extract "vcpus"
68 e8230242 Iustin Pop
  tags  <- extract "tags"
69 5a4a3b7f Iustin Pop
  dt    <- extract "disk_template"
70 e4c5beaf Iustin Pop
  let running = "running"
71 5a4a3b7f Iustin Pop
  return (n, Instance.create n mem disk vcpus running tags True 0 0 dt)
72 585d4420 Iustin Pop
73 525bfb36 Iustin Pop
-- | Parses an instance as found in the cluster instance list.
74 28f19313 Iustin Pop
parseInstance :: NameAssoc -- ^ The node name-to-index association list
75 28f19313 Iustin Pop
              -> String    -- ^ The name of the instance
76 28f19313 Iustin Pop
              -> JSRecord  -- ^ The JSON object
77 e4c5beaf Iustin Pop
              -> Result (String, Instance.Instance)
78 e4c5beaf Iustin Pop
parseInstance ktn n a = do
79 262f3e6c Iustin Pop
  base <- parseBaseInstance n a
80 e8230242 Iustin Pop
  nodes <- fromObj a "nodes"
81 e41f4ba0 Iustin Pop
  pnode <- if null nodes
82 e41f4ba0 Iustin Pop
           then Bad $ "empty node list for instance " ++ n
83 e41f4ba0 Iustin Pop
           else readEitherString $ head nodes
84 262f3e6c Iustin Pop
  pidx <- lookupNode ktn n pnode
85 262f3e6c Iustin Pop
  let snodes = tail nodes
86 262f3e6c Iustin Pop
  sidx <- (if null snodes then return Node.noSecondary
87 262f3e6c Iustin Pop
           else readEitherString (head snodes) >>= lookupNode ktn n)
88 262f3e6c Iustin Pop
  return (n, Instance.setBoth (snd base) pidx sidx)
89 585d4420 Iustin Pop
90 9188aeef Iustin Pop
-- | Parses a node as found in the cluster node list.
91 28f19313 Iustin Pop
parseNode :: NameAssoc   -- ^ The group association
92 28f19313 Iustin Pop
          -> String      -- ^ The node's name
93 28f19313 Iustin Pop
          -> JSRecord    -- ^ The JSON object
94 9188aeef Iustin Pop
          -> Result (String, Node.Node)
95 10ef6b4e Iustin Pop
parseNode ktg n a = do
96 3eeea90f Iustin Pop
  let desc = "invalid data for node '" ++ n ++ "'"
97 3eeea90f Iustin Pop
      extract x = tryFromObj desc a x
98 e8230242 Iustin Pop
  offline <- extract "offline"
99 e8230242 Iustin Pop
  drained <- extract "drained"
100 e8230242 Iustin Pop
  guuid   <- extract "group"
101 3eeea90f Iustin Pop
  vm_capable  <- annotateResult desc $ maybeFromObj a "vm_capable"
102 3eeea90f Iustin Pop
  let vm_capable' = fromMaybe True vm_capable
103 10ef6b4e Iustin Pop
  gidx <- lookupGroup ktg n guuid
104 3eeea90f Iustin Pop
  node <- (if offline || drained || not vm_capable'
105 10ef6b4e Iustin Pop
           then return $ Node.create n 0 0 0 0 0 0 True gidx
106 262f3e6c Iustin Pop
           else do
107 e8230242 Iustin Pop
             mtotal <- extract "total_memory"
108 e8230242 Iustin Pop
             mnode  <- extract "reserved_memory"
109 e8230242 Iustin Pop
             mfree  <- extract "free_memory"
110 e8230242 Iustin Pop
             dtotal <- extract "total_disk"
111 e8230242 Iustin Pop
             dfree  <- extract "free_disk"
112 e8230242 Iustin Pop
             ctotal <- extract "total_cpus"
113 262f3e6c Iustin Pop
             return $ Node.create n mtotal mnode mfree
114 10ef6b4e Iustin Pop
                    dtotal dfree ctotal False gidx)
115 262f3e6c Iustin Pop
  return (n, node)
116 144f190b Iustin Pop
117 a679e9dc Iustin Pop
-- | Parses a group as found in the cluster group list.
118 28f19313 Iustin Pop
parseGroup :: String     -- ^ The group UUID
119 28f19313 Iustin Pop
           -> JSRecord   -- ^ The JSON object
120 a679e9dc Iustin Pop
           -> Result (String, Group.Group)
121 a679e9dc Iustin Pop
parseGroup u a = do
122 1b2cb110 Iustin Pop
  let extract x = tryFromObj ("invalid data for group '" ++ u ++ "'") a x
123 1b2cb110 Iustin Pop
  name <- extract "name"
124 1b2cb110 Iustin Pop
  apol <- extract "alloc_policy"
125 1b2cb110 Iustin Pop
  return (u, Group.create name u apol)
126 a679e9dc Iustin Pop
127 28f19313 Iustin Pop
parseTargetGroups :: JSRecord      -- ^ The JSON object (request dict)
128 28f19313 Iustin Pop
                  -> Group.List    -- ^ The existing groups
129 695c1bab Iustin Pop
                  -> Result [Gdx]
130 695c1bab Iustin Pop
parseTargetGroups req map_g = do
131 695c1bab Iustin Pop
  group_uuids <- fromObjWithDefault req "target_groups" []
132 695c1bab Iustin Pop
  mapM (liftM Group.idx . Container.findByName map_g) group_uuids
133 695c1bab Iustin Pop
134 9188aeef Iustin Pop
-- | Top-level parser.
135 9188aeef Iustin Pop
parseData :: String         -- ^ The JSON message as received from Ganeti
136 9188aeef Iustin Pop
          -> Result Request -- ^ A (possible valid) request
137 e4c5beaf Iustin Pop
parseData body = do
138 c96d44df Iustin Pop
  decoded <- fromJResult "Parsing input IAllocator message" (decodeStrict body)
139 262f3e6c Iustin Pop
  let obj = fromJSObject decoded
140 e8230242 Iustin Pop
      extrObj x = tryFromObj "invalid iallocator message" obj x
141 e4c5beaf Iustin Pop
  -- request parser
142 e8230242 Iustin Pop
  request <- liftM fromJSObject (extrObj "request")
143 e8230242 Iustin Pop
  let extrReq x = tryFromObj "invalid request dict" request x
144 a679e9dc Iustin Pop
  -- existing group parsing
145 e8230242 Iustin Pop
  glist <- liftM fromJSObject (extrObj "nodegroups")
146 a679e9dc Iustin Pop
  gobj <- mapM (\(x, y) -> asJSObject y >>= parseGroup x . fromJSObject) glist
147 10ef6b4e Iustin Pop
  let (ktg, gl) = assignIndices gobj
148 e4c5beaf Iustin Pop
  -- existing node parsing
149 e8230242 Iustin Pop
  nlist <- liftM fromJSObject (extrObj "nodes")
150 10ef6b4e Iustin Pop
  nobj <- mapM (\(x,y) ->
151 10ef6b4e Iustin Pop
                    asJSObject y >>= parseNode ktg x . fromJSObject) nlist
152 497e30a1 Iustin Pop
  let (ktn, nl) = assignIndices nobj
153 e4c5beaf Iustin Pop
  -- existing instance parsing
154 e8230242 Iustin Pop
  ilist <- extrObj "instances"
155 e4c5beaf Iustin Pop
  let idata = fromJSObject ilist
156 262f3e6c Iustin Pop
  iobj <- mapM (\(x,y) ->
157 262f3e6c Iustin Pop
                    asJSObject y >>= parseInstance ktn x . fromJSObject) idata
158 497e30a1 Iustin Pop
  let (kti, il) = assignIndices iobj
159 669ea132 Iustin Pop
  -- cluster tags
160 e8230242 Iustin Pop
  ctags <- extrObj "cluster_tags"
161 2d1708e0 Guido Trotter
  cdata <- mergeData [] [] [] [] (ClusterData gl nl il ctags)
162 017a0c3d Iustin Pop
  let map_n = cdNodes cdata
163 695c1bab Iustin Pop
      map_i = cdInstances cdata
164 695c1bab Iustin Pop
      map_g = cdGroups cdata
165 e8230242 Iustin Pop
  optype <- extrReq "type"
166 e4c5beaf Iustin Pop
  rqtype <-
167 df5227dc Iustin Pop
      case () of
168 df5227dc Iustin Pop
        _ | optype == C.iallocatorModeAlloc ->
169 df5227dc Iustin Pop
              do
170 df5227dc Iustin Pop
                rname     <- extrReq "name"
171 df5227dc Iustin Pop
                req_nodes <- extrReq "required_nodes"
172 df5227dc Iustin Pop
                inew      <- parseBaseInstance rname request
173 df5227dc Iustin Pop
                let io = snd inew
174 df5227dc Iustin Pop
                return $ Allocate io req_nodes
175 df5227dc Iustin Pop
          | optype == C.iallocatorModeReloc ->
176 df5227dc Iustin Pop
              do
177 df5227dc Iustin Pop
                rname     <- extrReq "name"
178 df5227dc Iustin Pop
                ridx      <- lookupInstance kti rname
179 df5227dc Iustin Pop
                req_nodes <- extrReq "required_nodes"
180 df5227dc Iustin Pop
                ex_nodes  <- extrReq "relocate_from"
181 df5227dc Iustin Pop
                ex_idex   <- mapM (Container.findByName map_n) ex_nodes
182 df5227dc Iustin Pop
                return $ Relocate ridx req_nodes (map Node.idx ex_idex)
183 df5227dc Iustin Pop
          | optype == C.iallocatorModeMevac ->
184 df5227dc Iustin Pop
              do
185 df5227dc Iustin Pop
                ex_names <- extrReq "evac_nodes"
186 df5227dc Iustin Pop
                ex_nodes <- mapM (Container.findByName map_n) ex_names
187 df5227dc Iustin Pop
                let ex_ndx = map Node.idx ex_nodes
188 df5227dc Iustin Pop
                return $ Evacuate ex_ndx
189 695c1bab Iustin Pop
          | optype == C.iallocatorModeMreloc ->
190 695c1bab Iustin Pop
              do
191 695c1bab Iustin Pop
                rl_names <- extrReq "instances"
192 695c1bab Iustin Pop
                rl_insts <- mapM (Container.findByName map_i) rl_names
193 695c1bab Iustin Pop
                let rl_idx = map Instance.idx rl_insts
194 cc532bdd Iustin Pop
                rl_mode <-
195 695c1bab Iustin Pop
                   case extrReq "reloc_mode" of
196 695c1bab Iustin Pop
                     Ok s | s == C.iallocatorMrelocKeep -> return KeepGroup
197 695c1bab Iustin Pop
                          | s == C.iallocatorMrelocChange ->
198 695c1bab Iustin Pop
                              do
199 695c1bab Iustin Pop
                                tg_groups <- parseTargetGroups request map_g
200 695c1bab Iustin Pop
                                return $ ChangeGroup tg_groups
201 695c1bab Iustin Pop
                          | s == C.iallocatorMrelocAny -> return AnyGroup
202 695c1bab Iustin Pop
                          | otherwise -> Bad $ "Invalid relocate mode " ++ s
203 695c1bab Iustin Pop
                     Bad x -> Bad x
204 695c1bab Iustin Pop
                return $ MultiReloc rl_idx rl_mode
205 4e84ca27 Iustin Pop
          | optype == C.iallocatorModeNodeEvac ->
206 4e84ca27 Iustin Pop
              do
207 4e84ca27 Iustin Pop
                rl_names <- extrReq "instances"
208 4e84ca27 Iustin Pop
                rl_insts <- mapM (Container.findByName map_i) rl_names
209 4e84ca27 Iustin Pop
                let rl_idx = map Instance.idx rl_insts
210 4e84ca27 Iustin Pop
                rl_mode <-
211 4e84ca27 Iustin Pop
                   case extrReq "evac_mode" of
212 4e84ca27 Iustin Pop
                     Ok s | s == C.iallocatorNevacAll -> return ChangeAll
213 4e84ca27 Iustin Pop
                          | s == C.iallocatorNevacPri -> return ChangePrimary
214 4e84ca27 Iustin Pop
                          | s == C.iallocatorNevacSec -> return ChangeSecondary
215 4e84ca27 Iustin Pop
                          | otherwise -> Bad $ "Invalid evacuate mode " ++ s
216 4e84ca27 Iustin Pop
                     Bad x -> Bad x
217 4e84ca27 Iustin Pop
                return $ NodeEvacuate rl_idx rl_mode
218 695c1bab Iustin Pop
219 df5227dc Iustin Pop
          | otherwise -> fail ("Invalid request type '" ++ optype ++ "'")
220 017a0c3d Iustin Pop
  return $ Request rqtype cdata
221 942403e6 Iustin Pop
222 d6cf394e Iustin Pop
-- | Formats the result into a valid IAllocator response message.
223 9188aeef Iustin Pop
formatResponse :: Bool     -- ^ Whether the request was successful
224 9188aeef Iustin Pop
               -> String   -- ^ Information text
225 d6cf394e Iustin Pop
               -> JSValue  -- ^ The JSON encoded result
226 d6cf394e Iustin Pop
               -> String   -- ^ The full JSON-formatted message
227 d6cf394e Iustin Pop
formatResponse success info result =
228 43643696 Iustin Pop
    let
229 34c5a24a Iustin Pop
        e_success = ("success", showJSON success)
230 34c5a24a Iustin Pop
        e_info = ("info", showJSON info)
231 d6cf394e Iustin Pop
        e_result = ("result", result)
232 b5cec17a Iustin Pop
    in encodeStrict $ makeObj [e_success, e_info, e_result]
233 cabce2f4 Iustin Pop
234 7c14b50a Iustin Pop
-- | Flatten the log of a solution into a string.
235 7c14b50a Iustin Pop
describeSolution :: Cluster.AllocSolution -> String
236 7c14b50a Iustin Pop
describeSolution = intercalate ", " . Cluster.asLog
237 cabce2f4 Iustin Pop
238 7c14b50a Iustin Pop
-- | Convert evacuation results into the result format.
239 7c14b50a Iustin Pop
formatEvacuate :: Cluster.AllocSolution -> Result IAllocResult
240 7c14b50a Iustin Pop
formatEvacuate as = do
241 7c14b50a Iustin Pop
  let info = describeSolution as
242 7c14b50a Iustin Pop
      elems = Cluster.asSolutions as
243 7c14b50a Iustin Pop
  when (null elems) $ fail info
244 7c14b50a Iustin Pop
  let sols = map (\(_, inst, nl, _) -> Instance.name inst : map Node.name nl)
245 7c14b50a Iustin Pop
             elems
246 34c5a24a Iustin Pop
  return (info, showJSON sols)
247 cabce2f4 Iustin Pop
248 7c14b50a Iustin Pop
-- | Convert allocation/relocation results into the result format.
249 7c14b50a Iustin Pop
formatAllocate :: Cluster.AllocSolution -> Result IAllocResult
250 7c14b50a Iustin Pop
formatAllocate as = do
251 7c14b50a Iustin Pop
  let info = describeSolution as
252 7c14b50a Iustin Pop
  case Cluster.asSolutions as of
253 7c14b50a Iustin Pop
    [] -> fail info
254 34c5a24a Iustin Pop
    (_, _, nodes, _):[] -> return (info, showJSON $ map (Node.name) nodes)
255 7c14b50a Iustin Pop
    _ -> fail "Internal error: multiple allocation solutions"
256 cabce2f4 Iustin Pop
257 cabce2f4 Iustin Pop
-- | Process a request and return new node lists
258 7c14b50a Iustin Pop
processRequest :: Request -> Result IAllocResult
259 cabce2f4 Iustin Pop
processRequest request =
260 cabce2f4 Iustin Pop
  let Request rqtype (ClusterData gl nl il _) = request
261 cabce2f4 Iustin Pop
  in case rqtype of
262 7c14b50a Iustin Pop
       Allocate xi reqn ->
263 7c14b50a Iustin Pop
           Cluster.tryMGAlloc gl nl il xi reqn >>= formatAllocate
264 7c14b50a Iustin Pop
       Relocate idx reqn exnodes ->
265 7c14b50a Iustin Pop
           Cluster.tryMGReloc gl nl il idx reqn exnodes >>= formatAllocate
266 7c14b50a Iustin Pop
       Evacuate exnodes ->
267 7c14b50a Iustin Pop
           Cluster.tryMGEvac gl nl il exnodes >>= formatEvacuate
268 cabce2f4 Iustin Pop
       MultiReloc _ _ -> fail "multi-reloc not handled"
269 cabce2f4 Iustin Pop
       NodeEvacuate _ _ -> fail "node-evacuate not handled"
270 cabce2f4 Iustin Pop
271 cabce2f4 Iustin Pop
-- | Reads the request from the data file(s)
272 cabce2f4 Iustin Pop
readRequest :: Options -> [String] -> IO Request
273 cabce2f4 Iustin Pop
readRequest opts args = do
274 cabce2f4 Iustin Pop
  when (null args) $ do
275 cabce2f4 Iustin Pop
         hPutStrLn stderr "Error: this program needs an input file."
276 cabce2f4 Iustin Pop
         exitWith $ ExitFailure 1
277 cabce2f4 Iustin Pop
278 cabce2f4 Iustin Pop
  input_data <- readFile (head args)
279 cabce2f4 Iustin Pop
  r1 <- case parseData input_data of
280 cabce2f4 Iustin Pop
          Bad err -> do
281 cabce2f4 Iustin Pop
            hPutStrLn stderr $ "Error: " ++ err
282 cabce2f4 Iustin Pop
            exitWith $ ExitFailure 1
283 cabce2f4 Iustin Pop
          Ok rq -> return rq
284 cabce2f4 Iustin Pop
  (if isJust (optDataFile opts) ||  (not . null . optNodeSim) opts
285 cabce2f4 Iustin Pop
   then do
286 cabce2f4 Iustin Pop
     cdata <- loadExternalData opts
287 cabce2f4 Iustin Pop
     let Request rqt _ = r1
288 cabce2f4 Iustin Pop
     return $ Request rqt cdata
289 cabce2f4 Iustin Pop
   else return r1)
290 00152519 Iustin Pop
291 00152519 Iustin Pop
-- | Main iallocator pipeline.
292 00152519 Iustin Pop
runIAllocator :: Request -> String
293 00152519 Iustin Pop
runIAllocator request =
294 7c14b50a Iustin Pop
  let (ok, info, result) =
295 7c14b50a Iustin Pop
          case processRequest request of
296 7c14b50a Iustin Pop
            Ok (msg, r) -> (True, "Request successful: " ++ msg, r)
297 7c14b50a Iustin Pop
            Bad msg -> (False, "Request failed: " ++ msg, JSArray [])
298 7c14b50a Iustin Pop
  in  formatResponse ok info result