Statistics
| Branch: | Tag: | Revision:

root / hspace.hs @ 9abe9caf

History | View | Annotate | Download (9.9 kB)

1 e10be8f2 Iustin Pop
{-| Cluster space sizing
2 e10be8f2 Iustin Pop
3 e10be8f2 Iustin Pop
-}
4 e10be8f2 Iustin Pop
5 e10be8f2 Iustin Pop
{-
6 e10be8f2 Iustin Pop
7 e10be8f2 Iustin Pop
Copyright (C) 2009 Google Inc.
8 e10be8f2 Iustin Pop
9 e10be8f2 Iustin Pop
This program is free software; you can redistribute it and/or modify
10 e10be8f2 Iustin Pop
it under the terms of the GNU General Public License as published by
11 e10be8f2 Iustin Pop
the Free Software Foundation; either version 2 of the License, or
12 e10be8f2 Iustin Pop
(at your option) any later version.
13 e10be8f2 Iustin Pop
14 e10be8f2 Iustin Pop
This program is distributed in the hope that it will be useful, but
15 e10be8f2 Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
16 e10be8f2 Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17 e10be8f2 Iustin Pop
General Public License for more details.
18 e10be8f2 Iustin Pop
19 e10be8f2 Iustin Pop
You should have received a copy of the GNU General Public License
20 e10be8f2 Iustin Pop
along with this program; if not, write to the Free Software
21 e10be8f2 Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22 e10be8f2 Iustin Pop
02110-1301, USA.
23 e10be8f2 Iustin Pop
24 e10be8f2 Iustin Pop
-}
25 e10be8f2 Iustin Pop
26 e10be8f2 Iustin Pop
module Main (main) where
27 e10be8f2 Iustin Pop
28 e10be8f2 Iustin Pop
import Data.List
29 e10be8f2 Iustin Pop
import Data.Function
30 e10be8f2 Iustin Pop
import Data.Maybe (isJust, fromJust, fromMaybe, isNothing)
31 e10be8f2 Iustin Pop
import Monad
32 e10be8f2 Iustin Pop
import System
33 e10be8f2 Iustin Pop
import System.IO
34 e10be8f2 Iustin Pop
import System.Console.GetOpt
35 e10be8f2 Iustin Pop
import qualified System
36 e10be8f2 Iustin Pop
37 e10be8f2 Iustin Pop
import Text.Printf (printf)
38 e10be8f2 Iustin Pop
39 e10be8f2 Iustin Pop
import qualified Ganeti.HTools.Container as Container
40 e10be8f2 Iustin Pop
import qualified Ganeti.HTools.Cluster as Cluster
41 e10be8f2 Iustin Pop
import qualified Ganeti.HTools.Node as Node
42 e10be8f2 Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
43 e10be8f2 Iustin Pop
import qualified Ganeti.HTools.CLI as CLI
44 e10be8f2 Iustin Pop
45 e10be8f2 Iustin Pop
import Ganeti.HTools.Utils
46 e10be8f2 Iustin Pop
47 e10be8f2 Iustin Pop
-- | Command line options structure.
48 e10be8f2 Iustin Pop
data Options = Options
49 e10be8f2 Iustin Pop
    { optShowNodes :: Bool           -- ^ Whether to show node status
50 e10be8f2 Iustin Pop
    , optNodef     :: FilePath       -- ^ Path to the nodes file
51 e10be8f2 Iustin Pop
    , optNodeSet   :: Bool           -- ^ The nodes have been set by options
52 e10be8f2 Iustin Pop
    , optInstf     :: FilePath       -- ^ Path to the instances file
53 e10be8f2 Iustin Pop
    , optInstSet   :: Bool           -- ^ The insts have been set by options
54 e10be8f2 Iustin Pop
    , optMaster    :: String         -- ^ Collect data from RAPI
55 e10be8f2 Iustin Pop
    , optVerbose   :: Int            -- ^ Verbosity level
56 e10be8f2 Iustin Pop
    , optOffline   :: [String]       -- ^ Names of offline nodes
57 e10be8f2 Iustin Pop
    , optIMem      :: Int            -- ^ Instance memory
58 e10be8f2 Iustin Pop
    , optIDsk      :: Int            -- ^ Instance disk
59 e10be8f2 Iustin Pop
    , optINodes    :: Int            -- ^ Nodes required for an instance
60 e10be8f2 Iustin Pop
    , optShowVer   :: Bool           -- ^ Just show the program version
61 e10be8f2 Iustin Pop
    , optShowHelp  :: Bool           -- ^ Just show the help
62 e10be8f2 Iustin Pop
    } deriving Show
