Add maybePrintInsts for the instance listing
[ganeti-local] / hail.hs
diff --git a/hail.hs b/hail.hs
index c9d6f5f..78eb8e1 100644 (file)
--- a/hail.hs
+++ b/hail.hs
 
 -}
 
+{-
+
+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 Main (main) where
 
 import Data.List
-import Data.Function
 import Data.Maybe (isJust, fromJust)
 import Monad
-import System
+import System (exitWith, ExitCode(..))
 import System.IO
-import System.Console.GetOpt
 import qualified System
 
-import Text.Printf (printf)
-
-import qualified Ganeti.HTools.Container as Container
 import qualified Ganeti.HTools.Cluster as Cluster
-import qualified Ganeti.HTools.Node as Node
-import qualified Ganeti.HTools.Instance as Instance
-import qualified Ganeti.HTools.CLI as CLI
+
+import Ganeti.HTools.CLI
 import Ganeti.HTools.IAlloc
 import Ganeti.HTools.Types
-
--- | Command line options structure.
-data Options = Options
-    { optShowVer   :: Bool           -- ^ Just show the program version
-    , optShowHelp  :: Bool           -- ^ Just show the help
-    } deriving Show
-
--- | Default values for the command line options.
-defaultOptions :: Options
-defaultOptions  = Options
- { optShowVer   = False
- , optShowHelp  = False
- }
-
-instance CLI.CLIOptions Options where
-    showVersion = optShowVer
-    showHelp    = optShowHelp
+import Ganeti.HTools.Loader (RqType(..), Request(..), ClusterData(..))
+import Ganeti.HTools.ExtLoader (loadExternalData)
 
 -- | Options list and functions
-options :: [OptDescr (Options -> Options)]
+options :: [OptType]
 options =
-    [ Option ['V']     ["version"]
-      (NoArg (\ opts -> opts { optShowVer = True}))
-      "show the version of the program"
-    , Option ['h']     ["help"]
-      (NoArg (\ opts -> opts { optShowHelp = True}))
-      "show help"
+    [ oPrintNodes
+    , oDataFile
+    , oNodeSim
+    , oShowVer
+    , oShowHelp
     ]
 
--- | Compute online nodes from a NodeList
-getOnline :: NodeList -> [Node.Node]
-getOnline = filter (not . Node.offline) . Container.elems
-
--- | Try to allocate an instance on the cluster
-tryAlloc :: (Monad m) =>
-            NodeList
-         -> InstanceList
-         -> Instance.Instance
-         -> Int
-         -> m [(Maybe NodeList, [Node.Node])]
-tryAlloc nl _ inst 2 =
-    let all_nodes = getOnline nl
-        all_pairs = liftM2 (,) all_nodes all_nodes
-        ok_pairs = filter (\(x, y) -> Node.idx x /= Node.idx y) all_pairs
-        sols = map (\(p, s) ->
-                        (fst $ Cluster.allocateOnPair nl inst p s, [p, s]))
-               ok_pairs
-    in return sols
-
-tryAlloc nl _ inst 1 =
-    let all_nodes = getOnline nl
-        sols = map (\p -> (fst $ Cluster.allocateOnSingle nl inst p, [p]))
-               all_nodes
-    in return sols
-
-tryAlloc _ _ _ reqn = fail $ "Unsupported number of alllocation \
-                             \destinations required (" ++ (show reqn) ++
-                                               "), only two supported"
-
--- | Try to allocate an instance on the cluster
-tryReloc :: (Monad m) =>
-            NodeList
-         -> InstanceList
-         -> Int
-         -> Int
-         -> [Int]
-         -> m [(Maybe NodeList, [Node.Node])]
-tryReloc nl il xid 1 ex_idx =
-    let all_nodes = getOnline nl
-        inst = Container.find xid il
-        ex_idx' = (Instance.pnode inst):ex_idx
-        valid_nodes = filter (not . flip elem ex_idx' . idx) all_nodes
-        valid_idxes = map Node.idx valid_nodes
-        sols1 = map (\x -> let (mnl, _, _, _) =
-                                    Cluster.applyMove nl inst
-                                               (Cluster.ReplaceSecondary x)
-                            in (mnl, [Container.find x nl])
-                     ) valid_idxes
-    in return sols1
-
-tryReloc _ _ _ reqn _  = fail $ "Unsupported number of relocation \
-                                \destinations required (" ++ (show reqn) ++
-                                                  "), only one supported"
-
-filterFails :: (Monad m) => [(Maybe NodeList, [Node.Node])]
-            -> m [(NodeList, [Node.Node])]
-filterFails sols =
-    if null sols then fail "No nodes onto which to allocate at all"
-    else let sols' = filter (isJust . fst) sols
-         in if null sols' then
-                fail "No valid allocation solutions"
-            else
-                return $ map (\(x, y) -> (fromJust x, y)) sols'
-
-processResults :: (Monad m) => [(NodeList, [Node.Node])]
-               -> m (String, [Node.Node])
-processResults sols =
-    let sols' = map (\(nl', ns) -> (Cluster.compCV  nl', ns)) sols
-        sols'' = sortBy (compare `on` fst) sols'
-        (best, w) = head sols''
-        (worst, l) = last sols''
-        info = printf "Valid results: %d, best score: %.8f for node(s) %s, \
-                      \worst score: %.8f for node(s) %s" (length sols'')
-                      best (intercalate "/" . map Node.name $ w)
-                      worst (intercalate "/" . map Node.name $ l)
-    in return (info, w)
+processResults :: (Monad m) =>
+                  RqType -> Cluster.AllocSolution
+               -> m Cluster.AllocSolution
+processResults _ (Cluster.AllocSolution { Cluster.asSolutions = [],
+                                          Cluster.asLog = msgs }) =
+  fail $ intercalate ", " msgs
+
+processResults (Evacuate _) as = return as
+
+processResults _ as =
+    case Cluster.asSolutions as of
+      _:[] -> return as
+      _ -> fail "Internal error: multiple allocation solutions"
+
+-- | Process a request and return new node lists
+processRequest :: Request
+               -> Result Cluster.AllocSolution
+processRequest request =
+  let Request rqtype (ClusterData gl nl il _) = request
+  in case rqtype of
+       Allocate xi reqn -> Cluster.tryMGAlloc gl nl il xi reqn
+       Relocate idx reqn exnodes -> Cluster.tryReloc nl il idx reqn exnodes
+       Evacuate exnodes -> Cluster.tryEvac nl il exnodes
+
+-- | Reads the request from the data file(s)
+readRequest :: Options -> [String] -> IO Request
+readRequest opts args = do
+  when (null args) $ do
+         hPutStrLn stderr "Error: this program needs an input file."
+         exitWith $ ExitFailure 1
+
+  input_data <- readFile (head args)
+  r1 <- case (parseData input_data) of
+          Bad err -> do
+            hPutStrLn stderr $ "Error: " ++ err
+            exitWith $ ExitFailure 1
+          Ok rq -> return rq
+  r2 <- if isJust (optDataFile opts) ||  (not . null . optNodeSim) opts
+        then  do
+          cdata <- loadExternalData opts
+          let Request rqt _ = r1
+          return $ Request rqt cdata
+        else return r1
+  return r2
 
 -- | Main function.
 main :: IO ()
 main = do
   cmd_args <- System.getArgs
-  (_, args) <- CLI.parseOpts cmd_args "hail" options defaultOptions
+  (opts, args) <- parseOpts cmd_args "hail" options
 
-  when (null args) $ do
-         hPutStrLn stderr "Error: this program needs an input file."
-         exitWith $ ExitFailure 1
+  let shownodes = optShowNodes opts
+
+  request <- readRequest opts args
+
+  let Request rq cdata = request
+
+  when (isJust shownodes) $ do
+         hPutStrLn stderr "Initial cluster status:"
+         hPutStrLn stderr $ Cluster.printNodes (cdNodes cdata)
+                       (fromJust shownodes)
 
-  let input_file = head args
-  input_data <- readFile input_file
-
-  request <- case (parseData input_data) of
-               Bad err -> do
-                 putStrLn $ "Error: " ++ err
-                 exitWith $ ExitFailure 1
-               Ok rq -> return rq
-
-  let Request rqtype nl il csf = request
-      new_nodes = case rqtype of
-                    Allocate xi reqn -> tryAlloc nl il xi reqn
-                    Relocate idx reqn exnodes ->
-                        tryReloc nl il idx reqn exnodes
-  let sols = new_nodes >>= filterFails >>= processResults
-  let (ok, info, rn) = case sols of
-               Ok (info, sn) -> (True, "Request successful: " ++ info,
-                                     map ((++ csf) . name) sn)
-               Bad s -> (False, "Request failed: " ++ s, [])
-      resp = formatResponse ok info rn
+  let sols = processRequest request >>= processResults rq
+  let (ok, info, rn) =
+          case sols of
+            Ok as -> (True, "Request successful: " ++
+                            intercalate ", " (Cluster.asLog as),
+                      Cluster.asSolutions as)
+            Bad s -> (False, "Request failed: " ++ s, [])
+      resp = formatResponse ok info rq rn
   putStrLn resp