Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Rapi.hs @ 57587760

History | View | Annotate | Download (4.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 e2fa2baf Iustin Pop
Copyright (C) 2009 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 669d7e3d Iustin Pop
module Ganeti.HTools.Rapi
27 dd4c56ed Iustin Pop
    (
28 040afc35 Iustin Pop
      loadData
29 dd4c56ed Iustin Pop
    ) where
30 a7654563 Iustin Pop
31 a7654563 Iustin Pop
import Network.Curl
32 b8b9a53c Iustin Pop
import Network.Curl.Types ()
33 a7654563 Iustin Pop
import Network.Curl.Code
34 e015b554 Iustin Pop
import Data.List
35 a7654563 Iustin Pop
import Control.Monad
36 ea017cbc Iustin Pop
import Text.JSON (JSObject, JSValue, fromJSObject, decodeStrict)
37 6402a260 Iustin Pop
import Text.JSON.Types (JSValue(..))
38 a7654563 Iustin Pop
import Text.Printf (printf)
39 040afc35 Iustin Pop
40 9ba5c28f Iustin Pop
import Ganeti.HTools.Utils
41 040afc35 Iustin Pop
import Ganeti.HTools.Loader
42 e4c5beaf Iustin Pop
import Ganeti.HTools.Types
43 040afc35 Iustin Pop
import qualified Ganeti.HTools.Node as Node
44 040afc35 Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
45 a7654563 Iustin Pop
46 9188aeef Iustin Pop
-- | Read an URL via curl and return the body if successful.
47 ba00ad4d Iustin Pop
getUrl :: (Monad m) => String -> IO (m String)
48 a7654563 Iustin Pop
getUrl url = do
49 a7654563 Iustin Pop
  (code, body) <- curlGetString url [CurlSSLVerifyPeer False,
50 135a6c6a Iustin Pop
                                     CurlSSLVerifyHost 0,
51 135a6c6a Iustin Pop
                                     CurlTimeout (fromIntegral queryTimeout),
52 135a6c6a Iustin Pop
                                     CurlConnectTimeout
53 135a6c6a Iustin Pop
                                     (fromIntegral connTimeout)]
54 a7654563 Iustin Pop
  return (case code of
55 ba00ad4d Iustin Pop
            CurlOK -> return body
56 ba00ad4d Iustin Pop
            _ -> fail $ printf "Curl error for '%s', error %s"
57 aab26f2d Iustin Pop
                 url (show code))
58 aab26f2d Iustin Pop
59 9188aeef Iustin Pop
-- | Append the default port if not passed in.
60 e015b554 Iustin Pop
formatHost :: String -> String
61 e015b554 Iustin Pop
formatHost master =
62 e015b554 Iustin Pop
    if elem ':' master then  master
63 e015b554 Iustin Pop
    else "https://" ++ master ++ ":5080"
64 e015b554 Iustin Pop
65 9188aeef Iustin Pop
-- | Parse a instance list in JSON format.
66 040afc35 Iustin Pop
getInstances :: NameAssoc
67 040afc35 Iustin Pop
             -> String
68 040afc35 Iustin Pop
             -> Result [(String, Instance.Instance)]
69 262f3e6c Iustin Pop
getInstances ktn body =
70 262f3e6c Iustin Pop
    loadJSArray body >>= mapM (parseInstance ktn . fromJSObject)
71 a7654563 Iustin Pop
72 9188aeef Iustin Pop
-- | Parse a node list in JSON format.
73 040afc35 Iustin Pop
getNodes :: String -> Result [(String, Node.Node)]
74 262f3e6c Iustin Pop
getNodes body = loadJSArray body >>= mapM (parseNode . fromJSObject)
75 a7654563 Iustin Pop
76 9188aeef Iustin Pop
-- | Construct an instance from a JSON object.
77 608efcce Iustin Pop
parseInstance :: [(String, Ndx)]
78 262f3e6c Iustin Pop
              -> [(String, JSValue)]
79 040afc35 Iustin Pop
              -> Result (String, Instance.Instance)
80 040afc35 Iustin Pop
parseInstance ktn a = do
81 117dc2d8 Iustin Pop
  name <- tryFromObj "Parsing new instance" a "name"
82 6402a260 Iustin Pop
  let owner_name = "Instance '" ++ name ++ "'"
83 6402a260 Iustin Pop
  let extract s x = tryFromObj owner_name x s
84 117dc2d8 Iustin Pop
  disk <- extract "disk_usage" a
85 117dc2d8 Iustin Pop
  beparams <- liftM fromJSObject (extract "beparams" a)
86 6402a260 Iustin Pop
  omem <- extract "oper_ram" a
87 6402a260 Iustin Pop
  mem <- (case omem of
88 6402a260 Iustin Pop
            JSRational _ _ -> annotateResult owner_name (fromJVal omem)
89 6402a260 Iustin Pop
            _ -> extract "memory" beparams)
90 117dc2d8 Iustin Pop
  vcpus <- extract "vcpus" beparams
91 117dc2d8 Iustin Pop
  pnode <- extract "pnode" a >>= lookupNode ktn name
92 117dc2d8 Iustin Pop
  snodes <- extract "snodes" a
93 040afc35 Iustin Pop
  snode <- (if null snodes then return Node.noSecondary
94 040afc35 Iustin Pop
            else readEitherString (head snodes) >>= lookupNode ktn name)
95 117dc2d8 Iustin Pop
  running <- extract "status" a
96 17e7af2b Iustin Pop
  tags <- extract "tags" a
97 17e7af2b Iustin Pop
  let inst = Instance.create name mem disk vcpus running tags pnode snode
98 040afc35 Iustin Pop
  return (name, inst)
99 a7654563 Iustin Pop
100 9188aeef Iustin Pop
-- | Construct a node from a JSON object.
101 262f3e6c Iustin Pop
parseNode :: [(String, JSValue)] -> Result (String, Node.Node)
102 040afc35 Iustin Pop
parseNode a = do
103 117dc2d8 Iustin Pop
  name <- tryFromObj "Parsing new node" a "name"
104 117dc2d8 Iustin Pop
  let extract s = tryFromObj ("Node '" ++ name ++ "'") a s
105 117dc2d8 Iustin Pop
  offline <- extract "offline"
106 b45222ce Iustin Pop
  drained <- extract "drained"
107 b45222ce Iustin Pop
  node <- (if offline || drained
108 262f3e6c Iustin Pop
           then return $ Node.create name 0 0 0 0 0 0 True
109 262f3e6c Iustin Pop
           else do
110 117dc2d8 Iustin Pop
             mtotal  <- extract "mtotal"
111 117dc2d8 Iustin Pop
             mnode   <- extract "mnode"
112 117dc2d8 Iustin Pop
             mfree   <- extract "mfree"
113 117dc2d8 Iustin Pop
             dtotal  <- extract "dtotal"
114 117dc2d8 Iustin Pop
             dfree   <- extract "dfree"
115 117dc2d8 Iustin Pop
             ctotal  <- extract "ctotal"
116 262f3e6c Iustin Pop
             return $ Node.create name mtotal mnode mfree
117 b45222ce Iustin Pop
                    dtotal dfree ctotal False)
118 262f3e6c Iustin Pop
  return (name, node)
119 00b15752 Iustin Pop
120 9188aeef Iustin Pop
-- | Builds the cluster data from an URL.
121 a8946537 Iustin Pop
loadData :: String -- ^ Cluster or URL to use as source
122 94e05c32 Iustin Pop
         -> IO (Result (Node.AssocList, Instance.AssocList, [String]))
123 040afc35 Iustin Pop
loadData master = do -- IO monad
124 040afc35 Iustin Pop
  let url = formatHost master
125 040afc35 Iustin Pop
  node_body <- getUrl $ printf "%s/2/nodes?bulk=1" url
126 040afc35 Iustin Pop
  inst_body <- getUrl $ printf "%s/2/instances?bulk=1" url
127 ea017cbc Iustin Pop
  tags_body <- getUrl $ printf "%s/2/tags" url
128 040afc35 Iustin Pop
  return $ do -- Result monad
129 040afc35 Iustin Pop
    node_data <- node_body >>= getNodes
130 497e30a1 Iustin Pop
    let (node_names, node_idx) = assignIndices node_data
131 040afc35 Iustin Pop
    inst_data <- inst_body >>= getInstances node_names
132 e3a684c5 Iustin Pop
    let (_, inst_idx) = assignIndices inst_data
133 ea017cbc Iustin Pop
    tags_data <- tags_body >>= (fromJResult . decodeStrict)
134 ea017cbc Iustin Pop
    return (node_idx, inst_idx, tags_data)