Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (8.5 kB)

1
{-| Implementation of the RAPI client interface.
2

    
3
-}
4

    
5
{-
6

    
7
Copyright (C) 2009, 2010, 2011, 2012 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
  ( loadData
30
  , parseData
31
  ) where
32

    
33
import Data.List (isPrefixOf)
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, fromJSObject, decodeStrict)
41
import Text.JSON.Types (JSValue(..))
42
import Text.Printf (printf)
43
import System.FilePath
44

    
45
import Ganeti.HTools.Loader
46
import Ganeti.HTools.Types
47
import Ganeti.HTools.JSON
48
import qualified Ganeti.HTools.Group as Group
49
import qualified Ganeti.HTools.Node as Node
50
import qualified Ganeti.HTools.Instance as Instance
51
import qualified Ganeti.Constants as C
52

    
53
{-# ANN module "HLint: ignore Eta reduce" #-}
54

    
55
-- | File method prefix.
56
filePrefix :: String
57
filePrefix = "file://"
58

    
59
-- | Read an URL via curl and return the body if successful.
60
getUrl :: (Monad m) => String -> IO (m String)
61

    
62
#ifdef NO_CURL
63
getUrl _ = return $ fail "RAPI/curl backend disabled at compile time"
64

    
65
#else
66

    
67
-- | The curl options we use.
68
curlOpts :: [CurlOption]
69
curlOpts = [ CurlSSLVerifyPeer False
70
           , CurlSSLVerifyHost 0
71
           , CurlTimeout (fromIntegral queryTimeout)
72
           , CurlConnectTimeout (fromIntegral connTimeout)
73
           ]
74

    
75
getUrl url = do
76
  (code, !body) <- curlGetString url curlOpts
77
  return (case code of
78
            CurlOK -> return body
79
            _ -> fail $ printf "Curl error for '%s', error %s"
80
                 url (show code))
81
#endif
82

    
83
-- | Helper to convert I/O errors in 'Bad' values.
84
ioErrToResult :: IO a -> IO (Result a)
85
ioErrToResult ioaction =
86
  catch (ioaction >>= return . Ok) (return . Bad . show)
87

    
88
-- | Append the default port if not passed in.
89
formatHost :: String -> String
90
formatHost master =
91
  if ':' `elem` master
92
    then  master
93
    else "https://" ++ master ++ ":" ++ show C.defaultRapiPort
94

    
95
-- | Parse a instance list in JSON format.
96
getInstances :: NameAssoc
97
             -> String
98
             -> Result [(String, Instance.Instance)]
99
getInstances ktn body =
100
  loadJSArray "Parsing instance data" body >>=
101
  mapM (parseInstance ktn . fromJSObject)
102

    
103
-- | Parse a node list in JSON format.
104
getNodes :: NameAssoc -> String -> Result [(String, Node.Node)]
105
getNodes ktg body = loadJSArray "Parsing node data" body >>=
106
                    mapM (parseNode ktg . fromJSObject)
107

    
108
-- | Parse a group list in JSON format.
109
getGroups :: String -> Result [(String, Group.Group)]
110
getGroups body = loadJSArray "Parsing group data" body >>=
111
                 mapM (parseGroup . fromJSObject)
112

    
113
-- | Construct an instance from a JSON object.
114
parseInstance :: NameAssoc
115
              -> JSRecord
116
              -> Result (String, Instance.Instance)
117
parseInstance ktn a = do
118
  name <- tryFromObj "Parsing new instance" a "name"
119
  let owner_name = "Instance '" ++ name ++ "', error while parsing data"
120
  let extract s x = tryFromObj owner_name x s
121
  disk <- extract "disk_usage" a
122
  beparams <- liftM fromJSObject (extract "beparams" a)
123
  omem <- extract "oper_ram" a
124
  mem <- case omem of
125
           JSRational _ _ -> annotateResult owner_name (fromJVal omem)
126
           _ -> extract "memory" beparams `mplus` extract "maxmem" beparams
127
  vcpus <- extract "vcpus" beparams
128
  pnode <- extract "pnode" a >>= lookupNode ktn name
129
  snodes <- extract "snodes" a
130
  snode <- if null snodes
131
             then return Node.noSecondary
132
             else readEitherString (head snodes) >>= lookupNode ktn name
133
  running <- extract "status" a
134
  tags <- extract "tags" a
135
  auto_balance <- extract "auto_balance" beparams
136
  dt <- extract "disk_template" a
137
  su <- extract "spindle_use" beparams
138
  let inst = Instance.create name mem disk vcpus running tags
139
             auto_balance pnode snode dt su
140
  return (name, inst)
141

    
142
-- | Construct a node from a JSON object.
143
parseNode :: NameAssoc -> JSRecord -> Result (String, Node.Node)
144
parseNode ktg a = do
145
  name <- tryFromObj "Parsing new node" a "name"
146
  let desc = "Node '" ++ name ++ "', error while parsing data"
147
      extract s = tryFromObj desc a s
148
  offline <- extract "offline"
149
  drained <- extract "drained"
150
  vm_cap  <- annotateResult desc $ maybeFromObj a "vm_capable"
151
  let vm_cap' = fromMaybe True vm_cap
152
  ndparams <- extract "ndparams" >>= asJSObject
153
  spindles <- tryFromObj desc (fromJSObject ndparams) "spindle_count"
154
  guuid   <- annotateResult desc $ maybeFromObj a "group.uuid"
155
  guuid' <-  lookupGroup ktg name (fromMaybe defaultGroupID guuid)
156
  node <- if offline || drained || not vm_cap'
157
            then return $ Node.create name 0 0 0 0 0 0 True 0 guuid'
158
            else do
159
              mtotal  <- extract "mtotal"
160
              mnode   <- extract "mnode"
161
              mfree   <- extract "mfree"
162
              dtotal  <- extract "dtotal"
163
              dfree   <- extract "dfree"
164
              ctotal  <- extract "ctotal"
165
              return $ Node.create name mtotal mnode mfree
166
                     dtotal dfree ctotal False spindles guuid'
167
  return (name, node)
168

    
169
-- | Construct a group from a JSON object.
170
parseGroup :: JSRecord -> Result (String, Group.Group)
171
parseGroup a = do
172
  name <- tryFromObj "Parsing new group" a "name"
173
  let extract s = tryFromObj ("Group '" ++ name ++ "'") a s
174
  uuid <- extract "uuid"
175
  apol <- extract "alloc_policy"
176
  ipol <- extract "ipolicy"
177
  return (uuid, Group.create name uuid apol ipol)
178

    
179
-- | Parse cluster data from the info resource.
180
parseCluster :: JSObject JSValue -> Result ([String], IPolicy)
181
parseCluster obj = do
182
  let obj' = fromJSObject obj
183
      extract s = tryFromObj "Parsing cluster data" obj' s
184
  tags <- extract "tags"
185
  ipolicy <- extract "ipolicy"
186
  return (tags, ipolicy)
187

    
188
-- | Loads the raw cluster data from an URL.
189
readDataHttp :: String -- ^ Cluster or URL to use as source
190
             -> IO (Result String, Result String, Result String, Result String)
191
readDataHttp master = do
192
  let url = formatHost master
193
  group_body <- getUrl $ printf "%s/2/groups?bulk=1" url
194
  node_body <- getUrl $ printf "%s/2/nodes?bulk=1" url
195
  inst_body <- getUrl $ printf "%s/2/instances?bulk=1" url
196
  info_body <- getUrl $ printf "%s/2/info" url
197
  return (group_body, node_body, inst_body, info_body)
198

    
199
-- | Loads the raw cluster data from the filesystem.
200
readDataFile:: String -- ^ Path to the directory containing the files
201
             -> IO (Result String, Result String, Result String, Result String)
202
readDataFile path = do
203
  group_body <- ioErrToResult $ readFile $ path </> "groups.json"
204
  node_body <- ioErrToResult $ readFile $ path </> "nodes.json"
205
  inst_body <- ioErrToResult $ readFile $ path </> "instances.json"
206
  info_body <- ioErrToResult $ readFile $ path </> "info.json"
207
  return (group_body, node_body, inst_body, info_body)
208

    
209
-- | Loads data via either 'readDataFile' or 'readDataHttp'.
210
readData :: String -- ^ URL to use as source
211
         -> IO (Result String, Result String, Result String, Result String)
212
readData url = do
213
  if filePrefix `isPrefixOf` url
214
    then readDataFile (drop (length filePrefix) url)
215
    else readDataHttp url
216

    
217
-- | Builds the cluster data from the raw Rapi content.
218
parseData :: (Result String, Result String, Result String, Result String)
219
          -> Result ClusterData
220
parseData (group_body, node_body, inst_body, info_body) = do
221
  group_data <- group_body >>= getGroups
222
  let (group_names, group_idx) = assignIndices group_data
223
  node_data <- node_body >>= getNodes group_names
224
  let (node_names, node_idx) = assignIndices node_data
225
  inst_data <- inst_body >>= getInstances node_names
226
  let (_, inst_idx) = assignIndices inst_data
227
  (tags, ipolicy) <- info_body >>=
228
                     (fromJResult "Parsing cluster info" . decodeStrict) >>=
229
                     parseCluster
230
  return (ClusterData group_idx node_idx inst_idx tags ipolicy)
231

    
232
-- | Top level function for data loading.
233
loadData :: String -- ^ Cluster or URL to use as source
234
         -> IO (Result ClusterData)
235
loadData = fmap parseData . readData