Statistics
| Branch: | Tag: | Revision:

root / hscan.hs @ 306cccd5

History | View | Annotate | Download (4.7 kB)

1 ba9349b8 Iustin Pop
{-# LANGUAGE CPP #-}
2 ba9349b8 Iustin Pop
3 ba9349b8 Iustin Pop
{-| Scan clusters via RAPI or LUXI and write state data files.
4 1b7a5835 Iustin Pop
5 1b7a5835 Iustin Pop
-}
6 1b7a5835 Iustin Pop
7 e2fa2baf Iustin Pop
{-
8 e2fa2baf Iustin Pop
9 3bf75b7d Iustin Pop
Copyright (C) 2009, 2010 Google Inc.
10 e2fa2baf Iustin Pop
11 e2fa2baf Iustin Pop
This program is free software; you can redistribute it and/or modify
12 e2fa2baf Iustin Pop
it under the terms of the GNU General Public License as published by
13 e2fa2baf Iustin Pop
the Free Software Foundation; either version 2 of the License, or
14 e2fa2baf Iustin Pop
(at your option) any later version.
15 e2fa2baf Iustin Pop
16 e2fa2baf Iustin Pop
This program is distributed in the hope that it will be useful, but
17 e2fa2baf Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
18 e2fa2baf Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19 e2fa2baf Iustin Pop
General Public License for more details.
20 e2fa2baf Iustin Pop
21 e2fa2baf Iustin Pop
You should have received a copy of the GNU General Public License
22 e2fa2baf Iustin Pop
along with this program; if not, write to the Free Software
23 e2fa2baf Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
24 e2fa2baf Iustin Pop
02110-1301, USA.
25 e2fa2baf Iustin Pop
26 e2fa2baf Iustin Pop
-}
27 e2fa2baf Iustin Pop
28 1b7a5835 Iustin Pop
module Main (main) where
29 1b7a5835 Iustin Pop
30 5182e970 Iustin Pop
import Data.Maybe (isJust, fromJust, fromMaybe)
31 1b7a5835 Iustin Pop
import Monad
32 0903280b Iustin Pop
import System (exitWith, ExitCode(..))
33 1b7a5835 Iustin Pop
import System.IO
34 1b7a5835 Iustin Pop
import System.FilePath
35 1b7a5835 Iustin Pop
import qualified System
36 1b7a5835 Iustin Pop
37 1b7a5835 Iustin Pop
import Text.Printf (printf)
38 1b7a5835 Iustin Pop
39 1b7a5835 Iustin Pop
import qualified Ganeti.HTools.Container as Container
40 1b7a5835 Iustin Pop
import qualified Ganeti.HTools.Cluster as Cluster
41 1b7a5835 Iustin Pop
import qualified Ganeti.HTools.Node as Node
42 1b7a5835 Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
43 ba9349b8 Iustin Pop
#ifndef NO_CURL
44 040afc35 Iustin Pop
import qualified Ganeti.HTools.Rapi as Rapi
45 ba9349b8 Iustin Pop
#endif
46 ba9349b8 Iustin Pop
import qualified Ganeti.HTools.Luxi as Luxi
47 e4c5beaf Iustin Pop
import qualified Ganeti.HTools.Loader as Loader
48 4a273e97 Iustin Pop
import Ganeti.HTools.Text (serializeCluster)
49 1b7a5835 Iustin Pop
50 0427285d Iustin Pop
import Ganeti.HTools.CLI
51 0427285d Iustin Pop
import Ganeti.HTools.Types
52 1b7a5835 Iustin Pop
53 1b7a5835 Iustin Pop
-- | Options list and functions
54 0427285d Iustin Pop
options :: [OptType]
55 1b7a5835 Iustin Pop
options =
56 0427285d Iustin Pop
    [ oPrintNodes
57 0427285d Iustin Pop
    , oOutputDir
58 ba9349b8 Iustin Pop
    , oLuxiSocket
59 0427285d Iustin Pop
    , oVerbose
60 0427285d Iustin Pop
    , oNoHeaders
61 0427285d Iustin Pop
    , oShowVer
62 0427285d Iustin Pop
    , oShowHelp
63 1b7a5835 Iustin Pop
    ]
64 1b7a5835 Iustin Pop
65 1b7a5835 Iustin Pop
-- | Return a one-line summary of cluster state
66 262a08a2 Iustin Pop
printCluster :: Node.List -> Instance.List
67 1b7a5835 Iustin Pop
             -> String
68 dbd6700b Iustin Pop
printCluster nl il =
69 1b7a5835 Iustin Pop
    let (bad_nodes, bad_instances) = Cluster.computeBadItems nl il
70 1b7a5835 Iustin Pop
        ccv = Cluster.compCV nl
71 1b7a5835 Iustin Pop
        nodes = Container.elems nl
72 dbd6700b Iustin Pop
        insts = Container.elems il
73 2060348b Iustin Pop
        t_ram = sum . map Node.tMem $ nodes
74 2060348b Iustin Pop
        t_dsk = sum . map Node.tDsk $ nodes
75 2060348b Iustin Pop
        f_ram = sum . map Node.fMem $ nodes
76 2060348b Iustin Pop
        f_dsk = sum . map Node.fDsk $ nodes
77 1b7a5835 Iustin Pop
    in
78 78694255 Iustin Pop
      printf "%5d %5d %5d %5d %6.0f %6d %6.0f %6d %.8f"
79 dbd6700b Iustin Pop
                 (length nodes) (length insts)
80 1b7a5835 Iustin Pop
                 (length bad_nodes) (length bad_instances)
81 78694255 Iustin Pop
                 t_ram f_ram
82 78694255 Iustin Pop
                 (t_dsk / 1024) (f_dsk `div` 1024)
83 1b7a5835 Iustin Pop
                 ccv
84 1b7a5835 Iustin Pop
85 1b7a5835 Iustin Pop
86 0944090a Iustin Pop
-- | Replace slashes with underscore for saving to filesystem
87 0944090a Iustin Pop
fixSlash :: String -> String
88 0944090a Iustin Pop
fixSlash = map (\x -> if x == '/' then '_' else x)
89 0944090a Iustin Pop
90 ba9349b8 Iustin Pop
91 ba9349b8 Iustin Pop
-- | Generates serialized data from loader input
92 ba9349b8 Iustin Pop
processData :: Result (Node.AssocList, Instance.AssocList, [String])
93 ba9349b8 Iustin Pop
            -> Result (Node.List, Instance.List, String)
94 ba9349b8 Iustin Pop
processData input_data = do
95 3e4480e0 Iustin Pop
  (nl, il, _) <- input_data >>= Loader.mergeData [] [] []
96 ba9349b8 Iustin Pop
  let (_, fix_nl) = Loader.checkData nl il
97 4a273e97 Iustin Pop
      adata = serializeCluster nl il
98 ba9349b8 Iustin Pop
  return (fix_nl, il, adata)
99 ba9349b8 Iustin Pop
100 ba9349b8 Iustin Pop
-- | Writes cluster data out
101 ba9349b8 Iustin Pop
writeData :: Int
102 ba9349b8 Iustin Pop
          -> String
103 ba9349b8 Iustin Pop
          -> Options
104 ba9349b8 Iustin Pop
          -> Result (Node.List, Instance.List, String)
105 f688711c Iustin Pop
          -> IO Bool
106 ba9349b8 Iustin Pop
writeData _ name _ (Bad err) =
107 f688711c Iustin Pop
  printf "\nError for %s: failed to load data. Details:\n%s\n" name err >>
108 f688711c Iustin Pop
  return False
109 ba9349b8 Iustin Pop
110 ba9349b8 Iustin Pop
writeData nlen name opts (Ok (nl, il, adata)) = do
111 c939b58e Iustin Pop
  printf "%-*s " nlen name :: IO ()
112 ba9349b8 Iustin Pop
  hFlush stdout
113 ba9349b8 Iustin Pop
  let shownodes = optShowNodes opts
114 ba9349b8 Iustin Pop
      odir = optOutPath opts
115 ba9349b8 Iustin Pop
      oname = odir </> fixSlash name
116 ba9349b8 Iustin Pop
  putStrLn $ printCluster nl il
117 ba9349b8 Iustin Pop
  hFlush stdout
118 ba9349b8 Iustin Pop
  when (isJust shownodes) $
119 ba9349b8 Iustin Pop
       putStr $ Cluster.printNodes nl (fromJust shownodes)
120 ba9349b8 Iustin Pop
  writeFile (oname <.> "data") adata
121 f688711c Iustin Pop
  return True
122 ba9349b8 Iustin Pop
123 1b7a5835 Iustin Pop
-- | Main function.
124 1b7a5835 Iustin Pop
main :: IO ()
125 1b7a5835 Iustin Pop
main = do
126 1b7a5835 Iustin Pop
  cmd_args <- System.getArgs
127 0427285d Iustin Pop
  (opts, clusters) <- parseOpts cmd_args "hscan" options
128 ba9349b8 Iustin Pop
  let local = "LOCAL"
129 1b7a5835 Iustin Pop
130 ba9349b8 Iustin Pop
  let nlen = if null clusters
131 ba9349b8 Iustin Pop
             then length local
132 ba9349b8 Iustin Pop
             else maximum . map length $ clusters
133 1b7a5835 Iustin Pop
134 0427285d Iustin Pop
  unless (optNoHeaders opts) $
135 1b7a5835 Iustin Pop
         printf "%-*s %5s %5s %5s %5s %6s %6s %6s %6s %10s\n" nlen
136 1b7a5835 Iustin Pop
                "Name" "Nodes" "Inst" "BNode" "BInst" "t_mem" "f_mem"
137 1b7a5835 Iustin Pop
                "t_disk" "f_disk" "Score"
138 1b7a5835 Iustin Pop
139 ba9349b8 Iustin Pop
  when (null clusters) $ do
140 5182e970 Iustin Pop
         let lsock = fromMaybe defaultLuxiSocket (optLuxi opts)
141 ba9349b8 Iustin Pop
         let name = local
142 ba9349b8 Iustin Pop
         input_data <- Luxi.loadData lsock
143 f688711c Iustin Pop
         result <- writeData nlen name opts (processData input_data)
144 f688711c Iustin Pop
         when (not result) $ exitWith $ ExitFailure 2
145 ba9349b8 Iustin Pop
146 ba9349b8 Iustin Pop
#ifndef NO_CURL
147 f688711c Iustin Pop
  results <- mapM (\ name ->
148 f688711c Iustin Pop
                    do
149 f688711c Iustin Pop
                      input_data <- Rapi.loadData name
150 f688711c Iustin Pop
                      writeData nlen name opts (processData input_data)
151 f688711c Iustin Pop
                  ) clusters
152 f688711c Iustin Pop
  when (not $ all id results) $ exitWith (ExitFailure 2)
153 ba9349b8 Iustin Pop
#else
154 ba9349b8 Iustin Pop
  when (not $ null clusters) $ do
155 ba9349b8 Iustin Pop
    putStrLn "RAPI/curl backend disabled at compile time, cannot scan clusters"
156 ba9349b8 Iustin Pop
    exitWith $ ExitFailure 1
157 ba9349b8 Iustin Pop
#endif