Statistics
| Branch: | Tag: | Revision:

root / hail.hs @ adc5c176

History | View | Annotate | Download (3.7 kB)

1 585d4420 Iustin Pop
{-| Solver for N+1 cluster errors
2 585d4420 Iustin Pop
3 585d4420 Iustin Pop
-}
4 585d4420 Iustin Pop
5 e2fa2baf Iustin Pop
{-
6 e2fa2baf Iustin Pop
7 e2fa2baf Iustin Pop
Copyright (C) 2009 Google Inc.
8 e2fa2baf Iustin Pop
9 e2fa2baf Iustin Pop
This program is free software; you can redistribute it and/or modify
10 e2fa2baf Iustin Pop
it under the terms of the GNU General Public License as published by
11 e2fa2baf Iustin Pop
the Free Software Foundation; either version 2 of the License, or
12 e2fa2baf Iustin Pop
(at your option) any later version.
13 e2fa2baf Iustin Pop
14 e2fa2baf Iustin Pop
This program is distributed in the hope that it will be useful, but
15 e2fa2baf Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
16 e2fa2baf Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17 e2fa2baf Iustin Pop
General Public License for more details.
18 e2fa2baf Iustin Pop
19 e2fa2baf Iustin Pop
You should have received a copy of the GNU General Public License
20 e2fa2baf Iustin Pop
along with this program; if not, write to the Free Software
21 e2fa2baf Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22 e2fa2baf Iustin Pop
02110-1301, USA.
23 e2fa2baf Iustin Pop
24 e2fa2baf Iustin Pop
-}
25 e2fa2baf Iustin Pop
26 585d4420 Iustin Pop
module Main (main) where
27 585d4420 Iustin Pop
28 585d4420 Iustin Pop
import Data.List
29 f3d53161 Iustin Pop
import Data.Maybe (isJust, fromJust)
30 585d4420 Iustin Pop
import Monad
31 0903280b Iustin Pop
import System (exitWith, ExitCode(..))
32 585d4420 Iustin Pop
import System.IO
33 585d4420 Iustin Pop
import qualified System
34 585d4420 Iustin Pop
35 585d4420 Iustin Pop
import Text.Printf (printf)
36 585d4420 Iustin Pop
37 585d4420 Iustin Pop
import qualified Ganeti.HTools.Cluster as Cluster
38 585d4420 Iustin Pop
import qualified Ganeti.HTools.Node as Node
39 0427285d Iustin Pop
40 0427285d Iustin Pop
import Ganeti.HTools.CLI
41 585d4420 Iustin Pop
import Ganeti.HTools.IAlloc
42 e4c5beaf Iustin Pop
import Ganeti.HTools.Types
43 19f38ee8 Iustin Pop
import Ganeti.HTools.Loader (RqType(..), Request(..))
44 585d4420 Iustin Pop
45 585d4420 Iustin Pop
-- | Options list and functions
46 0427285d Iustin Pop
options :: [OptType]
47 f3d53161 Iustin Pop
options = [oPrintNodes, oShowVer, oShowHelp]
48 f826c5e0 Iustin Pop
49 54365762 Iustin Pop
processResults :: (Monad m) =>
50 54365762 Iustin Pop
                  RqType -> Cluster.AllocSolution
51 54365762 Iustin Pop
               -> m (String, Cluster.AllocSolution)
52 54365762 Iustin Pop
processResults _ (_, _, []) = fail "No valid allocation solutions"
53 54365762 Iustin Pop
processResults (Evacuate _) as@(fstats, successes, sols) =
54 54365762 Iustin Pop
    let best = fst $ head sols
55 54365762 Iustin Pop
        tfails = length fstats
56 54365762 Iustin Pop
        info = printf "for last allocation, successes %d, failures %d,\
57 54365762 Iustin Pop
                      \ best score: %.8f" successes tfails best::String
58 54365762 Iustin Pop
    in return (info, as)
59 54365762 Iustin Pop
60 54365762 Iustin Pop
processResults _ as@(fstats, successes, sols) =
61 478df686 Iustin Pop
    case sols of
