Statistics
| Branch: | Tag: | Revision:

root / hspace.hs @ 9abe9caf

History | View | Annotate | Download (9.9 kB)

1
{-| Cluster space sizing
2

    
3
-}
4

    
5
{-
6

    
7
Copyright (C) 2009 Google Inc.
8

    
9
This program is free software; you can redistribute it and/or modify
10
it under the terms of the GNU General Public License as published by
11
the Free Software Foundation; either version 2 of the License, or
12
(at your option) any later version.
13

    
14
This program is distributed in the hope that it will be useful, but
15
WITHOUT ANY WARRANTY; without even the implied warranty of
16
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17
General Public License for more details.
18

    
19
You should have received a copy of the GNU General Public License
20
along with this program; if not, write to the Free Software
21
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22
02110-1301, USA.
23

    
24
-}
25

    
26
module Main (main) where
27

    
28
import Data.List
29
import Data.Function
30
import Data.Maybe (isJust, fromJust, fromMaybe, isNothing)
31
import Monad
32
import System
33
import System.IO
34
import System.Console.GetOpt
35
import qualified System
36

    
37
import Text.Printf (printf)
38

    
39
import qualified Ganeti.HTools.Container as Container
40
import qualified Ganeti.HTools.Cluster as Cluster
41
import qualified Ganeti.HTools.Node as Node
42
import qualified Ganeti.HTools.Instance as Instance
43
import qualified Ganeti.HTools.CLI as CLI
44

    
45
import Ganeti.HTools.Utils
46

    
47
-- | Command line options structure.
48
data Options = Options
49
    { optShowNodes :: Bool           -- ^ Whether to show node status
50
    , optNodef     :: FilePath       -- ^ Path to the nodes file
51
    , optNodeSet   :: Bool           -- ^ The nodes have been set by options
52
    , optInstf     :: FilePath       -- ^ Path to the instances file
53
    , optInstSet   :: Bool           -- ^ The insts have been set by options
54
    , optMaster    :: String         -- ^ Collect data from RAPI
55
    , optVerbose   :: Int            -- ^ Verbosity level
56
    , optOffline   :: [String]       -- ^ Names of offline nodes
57
    , optIMem      :: Int            -- ^ Instance memory
58
    , optIDsk      :: Int            -- ^ Instance disk
59
    , optINodes    :: Int            -- ^ Nodes required for an instance
60
    , optShowVer   :: Bool           -- ^ Just show the program version
61
    , optShowHelp  :: Bool           -- ^ Just show the help
62
    } deriving Show
63

    
64
instance CLI.CLIOptions Options where
65
    showVersion = optShowVer
66
    showHelp    = optShowHelp
67

    
68
instance CLI.EToolOptions Options where
69
    nodeFile   = optNodef
70
    nodeSet    = optNodeSet
71
    instFile   = optInstf
72
    instSet    = optInstSet
73
    masterName = optMaster
74
    silent a   = (optVerbose a) == 0
75

    
76
-- | Default values for the command line options.
77
defaultOptions :: Options
78
defaultOptions  = Options
79
 { optShowNodes = False
80
 , optNodef     = "nodes"
81
 , optNodeSet   = False
82
 , optInstf     = "instances"
83
 , optInstSet   = False
84
 , optMaster    = ""
85
 , optVerbose   = 1
86
 , optOffline   = []
87
 , optIMem      = 4096
88
 , optIDsk      = 102400
89
 , optINodes    = 2
90
 , optShowVer   = False
91
 , optShowHelp  = False
92
 }
