Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Program / Hscan.hs @ 8b5a517a

History | View | Annotate | Download (4.7 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 7b695a0d Iustin Pop
module Ganeti.HTools.Program.Hscan (main) where
27 1b7a5835 Iustin Pop
28 cc532bdd Iustin Pop
import Control.Monad
29 5182e970 Iustin Pop
import Data.Maybe (isJust, fromJust, fromMaybe)
30 7345b69b Iustin Pop
import System.Environment (getArgs)
31 7345b69b Iustin Pop
import System.Exit
32 1b7a5835 Iustin Pop
import System.IO
33 1b7a5835 Iustin Pop
import System.FilePath
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 179c0828 Iustin Pop
-- | Options list and functions.
50 0427285d Iustin Pop
options :: [OptType]
51 1b7a5835 Iustin Pop
options =
52 ebf38064 Iustin Pop
  [ oPrintNodes
53 ebf38064 Iustin Pop
  , oOutputDir
54 ebf38064 Iustin Pop
  , oLuxiSocket
55 ebf38064 Iustin Pop
  , oVerbose
56 ebf38064 Iustin Pop
  , oNoHeaders
57 ebf38064 Iustin Pop
  , oShowVer
58 ebf38064 Iustin Pop
  , oShowHelp
59 ebf38064 Iustin Pop
  ]
60 1b7a5835 Iustin Pop
61 179c0828 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 ebf38064 Iustin Pop
  let (bad_nodes, bad_instances) = Cluster.computeBadItems nl il
66 ebf38064 Iustin Pop
      ccv = Cluster.compCV nl
67 ebf38064 Iustin Pop
      nodes = Container.elems nl
68 ebf38064 Iustin Pop
      insts = Container.elems il
69 ebf38064 Iustin Pop
      t_ram = sum . map Node.tMem $ nodes
70 ebf38064 Iustin Pop
      t_dsk = sum . map Node.tDsk $ nodes
71 ebf38064 Iustin Pop
      f_ram = sum . map Node.fMem $ nodes
72 ebf38064 Iustin Pop
      f_dsk = sum . map Node.fDsk $ nodes
73 ebf38064 Iustin Pop
  in printf "%5d %5d %5d %5d %6.0f %6d %6.0f %6d %.8f"
74 ebf38064 Iustin Pop
       (length nodes) (length insts)
75 ebf38064 Iustin Pop
       (length bad_nodes) (length bad_instances)
76 ebf38064 Iustin Pop
       t_ram f_ram (t_dsk / 1024) (f_dsk `div` 1024) ccv
77 1b7a5835 Iustin Pop
78 179c0828 Iustin Pop
-- | Replace slashes with underscore for saving to filesystem.
79 0944090a Iustin Pop
fixSlash :: String -> String
80 0944090a Iustin Pop
fixSlash = map (\x -> if x == '/' then '_' else x)
81 0944090a Iustin Pop
82 86ea20e8 Iustin Pop
-- | Generates serialized data from loader input.
83 693342ad Iustin Pop
processData :: ClusterData -> Result ClusterData
84 ba9349b8 Iustin Pop
processData input_data = do
85 71375ef7 Iustin Pop
  cdata@(ClusterData _ nl il _ _) <- mergeData [] [] [] [] input_data
86 017a0c3d Iustin Pop
  let (_, fix_nl) = checkData nl il
87 86ea20e8 Iustin Pop
  return cdata { cdNodes = fix_nl }
88 ba9349b8 Iustin Pop
89 179c0828 Iustin Pop
-- | Writes cluster data out.
90 ba9349b8 Iustin Pop
writeData :: Int
91 ba9349b8 Iustin Pop
          -> String
92 ba9349b8 Iustin Pop
          -> Options
93 86ea20e8 Iustin Pop
          -> Result ClusterData
94 f688711c Iustin Pop
          -> IO Bool
95 ba9349b8 Iustin Pop
writeData _ name _ (Bad err) =
96 f688711c Iustin Pop
  printf "\nError for %s: failed to load data. Details:\n%s\n" name err >>
97 f688711c Iustin Pop
  return False
98 ba9349b8 Iustin Pop
99 86ea20e8 Iustin Pop
writeData nlen name opts (Ok cdata) = do
100 693342ad Iustin Pop
  let fixdata = processData cdata
101 693342ad Iustin Pop
  case fixdata of
102 693342ad Iustin Pop
    Bad err -> printf "\nError for %s: failed to process data. Details:\n%s\n"
103 693342ad Iustin Pop
               name err >> return False
104 693342ad Iustin Pop
    Ok processed -> writeDataInner nlen name opts cdata processed
105 693342ad Iustin Pop
106 179c0828 Iustin Pop
-- | Inner function for writing cluster data to disk.
107 693342ad Iustin Pop
writeDataInner :: Int
108 693342ad Iustin Pop
               -> String
109 693342ad Iustin Pop
               -> Options
110 693342ad Iustin Pop
               -> ClusterData
111 693342ad Iustin Pop
               -> ClusterData
112 693342ad Iustin Pop
               -> IO Bool
113 693342ad Iustin Pop
writeDataInner nlen name opts cdata fixdata = do
114 71375ef7 Iustin Pop
  let (ClusterData _ nl il _ _) = fixdata
115 c939b58e Iustin Pop
  printf "%-*s " nlen name :: IO ()
116 ba9349b8 Iustin Pop
  hFlush stdout
117 ba9349b8 Iustin Pop
  let shownodes = optShowNodes opts
118 ba9349b8 Iustin Pop
      odir = optOutPath opts
119 ba9349b8 Iustin Pop
      oname = odir </> fixSlash name
120 ba9349b8 Iustin Pop
  putStrLn $ printCluster nl il
121 ba9349b8 Iustin Pop
  hFlush stdout
122 ba9349b8 Iustin Pop
  when (isJust shownodes) $
123 ba9349b8 Iustin Pop
       putStr $ Cluster.printNodes nl (fromJust shownodes)
124 86ea20e8 Iustin Pop
  writeFile (oname <.> "data") (serializeCluster cdata)
125 f688711c Iustin Pop
  return True
126 ba9349b8 Iustin Pop
127 1b7a5835 Iustin Pop
-- | Main function.
128 1b7a5835 Iustin Pop
main :: IO ()
129 1b7a5835 Iustin Pop
main = do
130 7345b69b Iustin Pop
  cmd_args <- getArgs
131 0427285d Iustin Pop
  (opts, clusters) <- parseOpts cmd_args "hscan" options
132 ba9349b8 Iustin Pop
  let local = "LOCAL"
133 1b7a5835 Iustin Pop
134 ba9349b8 Iustin Pop
  let nlen = if null clusters
135 ba9349b8 Iustin Pop
             then length local
136 ba9349b8 Iustin Pop
             else maximum . map length $ clusters
137 1b7a5835 Iustin Pop
138 0427285d Iustin Pop
  unless (optNoHeaders opts) $
139 1b7a5835 Iustin Pop
         printf "%-*s %5s %5s %5s %5s %6s %6s %6s %6s %10s\n" nlen
140 1b7a5835 Iustin Pop
                "Name" "Nodes" "Inst" "BNode" "BInst" "t_mem" "f_mem"
141 1b7a5835 Iustin Pop
                "t_disk" "f_disk" "Score"
142 1b7a5835 Iustin Pop
143 ba9349b8 Iustin Pop
  when (null clusters) $ do
144 5182e970 Iustin Pop
         let lsock = fromMaybe defaultLuxiSocket (optLuxi opts)
145 ba9349b8 Iustin Pop
         let name = local
146 ba9349b8 Iustin Pop
         input_data <- Luxi.loadData lsock
147 693342ad Iustin Pop
         result <- writeData nlen name opts input_data
148 d5072e4c Iustin Pop
         unless result $ exitWith $ ExitFailure 2
149 ba9349b8 Iustin Pop
150 d5072e4c Iustin Pop
  results <- mapM (\name -> Rapi.loadData name >>= writeData nlen name opts)
151 d5072e4c Iustin Pop
             clusters
152 d5072e4c Iustin Pop
  unless (all id results) $ exitWith (ExitFailure 2)