Statistics
| Branch: | Tag: | Revision:

root / hail.hs @ 608efcce

History | View | Annotate | Download (5.4 kB)

1 585d4420 Iustin Pop
{-| Solver for N+1 cluster errors
2 585d4420 Iustin Pop
3 585d4420 Iustin Pop
-}
4 585d4420 Iustin Pop
5 585d4420 Iustin Pop
module Main (main) where
6 585d4420 Iustin Pop
7 585d4420 Iustin Pop
import Data.List
8 585d4420 Iustin Pop
import Data.Function
9 842e3764 Iustin Pop
import Data.Maybe (isJust, fromJust)
10 585d4420 Iustin Pop
import Monad
11 585d4420 Iustin Pop
import System
12 585d4420 Iustin Pop
import System.IO
13 585d4420 Iustin Pop
import System.Console.GetOpt
14 585d4420 Iustin Pop
import qualified System
15 585d4420 Iustin Pop
16 585d4420 Iustin Pop
import Text.Printf (printf)
17 585d4420 Iustin Pop
18 585d4420 Iustin Pop
import qualified Ganeti.HTools.Container as Container
19 585d4420 Iustin Pop
import qualified Ganeti.HTools.Cluster as Cluster
20 585d4420 Iustin Pop
import qualified Ganeti.HTools.Node as Node
21 ed41c179 Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
22 585d4420 Iustin Pop
import qualified Ganeti.HTools.CLI as CLI
23 585d4420 Iustin Pop
import Ganeti.HTools.IAlloc
24 e4c5beaf Iustin Pop
import Ganeti.HTools.Types
25 585d4420 Iustin Pop
26 585d4420 Iustin Pop
-- | Command line options structure.
27 585d4420 Iustin Pop
data Options = Options
28 842e3764 Iustin Pop
    { optShowVer   :: Bool           -- ^ Just show the program version
29 585d4420 Iustin Pop
    , optShowHelp  :: Bool           -- ^ Just show the help
30 585d4420 Iustin Pop
    } deriving Show
31 585d4420 Iustin Pop
32 585d4420 Iustin Pop
-- | Default values for the command line options.
33 585d4420 Iustin Pop
defaultOptions :: Options
34 585d4420 Iustin Pop
defaultOptions  = Options
35 842e3764 Iustin Pop
 { optShowVer   = False
36 585d4420 Iustin Pop
 , optShowHelp  = False
37 585d4420 Iustin Pop
 }
38 585d4420 Iustin Pop
39 842e3764 Iustin Pop
instance CLI.CLIOptions Options where
40 842e3764 Iustin Pop
    showVersion = optShowVer
41 842e3764 Iustin Pop
    showHelp    = optShowHelp
42 842e3764 Iustin Pop
43 585d4420 Iustin Pop
-- | Options list and functions
44 585d4420 Iustin Pop
options :: [OptDescr (Options -> Options)]
45 585d4420 Iustin Pop
options =
46 842e3764 Iustin Pop
    [ Option ['V']     ["version"]
47 585d4420 Iustin Pop
      (NoArg (\ opts -> opts { optShowVer = True}))
48 585d4420 Iustin Pop
      "show the version of the program"
49 585d4420 Iustin Pop
    , Option ['h']     ["help"]
50 585d4420 Iustin Pop
      (NoArg (\ opts -> opts { optShowHelp = True}))
51 585d4420 Iustin Pop
      "show help"
52 585d4420 Iustin Pop
    ]
53 585d4420 Iustin Pop
54 262a08a2 Iustin Pop
-- | Compute online nodes from a Node.List
55 262a08a2 Iustin Pop
getOnline :: Node.List -> [Node.Node]
56 8c2ebac8 Iustin Pop
getOnline = filter (not . Node.offline) . Container.elems
57 8c2ebac8 Iustin Pop
58 ed41c179 Iustin Pop
-- | Try to allocate an instance on the cluster
59 f826c5e0 Iustin Pop
tryAlloc :: (Monad m) =>
60 262a08a2 Iustin Pop
            Node.List
