Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / IAlloc.hs @ 1b2cb110

History | View | Annotate | Download (7.4 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
    ( parseData
28
    , formatResponse
29
    ) where
30

    
31
import Data.Either ()
32
import Control.Monad
33
import Text.JSON (JSObject, JSValue(JSBool, JSString, JSArray),
34
                  makeObj, encodeStrict, decodeStrict,
35
                  fromJSObject, toJSString)
36
import qualified Ganeti.HTools.Container as Container
37
import qualified Ganeti.HTools.Group as Group
38
import qualified Ganeti.HTools.Node as Node
39
import qualified Ganeti.HTools.Instance as Instance
40
import Ganeti.HTools.Loader
41
import Ganeti.HTools.Utils
42
import Ganeti.HTools.Types
43

    
44
-- | Parse the basic specifications of an instance.
45
--
46
-- Instances in the cluster instance list and the instance in an
47
-- 'Allocate' request share some common properties, which are read by
48
-- this function.
49
parseBaseInstance :: String
50
                  -> [(String, JSValue)]
51
                  -> Result (String, Instance.Instance)
52
parseBaseInstance n a = do
53
  let extract x = tryFromObj ("invalid data for instance '" ++ n ++ "'") a x
54
  disk  <- extract "disk_space_total"
55
  mem   <- extract "memory"
56
  vcpus <- extract "vcpus"
57
  tags  <- extract "tags"
58
  let running = "running"
59
  return (n, Instance.create n mem disk vcpus running tags 0 0)
60

    
61
-- | Parses an instance as found in the cluster instance listg.
62
parseInstance :: NameAssoc        -- ^ The node name-to-index association list
63
              -> String           -- ^ The name of the instance
64
              -> [(String, JSValue)] -- ^ The JSON object
65
              -> Result (String, Instance.Instance)
66
parseInstance ktn n a = do
67
  base <- parseBaseInstance n a
68
  nodes <- fromObj a "nodes"
69
  pnode <- if null nodes
70
           then Bad $ "empty node list for instance " ++ n
71
           else readEitherString $ head nodes
72
  pidx <- lookupNode ktn n pnode
73
  let snodes = tail nodes
74
  sidx <- (if null snodes then return Node.noSecondary
75
           else readEitherString (head snodes) >>= lookupNode ktn n)
76
  return (n, Instance.setBoth (snd base) pidx sidx)
77

    
78
-- | Parses a node as found in the cluster node list.
79
parseNode :: NameAssoc           -- ^ The group association
80
          -> String              -- ^ The node's name
81
          -> [(String, JSValue)] -- ^ The JSON object
82
          -> Result (String, Node.Node)
83
parseNode ktg n a = do
84
  let extract x = tryFromObj ("invalid data for node '" ++ n ++ "'") a x
85
  offline <- extract "offline"
86
  drained <- extract "drained"
87
  guuid   <- extract "group"
88
  gidx <- lookupGroup ktg n guuid
89
  node <- (if offline || drained
90
           then return $ Node.create n 0 0 0 0 0 0 True gidx
91
           else do
92
             mtotal <- extract "total_memory"
93
             mnode  <- extract "reserved_memory"
94
             mfree  <- extract "free_memory"
95
             dtotal <- extract "total_disk"
96
             dfree  <- extract "free_disk"
97
             ctotal <- extract "total_cpus"
98
             return $ Node.create n mtotal mnode mfree
99
                    dtotal dfree ctotal False gidx)
100
  return (n, node)
101

    
102
-- | Parses a group as found in the cluster group list.
103
parseGroup :: String              -- ^ The group UUID
104
           -> [(String, JSValue)] -- ^ The JSON object
105
           -> Result (String, Group.Group)
106
parseGroup u a = do
107
  let extract x = tryFromObj ("invalid data for group '" ++ u ++ "'") a x
108
  name <- extract "name"
109
  apol <- extract "alloc_policy"
110
  return (u, Group.create name u apol)
111

    
112
-- | Top-level parser.
113
parseData :: String         -- ^ The JSON message as received from Ganeti
114
          -> Result Request -- ^ A (possible valid) request
115
parseData body = do
116
  decoded <- fromJResult "Parsing input IAllocator message" (decodeStrict body)
117
  let obj = fromJSObject decoded
118
      extrObj x = tryFromObj "invalid iallocator message" obj x
119
  -- request parser
120
  request <- liftM fromJSObject (extrObj "request")
121
  let extrReq x = tryFromObj "invalid request dict" request x
122
  -- existing group parsing
123
  glist <- liftM fromJSObject (extrObj "nodegroups")
124
  gobj <- mapM (\(x, y) -> asJSObject y >>= parseGroup x . fromJSObject) glist
125
  let (ktg, gl) = assignIndices gobj
126
  -- existing node parsing
127
  nlist <- liftM fromJSObject (extrObj "nodes")
128
  nobj <- mapM (\(x,y) ->
129
                    asJSObject y >>= parseNode ktg x . fromJSObject) nlist
130
  let (ktn, nl) = assignIndices nobj
131
  -- existing instance parsing
132
  ilist <- extrObj "instances"
133
  let idata = fromJSObject ilist
134
  iobj <- mapM (\(x,y) ->
135
                    asJSObject y >>= parseInstance ktn x . fromJSObject) idata
136
  let (kti, il) = assignIndices iobj
137
  -- cluster tags
138
  ctags <- extrObj "cluster_tags"
139
  cdata <- mergeData [] [] [] (ClusterData gl nl il ctags)
140
  let map_n = cdNodes cdata
141
  optype <- extrReq "type"
142
  rqtype <-
143
      case optype of
144
        "allocate" ->
145
            do
146
              rname     <- extrReq "name"
147
              req_nodes <- extrReq "required_nodes"
148
              inew      <- parseBaseInstance rname request
149
              let io = snd inew
150
              return $ Allocate io req_nodes
151
        "relocate" ->
152
            do
153
              rname     <- extrReq "name"
154
              ridx      <- lookupInstance kti rname
155
              req_nodes <- extrReq "required_nodes"
156
              ex_nodes  <- extrReq "relocate_from"
157
              ex_idex   <- mapM (Container.findByName map_n) ex_nodes
158
              return $ Relocate ridx req_nodes (map Node.idx ex_idex)
159
        "multi-evacuate" ->
160
            do
161
              ex_names <- extrReq "evac_nodes"
162
              ex_nodes <- mapM (Container.findByName map_n) ex_names
163
              let ex_ndx = map Node.idx ex_nodes
164
              return $ Evacuate ex_ndx
165
        other -> fail ("Invalid request type '" ++ other ++ "'")
166
  return $ Request rqtype cdata
167

    
168
-- | Format the result
169
formatRVal :: RqType -> [Node.AllocElement] -> JSValue
170
formatRVal _ [] = JSArray []
171

    
172
formatRVal (Evacuate _) elems =
173
    let sols = map (\(_, inst, nl, _) -> Instance.name inst : map Node.name nl)
174
               elems
175
        jsols = map (JSArray . map (JSString . toJSString)) sols
176
    in JSArray jsols
177

    
178
formatRVal _ elems =
179
    let (_, _, nodes, _) = head elems
180
        nodes' = map Node.name nodes
181
    in JSArray $ map (JSString . toJSString) nodes'
182

    
183
-- | Formats the response into a valid IAllocator response message.
184
formatResponse :: Bool     -- ^ Whether the request was successful
185
               -> String   -- ^ Information text
186
               -> RqType   -- ^ Request type
187
               -> [Node.AllocElement] -- ^ The resulting allocations
188
               -> String   -- ^ The JSON-formatted message
189
formatResponse success info rq elems =
190
    let
191
        e_success = ("success", JSBool success)
192
        e_info = ("info", JSString . toJSString $ info)
193
        e_nodes = ("nodes", formatRVal rq elems)
194
    in encodeStrict $ makeObj [e_success, e_info, e_nodes]