Statistics
| Branch: | Tag: | Revision:

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

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