Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Program / Hscan.hs @ 7ec2f76b

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