Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / IAlloc.hs @ 34c00528

History | View | Annotate | Download (7.1 kB)

1
{-| Implementation of the iallocator interface.
2

    
3
-}
4

    
5
{-
6

    
7
Copyright (C) 2009, 2010 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
  disk <- fromObj "disk_space_total" a
54
  mem <- fromObj "memory" a
55
  vcpus <- fromObj "vcpus" a
56
  tags <- fromObj "tags" a
57
  let running = "running"
58
  return (n, Instance.create n mem disk vcpus running tags 0 0)
59

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

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

    
100
-- | Parses a group as found in the cluster group list.
101
parseGroup :: String              -- ^ The group UUID
102
           -> [(String, JSValue)] -- ^ The JSON object
103
           -> Result (String, Group.Group)
104
parseGroup u a = do
105
  name <- fromObj "name" a
106
  return (u, Group.create name u AllocPreferred)
107

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

    
161
-- | Format the result
162
formatRVal :: RqType -> [Node.AllocElement] -> JSValue
163
formatRVal _ [] = JSArray []
164

    
165
formatRVal (Evacuate _) elems =
166
    let sols = map (\(_, inst, nl, _) -> Instance.name inst : map Node.name nl)
167
               elems
168
        jsols = map (JSArray . map (JSString . toJSString)) sols
169
    in JSArray jsols
170

    
171
formatRVal _ elems =
172
    let (_, _, nodes, _) = head elems
173
        nodes' = map Node.name nodes
174
    in JSArray $ map (JSString . toJSString) nodes'
175

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