Add maybePrintInsts for the instance listing
[ganeti-local] / hscan.hs
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 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 :: Result ClusterData -> Result ClusterData
93 processData input_data = do
94   cdata@(ClusterData _ nl il _) <- input_data >>= mergeData [] [] []
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 (ClusterData _ nl il _) = cdata
110   printf "%-*s " nlen name :: IO ()
111   hFlush stdout
112   let shownodes = optShowNodes opts
113       odir = optOutPath opts
114       oname = odir </> fixSlash name
115   putStrLn $ printCluster nl il
116   hFlush stdout
117   when (isJust shownodes) $
118        putStr $ Cluster.printNodes nl (fromJust shownodes)
119   writeFile (oname <.> "data") (serializeCluster cdata)
120   return True
121
122 -- | Main function.
123 main :: IO ()
124 main = do
125   cmd_args <- System.getArgs
126   (opts, clusters) <- parseOpts cmd_args "hscan" options
127   let local = "LOCAL"
128
129   let nlen = if null clusters
130              then length local
131              else maximum . map length $ clusters
132
133   unless (optNoHeaders opts) $
134          printf "%-*s %5s %5s %5s %5s %6s %6s %6s %6s %10s\n" nlen
135                 "Name" "Nodes" "Inst" "BNode" "BInst" "t_mem" "f_mem"
136                 "t_disk" "f_disk" "Score"
137
138   when (null clusters) $ do
139          let lsock = fromMaybe defaultLuxiSocket (optLuxi opts)
140          let name = local
141          input_data <- Luxi.loadData lsock
142          result <- writeData nlen name opts (processData input_data)
143          when (not result) $ exitWith $ ExitFailure 2
144
145 #ifndef NO_CURL
146   results <- mapM (\ name ->
147                     do
148                       input_data <- Rapi.loadData name
149                       writeData nlen name opts (processData input_data)
150                   ) clusters
151   when (not $ all id results) $ exitWith (ExitFailure 2)
152 #else
153   when (not $ null clusters) $ do
154     putStrLn "RAPI/curl backend disabled at compile time, cannot scan clusters"
155     exitWith $ ExitFailure 1
156 #endif