Statistics
| Branch: | Tag: | Revision:

root / htools / hscan.hs @ d5072e4c

History | View | Annotate | Download (5 kB)

1
{-# LANGUAGE CPP #-}
2

    
3
{-| Scan clusters via RAPI or LUXI and write state data files.
4

    
5
-}
6

    
7
{-
8

    
9
Copyright (C) 2009, 2010, 2011 Google Inc.
10

    
11
This program is free software; you can redistribute it and/or modify
12
it under the terms of the GNU General Public License as published by
13
the Free Software Foundation; either version 2 of the License, or
14
(at your option) any later version.
15

    
16
This program is distributed in the hope that it will be useful, but
17
WITHOUT ANY WARRANTY; without even the implied warranty of
18
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19
General Public License for more details.
20

    
21
You should have received a copy of the GNU General Public License
22
along with this program; if not, write to the Free Software
23
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
24
02110-1301, USA.
25

    
26
-}
27

    
28
module Main (main) where
29

    
30
import Data.Maybe (isJust, fromJust, fromMaybe)
31
import Monad
32
import System (exitWith, ExitCode(..))
33
import System.IO
34
import System.FilePath
35
import qualified System
36

    
37
import Text.Printf (printf)
38

    
39
import qualified Ganeti.HTools.Container as Container
40
import qualified Ganeti.HTools.Cluster as Cluster
41
import qualified Ganeti.HTools.Node as Node
42
import qualified Ganeti.HTools.Instance as Instance
43
#ifndef NO_CURL
44
import qualified Ganeti.HTools.Rapi as Rapi
45
#endif
46
import qualified Ganeti.HTools.Luxi as Luxi
47
import Ganeti.HTools.Loader (checkData, mergeData, ClusterData(..))
48
import Ganeti.HTools.Text (serializeCluster)
49

    
50
import Ganeti.HTools.CLI
51
import Ganeti.HTools.Types
52

    
53
-- | Options list and functions
54
options :: [OptType]
55
options =
56
    [ oPrintNodes
57
    , oOutputDir
58
    , oLuxiSocket
59
    , oVerbose
60
    , oNoHeaders
61
    , oShowVer
62
    , oShowHelp
63
    ]
64

    
65
-- | Return a one-line summary of cluster state
66
printCluster :: Node.List -> Instance.List
67
             -> String
68
printCluster nl il =
69
    let (bad_nodes, bad_instances) = Cluster.computeBadItems nl il
70
        ccv = Cluster.compCV nl
71
        nodes = Container.elems nl
72
        insts = Container.elems il
73
        t_ram = sum . map Node.tMem $ nodes
74
        t_dsk = sum . map Node.tDsk $ nodes
75
        f_ram = sum . map Node.fMem $ nodes
76
        f_dsk = sum . map Node.fDsk $ nodes
77
    in
78
      printf "%5d %5d %5d %5d %6.0f %6d %6.0f %6d %.8f"
79
                 (length nodes) (length insts)
80
                 (length bad_nodes) (length bad_instances)
81
                 t_ram f_ram
82
                 (t_dsk / 1024) (f_dsk `div` 1024)
83
                 ccv
84

    
85

    
86
-- | Replace slashes with underscore for saving to filesystem
87
fixSlash :: String -> String
88
fixSlash = map (\x -> if x == '/' then '_' else x)
89

    
90

    
91
-- | Generates serialized data from loader input.
92
processData :: ClusterData -> Result ClusterData
93
processData input_data = do
94
  cdata@(ClusterData _ nl il _) <- mergeData [] [] [] input_data
95
  let (_, fix_nl) = checkData nl il
96
  return cdata { cdNodes = fix_nl }
97

    
98
-- | Writes cluster data out
99
writeData :: Int
100
          -> String
101
          -> Options
102
          -> Result ClusterData
103
          -> IO Bool
104
writeData _ name _ (Bad err) =
105
  printf "\nError for %s: failed to load data. Details:\n%s\n" name err >>
106
  return False
107

    
108
writeData nlen name opts (Ok cdata) = do
109
  let fixdata = processData cdata
110
  case fixdata of
111
    Bad err -> printf "\nError for %s: failed to process data. Details:\n%s\n"
112
               name err >> return False
113
    Ok processed -> writeDataInner nlen name opts cdata processed
114

    
115
writeDataInner :: Int
116
               -> String
117
               -> Options
118
               -> ClusterData
119
               -> ClusterData
120
               -> IO Bool
121
writeDataInner nlen name opts cdata fixdata = do
122
  let (ClusterData _ nl il _) = fixdata
123
  printf "%-*s " nlen name :: IO ()
124
  hFlush stdout
125
  let shownodes = optShowNodes opts
126
      odir = optOutPath opts
127
      oname = odir </> fixSlash name
128
  putStrLn $ printCluster nl il
129
  hFlush stdout
130
  when (isJust shownodes) $
131
       putStr $ Cluster.printNodes nl (fromJust shownodes)
132
  writeFile (oname <.> "data") (serializeCluster cdata)
133
  return True
134

    
135
-- | Main function.
136
main :: IO ()
137
main = do
138
  cmd_args <- System.getArgs
139
  (opts, clusters) <- parseOpts cmd_args "hscan" options
140
  let local = "LOCAL"
141

    
142
  let nlen = if null clusters
143
             then length local
144
             else maximum . map length $ clusters
145

    
146
  unless (optNoHeaders opts) $
147
         printf "%-*s %5s %5s %5s %5s %6s %6s %6s %6s %10s\n" nlen
148
                "Name" "Nodes" "Inst" "BNode" "BInst" "t_mem" "f_mem"
149
                "t_disk" "f_disk" "Score"
150

    
151
  when (null clusters) $ do
152
         let lsock = fromMaybe defaultLuxiSocket (optLuxi opts)
153
         let name = local
154
         input_data <- Luxi.loadData lsock
155
         result <- writeData nlen name opts input_data
156
         unless result $ exitWith $ ExitFailure 2
157

    
158
#ifndef NO_CURL
159
  results <- mapM (\name -> Rapi.loadData name >>= writeData nlen name opts)
160
             clusters
161
  unless (all id results) $ exitWith (ExitFailure 2)
162
#else
163
  when (not $ null clusters) $ do
164
    putStrLn "RAPI/curl backend disabled at compile time, cannot scan clusters"
165
    exitWith $ ExitFailure 1
166
#endif