61 262a08a2 Iustin Pop
         -> Instance.List
62 ed41c179 Iustin Pop
         -> Instance.Instance
63 ed41c179 Iustin Pop
         -> Int
64 262a08a2 Iustin Pop
         -> m [(Maybe Node.List, [Node.Node])]
65 5e15f460 Iustin Pop
tryAlloc nl _ inst 2 =
66 8c2ebac8 Iustin Pop
    let all_nodes = getOnline nl
67 4a340313 Iustin Pop
        all_pairs = liftM2 (,) all_nodes all_nodes
68 4a340313 Iustin Pop
        ok_pairs = filter (\(x, y) -> Node.idx x /= Node.idx y) all_pairs
69 5e15f460 Iustin Pop
        sols = map (\(p, s) ->
70 5e15f460 Iustin Pop
                        (fst $ Cluster.allocateOnPair nl inst p s, [p, s]))
71 5e15f460 Iustin Pop
               ok_pairs
72 5e15f460 Iustin Pop
    in return sols
73 5e15f460 Iustin Pop
74 5e15f460 Iustin Pop
tryAlloc nl _ inst 1 =
75 8c2ebac8 Iustin Pop
    let all_nodes = getOnline nl
76 5e15f460 Iustin Pop
        sols = map (\p -> (fst $ Cluster.allocateOnSingle nl inst p, [p]))
77 5e15f460 Iustin Pop
               all_nodes
78 5e15f460 Iustin Pop
    in return sols
