Statistics
| Branch: | Tag: | Revision:

root / htools / hscan.hs @ 2e5eb96a

History | View | Annotate | Download (4.8 kB)

1 ba9349b8 Iustin Pop
{-| Scan clusters via RAPI or LUXI and write state data files.
2 1b7a5835 Iustin Pop
3 1b7a5835 Iustin Pop
-}
4 1b7a5835 Iustin Pop
5 e2fa2baf Iustin Pop
{-
6 e2fa2baf Iustin Pop
7 693342ad Iustin Pop
Copyright (C) 2009, 2010, 2011 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 1b7a5835 Iustin Pop
module Main (main) where
27 1b7a5835 Iustin Pop
28 5182e970 Iustin Pop
import Data.Maybe (isJust, fromJust, fromMaybe)
29 1b7a5835 Iustin Pop
import Monad
30 0903280b Iustin Pop
import System (exitWith, ExitCode(..))
31 1b7a5835 Iustin Pop
import System.IO
32 1b7a5835 Iustin Pop
import System.FilePath
33 1b7a5835 Iustin Pop
import qualified System
34 1b7a5835 Iustin Pop
35 1b7a5835 Iustin Pop
import Text.Printf (printf)
36 1b7a5835 Iustin Pop
37 1b7a5835 Iustin Pop
import qualified Ganeti.HTools.Container as Container
38 1b7a5835 Iustin Pop
import qualified Ganeti.HTools.Cluster as Cluster
39 1b7a5835 Iustin Pop
import qualified Ganeti.HTools.Node as Node
40 1b7a5835 Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
41 040afc35 Iustin Pop
import qualified Ganeti.HTools.Rapi as Rapi
42 ba9349b8 Iustin Pop
import qualified Ganeti.HTools.Luxi as Luxi
43 017a0c3d Iustin Pop
import Ganeti.HTools.Loader (checkData, mergeData, ClusterData(..))
44 4a273e97 Iustin Pop
import Ganeti.HTools.Text (serializeCluster)
45 1b7a5835 Iustin Pop
46 0427285d Iustin Pop
import Ganeti.HTools.CLI
47 0427285d Iustin Pop
import Ganeti.HTools.Types
48 1b7a5835 Iustin Pop
49 1b7a5835 Iustin Pop
-- | Options list and functions
50 0427285d Iustin Pop
options :: [OptType]
51 1b7a5835 Iustin Pop
options =
52 0427285d Iustin Pop
    [ oPrintNodes
53 0427285d Iustin Pop
    , oOutputDir
54 ba9349b8 Iustin Pop
    , oLuxiSocket
55 0427285d Iustin Pop
    , oVerbose
56 0427285d Iustin Pop
    , oNoHeaders
57 0427285d Iustin Pop
    , oShowVer
58 0427285d Iustin Pop
    , oShowHelp
59 1b7a5835 Iustin Pop
    ]
60 1b7a5835 Iustin Pop
61 1b7a5835 Iustin Pop
-- | Return a one-line summary of cluster state
62 262a08a2 Iustin Pop
printCluster :: Node.List -> Instance.List
63 1b7a5835 Iustin Pop
             -> String
64 dbd6700b Iustin Pop
printCluster nl il =
65 1b7a5835 Iustin Pop
    let (bad_nodes, bad_instances) = Cluster.computeBadItems nl il
66 1b7a5835 Iustin Pop
        ccv = Cluster.compCV nl
67 1b7a5835 Iustin Pop
        nodes = Container.elems nl
68 dbd6700b Iustin Pop
        insts = Container.elems il
69 2060348b Iustin Pop
        t_ram = sum . map Node.tMem $ nodes
70 2060348b Iustin Pop
        t_dsk = sum . map Node.tDsk $ nodes
71 2060348b Iustin Pop
        f_ram = sum . map Node.fMem $ nodes
72 2060348b Iustin Pop
        f_dsk = sum . map Node.fDsk $ nodes
73 1b7a5835 Iustin Pop
    in
74 78694255 Iustin Pop
      printf "%5d %5d %5d %5d %6.0f %6d %6.0f %6d %.8f"
75 dbd6700b Iustin Pop
                 (length nodes) (length insts)
76 1b7a5835 Iustin Pop
                 (length bad_nodes) (length bad_instances)
77 78694255 Iustin Pop
                 t_ram f_ram
78 78694255 Iustin Pop
                 (t_dsk / 1024) (f_dsk `div` 1024)
79 1b7a5835 Iustin Pop
                 ccv
80 1b7a5835 Iustin Pop
81 1b7a5835 Iustin Pop
82 0944090a Iustin Pop
-- | Replace slashes with underscore for saving to filesystem
83 0944090a Iustin Pop
fixSlash :: String -> String
84 0944090a Iustin Pop
fixSlash = map (\x -> if x == '/' then '_' else x)
85 0944090a Iustin Pop
86 ba9349b8 Iustin Pop
87 86ea20e8 Iustin Pop
-- | Generates serialized data from loader input.
88 693342ad Iustin Pop
processData :: ClusterData -> Result ClusterData
89 ba9349b8 Iustin Pop
processData input_data = do
90 693342ad Iustin Pop
  cdata@(ClusterData _ nl il _) <- mergeData [] [] [] input_data
91 017a0c3d Iustin Pop
  let (_, fix_nl) = checkData nl il
92 86ea20e8 Iustin Pop
  return cdata { cdNodes = fix_nl }
93 ba9349b8 Iustin Pop
94 ba9349b8 Iustin Pop
-- | Writes cluster data out
95 ba9349b8 Iustin Pop
writeData :: Int
96 ba9349b8 Iustin Pop
          -> String
97 ba9349b8 Iustin Pop
          -> Options
98 86ea20e8 Iustin Pop
          -> Result ClusterData
99 f688711c Iustin Pop
          -> IO Bool
100 ba9349b8 Iustin Pop
writeData _ name _ (Bad err) =
101 f688711c Iustin Pop
  printf "\nError for %s: failed to load data. Details:\n%s\n" name err >>
102 f688711c Iustin Pop
  return False
103 ba9349b8 Iustin Pop
104 86ea20e8 Iustin Pop
writeData nlen name opts (Ok cdata) = do
105 693342ad Iustin Pop
  let fixdata = processData cdata
106 693342ad Iustin Pop
  case fixdata of
107 693342ad Iustin Pop
    Bad err -> printf "\nError for %s: failed to process data. Details:\n%s\n"
108 693342ad Iustin Pop
               name err >> return False
109 693342ad Iustin Pop
    Ok processed -> writeDataInner nlen name opts cdata processed
110 693342ad Iustin Pop
111 693342ad Iustin Pop
writeDataInner :: Int
112 693342ad Iustin Pop
               -> String
113 693342ad Iustin Pop
               -> Options
114 693342ad Iustin Pop
               -> ClusterData
115 693342ad Iustin Pop
               -> ClusterData
116 693342ad Iustin Pop
               -> IO Bool
117 693342ad Iustin Pop
writeDataInner nlen name opts cdata fixdata = do
118 693342ad Iustin Pop
  let (ClusterData _ nl il _) = fixdata
119 c939b58e Iustin Pop
  printf "%-*s " nlen name :: IO ()
120 ba9349b8 Iustin Pop
  hFlush stdout
121 ba9349b8 Iustin Pop
  let shownodes = optShowNodes opts
122 ba9349b8 Iustin Pop
      odir = optOutPath opts
123 ba9349b8 Iustin Pop
      oname = odir </> fixSlash name
124 ba9349b8 Iustin Pop
  putStrLn $ printCluster nl il
125 ba9349b8 Iustin Pop
  hFlush stdout
126 ba9349b8 Iustin Pop
  when (isJust shownodes) $
127 ba9349b8 Iustin Pop
       putStr $ Cluster.printNodes nl (fromJust shownodes)
128 86ea20e8 Iustin Pop
  writeFile (oname <.> "data") (serializeCluster cdata)
129 f688711c Iustin Pop
  return True
130 ba9349b8 Iustin Pop
131 1b7a5835 Iustin Pop
-- | Main function.
132 1b7a5835 Iustin Pop
main :: IO ()
133 1b7a5835 Iustin Pop
main = do
134 1b7a5835 Iustin Pop
  cmd_args <- System.getArgs
135 0427285d Iustin Pop
  (opts, clusters) <- parseOpts cmd_args "hscan" options
136 ba9349b8 Iustin Pop
  let local = "LOCAL"
137 1b7a5835 Iustin Pop
138 ba9349b8 Iustin Pop
  let nlen = if null clusters
139 ba9349b8 Iustin Pop
             then length local
140 ba9349b8 Iustin Pop
             else maximum . map length $ clusters
141 1b7a5835 Iustin Pop
142 0427285d Iustin Pop
  unless (optNoHeaders opts) $
143 1b7a5835 Iustin Pop
         printf "%-*s %5s %5s %5s %5s %6s %6s %6s %6s %10s\n" nlen
144 1b7a5835 Iustin Pop
                "Name" "Nodes" "Inst" "BNode" "BInst" "t_mem" "f_mem"
145 1b7a5835 Iustin Pop
                "t_disk" "f_disk" "Score"
146 1b7a5835 Iustin Pop
147 ba9349b8 Iustin Pop
  when (null clusters) $ do
148 5182e970 Iustin Pop
         let lsock = fromMaybe defaultLuxiSocket (optLuxi opts)
149 ba9349b8 Iustin Pop
         let name = local
150 ba9349b8 Iustin Pop
         input_data <- Luxi.loadData lsock
151 693342ad Iustin Pop
         result <- writeData nlen name opts input_data
152 d5072e4c Iustin Pop
         unless result $ exitWith $ ExitFailure 2
153 ba9349b8 Iustin Pop
154 d5072e4c Iustin Pop
  results <- mapM (\name -> Rapi.loadData name >>= writeData nlen name opts)
155 d5072e4c Iustin Pop
             clusters
156 d5072e4c Iustin Pop
  unless (all id results) $ exitWith (ExitFailure 2)