Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / IAlloc.hs @ 9dcec001

History | View | Annotate | Download (5.5 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 e2fa2baf Iustin Pop
Copyright (C) 2009 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 19f38ee8 Iustin Pop
    ( parseData
28 43643696 Iustin Pop
    , formatResponse
29 43643696 Iustin Pop
    ) where
30 43643696 Iustin Pop
31 43643696 Iustin Pop
import Data.Either ()
32 43643696 Iustin Pop
import Control.Monad
33 942403e6 Iustin Pop
import Text.JSON (JSObject, JSValue(JSBool, JSString, JSArray),
34 942403e6 Iustin Pop
                  makeObj, encodeStrict, decodeStrict,
35 942403e6 Iustin Pop
                  fromJSObject, toJSString)
36 262a08a2 Iustin Pop
import qualified Ganeti.HTools.Container as Container
37 942403e6 Iustin Pop
import qualified Ganeti.HTools.Node as Node
38 942403e6 Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
39 e4c5beaf Iustin Pop
import Ganeti.HTools.Loader
40 e4c5beaf Iustin Pop
import Ganeti.HTools.Utils
41 e4c5beaf Iustin Pop
import Ganeti.HTools.Types
42 43643696 Iustin Pop
43 9188aeef Iustin Pop
-- | Parse the basic specifications of an instance.
44 9188aeef Iustin Pop
--
45 9188aeef Iustin Pop
-- Instances in the cluster instance list and the instance in an
46 9188aeef Iustin Pop
-- 'Allocate' request share some common properties, which are read by
47 9188aeef Iustin Pop
-- this function.
48 e4c5beaf Iustin Pop
parseBaseInstance :: String
49 e4c5beaf Iustin Pop
                  -> JSObject JSValue
50 e4c5beaf Iustin Pop
                  -> Result (String, Instance.Instance)
51 e4c5beaf Iustin Pop
parseBaseInstance n a = do
52 e4c5beaf Iustin Pop
  disk <- case fromObj "disk_usage" a of
53 e4c5beaf Iustin Pop
            Bad _ -> do
54 e4c5beaf Iustin Pop
                all_d <- fromObj "disks" a >>= asObjectList
55 e4c5beaf Iustin Pop
                szd <- mapM (fromObj "size") all_d
56 e4c5beaf Iustin Pop
                let sze = map (+128) szd
57 e4c5beaf Iustin Pop
                    szf = (sum sze)::Int
58 e4c5beaf Iustin Pop
                return szf
59 e4c5beaf Iustin Pop
            x@(Ok _) -> x
60 e4c5beaf Iustin Pop
  mem <- fromObj "memory" a
61 e4c5beaf Iustin Pop
  let running = "running"
62 2727257a Iustin Pop
  return $ (n, Instance.create n mem disk running 0 0)
63 585d4420 Iustin Pop
64 9188aeef Iustin Pop
-- | Parses an instance as found in the cluster instance list.
65 9188aeef Iustin Pop
parseInstance :: NameAssoc        -- ^ The node name-to-index association list
66 9188aeef Iustin Pop
              -> String           -- ^ The name of the instance
67 9188aeef Iustin Pop
              -> JSObject JSValue -- ^ The JSON object
68 e4c5beaf Iustin Pop
              -> Result (String, Instance.Instance)
69 e4c5beaf Iustin Pop
parseInstance ktn n a = do
70 585d4420 Iustin Pop
    base <- parseBaseInstance n a
71 e4c5beaf Iustin Pop
    nodes <- fromObj "nodes" a
72 e4c5beaf Iustin Pop
    pnode <- readEitherString $ head nodes
73 e4c5beaf Iustin Pop
    pidx <- lookupNode ktn n pnode
74 bd1794b2 Iustin Pop
    let snodes = tail nodes
75 bd1794b2 Iustin Pop
    sidx <- (if null snodes then return Node.noSecondary
76 bd1794b2 Iustin Pop
             else (readEitherString $ head snodes) >>= lookupNode ktn n)
77 e4c5beaf Iustin Pop
    return (n, Instance.setBoth (snd base) pidx sidx)
78 585d4420 Iustin Pop
79 9188aeef Iustin Pop
-- | Parses a node as found in the cluster node list.
80 9188aeef Iustin Pop
parseNode :: String           -- ^ The node's name
81 9188aeef Iustin Pop
          -> JSObject JSValue -- ^ The JSON object
82 9188aeef Iustin Pop
          -> Result (String, Node.Node)
83 e4c5beaf Iustin Pop
parseNode n a = do
84 e4c5beaf Iustin Pop
    let name = n
85 e4c5beaf Iustin Pop
    offline <- fromObj "offline" a
86 8c2ebac8 Iustin Pop
    drained <- fromObj "drained" a
87 1de50907 Iustin Pop
    node <- (case offline of
88 1de50907 Iustin Pop
               True -> return $ Node.create name 0 0 0 0 0 True
89 1de50907 Iustin Pop
               _ -> do
90 1de50907 Iustin Pop
                 mtotal <- fromObj "total_memory" a
91 1de50907 Iustin Pop
                 mnode <- fromObj "reserved_memory" a
92 1de50907 Iustin Pop
                 mfree <- fromObj "free_memory" a
93 1de50907 Iustin Pop
                 dtotal <- fromObj "total_disk" a
94 1de50907 Iustin Pop
                 dfree <- fromObj "free_disk" a
95 1de50907 Iustin Pop
                 return $ Node.create n mtotal mnode mfree
96 1de50907 Iustin Pop
                        dtotal dfree (offline || drained))
97 1de50907 Iustin Pop
    return (name, node)
98 144f190b Iustin Pop
99 9188aeef Iustin Pop
-- | Top-level parser.
100 9188aeef Iustin Pop
parseData :: String         -- ^ The JSON message as received from Ganeti
101 9188aeef Iustin Pop
          -> Result Request -- ^ A (possible valid) request
102 e4c5beaf Iustin Pop
parseData body = do
103 e4c5beaf Iustin Pop
  decoded <- fromJResult $ decodeStrict body
104 e4c5beaf Iustin Pop
  let obj = decoded
105 e4c5beaf Iustin Pop
  -- request parser
106 e4c5beaf Iustin Pop
  request <- fromObj "request" obj
107 e4c5beaf Iustin Pop
  rname <- fromObj "name" request
108 e4c5beaf Iustin Pop
  -- existing node parsing
109 e4c5beaf Iustin Pop
  nlist <- fromObj "nodes" obj
110 e4c5beaf Iustin Pop
  let ndata = fromJSObject nlist
111 e4c5beaf Iustin Pop
  nobj <- (mapM (\(x,y) -> asJSObject y >>= parseNode x)) ndata
112 497e30a1 Iustin Pop
  let (ktn, nl) = assignIndices nobj
113 e4c5beaf Iustin Pop
  -- existing instance parsing
114 e4c5beaf Iustin Pop
  ilist <- fromObj "instances" obj
115 e4c5beaf Iustin Pop
  let idata = fromJSObject ilist
116 e4c5beaf Iustin Pop
  iobj <- (mapM (\(x,y) -> asJSObject y >>= parseInstance ktn x)) idata
117 497e30a1 Iustin Pop
  let (kti, il) = assignIndices iobj
118 ed41c179 Iustin Pop
  (map_n, map_i, csf) <- mergeData (nl, il)
119 ed41c179 Iustin Pop
  req_nodes <- fromObj "required_nodes" request
120 e4c5beaf Iustin Pop
  optype <- fromObj "type" request
121 e4c5beaf Iustin Pop
  rqtype <-
122 e4c5beaf Iustin Pop
      case optype of
123 e4c5beaf Iustin Pop
        "allocate" ->
124 e4c5beaf Iustin Pop
            do
125 e4c5beaf Iustin Pop
              inew <- parseBaseInstance rname request
126 ed41c179 Iustin Pop
              let io = snd inew
127 ed41c179 Iustin Pop
              return $ Allocate io req_nodes
128 e4c5beaf Iustin Pop
        "relocate" ->
129 e4c5beaf Iustin Pop
            do
130 5a1edeb6 Iustin Pop
              ridx <- lookupInstance kti rname
131 ed41c179 Iustin Pop
              ex_nodes <- fromObj "relocate_from" request
132 ed41c179 Iustin Pop
              let ex_nodes' = map (stripSuffix $ length csf) ex_nodes
133 262a08a2 Iustin Pop
              ex_idex <- mapM (Container.findByName map_n) ex_nodes'
134 ed41c179 Iustin Pop
              return $ Relocate ridx req_nodes ex_idex
135 e4c5beaf Iustin Pop
        other -> fail $ ("Invalid request type '" ++ other ++ "'")
136 8472a321 Iustin Pop
  return $ Request rqtype map_n map_i csf
137 942403e6 Iustin Pop
138 9188aeef Iustin Pop
-- | Formats the response into a valid IAllocator response message.
139 9188aeef Iustin Pop
formatResponse :: Bool     -- ^ Whether the request was successful
140 9188aeef Iustin Pop
               -> String   -- ^ Information text
141 9188aeef Iustin Pop
               -> [String] -- ^ The list of chosen nodes
142 9188aeef Iustin Pop
               -> String   -- ^ The JSON-formatted message
143 43643696 Iustin Pop
formatResponse success info nodes =
144 43643696 Iustin Pop
    let
145 43643696 Iustin Pop
        e_success = ("success", JSBool success)
146 43643696 Iustin Pop
        e_info = ("info", JSString . toJSString $ info)
147 43643696 Iustin Pop
        e_nodes = ("nodes", JSArray $ map (JSString . toJSString) nodes)
148 43643696 Iustin Pop
    in encodeStrict $ makeObj [e_success, e_info, e_nodes]