Update NEWS file for the 0.2.6 release
[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 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.List
31 import Data.Maybe (isJust, fromJust, fromMaybe)
32 import Monad
33 import System (exitWith, ExitCode(..))
34 import System.IO
35 import System.FilePath
36 import qualified System
37
38 import Text.Printf (printf)
39
40 import qualified Ganeti.HTools.Container as Container
41 import qualified Ganeti.HTools.Cluster as Cluster
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
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 -- | Serialize a single node
66 serializeNode :: Node.Node -> String
67 serializeNode node =
68     printf "%s|%.0f|%d|%d|%.0f|%d|%.0f|%c" (Node.name node)
69                (Node.tMem node) (Node.nMem node) (Node.fMem node)
70                (Node.tDsk node) (Node.fDsk node) (Node.tCpu node)
71                (if Node.offline node then 'Y' else 'N')
72
73 -- | Generate node file data from node objects
74 serializeNodes :: Node.List -> String
75 serializeNodes = unlines . map serializeNode . Container.elems
76
77 -- | Serialize a single instance
78 serializeInstance :: Node.List -> Instance.Instance -> String
79 serializeInstance nl inst =
80     let
81         iname = Instance.name inst
82         pnode = Container.nameOf nl (Instance.pNode inst)
83         sidx = Instance.sNode inst
84         snode = (if sidx == Node.noSecondary
85                     then ""
86                     else Container.nameOf nl sidx)
87     in
88       printf "%s|%d|%d|%d|%s|%s|%s|%s"
89              iname (Instance.mem inst) (Instance.dsk inst)
90              (Instance.vcpus inst) (Instance.runSt inst)
91              pnode snode (intercalate "," (Instance.tags inst))
92
93 -- | Generate instance file data from instance objects
94 serializeInstances :: Node.List -> Instance.List -> String
95 serializeInstances nl =
96     unlines . map (serializeInstance nl) . Container.elems
97
98 -- | Return a one-line summary of cluster state
99 printCluster :: Node.List -> Instance.List
100              -> String
101 printCluster nl il =
102     let (bad_nodes, bad_instances) = Cluster.computeBadItems nl il
103         ccv = Cluster.compCV nl
104         nodes = Container.elems nl
105         insts = Container.elems il
106         t_ram = sum . map Node.tMem $ nodes
107         t_dsk = sum . map Node.tDsk $ nodes
108         f_ram = sum . map Node.fMem $ nodes
109         f_dsk = sum . map Node.fDsk $ nodes
110     in
111       printf "%5d %5d %5d %5d %6.0f %6d %6.0f %6d %.8f"
112                  (length nodes) (length insts)
113                  (length bad_nodes) (length bad_instances)
114                  t_ram f_ram
115                  (t_dsk / 1024) (f_dsk `div` 1024)
116                  ccv
117
118
119 -- | Replace slashes with underscore for saving to filesystem
120 fixSlash :: String -> String
121 fixSlash = map (\x -> if x == '/' then '_' else x)
122
123
124 -- | Generates serialized data from loader input
125 processData :: Result (Node.AssocList, Instance.AssocList, [String])
126             -> Result (Node.List, Instance.List, String)
127 processData input_data = do
128   (nl, il, _) <- input_data >>= Loader.mergeData [] [] []
129   let (_, fix_nl) = Loader.checkData nl il
130   let ndata = serializeNodes nl
131       idata = serializeInstances nl il
132       adata = ndata ++ ['\n'] ++ idata
133   return (fix_nl, il, adata)
134
135 -- | Writes cluster data out
136 writeData :: Int
137           -> String
138           -> Options
139           -> Result (Node.List, Instance.List, String)
140           -> IO Bool
141 writeData _ name _ (Bad err) =
142   printf "\nError for %s: failed to load data. Details:\n%s\n" name err >>
143   return False
144
145 writeData nlen name opts (Ok (nl, il, adata)) = do
146   printf "%-*s " nlen name :: IO ()
147   hFlush stdout
148   let shownodes = optShowNodes opts
149       odir = optOutPath opts
150       oname = odir </> fixSlash name
151   putStrLn $ printCluster nl il
152   hFlush stdout
153   when (isJust shownodes) $
154        putStr $ Cluster.printNodes nl (fromJust shownodes)
155   writeFile (oname <.> "data") adata
156   return True
157
158 -- | Main function.
159 main :: IO ()
160 main = do
161   cmd_args <- System.getArgs
162   (opts, clusters) <- parseOpts cmd_args "hscan" options
163   let local = "LOCAL"
164
165   let nlen = if null clusters
166              then length local
167              else maximum . map length $ clusters
168
169   unless (optNoHeaders opts) $
170          printf "%-*s %5s %5s %5s %5s %6s %6s %6s %6s %10s\n" nlen
171                 "Name" "Nodes" "Inst" "BNode" "BInst" "t_mem" "f_mem"
172                 "t_disk" "f_disk" "Score"
173
174   when (null clusters) $ do
175          let lsock = fromMaybe defaultLuxiSocket (optLuxi opts)
176          let name = local
177          input_data <- Luxi.loadData lsock
178          result <- writeData nlen name opts (processData input_data)
179          when (not result) $ exitWith $ ExitFailure 2
180
181 #ifndef NO_CURL
182   results <- mapM (\ name ->
183                     do
184                       input_data <- Rapi.loadData name
185                       writeData nlen name opts (processData input_data)
186                   ) clusters
187   when (not $ all id results) $ exitWith (ExitFailure 2)
188 #else
189   when (not $ null clusters) $ do
190     putStrLn "RAPI/curl backend disabled at compile time, cannot scan clusters"
191     exitWith $ ExitFailure 1
192 #endif