Statistics
| Branch: | Tag: | Revision:

root / hspace.hs @ b2278348

History | View | Annotate | Download (9.6 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.Char (toUpper)
29
import Data.List
30
import Data.Function
31
import Monad
32
import System
33
import System.IO
34
import qualified System
35

    
36
import Text.Printf (printf, hPrintf)
37

    
38
import qualified Ganeti.HTools.Container as Container
39
import qualified Ganeti.HTools.Cluster as Cluster
40
import qualified Ganeti.HTools.Node as Node
41
import qualified Ganeti.HTools.Instance as Instance
42

    
43
import Ganeti.HTools.Utils
44
import Ganeti.HTools.Types
45
import Ganeti.HTools.CLI
46

    
47
-- | Options list and functions
48
options :: [OptType]
49
options =
50
    [ oPrintNodes
51
    , oNodeFile
52
    , oInstFile
53
    , oNodeSim
54
    , oRapiMaster
55
    , oLuxiSocket
56
    , oVerbose
57
    , oQuiet
58
    , oOfflineNode
59
    , oIMem
60
    , oIDisk
61
    , oIVcpus
62
    , oINodes
63
    , oMaxCpu
64
    , oMinDisk
65
    , oShowVer
66
    , oShowHelp
67
    ]
68

    
69
data Phase = PInitial | PFinal
70

    
71
statsData :: [(String, Cluster.CStats -> String)]
72
statsData = [ ("SCORE", printf "%.8f" . Cluster.cs_score)
73
            , ("INST_CNT", printf "%d" . Cluster.cs_ninst)
74
            , ("MEM_FREE", printf "%d" . Cluster.cs_fmem)
75
            , ("MEM_AVAIL", printf "%d" . Cluster.cs_amem)
76
            , ("MEM_RESVD",
77
               \cs -> printf "%d" (Cluster.cs_fmem cs - Cluster.cs_amem cs))
78
            , ("MEM_INST", printf "%d" . Cluster.cs_imem)
79
            , ("MEM_OVERHEAD",
80
               \cs -> printf "%d" (Cluster.cs_xmem cs + Cluster.cs_nmem cs))
81
            , ("MEM_EFF",
82
               \cs -> printf "%.8f" (fromIntegral (Cluster.cs_imem cs) /
83
                                     Cluster.cs_tmem cs))
84
            , ("DSK_FREE", printf "%d" . Cluster.cs_fdsk)
85
            , ("DSK_AVAIL", printf "%d ". Cluster.cs_adsk)
86
            , ("DSK_RESVD",
87
               \cs -> printf "%d" (Cluster.cs_fdsk cs - Cluster.cs_adsk cs))
88
            , ("DSK_INST", printf "%d" . Cluster.cs_idsk)
89
            , ("DSK_EFF",
90
               \cs -> printf "%.8f" (fromIntegral (Cluster.cs_idsk cs) /
91
                                    Cluster.cs_tdsk cs))
92
            , ("CPU_INST", printf "%d" . Cluster.cs_icpu)
93
            , ("CPU_EFF",
94
               \cs -> printf "%.8f" (fromIntegral (Cluster.cs_icpu cs) /
95
                                     Cluster.cs_tcpu cs))
96
            , ("MNODE_MEM_AVAIL", printf "%d" . Cluster.cs_mmem)
97
            , ("MNODE_DSK_AVAIL", printf "%d" . Cluster.cs_mdsk)
98
            ]
99

    
100
specData :: [(String, Options -> String)]
101
specData = [ ("MEM", printf "%d" . optIMem)
102
           , ("DSK", printf "%d" . optIDsk)
103
           , ("CPU", printf "%d" . optIVCPUs)
104
           , ("RQN", printf "%d" . optINodes)
105
           ]
106

    
107
clusterData :: [(String, Cluster.CStats -> String)]
108
clusterData = [ ("MEM", printf "%.0f" . Cluster.cs_tmem)
109
              , ("DSK", printf "%.0f" . Cluster.cs_tdsk)
110
              , ("CPU", printf "%.0f" . Cluster.cs_tcpu)
111
              ]
112

    
113
-- | Recursively place instances on the cluster until we're out of space
114
iterateDepth :: Node.List
115
             -> Instance.List
116
             -> Instance.Instance
117
             -> Int
118
             -> [Instance.Instance]
119
             -> Result (FailStats, Node.List, [Instance.Instance])
120
iterateDepth nl il newinst nreq ixes =
121
      let depth = length ixes
122
          newname = printf "new-%d" depth::String
123
          newidx = length (Container.elems il) + depth
124
          newi2 = Instance.setIdx (Instance.setName newinst newname) newidx
125
      in case Cluster.tryAlloc nl il newi2 nreq of
126
           Bad s -> Bad s
127
           Ok (errs, _, sols3) ->
128
               case sols3 of
129
                 Nothing -> Ok (Cluster.collapseFailures errs, nl, ixes)
130
                 Just (_, (xnl, xi, _)) ->
131
                     iterateDepth xnl il newinst nreq $! (xi:ixes)
132

    
133
-- | Function to print stats for a given phase
134
printStats :: Phase -> Cluster.CStats -> [(String, String)]
135
printStats ph cs =
136
  map (\(s, fn) -> (printf "%s_%s" kind s, fn cs)) statsData
137
  where kind = case ph of
138
                 PInitial -> "INI"
139
                 PFinal -> "FIN"
140

    
141
-- | Print final stats and related metrics
142
printResults :: Node.List -> Int -> Int -> [(FailMode, Int)] -> IO ()
143
printResults fin_nl num_instances allocs sreason = do
144
  let fin_stats = Cluster.totalResources fin_nl
145
      fin_instances = num_instances + allocs
146

    
147
  when (num_instances + allocs /= Cluster.cs_ninst fin_stats) $
148
       do
149
         hPrintf stderr "ERROR: internal inconsistency, allocated (%d)\
150
                        \ != counted (%d)\n" (num_instances + allocs)
151
                                 (Cluster.cs_ninst fin_stats)
152
         exitWith $ ExitFailure 1
153

    
154
  printKeys $ printStats PFinal fin_stats
155
  printKeys [ ("ALLOC_USAGE", printf "%.8f"
156
                                ((fromIntegral num_instances::Double) /
157
                                 fromIntegral fin_instances))
158
            , ("ALLOC_INSTANCES", printf "%d" allocs)
159
            , ("ALLOC_FAIL_REASON", map toUpper . show . fst $ head sreason)
160
            ]
161
  printKeys $ map (\(x, y) -> (printf "ALLOC_%s_CNT" (show x),
162
                               printf "%d" y)) sreason
163
  -- this should be the final entry
164
  printKeys [("OK", "1")]
165

    
166
-- | Format a list of key/values as a shell fragment
167
printKeys :: [(String, String)] -> IO ()
168
printKeys = mapM_ (\(k, v) -> printf "HTS_%s=%s\n" (map toUpper k) v)
169

    
170
-- | Main function.
171
main :: IO ()
172
main = do
173
  cmd_args <- System.getArgs
174
  (opts, args) <- parseOpts cmd_args "hspace" options
175

    
176
  unless (null args) $ do
177
         hPutStrLn stderr "Error: this program doesn't take any arguments."
178
         exitWith $ ExitFailure 1
179

    
180
  let verbose = optVerbose opts
181

    
182
  (fixed_nl, il, csf) <- loadExternalData opts
183

    
184
  printKeys $ map (\(a, fn) -> ("SPEC_" ++ a, fn opts)) specData
185

    
186
  let num_instances = length $ Container.elems il
187

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

    
199
  when (length offline_wrong > 0) $ do
200
         hPrintf stderr "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
         hPrintf stderr "Error: Invalid required nodes (%d)\n" req_nodes
206
         exitWith $ ExitFailure 1
207

    
208
  let nm = Container.map (\n -> if elem (Node.idx n) offline_indices
209
                                then Node.setOffline n True
210
                                else n) fixed_nl
211
      nl = Container.map (flip Node.setMdsk m_dsk . flip Node.setMcpu m_cpu)
212
           nm
213

    
214
  when (length csf > 0 && verbose > 1) $
215
       hPrintf stderr "Note: Stripping common suffix of '%s' from names\n" csf
216

    
217
  when (optShowNodes opts) $
218
       do
219
         hPutStrLn stderr "Initial cluster status:"
220
         hPutStrLn stderr $ Cluster.printNodes nl
221

    
222
  let ini_cv = Cluster.compCV nl
223
      ini_stats = Cluster.totalResources nl
224

    
225
  when (verbose > 2) $
226
         hPrintf stderr "Initial coefficients: overall %.8f, %s\n"
227
                 ini_cv (Cluster.printStats nl)
228

    
229
  printKeys $ map (\(a, fn) -> ("CLUSTER_" ++ a, fn ini_stats)) clusterData
230
  printKeys [("CLUSTER_NODES", printf "%d" (length all_nodes))]
231
  printKeys $ printStats PInitial ini_stats
232

    
233
  let bad_nodes = fst $ Cluster.computeBadItems nl il
234
  when (length bad_nodes > 0) $ do
235
         -- This is failn1 case, so we print the same final stats and
236
         -- exit early
237
         printResults nl num_instances 0 [(FailN1, 1)]
238
         exitWith ExitSuccess
239

    
240
  let nmlen = Container.maxNameLen nl
241
      newinst = Instance.create "new" (optIMem opts) (optIDsk opts)
242
                (optIVCPUs opts) "ADMIN_down" (-1) (-1)
243

    
244
  let result = iterateDepth nl il newinst req_nodes []
245
  (ereason, fin_nl, ixes) <- (case result of
246
                                Bad s -> do
247
                                  hPrintf stderr "Failure: %s\n" s
248
                                  exitWith $ ExitFailure 1
249
                                Ok x -> return x)
250
  let allocs = length ixes
251
      fin_ixes = reverse ixes
252
      ix_namelen = maximum . map (length . Instance.name) $ fin_ixes
253
      sreason = reverse $ sortBy (compare `on` snd) ereason
254

    
255
  when (verbose > 1) $
256
         hPutStr stderr . unlines $
257
         map (\i -> printf "Inst: %*s %-*s %-*s"
258
                    ix_namelen (Instance.name i)
259
                    nmlen (Container.nameOf fin_nl $ Instance.pnode i)
260
                    nmlen (let sdx = Instance.snode i
261
                           in if sdx == Node.noSecondary then ""
262
                              else Container.nameOf fin_nl sdx)
263
             ) fin_ixes
264

    
265
  when (optShowNodes opts) $
266
       do
267
         hPutStrLn stderr ""
268
         hPutStrLn stderr "Final cluster status:"
269
         hPutStrLn stderr $ Cluster.printNodes fin_nl
270

    
271
  printResults fin_nl num_instances allocs sreason