Add 'Read' instances for most objects
[ganeti-local] / Ganeti / HTools / Rapi.hs
index da1a9b5..cab5efe 100644 (file)
 
 -}
 
+{-
+
+Copyright (C) 2009, 2010 Google Inc.
+
+This program is free software; you can redistribute it and/or modify
+it under the terms of the GNU General Public License as published by
+the Free Software Foundation; either version 2 of the License, or
+(at your option) any later version.
+
+This program is distributed in the hope that it will be useful, but
+WITHOUT ANY WARRANTY; without even the implied warranty of
+MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
+General Public License for more details.
+
+You should have received a copy of the GNU General Public License
+along with this program; if not, write to the Free Software
+Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
+02110-1301, USA.
+
+-}
+
 module Ganeti.HTools.Rapi
     (
-      getNodes
-    , getInstances
+      loadData
+    , parseData
     ) where
 
 import Network.Curl
 import Network.Curl.Types ()
-import Network.Curl.Code
-import Data.Either ()
-import Data.Maybe
 import Control.Monad
-import Text.JSON
+import Text.JSON (JSObject, JSValue, fromJSObject, decodeStrict)
+import Text.JSON.Types (JSValue(..))
 import Text.Printf (printf)
-import Ganeti.HTools.Utils ()
-
-
--- Some constants
 
--- | The fixed drbd overhead per disk (only used with 1.2's sdx_size)
-drbdOverhead = 128
+import Ganeti.HTools.Utils
+import Ganeti.HTools.Loader
+import Ganeti.HTools.Types
+import qualified Ganeti.HTools.Group as Group
+import qualified Ganeti.HTools.Node as Node
+import qualified Ganeti.HTools.Instance as Instance
 
-{-- Our cheap monad-like stuff.
-
-Thi is needed since Either e a is already a monad instance somewhere
-in the standard libraries (Control.Monad.Error) and we don't need that
-entire thing.
-
--}
-combine :: (Either String a) -> (a -> Either String b)  -> (Either String b)
-combine (Left s) _ = Left s
-combine (Right s) f = f s
-
-ensureList :: [Either String a] -> Either String [a]
-ensureList lst =
-    foldr (\elem accu ->
-               case (elem, accu) of
-                 (Left x, _) -> Left x
-                 (_, Left x) -> Left x -- should never happen
-                 (Right e, Right a) -> Right (e:a)
-          )
-    (Right []) lst
-
-listHead :: Either String [a] -> Either String a
-listHead lst =
-    case lst of
-      Left x -> Left x
-      Right (x:_) -> Right x
-      Right [] -> Left "List empty"
-
-loadJSArray :: String -> Either String [JSObject JSValue]
-loadJSArray s = resultToEither $ decodeStrict s
-
-fromObj :: JSON a => String -> JSObject JSValue -> Either String a
-fromObj k o =
-    case lookup k (fromJSObject o) of
-      Nothing -> Left $ printf "key '%s' not found" k
-      Just val -> resultToEither $ readJSON val
-
-getStringElement :: String -> JSObject JSValue -> Either String String
-getStringElement = fromObj
-
-getIntElement :: String -> JSObject JSValue -> Either String Int
-getIntElement = fromObj
-
-getListElement :: String -> JSObject JSValue
-               -> Either String [JSValue]
-getListElement = fromObj
-
-readString :: JSValue -> Either String String
-readString v =
-    case v of
-      JSString s -> Right $ fromJSString s
-      _ -> Left "Wrong JSON type"
-
-concatElems :: Either String String
-            -> Either String String
-            -> Either String String
-concatElems = apply2 (\x y -> x ++ "|" ++ y)
-
-apply1 :: (a -> b) -> Either String a -> Either String b
-apply1 fn a =
-    case a of
-      Left x -> Left x
-      Right y -> Right $ fn y
-
-apply2 :: (a -> b -> c)
-       -> Either String a
-       -> Either String b
-       -> Either String c
-apply2 fn a b =
-    case (a, b) of
-      (Right x, Right y) -> Right $ fn x y
-      (Left x, _) -> Left x
-      (_, Left y) -> Left y
-
-getUrl :: String -> IO (Either String String)
+-- | Read an URL via curl and return the body if successful.
+getUrl :: (Monad m) => String -> IO (m String)
 getUrl url = do
   (code, body) <- curlGetString url [CurlSSLVerifyPeer False,
-                                     CurlSSLVerifyHost 0]
+                                     CurlSSLVerifyHost 0,
+                                     CurlTimeout (fromIntegral queryTimeout),
+                                     CurlConnectTimeout
+                                     (fromIntegral connTimeout)]
   return (case code of
-            CurlOK -> Right body
-            _ -> Left $ printf "Curl error for '%s', error %s"
+            CurlOK -> return body
+            _ -> fail $ printf "Curl error for '%s', error %s"
                  url (show code))
 
