Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Program / Hscan.hs @ ef947a42

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