Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Rapi.hs @ 4d8e5008

History | View | Annotate | Download (6.6 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
module Ganeti.HTools.Rapi
27
    (
28
      loadData
29
    , parseData
30
    ) where
31

    
32
import Data.Maybe (isJust)
33
import Network.Curl
34
import Network.Curl.Types ()
35
import Control.Monad
36
import Text.JSON (JSObject, JSValue, fromJSObject, decodeStrict)
37
import Text.JSON.Types (JSValue(..))
38
import Text.Printf (printf)
39

    
40
import Ganeti.HTools.Utils
41
import Ganeti.HTools.Loader
42
import Ganeti.HTools.Types
43
import qualified Ganeti.HTools.Group as Group
44
import qualified Ganeti.HTools.Node as Node
45
import qualified Ganeti.HTools.Instance as Instance
46

    
47
-- | The curl options we use
48
curlOpts :: [CurlOption]
49
curlOpts = [ CurlSSLVerifyPeer False
50
           , CurlSSLVerifyHost 0
51
           , CurlTimeout (fromIntegral queryTimeout)
52
           , CurlConnectTimeout (fromIntegral connTimeout)
53
           ]
54

    
55
-- | Read an URL via curl and return the body if successful.
56
getUrl :: (Monad m) => String -> IO (m String)
57
getUrl url = do
58
  (code, body) <- curlGetString url curlOpts
59
  return (case code of
60
            CurlOK -> return body
61
            _ -> fail $ printf "Curl error for '%s', error %s"
62
                 url (show code))
63

    
64
-- | Append the default port if not passed in.
65
formatHost :: String -> String
66
formatHost master =
67
    if ':' `elem` master then  master
68
    else "https://" ++ master ++ ":5080"
69

    
70
-- | Parse a instance list in JSON format.
71
getInstances :: NameAssoc
72
             -> String
73
             -> Result [(String, Instance.Instance)]
74
getInstances ktn body =
75
    loadJSArray "Parsing instance data" body >>=
76
    mapM (parseInstance ktn . fromJSObject)
77

    
78
-- | Parse a node list in JSON format.
79
getNodes :: NameAssoc -> String -> Result [(String, Node.Node)]
80
getNodes ktg body = loadJSArray "Parsing node data" body >>=
81
                mapM (parseNode ktg . fromJSObject)
82

    
83
-- | Parse a group list in JSON format.
84
getGroups :: String -> Result [(String, Group.Group)]
85
getGroups body = loadJSArray "Parsing group data" body >>=
86
                mapM (parseGroup . fromJSObject)
87

    
88
getFakeGroups :: Result [(String, Group.Group)]
89
getFakeGroups =
90
  return $ [(defaultGroupID,
91
             Group.create "default" defaultGroupID AllocPreferred)]
92

    
93
-- | Construct an instance from a JSON object.
94
parseInstance :: NameAssoc
95
              -> [(String, JSValue)]
96
              -> Result (String, Instance.Instance)
97
parseInstance ktn a = do
98
  name <- tryFromObj "Parsing new instance" a "name"
99
  let owner_name = "Instance '" ++ name ++ "'"
100
  let extract s x = tryFromObj owner_name x s
101
  disk <- extract "disk_usage" a
102
  beparams <- liftM fromJSObject (extract "beparams" a)
103
  omem <- extract "oper_ram" a
104
  mem <- (case omem of
105
            JSRational _ _ -> annotateResult owner_name (fromJVal omem)
106
            _ -> extract "memory" beparams)
107
  vcpus <- extract "vcpus" beparams
108
  pnode <- extract "pnode" a >>= lookupNode ktn name
109
  snodes <- extract "snodes" a
110
  snode <- (if null snodes then return Node.noSecondary
111
            else readEitherString (head snodes) >>= lookupNode ktn name)
112
  running <- extract "status" a
113
  tags <- extract "tags" a
114
  let inst = Instance.create name mem disk vcpus running tags pnode snode
115
  return (name, inst)
116

    
117
-- | Construct a node from a JSON object.
118
parseNode :: NameAssoc -> [(String, JSValue)] -> Result (String, Node.Node)
119
parseNode ktg a = do
120
  name <- tryFromObj "Parsing new node" a "name"
121
  let extract s = tryFromObj ("Node '" ++ name ++ "'") a s
122
  offline <- extract "offline"
123
  drained <- extract "drained"
124
  guuid   <- (if isJust $ lookup "group.uuid" a
125
             then extract "group.uuid"
126
             else return defaultGroupID) >>= lookupGroup ktg name
127
  node <- (if offline || drained
128
           then return $ Node.create name 0 0 0 0 0 0 True guuid
129
           else do
130
             mtotal  <- extract "mtotal"
131
             mnode   <- extract "mnode"
132
             mfree   <- extract "mfree"
133
             dtotal  <- extract "dtotal"
134
             dfree   <- extract "dfree"
135
             ctotal  <- extract "ctotal"
136
             return $ Node.create name mtotal mnode mfree
137
                    dtotal dfree ctotal False guuid)
138
  return (name, node)
139

    
140
-- | Construct a group from a JSON object.
141
parseGroup :: [(String, JSValue)] -> Result (String, Group.Group)
142
parseGroup a = do
143
  name <- tryFromObj "Parsing new group" a "name"
144
  let extract s = tryFromObj ("Group '" ++ name ++ "'") a s
145
  uuid <- extract "uuid"
146
  apol <- extract "alloc_policy"
147
  return (uuid, Group.create name uuid apol)
148

    
149
-- | Loads the raw cluster data from an URL.
150
readData :: String -- ^ Cluster or URL to use as source
151
         -> IO (Result String, Result String, Result String, Result String)
152
readData master = do
153
  let url = formatHost master
154
  group_body <- getUrl $ printf "%s/2/groups?bulk=1" url
155
  node_body <- getUrl $ printf "%s/2/nodes?bulk=1" url
156
  inst_body <- getUrl $ printf "%s/2/instances?bulk=1" url
157
  tags_body <- getUrl $ printf "%s/2/tags" url
158
  return (group_body, node_body, inst_body, tags_body)
159

    
160
-- | Builds the cluster data from the raw Rapi content
161
parseData :: (Result String, Result String, Result String, Result String)
162
          -> Result ClusterData
163
parseData (group_body, node_body, inst_body, tags_body) = do
164
  group_data <-
165
      -- TODO: handle different ganeti versions properly, not via "all
166
      -- errors mean Ganeti 2.3"
167
      case group_body of
168
        Bad _ -> getFakeGroups
169
        Ok v -> getGroups v
170
  let (group_names, group_idx) = assignIndices group_data
171
  node_data <- node_body >>= getNodes group_names
172
  let (node_names, node_idx) = assignIndices node_data
173
  inst_data <- inst_body >>= getInstances node_names
174
  let (_, inst_idx) = assignIndices inst_data
175
  tags_data <- tags_body >>= (fromJResult "Parsing tags data" . decodeStrict)
176
  return (ClusterData group_idx node_idx inst_idx tags_data)
177

    
178
-- | Top level function for data loading
179
loadData :: String -- ^ Cluster or URL to use as source
180
         -> IO (Result ClusterData)
181
loadData master = readData master >>= return . parseData