Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / IAlloc.hs @ 2e5eb96a

History | View | Annotate | Download (7.7 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 Data.Maybe (fromMaybe)
33
import Control.Monad
34
import Text.JSON (JSObject, JSValue(JSBool, JSString, JSArray),
35
                  makeObj, encodeStrict, decodeStrict,
36
                  fromJSObject, toJSString)
37
import qualified Ganeti.HTools.Container as Container
38
import qualified Ganeti.HTools.Group as Group
39
import qualified Ganeti.HTools.Node as Node
40
import qualified Ganeti.HTools.Instance as Instance
41
import qualified Ganeti.Constants as C
42
import Ganeti.HTools.Loader
43
import Ganeti.HTools.Utils
44
import Ganeti.HTools.Types
45

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

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

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

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

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

    
173
-- | Format the result
174
formatRVal :: RqType -> [Node.AllocElement] -> JSValue
175
formatRVal _ [] = JSArray []
176

    
177
formatRVal (Evacuate _) elems =
178
    let sols = map (\(_, inst, nl, _) -> Instance.name inst : map Node.name nl)
179
               elems
180
        jsols = map (JSArray . map (JSString . toJSString)) sols
181
    in JSArray jsols
182

    
183
formatRVal _ elems =
184
    let (_, _, nodes, _) = head elems
185
        nodes' = map Node.name nodes
186
    in JSArray $ map (JSString . toJSString) nodes'
187

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