Add RAPI support to hn1
authorIustin Pop <iustin@google.com>
Sat, 14 Feb 2009 08:05:06 +0000 (09:05 +0100)
committerIustin Pop <iustin@google.com>
Sat, 14 Feb 2009 08:05:06 +0000 (09:05 +0100)
This patch moves a function to Utils and changes hn1 to be able to take
data from RAPI.

src/Rapi.hs
src/Utils.hs
src/hbal.hs
src/hn1.hs

index 3405e36..263cf13 100644 (file)
@@ -3,7 +3,10 @@
 -}
 
 module Rapi
-    where
+    (
+      getNodes
+    , getInstances
+    ) where
 
 import Network.Curl
 import Network.Curl.Types ()
index d771a0b..5325d6e 100644 (file)
@@ -4,6 +4,9 @@ module Utils where
 
 import Data.List
 import Data.Either
+import System
+import System.IO
+import Monad
 
 import Debug.Trace
 
@@ -65,3 +68,13 @@ stdDev lst =
 -- | Coefficient of variation.
 varianceCoeff :: Floating a => [a] -> a
 varianceCoeff lst = (stdDev lst) / (fromIntegral $ length lst)
+
+-- | Get a Right result or print the error and exit
+readData :: (String -> IO (Either String String)) -> String -> IO String
+readData fn host = do
+  nd <- fn host
+  when (isLeft nd) $
+       do
+         putStrLn $ fromLeft nd
+         exitWith $ ExitFailure 1
+  return $ fromRight nd
index 58a3008..5648371 100644 (file)
@@ -121,16 +121,6 @@ parseOpts argv =
           ioError (userError (concat errs ++ usageInfo header options))
       where header = "Usage: hbal [OPTION...]"
 
--- | Get a Right result or print the error and exit
-readData :: (String -> IO (Either String String)) -> String -> IO String
-readData fn host = do
-  nd <- fn host
-  when (isLeft nd) $
-       do
-         putStrLn $ fromLeft nd
-         exitWith $ ExitFailure 1
-  return $ fromRight nd
-
 -- | Main function.
 main :: IO ()
 main = do
index 73d7549..6efbf8d 100644 (file)
@@ -17,6 +17,8 @@ import Text.Printf (printf)
 import qualified Container
 import qualified Instance
 import qualified Cluster
+import Utils
+import Rapi
 
 -- | Command line options structure.
 data Options = Options
@@ -28,6 +30,7 @@ data Options = Options
     , optMaxRemovals :: Int
     , optMinDelta    :: Int
     , optMaxDelta    :: Int
+    , optMaster    :: String
     } deriving Show
 
 -- | Default values for the command line options.
@@ -41,6 +44,7 @@ defaultOptions    = Options
  , optMaxRemovals = -1
  , optMinDelta    = 0
  , optMaxDelta    = -1
+ , optMaster    = ""
  }
 
 {- | Start computing the solution at the given depth and recurse until
@@ -99,6 +103,9 @@ options =
      , Option ['l']     ["min-delta"]
       (ReqArg (\ i opts -> opts { optMinDelta =  (read i)::Int }) "L")
       "return once a solution with delta L or lower has been found"
+     , Option ['m']     ["master"]
+      (ReqArg (\ m opts -> opts { optMaster = m }) "ADDRESS")
+      "collect data via RAPI at the given ADDRESS"
      ]
 
 -- | Command line parser, using the 'options' structure.
@@ -117,9 +124,15 @@ main = do
   cmd_args <- System.getArgs
   (opts, _) <- parseOpts cmd_args
   let min_depth = optMinDepth opts
-  (nl, il, ktn, kti) <- liftM2 Cluster.loadData
-                        (readFile $ optNodef opts)
-                        (readFile $ optInstf opts)
+  let (node_data, inst_data) =
+          case optMaster opts of
+            "" -> (readFile $ optNodef opts,
+                   readFile $ optInstf opts)
+            host -> (readData getNodes host,
+                     readData getInstances host)
+
+  (nl, il, ktn, kti) <- liftM2 Cluster.loadData node_data inst_data
+
   printf "Loaded %d nodes, %d instances\n"
              (Container.size nl)
              (Container.size il)