63 e10be8f2 Iustin Pop
64 e10be8f2 Iustin Pop
instance CLI.CLIOptions Options where
65 e10be8f2 Iustin Pop
    showVersion = optShowVer
66 e10be8f2 Iustin Pop
    showHelp    = optShowHelp
67 e10be8f2 Iustin Pop
68 e10be8f2 Iustin Pop
instance CLI.EToolOptions Options where
69 e10be8f2 Iustin Pop
    nodeFile   = optNodef
70 e10be8f2 Iustin Pop
    nodeSet    = optNodeSet
71 e10be8f2 Iustin Pop
    instFile   = optInstf
72 e10be8f2 Iustin Pop
    instSet    = optInstSet
73 e10be8f2 Iustin Pop
    masterName = optMaster
74 e10be8f2 Iustin Pop
    silent a   = (optVerbose a) == 0
75 e10be8f2 Iustin Pop
76 e10be8f2 Iustin Pop
-- | Default values for the command line options.
77 e10be8f2 Iustin Pop
defaultOptions :: Options
78 e10be8f2 Iustin Pop
defaultOptions  = Options
79 e10be8f2 Iustin Pop
 { optShowNodes = False
80 e10be8f2 Iustin Pop
 , optNodef     = "nodes"
81 e10be8f2 Iustin Pop
 , optNodeSet   = False
82 e10be8f2 Iustin Pop
 , optInstf     = "instances"
83 e10be8f2 Iustin Pop
 , optInstSet   = False
84 e10be8f2 Iustin Pop
 , optMaster    = ""
85 e10be8f2 Iustin Pop
 , optVerbose   = 1
86 e10be8f2 Iustin Pop
 , optOffline   = []
87 e10be8f2 Iustin Pop
 , optIMem      = 4096
88 e10be8f2 Iustin Pop
 , optIDsk      = 102400
89 e10be8f2 Iustin Pop
 , optINodes    = 2
90 e10be8f2 Iustin Pop
 , optShowVer   = False
91 e10be8f2 Iustin Pop
 , optShowHelp  = False
92 e10be8f2 Iustin Pop
 }
93 e10be8f2 Iustin Pop
94 e10be8f2 Iustin Pop
-- | Options list and functions
95 e10be8f2 Iustin Pop
options :: [OptDescr (Options -> Options)]
96 e10be8f2 Iustin Pop
options =
97 e10be8f2 Iustin Pop
    [ Option ['p']     ["print-nodes"]
98 e10be8f2 Iustin Pop
      (NoArg (\ opts -> opts { optShowNodes = True }))
99 e10be8f2 Iustin Pop
      "print the final node list"
100 e10be8f2 Iustin Pop
    , Option ['n']     ["nodes"]
101 e10be8f2 Iustin Pop
      (ReqArg (\ f opts -> opts { optNodef = f, optNodeSet = True }) "FILE")
102 e10be8f2 Iustin Pop
      "the node list FILE"
103 e10be8f2 Iustin Pop
    , Option ['i']     ["instances"]
104 e10be8f2 Iustin Pop
      (ReqArg (\ f opts -> opts { optInstf =  f, optInstSet = True }) "FILE")
105 e10be8f2 Iustin Pop
      "the instance list FILE"
106 e10be8f2 Iustin Pop
    , Option ['m']     ["master"]
107 e10be8f2 Iustin Pop
      (ReqArg (\ m opts -> opts { optMaster = m }) "ADDRESS")
108 e10be8f2 Iustin Pop
      "collect data via RAPI at the given ADDRESS"
109 e10be8f2 Iustin Pop
    , Option ['v']     ["verbose"]
110 e10be8f2 Iustin Pop
      (NoArg (\ opts -> opts { optVerbose = (optVerbose opts) + 1 }))
111 e10be8f2 Iustin Pop
      "increase the verbosity level"
112 e10be8f2 Iustin Pop
    , Option ['q']     ["quiet"]
113 e10be8f2 Iustin Pop
      (NoArg (\ opts -> opts { optVerbose = (optVerbose opts) - 1 }))
114 e10be8f2 Iustin Pop
      "decrease the verbosity level"
115 e10be8f2 Iustin Pop
    , Option ['O']     ["offline"]
116 e10be8f2 Iustin Pop
      (ReqArg (\ n opts -> opts { optOffline = n:optOffline opts }) "NODE")
117 e10be8f2 Iustin Pop
      "set node as offline"
118 e10be8f2 Iustin Pop
    , Option []        ["memory"]
119 e10be8f2 Iustin Pop
      (ReqArg (\ m opts -> opts { optIMem = read m }) "MEMORY")
120 e10be8f2 Iustin Pop
      "memory size for instances"
121 e10be8f2 Iustin Pop
    , Option []        ["disk"]
122 e10be8f2 Iustin Pop
      (ReqArg (\ d opts -> opts { optIDsk = read d }) "DISK")
123 e10be8f2 Iustin Pop
      "disk size for instances"
124 e10be8f2 Iustin Pop
    , Option []        ["req-nodes"]
125 e10be8f2 Iustin Pop
      (ReqArg (\ n opts -> opts { optINodes = read n }) "NODES")
126 e10be8f2 Iustin Pop
      "number of nodes for the new instances (1=plain, 2=mirrored)"
127 e10be8f2 Iustin Pop
    , Option ['V']     ["version"]
128 e10be8f2 Iustin Pop
      (NoArg (\ opts -> opts { optShowVer = True}))
129 e10be8f2 Iustin Pop
      "show the version of the program"
130 e10be8f2 Iustin Pop
    , Option ['h']     ["help"]
131 e10be8f2 Iustin Pop
      (NoArg (\ opts -> opts { optShowHelp = True}))
132 e10be8f2 Iustin Pop
      "show help"
133 e10be8f2 Iustin Pop
    ]
