Text: read/write the allocation policy
[ganeti-local] / hail.hs
diff --git a/hail.hs b/hail.hs
index ca50131..a408987 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, fromMaybe)
+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.Utils
 import Ganeti.HTools.Types
-
--- | Command line options structure.
-data Options = Options
-    { optShowNodes :: Bool           -- ^ Whether to show node status
-    , optShowCmds  :: Maybe FilePath -- ^ Whether to show the command list
-    , optOneline   :: Bool           -- ^ Switch output to a single line
-    , optNodef     :: FilePath       -- ^ Path to the nodes file
-    , optNodeSet   :: Bool           -- ^ The nodes have been set by options
-    , optInstf     :: FilePath       -- ^ Path to the instances file
-    , optInstSet   :: Bool           -- ^ The insts have been set by options
-    , optMaxLength :: Int            -- ^ Stop after this many steps
-    , optMaster    :: String         -- ^ Collect data from RAPI
-    , optVerbose   :: Int            -- ^ Verbosity level
-    , optOffline   :: [String]       -- ^ Names of offline nodes
-    , optMinScore  :: Cluster.Score  -- ^ The minimum score we aim for
-    , optShowVer   :: Bool           -- ^ Just show the program version
-    , optShowHelp  :: Bool           -- ^ Just show the help
-    } deriving Show
-
-instance CLI.CLIOptions Options where
-    showVersion = optShowVer
-    showHelp    = optShowHelp
-
--- | Default values for the command line options.
-defaultOptions :: Options
-defaultOptions  = Options
- { optShowNodes = False
- , optShowCmds  = Nothing
- , optOneline   = False
- , optNodef     = "nodes"
- , optNodeSet   = False
- , optInstf     = "instances"
- , optInstSet   = False
- , optMaxLength = -1
- , optMaster    = ""
- , optVerbose   = 1
- , optOffline   = []
- , optMinScore  = 1e-9
- , optShowVer   = False
- , optShowHelp  = False
- }
+import Ganeti.HTools.Loader (RqType(..), Request(..))
 
 -- | Options list and functions
-options :: [OptDescr (Options -> Options)]
-options =
-    [ Option ['p']     ["print-nodes"]
-      (NoArg (\ opts -> opts { optShowNodes = True }))
-      "print the final node list"
-    , Option ['C']     ["print-commands"]
-      (OptArg ((\ f opts -> opts { optShowCmds = Just f }) . fromMaybe "-")
-                  "FILE")
-      "print the ganeti command list for reaching the solution,\
-      \if an argument is passed then write the commands to a file named\
-      \ as such"
-    , Option ['o']     ["oneline"]
-      (NoArg (\ opts -> opts { optOneline = True }))
-      "print the ganeti command list for reaching the solution"
-    , Option ['n']     ["nodes"]
-      (ReqArg (\ f opts -> opts { optNodef = f, optNodeSet = True }) "FILE")
-      "the node list FILE"
-    , Option ['i']     ["instances"]
-      (ReqArg (\ f opts -> opts { optInstf =  f, optInstSet = True }) "FILE")
-      "the instance list FILE"
-    , Option ['m']     ["master"]
-      (ReqArg (\ m opts -> opts { optMaster = m }) "ADDRESS")
-      "collect data via RAPI at the given ADDRESS"
-    , Option ['l']     ["max-length"]
-      (ReqArg (\ i opts -> opts { optMaxLength =  (read i)::Int }) "N")
-      "cap the solution at this many moves (useful for very unbalanced \
-      \clusters)"
-    , Option ['v']     ["verbose"]
-      (NoArg (\ opts -> opts { optVerbose = (optVerbose opts) + 1 }))
-      "increase the verbosity level"
-    , Option ['q']     ["quiet"]
-      (NoArg (\ opts -> opts { optVerbose = (optVerbose opts) - 1 }))
-      "decrease the verbosity level"
-    , Option ['O']     ["offline"]
-      (ReqArg (\ n opts -> opts { optOffline = n:optOffline opts }) "NODE")
-      " set node as offline"
-    , Option ['e']     ["min-score"]
-      (ReqArg (\ e opts -> opts { optMinScore = read e }) "EPSILON")
-      " mininum score to aim for"
-    , Option ['V']     ["version"]
-      (NoArg (\ opts -> opts { optShowVer = True}))
-      "show the version of the program"
-    , Option ['h']     ["help"]
-      (NoArg (\ opts -> opts { optShowHelp = True}))
-      "show help"
-    ]
-
--- | Try to allocate an instance on the cluster
-tryAlloc :: NodeList
-         -> InstanceList
-         -> Instance.Instance
-         -> Int
-         -> Result [Node.Node]
-tryAlloc nl il xi _ = Bad "alloc not implemented"
-
--- | Try to allocate an instance on the cluster
-tryReloc :: NodeList
-         -> InstanceList
-         -> Int
-         -> Int
-         -> [Int]
-         -> Result [Node.Node]
-tryReloc nl il xid reqn ex_idx =
-    let all_nodes = Container.elems nl
-        valid_nodes = filter (not . flip elem ex_idx . idx) all_nodes
-    in Ok (take reqn valid_nodes)
+options :: [OptType]
+options = [oPrintNodes, oShowVer, oShowHelp]
+
+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 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
 
 -- | Main function.
 main :: IO ()
 main = do
   cmd_args <- System.getArgs
-  (opts, 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 input_file = head args
+      shownodes = optShowNodes opts
   input_data <- readFile input_file
 
   request <- case (parseData input_data) of
                Bad err -> do
-                 putStrLn $ "Error: " ++ err
+                 hPutStrLn stderr $ "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 (ok, info, rn) = case new_nodes of
-               Ok sn -> (True, "Request successfull", map name sn)
-               Bad s -> (False, "Request failed: " ++ s, [])
-      resp = formatResponse ok info rn
+  let Request rq _ nl _ _ = request
+
+  when (isJust shownodes) $ do
+         hPutStrLn stderr "Initial cluster status:"
+         hPutStrLn stderr $ Cluster.printNodes nl (fromJust shownodes)
+
+  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