62 23f9ab76 Iustin Pop
      (best, (_, _, w)):[] ->
63 478df686 Iustin Pop
          let tfails = length fstats
64 478df686 Iustin Pop
              info = printf "successes %d, failures %d,\
65 478df686 Iustin Pop
                            \ best score: %.8f for node(s) %s"
66 fbb95f28 Iustin Pop
                            successes tfails
67 478df686 Iustin Pop
                            best (intercalate "/" . map Node.name $ w)::String
68 54365762 Iustin Pop
          in return (info, as)
69 23f9ab76 Iustin Pop
      _ -> fail "Internal error: multiple allocation solutions"
70 585d4420 Iustin Pop
71 78694255 Iustin Pop
-- | Process a request and return new node lists
72 f2280553 Iustin Pop
processRequest :: Request
73 478df686 Iustin Pop
               -> Result Cluster.AllocSolution
74 78694255 Iustin Pop
processRequest request =
75 3e4480e0 Iustin Pop
  let Request rqtype nl il _ = request
76 78694255 Iustin Pop
  in case rqtype of
77 78694255 Iustin Pop
       Allocate xi reqn -> Cluster.tryAlloc nl il xi reqn
78 78694255 Iustin Pop
       Relocate idx reqn exnodes -> Cluster.tryReloc nl il idx reqn exnodes
79 54365762 Iustin Pop
       Evacuate exnodes -> Cluster.tryEvac nl il exnodes
80 78694255 Iustin Pop
81 585d4420 Iustin Pop
-- | Main function.
82 585d4420 Iustin Pop
main :: IO ()
83 585d4420 Iustin Pop
main = do
84 585d4420 Iustin Pop
  cmd_args <- System.getArgs
85 f3d53161 Iustin Pop
  (opts, args) <- parseOpts cmd_args "hail" options
86 585d4420 Iustin Pop
87 585d4420 Iustin Pop
  when (null args) $ do
88 585d4420 Iustin Pop
         hPutStrLn stderr "Error: this program needs an input file."
89 585d4420 Iustin Pop
         exitWith $ ExitFailure 1
90 585d4420 Iustin Pop
91 585d4420 Iustin Pop
  let input_file = head args
92 f3d53161 Iustin Pop
      shownodes = optShowNodes opts
93 585d4420 Iustin Pop
  input_data <- readFile input_file
94 585d4420 Iustin Pop
95 585d4420 Iustin Pop
  request <- case (parseData input_data) of
96 585d4420 Iustin Pop
               Bad err -> do
97 2795466b Iustin Pop
                 hPutStrLn stderr $ "Error: " ++ err
98 585d4420 Iustin Pop
                 exitWith $ ExitFailure 1
99 585d4420 Iustin Pop
               Ok rq -> return rq
100 585d4420 Iustin Pop
101 3e4480e0 Iustin Pop
  let Request rq nl _ _ = request
102 f3d53161 Iustin Pop
103 f3d53161 Iustin Pop
  when (isJust shownodes) $ do
104 f3d53161 Iustin Pop
         hPutStrLn stderr "Initial cluster status:"
105 f3d53161 Iustin Pop
         hPutStrLn stderr $ Cluster.printNodes nl (fromJust shownodes)
106 f3d53161 Iustin Pop
107 54365762 Iustin Pop
  let sols = processRequest request >>= processResults rq
108 478df686 Iustin Pop
  let (ok, info, rn) =
109 478df686 Iustin Pop
          case sols of
110 54365762 Iustin Pop
            Ok (ginfo, (_, _, sn)) -> (True, "Request successful: " ++ ginfo,
111 54365762 Iustin Pop
                                       map snd sn)
112 478df686 Iustin Pop
            Bad s -> (False, "Request failed: " ++ s, [])
113 3e4480e0 Iustin Pop
      resp = formatResponse ok info rq rn
114 ed41c179 Iustin Pop
  putStrLn resp