Add a small class for Nodes and Instances
[ganeti-local] / Ganeti / HTools / IAlloc.hs
index 483d6c9..241bbd8 100644 (file)
@@ -9,136 +9,100 @@ module Ganeti.HTools.IAlloc
     ) where
 
 import Data.Either ()
     ) where
 
 import Data.Either ()
-import Data.Maybe
+--import Data.Maybe
 import Control.Monad
 import Control.Monad
-import Text.JSON
-import Text.Printf (printf)
-import Ganeti.HTools.Utils ()
-
-
--- Some constants
-
-{-- 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
-
-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 $ 128 * 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)
-
-parseData :: String -> Maybe String
-
-parseData x = Just x
+import Text.JSON (JSObject, JSValue(JSBool, JSString, JSArray),
+                  makeObj, encodeStrict, decodeStrict,
+                  fromJSObject, toJSString)
+--import Text.Printf (printf)
+import qualified Ganeti.HTools.Node as Node
+import qualified Ganeti.HTools.Instance as Instance
+import Ganeti.HTools.Loader
+import Ganeti.HTools.Utils
+import Ganeti.HTools.Types
+
+data RqType
+    = Allocate String Instance.Instance
+    | Relocate Int
+    deriving (Show)
+
+data Request = Request RqType IdxNode IdxInstance NameList NameList
+    deriving (Show)
+
+parseBaseInstance :: String
+                  -> JSObject JSValue
+                  -> Result (String, Instance.Instance)
+parseBaseInstance n a = do
+  disk <- case fromObj "disk_usage" a of
+            Bad _ -> do
+                all_d <- fromObj "disks" a >>= asObjectList
+                szd <- mapM (fromObj "size") all_d
+                let sze = map (+128) szd
+                    szf = (sum sze)::Int
+                return szf
+            x@(Ok _) -> x
+  mem <- fromObj "memory" a
+  let running = "running"
+  return $ (n, Instance.create n mem disk running 0 0)
+
+parseInstance :: NameAssoc
+              -> String
+              -> JSObject JSValue
+              -> Result (String, Instance.Instance)
+parseInstance ktn n a = do
+    base <- parseBaseInstance n a
+    nodes <- fromObj "nodes" a
+    pnode <- readEitherString $ head nodes
+    snode <- readEitherString $ (head . tail) nodes
+    pidx <- lookupNode ktn n pnode
+    sidx <- lookupNode ktn n snode
+    return (n, Instance.setBoth (snd base) pidx sidx)
+
+parseNode :: String -> JSObject JSValue -> Result (String, Node.Node)
+parseNode n a = do
+    let name = n
+    mtotal <- fromObj "total_memory" a
+    mnode <- fromObj "reserved_memory" a
+    mfree <- fromObj "free_memory" a
+    dtotal <- fromObj "total_disk" a
+    dfree <- fromObj "free_disk" a
+    offline <- fromObj "offline" a
+    drained <- fromObj "offline" a
+    return $ (name, Node.create n mtotal mnode mfree dtotal dfree
+                      (offline || drained))
+
+parseData :: String -> Result Request
+parseData body = do
+  decoded <- fromJResult $ decodeStrict body
+  let obj = decoded
+  -- request parser
+  request <- fromObj "request" obj
+  rname <- fromObj "name" request
+  -- existing node parsing
+  nlist <- fromObj "nodes" obj
+  let ndata = fromJSObject nlist
+  nobj <- (mapM (\(x,y) -> asJSObject y >>= parseNode x)) ndata
+  let (ktn, nl) = assignIndices nobj
+  -- existing instance parsing
+  ilist <- fromObj "instances" obj
+  let idata = fromJSObject ilist
+  iobj <- (mapM (\(x,y) -> asJSObject y >>= parseInstance ktn x)) idata
+  let (kti, il) = assignIndices iobj
+  optype <- fromObj "type" request
+  rqtype <-
+      case optype of
+        "allocate" ->
+            do
+              inew <- parseBaseInstance rname request
+              let (iname, io) = inew
+              return $ Allocate iname io
+        "relocate" ->
+            do
+              ridx <- lookupNode kti rname rname
+              return $ Relocate ridx
+        other -> fail $ ("Invalid request type '" ++ other ++ "'")
+
+  return $ Request rqtype nl il (swapPairs ktn) (swapPairs kti)
 
 formatResponse :: Bool -> String -> [String] -> String
 formatResponse success info nodes =
 
 formatResponse :: Bool -> String -> [String] -> String
 formatResponse success info nodes =