93

    
94
-- | Options list and functions
95
options :: [OptDescr (Options -> Options)]
96
options =
97
    [ Option ['p']     ["print-nodes"]
98
      (NoArg (\ opts -> opts { optShowNodes = True }))
99
      "print the final node list"
100
    , Option ['n']     ["nodes"]
101
      (ReqArg (\ f opts -> opts { optNodef = f, optNodeSet = True }) "FILE")
102
      "the node list FILE"
103
    , Option ['i']     ["instances"]
104
      (ReqArg (\ f opts -> opts { optInstf =  f, optInstSet = True }) "FILE")
105
      "the instance list FILE"
106
    , Option ['m']     ["master"]
107
      (ReqArg (\ m opts -> opts { optMaster = m }) "ADDRESS")
108
      "collect data via RAPI at the given ADDRESS"
109
    , Option ['v']     ["verbose"]
110
      (NoArg (\ opts -> opts { optVerbose = (optVerbose opts) + 1 }))
111
      "increase the verbosity level"
112
    , Option ['q']     ["quiet"]
113
      (NoArg (\ opts -> opts { optVerbose = (optVerbose opts) - 1 }))
114
      "decrease the verbosity level"
115
    , Option ['O']     ["offline"]
116
      (ReqArg (\ n opts -> opts { optOffline = n:optOffline opts }) "NODE")
117
      "set node as offline"
118
    , Option []        ["memory"]
119
      (ReqArg (\ m opts -> opts { optIMem = read m }) "MEMORY")
120
      "memory size for instances"
121
    , Option []        ["disk"]
122
      (ReqArg (\ d opts -> opts { optIDsk = read d }) "DISK")
123
      "disk size for instances"
124
    , Option []        ["req-nodes"]
125
      (ReqArg (\ n opts -> opts { optINodes = read n }) "NODES")
126
      "number of nodes for the new instances (1=plain, 2=mirrored)"
127
    , Option ['V']     ["version"]
128
      (NoArg (\ opts -> opts { optShowVer = True}))
129
      "show the version of the program"
130
    , Option ['h']     ["help"]
131
      (NoArg (\ opts -> opts { optShowHelp = True}))
132
      "show help"
133
    ]
134

    
135
filterFails :: (Monad m) => [(Maybe Node.List, Instance.Instance, [Node.Node])]
136
            -> m [(Node.List, Instance.Instance, [Node.Node])]
137
filterFails sols =
138
    if null sols then fail "No nodes onto which to allocate at all"
139
    else let sols' = filter (isJust . fst3) sols
140
         in if null sols' then
141
                fail "No valid allocation solutions"
142
            else
143
                return $ map (\(x, y, z) -> (fromJust x, y, z)) sols'
144

    
145
processResults :: (Monad m) => [(Node.List, Instance.Instance, [Node.Node])]
146
               -> m (Node.List, Instance.Instance, [Node.Node])