134 e10be8f2 Iustin Pop
135 9dcec001 Iustin Pop
filterFails :: (Monad m) => [(Maybe Node.List, Instance.Instance, [Node.Node])]
136 9dcec001 Iustin Pop
            -> m [(Node.List, Instance.Instance, [Node.Node])]
137 e10be8f2 Iustin Pop
filterFails sols =
138 e10be8f2 Iustin Pop
    if null sols then fail "No nodes onto which to allocate at all"
139 9dcec001 Iustin Pop
    else let sols' = filter (isJust . fst3) sols
140 e10be8f2 Iustin Pop
         in if null sols' then
141 e10be8f2 Iustin Pop
                fail "No valid allocation solutions"
142 e10be8f2 Iustin Pop
            else
143 9dcec001 Iustin Pop
                return $ map (\(x, y, z) -> (fromJust x, y, z)) sols'
144 e10be8f2 Iustin Pop
145 9dcec001 Iustin Pop
processResults :: (Monad m) => [(Node.List, Instance.Instance, [Node.Node])]
146 9dcec001 Iustin Pop
               -> m (Node.List, Instance.Instance, [Node.Node])
147 e10be8f2 Iustin Pop
processResults sols =
148 9dcec001 Iustin Pop
    let sols' = map (\e@(nl', _, _) -> (Cluster.compCV  nl', e)) sols
149 e10be8f2 Iustin Pop
        sols'' = sortBy (compare `on` fst) sols'
150 e10be8f2 Iustin Pop
    in return $ snd $ head sols''
151 e10be8f2 Iustin Pop
152 e10be8f2 Iustin Pop
iterateDepth :: Node.List
153 e10be8f2 Iustin Pop
             -> Instance.List
154 e10be8f2 Iustin Pop
             -> Instance.Instance
155 e10be8f2 Iustin Pop
             -> Int
156 9dcec001 Iustin Pop
             -> [Instance.Instance]
157 9dcec001 Iustin Pop
             -> (Node.List, [Instance.Instance])
158 9dcec001 Iustin Pop
iterateDepth nl il newinst nreq ixes =
159 9dcec001 Iustin Pop
      let depth = length ixes
160 9dcec001 Iustin Pop
          newname = printf "new-%d" depth
161 e10be8f2 Iustin Pop
          newidx = (length $ Container.elems il) + depth
162 e10be8f2 Iustin Pop
          newi2 = Instance.setIdx (Instance.setName newinst newname) newidx
163 e10be8f2 Iustin Pop
          sols = Cluster.tryAlloc nl il newi2 nreq
164 9dcec001 Iustin Pop
          orig = (nl, ixes)
165 e10be8f2 Iustin Pop
      in
166 e10be8f2 Iustin Pop
        if isNothing sols then orig
167 e10be8f2 Iustin Pop
        else let sols' = fromJust sols
168 e10be8f2 Iustin Pop
                 sols'' = filterFails sols'
169 e10be8f2 Iustin Pop
             in if isNothing sols'' then orig
170 9dcec001 Iustin Pop
                else let (xnl, xi, _) = fromJust $ processResults $
171 9dcec001 Iustin Pop
                                        fromJust sols''
172 9dcec001 Iustin Pop
                     in iterateDepth xnl il newinst nreq (xi:ixes)
173 e10be8f2 Iustin Pop
174 e10be8f2 Iustin Pop
175 e10be8f2 Iustin Pop
-- | Main function.
176 e10be8f2 Iustin Pop
main :: IO ()
177 e10be8f2 Iustin Pop
main = do
178 e10be8f2 Iustin Pop
  cmd_args <- System.getArgs
179 e10be8f2 Iustin Pop
  (opts, args) <- CLI.parseOpts cmd_args "hspace" options defaultOptions
180 e10be8f2 Iustin Pop
181 e10be8f2 Iustin Pop
  unless (null args) $ do
182 e10be8f2 Iustin Pop
         hPutStrLn stderr "Error: this program doesn't take any arguments."
183 e10be8f2 Iustin Pop
         exitWith $ ExitFailure 1
184 e10be8f2 Iustin Pop
185 e10be8f2 Iustin Pop
  let verbose = optVerbose opts
186 e10be8f2 Iustin Pop
187 e10be8f2 Iustin Pop
  (fixed_nl, il, csf) <- CLI.loadExternalData opts
188 9dcec001 Iustin Pop
  let num_instances = length $ Container.elems il
189 e10be8f2 Iustin Pop
190 e10be8f2 Iustin Pop
  let offline_names = optOffline opts
191 e10be8f2 Iustin Pop
      all_nodes = Container.elems fixed_nl
192 e10be8f2 Iustin Pop
      all_names = map Node.name all_nodes
193 e10be8f2 Iustin Pop
      offline_wrong = filter (\n -> not $ elem n all_names) offline_names
194 e10be8f2 Iustin Pop
      offline_indices = map Node.idx $
195 e10be8f2 Iustin Pop
                        filter (\n -> elem (Node.name n) offline_names)
196 e10be8f2 Iustin Pop
                               all_nodes
197 9abe9caf Iustin Pop
      req_nodes = optINodes opts
198 e10be8f2 Iustin Pop
199 e10be8f2 Iustin Pop
  when (length offline_wrong > 0) $ do
200 9dcec001 Iustin Pop
         printf "Error: Wrong node name(s) set as offline: %s\n"
201 e10be8f2 Iustin Pop
                (commaJoin offline_wrong)
202 e10be8f2 Iustin Pop
         exitWith $ ExitFailure 1
203 e10be8f2 Iustin Pop
204 9abe9caf Iustin Pop
  when (req_nodes /= 1 && req_nodes /= 2) $ do
205 9abe9caf Iustin Pop
         printf "Error: Invalid required nodes (%d)\n" req_nodes
206 9abe9caf Iustin Pop
         exitWith $ ExitFailure 1
207 9abe9caf Iustin Pop
208 e10be8f2 Iustin Pop
  let nl = Container.map (\n -> if elem (Node.idx n) offline_indices
209 e10be8f2 Iustin Pop
                                then Node.setOffline n True
210 e10be8f2 Iustin Pop
                                else n) fixed_nl
211 e10be8f2 Iustin Pop
212 e10be8f2 Iustin Pop
  when (length csf > 0 && verbose > 1) $ do
213 e10be8f2 Iustin Pop
         printf "Note: Stripping common suffix of '%s' from names\n" csf
214 e10be8f2 Iustin Pop
215 e10be8f2 Iustin Pop
  let bad_nodes = fst $ Cluster.computeBadItems nl il
216 e10be8f2 Iustin Pop
  when (length bad_nodes > 0) $ do
217 9dcec001 Iustin Pop
         putStrLn "Error: Cluster not N+1, no space to allocate."
218 e10be8f2 Iustin Pop
         exitWith $ ExitFailure 1
219 e10be8f2 Iustin Pop
220 e10be8f2 Iustin Pop
  when (optShowNodes opts) $
221 e10be8f2 Iustin Pop
       do
222 e10be8f2 Iustin Pop
         putStrLn "Initial cluster status:"
223 e10be8f2 Iustin Pop
         putStrLn $ Cluster.printNodes nl
224 e10be8f2 Iustin Pop
225 e10be8f2 Iustin Pop
  let ini_cv = Cluster.compCV nl
226 9dcec001 Iustin Pop
      (orig_mem, orig_disk) = Cluster.totalResources nl
227 e10be8f2 Iustin Pop
228 e10be8f2 Iustin Pop
  (if verbose > 2 then
229 e10be8f2 Iustin Pop
       printf "Initial coefficients: overall %.8f, %s\n"
230 e10be8f2 Iustin Pop
       ini_cv (Cluster.printStats nl)
231 e10be8f2 Iustin Pop
   else
232 e10be8f2 Iustin Pop
       printf "Initial score: %.8f\n" ini_cv)
233 9dcec001 Iustin Pop
  printf "Initial instances: %d\n" num_instances
234 9dcec001 Iustin Pop
  printf "Initial free RAM: %d\n" orig_mem
235 9dcec001 Iustin Pop
  printf "Initial free disk: %d\n" orig_disk
236 e10be8f2 Iustin Pop
237 9dcec001 Iustin Pop
  let nmlen = Container.maxNameLen nl
238 e10be8f2 Iustin Pop
      newinst = Instance.create "new" (optIMem opts) (optIDsk opts)
239 e10be8f2 Iustin Pop
                "ADMIN_down" (-1) (-1)
240 e10be8f2 Iustin Pop
241 9abe9caf Iustin Pop
  let (fin_nl, ixes) = iterateDepth nl il newinst req_nodes []
242 9dcec001 Iustin Pop
      allocs = length ixes
243 9dcec001 Iustin Pop
      fin_instances = num_instances + allocs
244 9dcec001 Iustin Pop
      fin_ixes = reverse ixes
245 9dcec001 Iustin Pop
      ix_namelen = maximum . map (length . Instance.name) $ fin_ixes
246 9dcec001 Iustin Pop
      (final_mem, final_disk) = Cluster.totalResources fin_nl
247 9dcec001 Iustin Pop
248 9dcec001 Iustin Pop
  printf "Final score: %.8f\n" (Cluster.compCV fin_nl)
249 9dcec001 Iustin Pop
  printf "Final instances: %d\n" (num_instances + allocs)
250 9dcec001 Iustin Pop
  printf "Final free RAM: %d\n" final_mem
251 9dcec001 Iustin Pop
  printf "Final free disk: %d\n" final_disk
252 9abe9caf Iustin Pop
  printf "Usage: %.5f\n" (((fromIntegral num_instances)::Double) /
253 9dcec001 Iustin Pop
                          (fromIntegral fin_instances))
254 9dcec001 Iustin Pop
  printf "Allocations: %d\n" allocs
255 9dcec001 Iustin Pop
  when (verbose > 1) $ do
256 9dcec001 Iustin Pop
         putStr . unlines . map (\i -> printf "Inst: %*s %-*s %-*s"
257 9dcec001 Iustin Pop
                     ix_namelen (Instance.name i)
258 9dcec001 Iustin Pop
                     nmlen (Container.nameOf fin_nl $ Instance.pnode i)
259 9abe9caf Iustin Pop
                     nmlen (let sdx = Instance.snode i
260 9abe9caf Iustin Pop
                            in if sdx == Node.noSecondary then ""
261 9abe9caf Iustin Pop
                               else Container.nameOf fin_nl sdx))
262 9dcec001 Iustin Pop
         $ fin_ixes
263 e10be8f2 Iustin Pop
264 e10be8f2 Iustin Pop
  when (optShowNodes opts) $
265 e10be8f2 Iustin Pop
       do
266 e10be8f2 Iustin Pop
         let (orig_mem, orig_disk) = Cluster.totalResources nl
267 e10be8f2 Iustin Pop
             (final_mem, final_disk) = Cluster.totalResources fin_nl
268 e10be8f2 Iustin Pop
         putStrLn ""
269 e10be8f2 Iustin Pop
         putStrLn "Final cluster status:"
270 e10be8f2 Iustin Pop
         putStrLn $ Cluster.printNodes fin_nl
271 e10be8f2 Iustin Pop
         when (verbose > 3) $
272 e10be8f2 Iustin Pop
              do
273 e10be8f2 Iustin Pop
                printf "Original: mem=%d disk=%d\n" orig_mem orig_disk
274 e10be8f2 Iustin Pop
                printf "Final:    mem=%d disk=%d\n" final_mem final_disk