Statistics
| Branch: | Tag: | Revision:

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

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