Simulation backend: allow multiple node groups
[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.Group as Group
42 import qualified Ganeti.HTools.Node as Node
43 import qualified Ganeti.HTools.Instance as Instance
44 #ifndef NO_CURL
45 import qualified Ganeti.HTools.Rapi as Rapi
46 #endif
47 import qualified Ganeti.HTools.Luxi as Luxi
48 import qualified Ganeti.HTools.Loader as Loader
49 import Ganeti.HTools.Text (serializeCluster)
50
51 import Ganeti.HTools.CLI
52 import Ganeti.HTools.Types
53
54 -- | Options list and functions
55 options :: [OptType]
56 options =
57     [ oPrintNodes
58     , oOutputDir
59     , oLuxiSocket
60     , oVerbose
61     , oNoHeaders
62     , oShowVer
63     , oShowHelp
64     ]
65
66 -- | Return a one-line summary of cluster state
67 printCluster :: Node.List -> Instance.List
68              -> String
69 printCluster nl il =
70     let (bad_nodes, bad_instances) = Cluster.computeBadItems nl il
71         ccv = Cluster.compCV nl
72         nodes = Container.elems nl
73         insts = Container.elems il
74         t_ram = sum . map Node.tMem $ nodes
75         t_dsk = sum . map Node.tDsk $ nodes
76         f_ram = sum . map Node.fMem $ nodes
77         f_dsk = sum . map Node.fDsk $ nodes
78     in
79       printf "%5d %5d %5d %5d %6.0f %6d %6.0f %6d %.8f"
80                  (length nodes) (length insts)
81                  (length bad_nodes) (length bad_instances)
82                  t_ram f_ram
83                  (t_dsk / 1024) (f_dsk `div` 1024)
84                  ccv
85
86
87 -- | Replace slashes with underscore for saving to filesystem
88 fixSlash :: String -> String
89 fixSlash = map (\x -> if x == '/' then '_' else x)
90
91
92 -- | Generates serialized data from loader input
93 processData :: Result (Group.List, Node.List, Instance.List, [String])
94             -> Result (Group.List, Node.List, Instance.List, String)
95 processData input_data = do
96   (gl, nl, il, ctags) <- input_data >>= Loader.mergeData [] [] []
97   let (_, fix_nl) = Loader.checkData nl il
98       adata = serializeCluster gl nl il ctags
99   return (gl, fix_nl, il, adata)
100
101 -- | Writes cluster data out
102 writeData :: Int
103           -> String
104           -> Options
105           -> Result (Group.List, Node.List, Instance.List, String)
106           -> IO Bool
107 writeData _ name _ (Bad err) =
108   printf "\nError for %s: failed to load data. Details:\n%s\n" name err >>
109   return False
110
111 writeData nlen name opts (Ok (_, nl, il, adata)) = do
112   printf "%-*s " nlen name :: IO ()
113   hFlush stdout
114   let shownodes = optShowNodes opts
115       odir = optOutPath opts
116       oname = odir </> fixSlash name
117   putStrLn $ printCluster nl il
118   hFlush stdout
119   when (isJust shownodes) $
120        putStr $ Cluster.printNodes nl (fromJust shownodes)
121   writeFile (oname <.> "data") adata
122   return True
123
124 -- | Main function.
125 main :: IO ()
126 main = do
127   cmd_args <- System.getArgs
128   (opts, clusters) <- parseOpts cmd_args "hscan" options
129   let local = "LOCAL"
130
131   let nlen = if null clusters
132              then length local
133              else maximum . map length $ clusters
134
135   unless (optNoHeaders opts) $
136          printf "%-*s %5s %5s %5s %5s %6s %6s %6s %6s %10s\n" nlen
137                 "Name" "Nodes" "Inst" "BNode" "BInst" "t_mem" "f_mem"
138                 "t_disk" "f_disk" "Score"
139
140   when (null clusters) $ do
141          let lsock = fromMaybe defaultLuxiSocket (optLuxi opts)
142          let name = local
143          input_data <- Luxi.loadData lsock
144          result <- writeData nlen name opts (processData input_data)
145          when (not result) $ exitWith $ ExitFailure 2
146
147 #ifndef NO_CURL
148   results <- mapM (\ name ->
149                     do
150                       input_data <- Rapi.loadData name
151                       writeData nlen name opts (processData input_data)
152                   ) clusters
153   when (not $ all id results) $ exitWith (ExitFailure 2)
154 #else
155   when (not $ null clusters) $ do
156     putStrLn "RAPI/curl backend disabled at compile time, cannot scan clusters"
157     exitWith $ ExitFailure 1
158 #endif