Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Rapi.hs @ ee9724b9

History | View | Annotate | Download (4.3 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 942403e6 Iustin Pop
import Text.JSON (JSObject, JSValue)
37 a7654563 Iustin Pop
import Text.Printf (printf)
38 040afc35 Iustin Pop
39 9ba5c28f Iustin Pop
import Ganeti.HTools.Utils
40 040afc35 Iustin Pop
import Ganeti.HTools.Loader
41 e4c5beaf Iustin Pop
import Ganeti.HTools.Types
42 040afc35 Iustin Pop
import qualified Ganeti.HTools.Node as Node
43 040afc35 Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
44 a7654563 Iustin Pop
45 9188aeef Iustin Pop
-- | Read an URL via curl and return the body if successful.
46 ba00ad4d Iustin Pop
getUrl :: (Monad m) => String -> IO (m String)
47 a7654563 Iustin Pop
getUrl url = do
48 a7654563 Iustin Pop
  (code, body) <- curlGetString url [CurlSSLVerifyPeer False,
49 135a6c6a Iustin Pop
                                     CurlSSLVerifyHost 0,
50 135a6c6a Iustin Pop
                                     CurlTimeout (fromIntegral queryTimeout),
51 135a6c6a Iustin Pop
                                     CurlConnectTimeout
52 135a6c6a Iustin Pop
                                     (fromIntegral connTimeout)]
53 a7654563 Iustin Pop
  return (case code of
54 ba00ad4d Iustin Pop
            CurlOK -> return body
55 ba00ad4d Iustin Pop
            _ -> fail $ printf "Curl error for '%s', error %s"
56 aab26f2d Iustin Pop
                 url (show code))
57 aab26f2d Iustin Pop
58 9188aeef Iustin Pop
-- | Append the default port if not passed in.
59 e015b554 Iustin Pop
formatHost :: String -> String
60 e015b554 Iustin Pop
formatHost master =
61 e015b554 Iustin Pop
    if elem ':' master then  master
62 e015b554 Iustin Pop
    else "https://" ++ master ++ ":5080"
63 e015b554 Iustin Pop
64 9188aeef Iustin Pop
-- | Parse a instance list in JSON format.
65 040afc35 Iustin Pop
getInstances :: NameAssoc
66 040afc35 Iustin Pop
             -> String
67 040afc35 Iustin Pop
             -> Result [(String, Instance.Instance)]
68 9f6dcdea Iustin Pop
getInstances ktn body = loadJSArray body >>= mapM (parseInstance ktn)
69 a7654563 Iustin Pop
70 9188aeef Iustin Pop
-- | Parse a node list in JSON format.
71 040afc35 Iustin Pop
getNodes :: String -> Result [(String, Node.Node)]
72 9f6dcdea Iustin Pop
getNodes body = loadJSArray body >>= mapM parseNode
73 a7654563 Iustin Pop
74 9188aeef Iustin Pop
-- | Construct an instance from a JSON object.
75 608efcce Iustin Pop
parseInstance :: [(String, Ndx)]
76 040afc35 Iustin Pop
              -> JSObject JSValue
77 040afc35 Iustin Pop
              -> Result (String, Instance.Instance)
78 040afc35 Iustin Pop
parseInstance ktn a = do
79 040afc35 Iustin Pop
  name <- fromObj "name" a
80 040afc35 Iustin Pop
  disk <- fromObj "disk_usage" a
81 040afc35 Iustin Pop
  mem <- fromObj "beparams" a >>= fromObj "memory"
82 d752eb39 Iustin Pop
  vcpus <- fromObj "beparams" a >>= fromObj "vcpus"
83 040afc35 Iustin Pop
  pnode <- fromObj "pnode" a >>= lookupNode ktn name
84 e4c5beaf Iustin Pop
  snodes <- fromObj "snodes" a
85 040afc35 Iustin Pop
  snode <- (if null snodes then return Node.noSecondary
86 040afc35 Iustin Pop
            else readEitherString (head snodes) >>= lookupNode ktn name)
87 040afc35 Iustin Pop
  running <- fromObj "status" a
88 d752eb39 Iustin Pop
  let inst = Instance.create name mem disk vcpus running pnode snode
89 040afc35 Iustin Pop
  return (name, inst)
90 a7654563 Iustin Pop
91 9188aeef Iustin Pop
-- | Construct a node from a JSON object.
92 040afc35 Iustin Pop
parseNode :: JSObject JSValue -> Result (String, Node.Node)
93 040afc35 Iustin Pop
parseNode a = do
94 040afc35 Iustin Pop
    name <- fromObj "name" a
95 040afc35 Iustin Pop
    offline <- fromObj "offline" a
96 9f6dcdea Iustin Pop
    node <- (if offline
97 9f6dcdea Iustin Pop
             then return $ Node.create name 0 0 0 0 0 0 True
98 9f6dcdea Iustin Pop
             else do
99 9f6dcdea Iustin Pop
               drained <- fromObj "drained" a
100 9f6dcdea Iustin Pop
               mtotal  <- fromObj "mtotal"  a
101 9f6dcdea Iustin Pop
               mnode   <- fromObj "mnode"   a
102 9f6dcdea Iustin Pop
               mfree   <- fromObj "mfree"   a
103 9f6dcdea Iustin Pop
               dtotal  <- fromObj "dtotal"  a
104 9f6dcdea Iustin Pop
               dfree   <- fromObj "dfree"   a
105 9f6dcdea Iustin Pop
               ctotal  <- fromObj "ctotal"  a
106 9f6dcdea Iustin Pop
               return $ Node.create name mtotal mnode mfree
107 9f6dcdea Iustin Pop
                      dtotal dfree ctotal (offline || drained))
108 040afc35 Iustin Pop
    return (name, node)
109 00b15752 Iustin Pop
110 9188aeef Iustin Pop
-- | Builds the cluster data from an URL.
111 a8946537 Iustin Pop
loadData :: String -- ^ Cluster or URL to use as source
112 e3a684c5 Iustin Pop
         -> IO (Result (Node.AssocList, Instance.AssocList))
113 040afc35 Iustin Pop
loadData master = do -- IO monad
114 040afc35 Iustin Pop
  let url = formatHost master
115 040afc35 Iustin Pop
  node_body <- getUrl $ printf "%s/2/nodes?bulk=1" url
116 040afc35 Iustin Pop
  inst_body <- getUrl $ printf "%s/2/instances?bulk=1" url
117 040afc35 Iustin Pop
  return $ do -- Result monad
118 040afc35 Iustin Pop
    node_data <- node_body >>= getNodes
119 497e30a1 Iustin Pop
    let (node_names, node_idx) = assignIndices node_data
120 040afc35 Iustin Pop
    inst_data <- inst_body >>= getInstances node_names
121 e3a684c5 Iustin Pop
    let (_, inst_idx) = assignIndices inst_data
122 e3a684c5 Iustin Pop
    return (node_idx, inst_idx)