-tryRapi :: String -> String -> IO (Either String String)
-tryRapi url1 url2 =
-    do
-      body1 <- getUrl url1
-      (case body1 of
-         Left _ -> getUrl url2
-         Right _ -> return body1)
-
-getInstances :: String -> IO (Either String String)
-getInstances master =
-    let
-        url2 = printf "https://%s:5080/2/instances?bulk=1" master
-        url1 = printf "http://%s:5080/instances?bulk=1" master
-    in do
-      body <- tryRapi url1 url2
-      let inst = body `combine` loadJSArray `combine` (parseList parseInstance)
-      return inst
-
-getNodes :: String -> IO (Either String String)
-getNodes master =
-    let
-        url2 = printf "https://%s:5080/2/nodes?bulk=1" master
-        url1 = printf "http://%s:5080/nodes?bulk=1" master
-    in do
-      body <- tryRapi url1 url2
-      let inst = body `combine` loadJSArray `combine` (parseList parseNode)
-      return inst
-
-parseList :: (JSObject JSValue -> Either String String)
-          -> [JSObject JSValue]
-          ->Either String String
-parseList fn idata =
-    let ml = ensureList $ map fn idata
-    in ml `combine` (Right . unlines)
-
-parseInstance :: JSObject JSValue -> Either String String
-parseInstance a =
-    let name = getStringElement "name" a
-        disk = case getIntElement "disk_usage" a of
-                 Left _ -> let log_sz = apply2 (+)
-                                        (getIntElement "sda_size" a)
-                                        (getIntElement "sdb_size" a)
-                           in apply2 (+) log_sz (Right $ drbdOverhead * 2)
-                 Right x -> Right x
-        bep = fromObj "beparams" a
-        pnode = getStringElement "pnode" a
-        snode = (listHead $ getListElement "snodes" a) `combine` readString
-        mem = case bep of
-                Left _ -> getIntElement "admin_ram" a
-                Right o -> getIntElement "memory" o
-        running = getStringElement "status" a
-    in
-      concatElems name $
-                  concatElems (show `apply1` mem) $
-                  concatElems (show `apply1` disk) $
-                  concatElems running $
-                  concatElems pnode snode
-
-parseNode :: JSObject JSValue -> Either String String
-parseNode a =
-    let name = getStringElement "name" a
-        mtotal = getIntElement "mtotal" a
-        mnode = getIntElement "mnode" a
-        mfree = getIntElement "mfree" a
-        dtotal = getIntElement "dtotal" a
-        dfree = getIntElement "dfree" a
-    in concatElems name $
-       concatElems (show `apply1` mtotal) $
-       concatElems (show `apply1` mnode) $
-       concatElems (show `apply1` mfree) $
-       concatElems (show `apply1` dtotal) (show `apply1` dfree)
+-- | Append the default port if not passed in.
+formatHost :: String -> String
+formatHost master =
+    if ':' `elem` master then  master
+    else "https://" ++ master ++ ":5080"
+
+-- | Parse a instance list in JSON format.
+getInstances :: NameAssoc
+             -> String
+             -> Result [(String, Instance.Instance)]
+getInstances ktn body =
+    loadJSArray "Parsing instance data" body >>=
+    mapM (parseInstance ktn . fromJSObject)
+
+-- | Parse a node list in JSON format.
+getNodes :: NameAssoc -> String -> Result [(String, Node.Node)]
+getNodes ktg body = loadJSArray "Parsing node data" body >>=
+                mapM (parseNode ktg . fromJSObject)
+
+-- | Parse a group list in JSON format.
+getGroups :: String -> Result [(String, Group.Group)]
+getGroups body = loadJSArray "Parsing group data" body >>=
+                mapM (parseGroup . fromJSObject)
+
+-- | Construct an instance from a JSON object.
+parseInstance :: NameAssoc
+              -> [(String, JSValue)]
+              -> Result (String, Instance.Instance)
+parseInstance ktn a = do
+  name <- tryFromObj "Parsing new instance" a "name"
+  let owner_name = "Instance '" ++ name ++ "'"
+  let extract s x = tryFromObj owner_name x s
+  disk <- extract "disk_usage" a
+  beparams <- liftM fromJSObject (extract "beparams" a)
+  omem <- extract "oper_ram" a
+  mem <- (case omem of
+            JSRational _ _ -> annotateResult owner_name (fromJVal omem)
+            _ -> extract "memory" beparams)
+  vcpus <- extract "vcpus" beparams
+  pnode <- extract "pnode" a >>= lookupNode ktn name
+  snodes <- extract "snodes" a
+  snode <- (if null snodes then return Node.noSecondary
+            else readEitherString (head snodes) >>= lookupNode ktn name)
+  running <- extract "status" a
+  tags <- extract "tags" a
+  let inst = Instance.create name mem disk vcpus running tags pnode snode
+  return (name, inst)
+
+-- | Construct a node from a JSON object.
+parseNode :: NameAssoc -> [(String, JSValue)] -> Result (String, Node.Node)
+parseNode ktg a = do
+  name <- tryFromObj "Parsing new node" a "name"
+  let extract s = tryFromObj ("Node '" ++ name ++ "'") a s
+  offline <- extract "offline"
+  drained <- extract "drained"
+  guuid   <- extract "group.uuid" >>= lookupGroup ktg name
+  node <- (if offline || drained
+           then return $ Node.create name 0 0 0 0 0 0 True guuid
+           else do
+             mtotal  <- extract "mtotal"
+             mnode   <- extract "mnode"
+             mfree   <- extract "mfree"
+             dtotal  <- extract "dtotal"
+             dfree   <- extract "dfree"
+             ctotal  <- extract "ctotal"
+             return $ Node.create name mtotal mnode mfree
+                    dtotal dfree ctotal False guuid)
+  return (name, node)
+
+-- | Construct a group from a JSON object.
+parseGroup :: [(String, JSValue)] -> Result (String, Group.Group)
+parseGroup a = do
+  name <- tryFromObj "Parsing new group" a "name"
+  let extract s = tryFromObj ("Group '" ++ name ++ "'") a s
+  uuid <- extract "uuid"
+  apol <- extract "alloc_policy"
+  return (uuid, Group.create name uuid apol)
+
+-- | Loads the raw cluster data from an URL.
+readData :: String -- ^ Cluster or URL to use as source
+         -> IO (Result String, Result String, Result String, Result String)
+readData master = do
+  let url = formatHost master
+  group_body <- getUrl $ printf "%s/2/groups?bulk=1" url
+  node_body <- getUrl $ printf "%s/2/nodes?bulk=1" url
+  inst_body <- getUrl $ printf "%s/2/instances?bulk=1" url
+  tags_body <- getUrl $ printf "%s/2/tags" url
+  return (group_body, node_body, inst_body, tags_body)
+
+-- | Builds the cluster data from the raw Rapi content
+parseData :: (Result String, Result String, Result String, Result String)
+          -> Result ClusterData
+parseData (group_body, node_body, inst_body, tags_body) = do
+  group_data <- group_body >>= getGroups
+  let (group_names, group_idx) = assignIndices group_data
+  node_data <- node_body >>= getNodes group_names
+  let (node_names, node_idx) = assignIndices node_data
+  inst_data <- inst_body >>= getInstances node_names
+  let (_, inst_idx) = assignIndices inst_data
+  tags_data <- tags_body >>= (fromJResult "Parsing tags data" . decodeStrict)
+  return (ClusterData group_idx node_idx inst_idx tags_data)
+
+-- | Top level function for data loading
+loadData :: String -- ^ Cluster or URL to use as source
+         -> IO (Result ClusterData)
+loadData master = readData master >>= return . parseData