Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / IAlloc.hs @ e7724ccc

History | View | Annotate | Download (5.3 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 734b1ff1 Iustin Pop
  disk <- fromObj "disk_space_total" a
53 e4c5beaf Iustin Pop
  mem <- fromObj "memory" a
54 d752eb39 Iustin Pop
  vcpus <- fromObj "vcpus" a
55 e4c5beaf Iustin Pop
  let running = "running"
56 9f6dcdea Iustin Pop
  return (n, Instance.create n mem disk vcpus running 0 0)
57 585d4420 Iustin Pop
58 9188aeef Iustin Pop
-- | Parses an instance as found in the cluster instance list.
59 9188aeef Iustin Pop
parseInstance :: NameAssoc        -- ^ The node name-to-index association list
60 9188aeef Iustin Pop
              -> String           -- ^ The name of the instance
61 9188aeef Iustin Pop
              -> JSObject JSValue -- ^ The JSON object
62 e4c5beaf Iustin Pop
              -> Result (String, Instance.Instance)
63 e4c5beaf Iustin Pop
parseInstance ktn n a = do
64 585d4420 Iustin Pop
    base <- parseBaseInstance n a
65 e4c5beaf Iustin Pop
    nodes <- fromObj "nodes" a
66 e4c5beaf Iustin Pop
    pnode <- readEitherString $ head nodes
67 e4c5beaf Iustin Pop
    pidx <- lookupNode ktn n pnode
68 bd1794b2 Iustin Pop
    let snodes = tail nodes
69 bd1794b2 Iustin Pop
    sidx <- (if null snodes then return Node.noSecondary
70 9f6dcdea Iustin Pop
             else readEitherString (head snodes) >>= lookupNode ktn n)
71 e4c5beaf Iustin Pop
    return (n, Instance.setBoth (snd base) pidx sidx)
72 585d4420 Iustin Pop
73 9188aeef Iustin Pop
-- | Parses a node as found in the cluster node list.
74 9188aeef Iustin Pop
parseNode :: String           -- ^ The node's name
75 9188aeef Iustin Pop
          -> JSObject JSValue -- ^ The JSON object
76 9188aeef Iustin Pop
          -> Result (String, Node.Node)
77 e4c5beaf Iustin Pop
parseNode n a = do
78 e4c5beaf Iustin Pop
    let name = n
79 e4c5beaf Iustin Pop
    offline <- fromObj "offline" a
80 8c2ebac8 Iustin Pop
    drained <- fromObj "drained" a
81 e97f211e Guido Trotter
    node <- (if offline || drained
82 9f6dcdea Iustin Pop
             then return $ Node.create name 0 0 0 0 0 0 True
83 9f6dcdea Iustin Pop
             else do
84 9f6dcdea Iustin Pop
               mtotal <- fromObj "total_memory" a
85 9f6dcdea Iustin Pop
               mnode  <- fromObj "reserved_memory" a
86 9f6dcdea Iustin Pop
               mfree  <- fromObj "free_memory"  a
87 9f6dcdea Iustin Pop
               dtotal <- fromObj "total_disk"   a
88 9f6dcdea Iustin Pop
               dfree  <- fromObj "free_disk"    a
89 9f6dcdea Iustin Pop
               ctotal <- fromObj "total_cpus"   a
90 9f6dcdea Iustin Pop
               return $ Node.create n mtotal mnode mfree
91 e97f211e Guido Trotter
                      dtotal dfree ctotal False)
92 1de50907 Iustin Pop
    return (name, node)
93 144f190b Iustin Pop
94 9188aeef Iustin Pop
-- | Top-level parser.
95 9188aeef Iustin Pop
parseData :: String         -- ^ The JSON message as received from Ganeti
96 9188aeef Iustin Pop
          -> Result Request -- ^ A (possible valid) request
97 e4c5beaf Iustin Pop
parseData body = do
98 e4c5beaf Iustin Pop
  decoded <- fromJResult $ decodeStrict body
99 e4c5beaf Iustin Pop
  let obj = decoded
100 e4c5beaf Iustin Pop
  -- request parser
101 e4c5beaf Iustin Pop
  request <- fromObj "request" obj
102 e4c5beaf Iustin Pop
  rname <- fromObj "name" request
103 e4c5beaf Iustin Pop
  -- existing node parsing
104 e4c5beaf Iustin Pop
  nlist <- fromObj "nodes" obj
105 e4c5beaf Iustin Pop
  let ndata = fromJSObject nlist
106 9f6dcdea Iustin Pop
  nobj <- mapM (\(x,y) -> asJSObject y >>= parseNode x) ndata
107 497e30a1 Iustin Pop
  let (ktn, nl) = assignIndices nobj
108 e4c5beaf Iustin Pop
  -- existing instance parsing
109 e4c5beaf Iustin Pop
  ilist <- fromObj "instances" obj
110 e4c5beaf Iustin Pop
  let idata = fromJSObject ilist
111 9f6dcdea Iustin Pop
  iobj <- mapM (\(x,y) -> asJSObject y >>= parseInstance ktn x) idata
112 497e30a1 Iustin Pop
  let (kti, il) = assignIndices iobj
113 aa8d2e71 Iustin Pop
  (map_n, map_i, csf) <- mergeData [] (nl, il)
114 ed41c179 Iustin Pop
  req_nodes <- fromObj "required_nodes" request
115 e4c5beaf Iustin Pop
  optype <- fromObj "type" request
116 e4c5beaf Iustin Pop
  rqtype <-
117 e4c5beaf Iustin Pop
      case optype of
118 e4c5beaf Iustin Pop
        "allocate" ->
119 e4c5beaf Iustin Pop
            do
120 e4c5beaf Iustin Pop
              inew <- parseBaseInstance rname request
121 ed41c179 Iustin Pop
              let io = snd inew
122 ed41c179 Iustin Pop
              return $ Allocate io req_nodes
123 e4c5beaf Iustin Pop
        "relocate" ->
124 e4c5beaf Iustin Pop
            do
125 5a1edeb6 Iustin Pop
              ridx <- lookupInstance kti rname
126 ed41c179 Iustin Pop
              ex_nodes <- fromObj "relocate_from" request
127 ed41c179 Iustin Pop
              let ex_nodes' = map (stripSuffix $ length csf) ex_nodes
128 262a08a2 Iustin Pop
              ex_idex <- mapM (Container.findByName map_n) ex_nodes'
129 e7724ccc Iustin Pop
              return $ Relocate ridx req_nodes (map Node.idx ex_idex)
130 9f6dcdea Iustin Pop
        other -> fail ("Invalid request type '" ++ other ++ "'")
131 8472a321 Iustin Pop
  return $ Request rqtype map_n map_i csf
132 942403e6 Iustin Pop
133 9188aeef Iustin Pop
-- | Formats the response into a valid IAllocator response message.
134 9188aeef Iustin Pop
formatResponse :: Bool     -- ^ Whether the request was successful
135 9188aeef Iustin Pop
               -> String   -- ^ Information text
136 9188aeef Iustin Pop
               -> [String] -- ^ The list of chosen nodes
137 9188aeef Iustin Pop
               -> String   -- ^ The JSON-formatted message
138 43643696 Iustin Pop
formatResponse success info nodes =
139 43643696 Iustin Pop
    let
140 43643696 Iustin Pop
        e_success = ("success", JSBool success)
141 43643696 Iustin Pop
        e_info = ("info", JSString . toJSString $ info)
142 43643696 Iustin Pop
        e_nodes = ("nodes", JSArray $ map (JSString . toJSString) nodes)
143 43643696 Iustin Pop
    in encodeStrict $ makeObj [e_success, e_info, e_nodes]