root / htools / Ganeti / HTools / Rapi.hs @ a69ff623
History | View | Annotate | Download (7 kB)
1 |
{-| Implementation of the RAPI client 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 |
{-# LANGUAGE BangPatterns, CPP #-} |
27 |
|
28 |
module Ganeti.HTools.Rapi |
29 |
( |
30 |
loadData |
31 |
, parseData |
32 |
) where |
33 |
|
34 |
import Data.Maybe (fromMaybe) |
35 |
#ifndef NO_CURL |
36 |
import Network.Curl |
37 |
import Network.Curl.Types () |
38 |
#endif |
39 |
import Control.Monad |
40 |
import Text.JSON (JSObject, JSValue, fromJSObject, decodeStrict) |
41 |
import Text.JSON.Types (JSValue(..)) |
42 |
import Text.Printf (printf) |
43 |
|
44 |
import Ganeti.HTools.Utils |
45 |
import Ganeti.HTools.Loader |
46 |
import Ganeti.HTools.Types |
47 |
import qualified Ganeti.HTools.Group as Group |
48 |
import qualified Ganeti.HTools.Node as Node |
49 |
import qualified Ganeti.HTools.Instance as Instance |
50 |
import qualified Ganeti.Constants as C |
51 |
|
52 |
-- | Read an URL via curl and return the body if successful. |
53 |
getUrl :: (Monad m) => String -> IO (m String) |
54 |
|
55 |
#ifdef NO_CURL |
56 |
getUrl _ = return $ fail "RAPI/curl backend disabled at compile time" |
57 |
|
58 |
#else |
59 |
|
60 |
-- | The curl options we use |
61 |
curlOpts :: [CurlOption] |
62 |
curlOpts = [ CurlSSLVerifyPeer False |
63 |
, CurlSSLVerifyHost 0 |
64 |
, CurlTimeout (fromIntegral queryTimeout) |
65 |
, CurlConnectTimeout (fromIntegral connTimeout) |
66 |
] |
67 |
|
68 |
getUrl url = do |
69 |
(code, !body) <- curlGetString url curlOpts |
70 |
return (case code of |
71 |
CurlOK -> return body |
72 |
_ -> fail $ printf "Curl error for '%s', error %s" |
73 |
url (show code)) |
74 |
#endif |
75 |
|
76 |
-- | Append the default port if not passed in. |
77 |
formatHost :: String -> String |
78 |
formatHost master = |
79 |
if ':' `elem` master then master |
80 |
else "https://" ++ master ++ ":" ++ show C.defaultRapiPort |
81 |
|
82 |
-- | Parse a instance list in JSON format. |
83 |
getInstances :: NameAssoc |
84 |
-> String |
85 |
-> Result [(String, Instance.Instance)] |
86 |
getInstances ktn body = |
87 |
loadJSArray "Parsing instance data" body >>= |
88 |
mapM (parseInstance ktn . fromJSObject) |
89 |
|
90 |
-- | Parse a node list in JSON format. |
91 |
getNodes :: NameAssoc -> String -> Result [(String, Node.Node)] |
92 |
getNodes ktg body = loadJSArray "Parsing node data" body >>= |
93 |
mapM (parseNode ktg . fromJSObject) |
94 |
|
95 |
-- | Parse a group list in JSON format. |
96 |
getGroups :: String -> Result [(String, Group.Group)] |
97 |
getGroups body = loadJSArray "Parsing group data" body >>= |
98 |
mapM (parseGroup . fromJSObject) |
99 |
|
100 |
getFakeGroups :: Result [(String, Group.Group)] |
101 |
getFakeGroups = |
102 |
return [(defaultGroupID, |
103 |
Group.create "default" defaultGroupID AllocPreferred)] |
104 |
|
105 |
-- | Construct an instance from a JSON object. |
106 |
parseInstance :: NameAssoc |
107 |
-> [(String, JSValue)] |
108 |
-> Result (String, Instance.Instance) |
109 |
parseInstance ktn a = do |
110 |
name <- tryFromObj "Parsing new instance" a "name" |
111 |
let owner_name = "Instance '" ++ name ++ "', error while parsing data" |
112 |
let extract s x = tryFromObj owner_name x s |
113 |
disk <- extract "disk_usage" a |
114 |
beparams <- liftM fromJSObject (extract "beparams" a) |
115 |
omem <- extract "oper_ram" a |
116 |
mem <- (case omem of |
117 |
JSRational _ _ -> annotateResult owner_name (fromJVal omem) |
118 |
_ -> extract "memory" beparams) |
119 |
vcpus <- extract "vcpus" beparams |
120 |
pnode <- extract "pnode" a >>= lookupNode ktn name |
121 |
snodes <- extract "snodes" a |
122 |
snode <- (if null snodes then return Node.noSecondary |
123 |
else readEitherString (head snodes) >>= lookupNode ktn name) |
124 |
running <- extract "status" a |
125 |
tags <- extract "tags" a |
126 |
auto_balance <- extract "auto_balance" beparams |
127 |
let inst = Instance.create name mem disk vcpus running tags |
128 |
auto_balance pnode snode |
129 |
return (name, inst) |
130 |
|
131 |
-- | Construct a node from a JSON object. |
132 |
parseNode :: NameAssoc -> [(String, JSValue)] -> Result (String, Node.Node) |
133 |
parseNode ktg a = do |
134 |
name <- tryFromObj "Parsing new node" a "name" |
135 |
let desc = "Node '" ++ name ++ "', error while parsing data" |
136 |
extract s = tryFromObj desc a s |
137 |
offline <- extract "offline" |
138 |
drained <- extract "drained" |
139 |
vm_cap <- annotateResult desc $ maybeFromObj a "vm_capable" |
140 |
let vm_cap' = fromMaybe True vm_cap |
141 |
guuid <- annotateResult desc $ maybeFromObj a "group.uuid" |
142 |
guuid' <- lookupGroup ktg name (fromMaybe defaultGroupID guuid) |
143 |
node <- (if offline || drained || not vm_cap' |
144 |
then return $ Node.create name 0 0 0 0 0 0 True guuid' |
145 |
else do |
146 |
mtotal <- extract "mtotal" |
147 |
mnode <- extract "mnode" |
148 |
mfree <- extract "mfree" |
149 |
dtotal <- extract "dtotal" |
150 |
dfree <- extract "dfree" |
151 |
ctotal <- extract "ctotal" |
152 |
return $ Node.create name mtotal mnode mfree |
153 |
dtotal dfree ctotal False guuid') |
154 |
return (name, node) |
155 |
|
156 |
-- | Construct a group from a JSON object. |
157 |
parseGroup :: [(String, JSValue)] -> Result (String, Group.Group) |
158 |
parseGroup a = do |
159 |
name <- tryFromObj "Parsing new group" a "name" |
160 |
let extract s = tryFromObj ("Group '" ++ name ++ "'") a s |
161 |
uuid <- extract "uuid" |
162 |
apol <- extract "alloc_policy" |
163 |
return (uuid, Group.create name uuid apol) |
164 |
|
165 |
-- | Loads the raw cluster data from an URL. |
166 |
readData :: String -- ^ Cluster or URL to use as source |
167 |
-> IO (Result String, Result String, Result String, Result String) |
168 |
readData master = do |
169 |
let url = formatHost master |
170 |
group_body <- getUrl $ printf "%s/2/groups?bulk=1" url |
171 |
node_body <- getUrl $ printf "%s/2/nodes?bulk=1" url |
172 |
inst_body <- getUrl $ printf "%s/2/instances?bulk=1" url |
173 |
tags_body <- getUrl $ printf "%s/2/tags" url |
174 |
return (group_body, node_body, inst_body, tags_body) |
175 |
|
176 |
-- | Builds the cluster data from the raw Rapi content |
177 |
parseData :: (Result String, Result String, Result String, Result String) |
178 |
-> Result ClusterData |
179 |
parseData (group_body, node_body, inst_body, tags_body) = do |
180 |
group_data <- |
181 |
-- TODO: handle different ganeti versions properly, not via "all |
182 |
-- errors mean Ganeti 2.3" |
183 |
case group_body of |
184 |
Bad _ -> getFakeGroups |
185 |
Ok v -> getGroups v |
186 |
let (group_names, group_idx) = assignIndices group_data |
187 |
node_data <- node_body >>= getNodes group_names |
188 |
let (node_names, node_idx) = assignIndices node_data |
189 |
inst_data <- inst_body >>= getInstances node_names |
190 |
let (_, inst_idx) = assignIndices inst_data |
191 |
tags_data <- tags_body >>= (fromJResult "Parsing tags data" . decodeStrict) |
192 |
return (ClusterData group_idx node_idx inst_idx tags_data) |
193 |
|
194 |
-- | Top level function for data loading |
195 |
loadData :: String -- ^ Cluster or URL to use as source |
196 |
-> IO (Result ClusterData) |
197 |
loadData = fmap parseData . readData |