79 f826c5e0 Iustin Pop
80 f826c5e0 Iustin Pop
tryAlloc _ _ _ reqn = fail $ "Unsupported number of alllocation \
81 f826c5e0 Iustin Pop
                             \destinations required (" ++ (show reqn) ++
82 f826c5e0 Iustin Pop
                                               "), only two supported"
83 ed41c179 Iustin Pop
84 ed41c179 Iustin Pop
-- | Try to allocate an instance on the cluster
85 f826c5e0 Iustin Pop
tryReloc :: (Monad m) =>
86 262a08a2 Iustin Pop
            Node.List
87 262a08a2 Iustin Pop
         -> Instance.List
88 608efcce Iustin Pop
         -> Idx
89 ed41c179 Iustin Pop
         -> Int
90 608efcce Iustin Pop
         -> [Ndx]
91 262a08a2 Iustin Pop
         -> m [(Maybe Node.List, [Node.Node])]
92 58709f92 Iustin Pop
tryReloc nl il xid 1 ex_idx =
93 8c2ebac8 Iustin Pop
    let all_nodes = getOnline nl
94 58709f92 Iustin Pop
        inst = Container.find xid il
95 8a6f10ce Iustin Pop
        ex_idx' = (Instance.pnode inst):ex_idx
96 608efcce Iustin Pop
        valid_nodes = filter (not . flip elem ex_idx' . Node.idx) all_nodes
97 58709f92 Iustin Pop
        valid_idxes = map Node.idx valid_nodes
98 58709f92 Iustin Pop
        sols1 = map (\x -> let (mnl, _, _, _) =
99 8a6f10ce Iustin Pop
                                    Cluster.applyMove nl inst
100 58709f92 Iustin Pop
                                               (Cluster.ReplaceSecondary x)
101 8a6f10ce Iustin Pop
                            in (mnl, [Container.find x nl])
102 58709f92 Iustin Pop
                     ) valid_idxes
103 f826c5e0 Iustin Pop
    in return sols1
104 f826c5e0 Iustin Pop
105 f826c5e0 Iustin Pop
tryReloc _ _ _ reqn _  = fail $ "Unsupported number of relocation \
106 f826c5e0 Iustin Pop
                                \destinations required (" ++ (show reqn) ++
107 f826c5e0 Iustin Pop
                                                  "), only one supported"
108 f826c5e0 Iustin Pop
109 262a08a2 Iustin Pop
filterFails :: (Monad m) => [(Maybe Node.List, [Node.Node])]
110 262a08a2 Iustin Pop
            -> m [(Node.List, [Node.Node])]
111 f826c5e0 Iustin Pop
filterFails sols =
112 f826c5e0 Iustin Pop
    if null sols then fail "No nodes onto which to allocate at all"
113 f826c5e0 Iustin Pop
    else let sols' = filter (isJust . fst) sols
114 f826c5e0 Iustin Pop
         in if null sols' then
115 f826c5e0 Iustin Pop
                fail "No valid allocation solutions"
116 58709f92 Iustin Pop
            else
117 f826c5e0 Iustin Pop
                return $ map (\(x, y) -> (fromJust x, y)) sols'
118 f826c5e0 Iustin Pop
119 262a08a2 Iustin Pop
processResults :: (Monad m) => [(Node.List, [Node.Node])]
120 f826c5e0 Iustin Pop
               -> m (String, [Node.Node])
121 f826c5e0 Iustin Pop
processResults sols =
122 f826c5e0 Iustin Pop
    let sols' = map (\(nl', ns) -> (Cluster.compCV  nl', ns)) sols
123 f826c5e0 Iustin Pop
        sols'' = sortBy (compare `on` fst) sols'
124 f826c5e0 Iustin Pop
        (best, w) = head sols''
125 f826c5e0 Iustin Pop
        (worst, l) = last sols''
126 5e15f460 Iustin Pop
        info = printf "Valid results: %d, best score: %.8f for node(s) %s, \
127 5e15f460 Iustin Pop
                      \worst score: %.8f for node(s) %s" (length sols'')
128 f826c5e0 Iustin Pop
                      best (intercalate "/" . map Node.name $ w)
129 f826c5e0 Iustin Pop
                      worst (intercalate "/" . map Node.name $ l)
130 f826c5e0 Iustin Pop
    in return (info, w)
131 585d4420 Iustin Pop
132 585d4420 Iustin Pop
-- | Main function.
133 585d4420 Iustin Pop
main :: IO ()
134 585d4420 Iustin Pop
main = do
135 585d4420 Iustin Pop
  cmd_args <- System.getArgs
136 842e3764 Iustin Pop
  (_, args) <- CLI.parseOpts cmd_args "hail" options defaultOptions
137 585d4420 Iustin Pop
138 585d4420 Iustin Pop
  when (null args) $ do
139 585d4420 Iustin Pop
         hPutStrLn stderr "Error: this program needs an input file."
140 585d4420 Iustin Pop
         exitWith $ ExitFailure 1
141 585d4420 Iustin Pop
142 585d4420 Iustin Pop
  let input_file = head args
143 585d4420 Iustin Pop
  input_data <- readFile input_file
144 585d4420 Iustin Pop
145 585d4420 Iustin Pop
  request <- case (parseData input_data) of
146 585d4420 Iustin Pop
               Bad err -> do
147 585d4420 Iustin Pop
                 putStrLn $ "Error: " ++ err
148 585d4420 Iustin Pop
                 exitWith $ ExitFailure 1
149 585d4420 Iustin Pop
               Ok rq -> return rq
150 585d4420 Iustin Pop
151 ed41c179 Iustin Pop
  let Request rqtype nl il csf = request
152 ed41c179 Iustin Pop
      new_nodes = case rqtype of
153 ed41c179 Iustin Pop
                    Allocate xi reqn -> tryAlloc nl il xi reqn
154 ed41c179 Iustin Pop
                    Relocate idx reqn exnodes ->
155 ed41c179 Iustin Pop
                        tryReloc nl il idx reqn exnodes
156 f826c5e0 Iustin Pop
  let sols = new_nodes >>= filterFails >>= processResults
157 f826c5e0 Iustin Pop
  let (ok, info, rn) = case sols of
158 58709f92 Iustin Pop
               Ok (info, sn) -> (True, "Request successful: " ++ info,
159 262a08a2 Iustin Pop
                                     map ((++ csf) . Node.name) sn)
160 ed41c179 Iustin Pop
               Bad s -> (False, "Request failed: " ++ s, [])
161 ed41c179 Iustin Pop
      resp = formatResponse ok info rn
162 ed41c179 Iustin Pop
  putStrLn resp