147
processResults sols =
148
    let sols' = map (\e@(nl', _, _) -> (Cluster.compCV  nl', e)) sols
149
        sols'' = sortBy (compare `on` fst) sols'
150
    in return $ snd $ head sols''
151

    
152
iterateDepth :: Node.List
153
             -> Instance.List
154
             -> Instance.Instance
155
             -> Int
156
             -> [Instance.Instance]
157
             -> (Node.List, [Instance.Instance])
158
iterateDepth nl il newinst nreq ixes =
159
      let depth = length ixes
160
          newname = printf "new-%d" depth
161
          newidx = (length $ Container.elems il) + depth
162
          newi2 = Instance.setIdx (Instance.setName newinst newname) newidx
163
          sols = Cluster.tryAlloc nl il newi2 nreq
164
          orig = (nl, ixes)
165
      in
166
        if isNothing sols then orig
167
        else let sols' = fromJust sols
168
                 sols'' = filterFails sols'
169
             in if isNothing sols'' then orig
170
                else let (xnl, xi, _) = fromJust $ processResults $
171
                                        fromJust sols''
172
                     in iterateDepth xnl il newinst nreq (xi:ixes)
173

    
174

    
175
-- | Main function.
176
main :: IO ()
177
main = do
178
  cmd_args <- System.getArgs
179
  (opts, args) <- CLI.parseOpts cmd_args "hspace" options defaultOptions
180

    
181
  unless (null args) $ do
182
         hPutStrLn stderr "Error: this program doesn't take any arguments."
183
         exitWith $ ExitFailure 1
184

    
185
  let verbose = optVerbose opts
186

    
187
  (fixed_nl, il, csf) <- CLI.loadExternalData opts
188
  let num_instances = length $ Container.elems il
189

    
190
  let offline_names = optOffline opts
191
      all_nodes = Container.elems fixed_nl
192
      all_names = map Node.name all_nodes
193
      offline_wrong = filter (\n -> not $ elem n all_names) offline_names
194
      offline_indices = map Node.idx $
195
                        filter (\n -> elem (Node.name n) offline_names)
196
                               all_nodes
197
      req_nodes = optINodes opts
198

    
199
  when (length offline_wrong > 0) $ do
200
         printf "Error: Wrong node name(s) set as offline: %s\n"
201
                (commaJoin offline_wrong)
202
         exitWith $ ExitFailure 1
203

    
204
  when (req_nodes /= 1 && req_nodes /= 2) $ do
205
         printf "Error: Invalid required nodes (%d)\n" req_nodes
206
         exitWith $ ExitFailure 1
207

    
208
  let nl = Container.map (\n -> if elem (Node.idx n) offline_indices
209
                                then Node.setOffline n True
210
                                else n) fixed_nl
211

    
212
  when (length csf > 0 && verbose > 1) $ do
213
         printf "Note: Stripping common suffix of '%s' from names\n" csf
214

    
215
  let bad_nodes = fst $ Cluster.computeBadItems nl il
216
  when (length bad_nodes > 0) $ do
217
         putStrLn "Error: Cluster not N+1, no space to allocate."
218
         exitWith $ ExitFailure 1
219

    
220
  when (optShowNodes opts) $
221
       do
222
         putStrLn "Initial cluster status:"
223
         putStrLn $ Cluster.printNodes nl
224

    
225
  let ini_cv = Cluster.compCV nl
226
      (orig_mem, orig_disk) = Cluster.totalResources nl
227

    
228
  (if verbose > 2 then
229
       printf "Initial coefficients: overall %.8f, %s\n"
230
       ini_cv (Cluster.printStats nl)
231
   else
232
       printf "Initial score: %.8f\n" ini_cv)
233
  printf "Initial instances: %d\n" num_instances
234
  printf "Initial free RAM: %d\n" orig_mem
235
  printf "Initial free disk: %d\n" orig_disk
236

    
237
  let nmlen = Container.maxNameLen nl
238
      newinst = Instance.create "new" (optIMem opts) (optIDsk opts)
239
                "ADMIN_down" (-1) (-1)
240

    
241
  let (fin_nl, ixes) = iterateDepth nl il newinst req_nodes []
242
      allocs = length ixes
243
      fin_instances = num_instances + allocs
244
      fin_ixes = reverse ixes
245
      ix_namelen = maximum . map (length . Instance.name) $ fin_ixes
246
      (final_mem, final_disk) = Cluster.totalResources fin_nl
247

    
248
  printf "Final score: %.8f\n" (Cluster.compCV fin_nl)
249
  printf "Final instances: %d\n" (num_instances + allocs)
250
  printf "Final free RAM: %d\n" final_mem
251
  printf "Final free disk: %d\n" final_disk
252
  printf "Usage: %.5f\n" (((fromIntegral num_instances)::Double) /
253
                          (fromIntegral fin_instances))
254
  printf "Allocations: %d\n" allocs
255
  when (verbose > 1) $ do
256
         putStr . unlines . map (\i -> printf "Inst: %*s %-*s %-*s"
257
                     ix_namelen (Instance.name i)
258
                     nmlen (Container.nameOf fin_nl $ Instance.pnode i)
259
                     nmlen (let sdx = Instance.snode i
260
                            in if sdx == Node.noSecondary then ""
261
                               else Container.nameOf fin_nl sdx))
262
         $ fin_ixes
263

    
264
  when (optShowNodes opts) $
265
       do
266
         let (orig_mem, orig_disk) = Cluster.totalResources nl
267
             (final_mem, final_disk) = Cluster.totalResources fin_nl
268
         putStrLn ""
269
         putStrLn "Final cluster status:"
270
         putStrLn $ Cluster.printNodes fin_nl
271
         when (verbose > 3) $
272
              do
273
                printf "Original: mem=%d disk=%d\n" orig_mem orig_disk
274
                printf "Final:    mem=%d disk=%d\n" final_mem final_disk