Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Rapi.hs @ d575c755

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