Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Backend / Rapi.hs @ 6d3d13ab

History | View | Annotate | Download (8.8 kB)

1 a7654563 Iustin Pop
{-| Implementation of the RAPI client interface.
2 a7654563 Iustin Pop
3 a7654563 Iustin Pop
-}
4 a7654563 Iustin Pop
5 e2fa2baf Iustin Pop
{-
6 e2fa2baf Iustin Pop
7 8bc34c7b Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012 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 c478f837 Iustin Pop
{-# LANGUAGE BangPatterns, CPP #-}
27 c9224fa4 Iustin Pop
28 879d9290 Iustin Pop
module Ganeti.HTools.Backend.Rapi
29 ebf38064 Iustin Pop
  ( loadData
30 ebf38064 Iustin Pop
  , parseData
31 ebf38064 Iustin Pop
  ) where
32 a7654563 Iustin Pop
33 30d25dd8 Iustin Pop
import Control.Exception
34 d575c755 Iustin Pop
import Data.List (isPrefixOf)
35 3986684e Iustin Pop
import Data.Maybe (fromMaybe)
36 c478f837 Iustin Pop
#ifndef NO_CURL
37 a7654563 Iustin Pop
import Network.Curl
38 b8b9a53c Iustin Pop
import Network.Curl.Types ()
39 c478f837 Iustin Pop
#endif
40 a7654563 Iustin Pop
import Control.Monad
41 28f19313 Iustin Pop
import Text.JSON (JSObject, fromJSObject, decodeStrict)
42 6402a260 Iustin Pop
import Text.JSON.Types (JSValue(..))
43 a7654563 Iustin Pop
import Text.Printf (printf)
44 d575c755 Iustin Pop
import System.FilePath
45 040afc35 Iustin Pop
46 01e52493 Iustin Pop
import Ganeti.BasicTypes
47 040afc35 Iustin Pop
import Ganeti.HTools.Loader
48 e4c5beaf Iustin Pop
import Ganeti.HTools.Types
49 f3baf5ef Iustin Pop
import Ganeti.JSON
50 a679e9dc Iustin Pop
import qualified Ganeti.HTools.Group as Group
51 040afc35 Iustin Pop
import qualified Ganeti.HTools.Node as Node
52 040afc35 Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
53 a69ff623 Iustin Pop
import qualified Ganeti.Constants as C
54 a7654563 Iustin Pop
55 3603605a Iustin Pop
{-# ANN module "HLint: ignore Eta reduce" #-}
56 3603605a Iustin Pop
57 d575c755 Iustin Pop
-- | File method prefix.
58 d575c755 Iustin Pop
filePrefix :: String
59 d575c755 Iustin Pop
filePrefix = "file://"
60 d575c755 Iustin Pop
61 c478f837 Iustin Pop
-- | Read an URL via curl and return the body if successful.
62 c478f837 Iustin Pop
getUrl :: (Monad m) => String -> IO (m String)
63 c478f837 Iustin Pop
64 c478f837 Iustin Pop
#ifdef NO_CURL
65 c478f837 Iustin Pop
getUrl _ = return $ fail "RAPI/curl backend disabled at compile time"
66 c478f837 Iustin Pop
67 c478f837 Iustin Pop
#else
68 c478f837 Iustin Pop
69 4cd79ca8 Iustin Pop
-- | Connection timeout (when using non-file methods).
70 4cd79ca8 Iustin Pop
connTimeout :: Long
71 4cd79ca8 Iustin Pop
connTimeout = 15
72 4cd79ca8 Iustin Pop
73 4cd79ca8 Iustin Pop
-- | The default timeout for queries (when using non-file methods).
74 4cd79ca8 Iustin Pop
queryTimeout :: Long
75 4cd79ca8 Iustin Pop
queryTimeout = 60
76 4cd79ca8 Iustin Pop
77 525bfb36 Iustin Pop
-- | The curl options we use.
78 4d8e5008 Iustin Pop
curlOpts :: [CurlOption]
79 4d8e5008 Iustin Pop
curlOpts = [ CurlSSLVerifyPeer False
80 4d8e5008 Iustin Pop
           , CurlSSLVerifyHost 0
81 4cd79ca8 Iustin Pop
           , CurlTimeout queryTimeout
82 4cd79ca8 Iustin Pop
           , CurlConnectTimeout connTimeout
83 4d8e5008 Iustin Pop
           ]
84 4d8e5008 Iustin Pop
85 a7654563 Iustin Pop
getUrl url = do
86 c9224fa4 Iustin Pop
  (code, !body) <- curlGetString url curlOpts
87 a7654563 Iustin Pop
  return (case code of
88 ba00ad4d Iustin Pop
            CurlOK -> return body
89 ba00ad4d Iustin Pop
            _ -> fail $ printf "Curl error for '%s', error %s"
90 aab26f2d Iustin Pop
                 url (show code))
91 c478f837 Iustin Pop
#endif
92 aab26f2d Iustin Pop
93 d575c755 Iustin Pop
-- | Helper to convert I/O errors in 'Bad' values.
94 d575c755 Iustin Pop
ioErrToResult :: IO a -> IO (Result a)
95 d575c755 Iustin Pop
ioErrToResult ioaction =
96 b9612abb Iustin Pop
  Control.Exception.catch (liftM Ok ioaction)
97 1251817b Iustin Pop
    (\e -> return . Bad . show $ (e::IOException))
98 d575c755 Iustin Pop
99 9188aeef Iustin Pop
-- | Append the default port if not passed in.
100 e015b554 Iustin Pop
formatHost :: String -> String
101 e015b554 Iustin Pop
formatHost master =
102 ebf38064 Iustin Pop
  if ':' `elem` master
103 ebf38064 Iustin Pop
    then  master
104 a69ff623 Iustin Pop
    else "https://" ++ master ++ ":" ++ show C.defaultRapiPort
105 e015b554 Iustin Pop
106 9188aeef Iustin Pop
-- | Parse a instance list in JSON format.
107 040afc35 Iustin Pop
getInstances :: NameAssoc
108 040afc35 Iustin Pop
             -> String
109 040afc35 Iustin Pop
             -> Result [(String, Instance.Instance)]
110 262f3e6c Iustin Pop
getInstances ktn body =
111 ebf38064 Iustin Pop
  loadJSArray "Parsing instance data" body >>=
112 ebf38064 Iustin Pop
  mapM (parseInstance ktn . fromJSObject)
113 a7654563 Iustin Pop
114 9188aeef Iustin Pop
-- | Parse a node list in JSON format.
115 10ef6b4e Iustin Pop
getNodes :: NameAssoc -> String -> Result [(String, Node.Node)]
116 10ef6b4e Iustin Pop
getNodes ktg body = loadJSArray "Parsing node data" body >>=
117 ebf38064 Iustin Pop
                    mapM (parseNode ktg . fromJSObject)
118 a7654563 Iustin Pop
119 a679e9dc Iustin Pop
-- | Parse a group list in JSON format.
120 a679e9dc Iustin Pop
getGroups :: String -> Result [(String, Group.Group)]
121 a679e9dc Iustin Pop
getGroups body = loadJSArray "Parsing group data" body >>=
122 ebf38064 Iustin Pop
                 mapM (parseGroup . fromJSObject)
123 a679e9dc Iustin Pop
124 9188aeef Iustin Pop
-- | Construct an instance from a JSON object.
125 6ff78049 Iustin Pop
parseInstance :: NameAssoc
126 28f19313 Iustin Pop
              -> JSRecord
127 040afc35 Iustin Pop
              -> Result (String, Instance.Instance)
128 040afc35 Iustin Pop
parseInstance ktn a = do
129 117dc2d8 Iustin Pop
  name <- tryFromObj "Parsing new instance" a "name"
130 6a062ff9 Iustin Pop
  let owner_name = "Instance '" ++ name ++ "', error while parsing data"
131 6402a260 Iustin Pop
  let extract s x = tryFromObj owner_name x s
132 117dc2d8 Iustin Pop
  disk <- extract "disk_usage" a
133 117dc2d8 Iustin Pop
  beparams <- liftM fromJSObject (extract "beparams" a)
134 6402a260 Iustin Pop
  omem <- extract "oper_ram" a
135 3603605a Iustin Pop
  mem <- case omem of
136 3603605a Iustin Pop
           JSRational _ _ -> annotateResult owner_name (fromJVal omem)
137 135f64a3 Iustin Pop
           _ -> extract "memory" beparams `mplus` extract "maxmem" beparams
138 117dc2d8 Iustin Pop
  vcpus <- extract "vcpus" beparams
139 117dc2d8 Iustin Pop
  pnode <- extract "pnode" a >>= lookupNode ktn name
140 117dc2d8 Iustin Pop
  snodes <- extract "snodes" a
141 3603605a Iustin Pop
  snode <- if null snodes
142 3603605a Iustin Pop
             then return Node.noSecondary
143 3603605a Iustin Pop
             else readEitherString (head snodes) >>= lookupNode ktn name
144 117dc2d8 Iustin Pop
  running <- extract "status" a
145 17e7af2b Iustin Pop
  tags <- extract "tags" a
146 a041ebb5 Iustin Pop
  auto_balance <- extract "auto_balance" beparams
147 5a4a3b7f Iustin Pop
  dt <- extract "disk_template" a
148 ec629280 René Nussbaumer
  su <- extract "spindle_use" beparams
149 a041ebb5 Iustin Pop
  let inst = Instance.create name mem disk vcpus running tags
150 b003b8c0 René Nussbaumer
             auto_balance pnode snode dt su
151 040afc35 Iustin Pop
  return (name, inst)
152 a7654563 Iustin Pop
153 9188aeef Iustin Pop
-- | Construct a node from a JSON object.
154 28f19313 Iustin Pop
parseNode :: NameAssoc -> JSRecord -> Result (String, Node.Node)
155 10ef6b4e Iustin Pop
parseNode ktg a = do
156 117dc2d8 Iustin Pop
  name <- tryFromObj "Parsing new node" a "name"
157 6a062ff9 Iustin Pop
  let desc = "Node '" ++ name ++ "', error while parsing data"
158 3986684e Iustin Pop
      extract s = tryFromObj desc a s
159 117dc2d8 Iustin Pop
  offline <- extract "offline"
160 b45222ce Iustin Pop
  drained <- extract "drained"
161 3986684e Iustin Pop
  vm_cap  <- annotateResult desc $ maybeFromObj a "vm_capable"
162 3986684e Iustin Pop
  let vm_cap' = fromMaybe True vm_cap
163 8bc34c7b Iustin Pop
  ndparams <- extract "ndparams" >>= asJSObject
164 8bc34c7b Iustin Pop
  spindles <- tryFromObj desc (fromJSObject ndparams) "spindle_count"
165 3986684e Iustin Pop
  guuid   <- annotateResult desc $ maybeFromObj a "group.uuid"
166 3986684e Iustin Pop
  guuid' <-  lookupGroup ktg name (fromMaybe defaultGroupID guuid)
167 3603605a Iustin Pop
  node <- if offline || drained || not vm_cap'
168 8bc34c7b Iustin Pop
            then return $ Node.create name 0 0 0 0 0 0 True 0 guuid'
169 3603605a Iustin Pop
            else do
170 3603605a Iustin Pop
              mtotal  <- extract "mtotal"
171 3603605a Iustin Pop
              mnode   <- extract "mnode"
172 3603605a Iustin Pop
              mfree   <- extract "mfree"
173 3603605a Iustin Pop
              dtotal  <- extract "dtotal"
174 3603605a Iustin Pop
              dfree   <- extract "dfree"
175 3603605a Iustin Pop
              ctotal  <- extract "ctotal"
176 3603605a Iustin Pop
              return $ Node.create name mtotal mnode mfree
177 8bc34c7b Iustin Pop
                     dtotal dfree ctotal False spindles guuid'
178 262f3e6c Iustin Pop
  return (name, node)
179 00b15752 Iustin Pop
180 a679e9dc Iustin Pop
-- | Construct a group from a JSON object.
181 28f19313 Iustin Pop
parseGroup :: JSRecord -> Result (String, Group.Group)
182 a679e9dc Iustin Pop
parseGroup a = do
183 a679e9dc Iustin Pop
  name <- tryFromObj "Parsing new group" a "name"
184 a679e9dc Iustin Pop
  let extract s = tryFromObj ("Group '" ++ name ++ "'") a s
185 a679e9dc Iustin Pop
  uuid <- extract "uuid"
186 2ddabf4f Iustin Pop
  apol <- extract "alloc_policy"
187 6cff91f5 Iustin Pop
  ipol <- extract "ipolicy"
188 6b6e335b Dato Simó
  tags <- extract "tags"
189 6b6e335b Dato Simó
  return (uuid, Group.create name uuid apol ipol tags)
190 a679e9dc Iustin Pop
191 df5d5433 Iustin Pop
-- | Parse cluster data from the info resource.
192 df5d5433 Iustin Pop
parseCluster :: JSObject JSValue -> Result ([String], IPolicy)
193 df5d5433 Iustin Pop
parseCluster obj = do
194 df5d5433 Iustin Pop
  let obj' = fromJSObject obj
195 df5d5433 Iustin Pop
      extract s = tryFromObj "Parsing cluster data" obj' s
196 df5d5433 Iustin Pop
  tags <- extract "tags"
197 df5d5433 Iustin Pop
  ipolicy <- extract "ipolicy"
198 df5d5433 Iustin Pop
  return (tags, ipolicy)
199 df5d5433 Iustin Pop
200 748bfcc2 Iustin Pop
-- | Loads the raw cluster data from an URL.
201 d575c755 Iustin Pop
readDataHttp :: String -- ^ Cluster or URL to use as source
202 d575c755 Iustin Pop
             -> IO (Result String, Result String, Result String, Result String)
203 d575c755 Iustin Pop
readDataHttp master = do
204 040afc35 Iustin Pop
  let url = formatHost master
205 a679e9dc Iustin Pop
  group_body <- getUrl $ printf "%s/2/groups?bulk=1" url
206 040afc35 Iustin Pop
  node_body <- getUrl $ printf "%s/2/nodes?bulk=1" url
207 040afc35 Iustin Pop
  inst_body <- getUrl $ printf "%s/2/instances?bulk=1" url
208 df5d5433 Iustin Pop
  info_body <- getUrl $ printf "%s/2/info" url
209 df5d5433 Iustin Pop
  return (group_body, node_body, inst_body, info_body)
210 748bfcc2 Iustin Pop
211 d575c755 Iustin Pop
-- | Loads the raw cluster data from the filesystem.
212 d575c755 Iustin Pop
readDataFile:: String -- ^ Path to the directory containing the files
213 d575c755 Iustin Pop
             -> IO (Result String, Result String, Result String, Result String)
214 d575c755 Iustin Pop
readDataFile path = do
215 2cdaf225 Iustin Pop
  group_body <- ioErrToResult . readFile $ path </> "groups.json"
216 2cdaf225 Iustin Pop
  node_body <- ioErrToResult . readFile $ path </> "nodes.json"
217 2cdaf225 Iustin Pop
  inst_body <- ioErrToResult . readFile $ path </> "instances.json"
218 2cdaf225 Iustin Pop
  info_body <- ioErrToResult . readFile $ path </> "info.json"
219 d575c755 Iustin Pop
  return (group_body, node_body, inst_body, info_body)
220 d575c755 Iustin Pop
221 d575c755 Iustin Pop
-- | Loads data via either 'readDataFile' or 'readDataHttp'.
222 d575c755 Iustin Pop
readData :: String -- ^ URL to use as source
223 d575c755 Iustin Pop
         -> IO (Result String, Result String, Result String, Result String)
224 5b11f8db Iustin Pop
readData url =
225 d575c755 Iustin Pop
  if filePrefix `isPrefixOf` url
226 d575c755 Iustin Pop
    then readDataFile (drop (length filePrefix) url)
227 d575c755 Iustin Pop
    else readDataHttp url
228 d575c755 Iustin Pop
229 525bfb36 Iustin Pop
-- | Builds the cluster data from the raw Rapi content.
230 a679e9dc Iustin Pop
parseData :: (Result String, Result String, Result String, Result String)
231 f4f6eb0b Iustin Pop
          -> Result ClusterData
232 df5d5433 Iustin Pop
parseData (group_body, node_body, inst_body, info_body) = do
233 3667467d Iustin Pop
  group_data <- group_body >>= getGroups
234 10ef6b4e Iustin Pop
  let (group_names, group_idx) = assignIndices group_data
235 10ef6b4e Iustin Pop
  node_data <- node_body >>= getNodes group_names
236 748bfcc2 Iustin Pop
  let (node_names, node_idx) = assignIndices node_data
237 748bfcc2 Iustin Pop
  inst_data <- inst_body >>= getInstances node_names
238 748bfcc2 Iustin Pop
  let (_, inst_idx) = assignIndices inst_data
239 df5d5433 Iustin Pop
  (tags, ipolicy) <- info_body >>=
240 df5d5433 Iustin Pop
                     (fromJResult "Parsing cluster info" . decodeStrict) >>=
241 df5d5433 Iustin Pop
                     parseCluster
242 df5d5433 Iustin Pop
  return (ClusterData group_idx node_idx inst_idx tags ipolicy)
243 748bfcc2 Iustin Pop
244 525bfb36 Iustin Pop
-- | Top level function for data loading.
245 748bfcc2 Iustin Pop
loadData :: String -- ^ Cluster or URL to use as source
246 f4f6eb0b Iustin Pop
         -> IO (Result ClusterData)
247 2a8e2dc9 Iustin Pop
loadData = fmap parseData . readData