Statistics
| Branch: | Tag: | Revision:

root / hscan.hs @ 8ed71b67

History | View | Annotate | Download (5 kB)

1 1b7a5835 Iustin Pop
{-| Scan clusters via RAPI and write instance/node data files.
2 1b7a5835 Iustin Pop
3 1b7a5835 Iustin Pop
-}
4 1b7a5835 Iustin Pop
5 e2fa2baf Iustin Pop
{-
6 e2fa2baf Iustin Pop
7 e2fa2baf Iustin Pop
Copyright (C) 2009 Google Inc.
8 e2fa2baf Iustin Pop
9 e2fa2baf Iustin Pop
This program is free software; you can redistribute it and/or modify
10 e2fa2baf Iustin Pop
it under the terms of the GNU General Public License as published by
11 e2fa2baf Iustin Pop
the Free Software Foundation; either version 2 of the License, or
12 e2fa2baf Iustin Pop
(at your option) any later version.
13 e2fa2baf Iustin Pop
14 e2fa2baf Iustin Pop
This program is distributed in the hope that it will be useful, but
15 e2fa2baf Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
16 e2fa2baf Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17 e2fa2baf Iustin Pop
General Public License for more details.
18 e2fa2baf Iustin Pop
19 e2fa2baf Iustin Pop
You should have received a copy of the GNU General Public License
20 e2fa2baf Iustin Pop
along with this program; if not, write to the Free Software
21 e2fa2baf Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22 e2fa2baf Iustin Pop
02110-1301, USA.
23 e2fa2baf Iustin Pop
24 e2fa2baf Iustin Pop
-}
25 e2fa2baf Iustin Pop
26 1b7a5835 Iustin Pop
module Main (main) where
27 1b7a5835 Iustin Pop
28 1b7a5835 Iustin Pop
import Data.List
29 1b7a5835 Iustin Pop
import Data.Function
30 1b7a5835 Iustin Pop
import Monad
31 1b7a5835 Iustin Pop
import System
32 1b7a5835 Iustin Pop
import System.IO
33 1b7a5835 Iustin Pop
import System.FilePath
34 1b7a5835 Iustin Pop
import qualified System
35 1b7a5835 Iustin Pop
36 1b7a5835 Iustin Pop
import Text.Printf (printf)
37 1b7a5835 Iustin Pop
38 1b7a5835 Iustin Pop
import qualified Ganeti.HTools.Container as Container
39 1b7a5835 Iustin Pop
import qualified Ganeti.HTools.Cluster as Cluster
40 1b7a5835 Iustin Pop
import qualified Ganeti.HTools.Node as Node
41 1b7a5835 Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
42 040afc35 Iustin Pop
import qualified Ganeti.HTools.Rapi as Rapi
43 e4c5beaf Iustin Pop
import qualified Ganeti.HTools.Loader as Loader
44 1b7a5835 Iustin Pop
45 0427285d Iustin Pop
import Ganeti.HTools.CLI
46 0427285d Iustin Pop
import Ganeti.HTools.Types
47 1b7a5835 Iustin Pop
48 1b7a5835 Iustin Pop
-- | Options list and functions
49 0427285d Iustin Pop
options :: [OptType]
50 1b7a5835 Iustin Pop
options =
51 0427285d Iustin Pop
    [ oPrintNodes
52 0427285d Iustin Pop
    , oOutputDir
53 0427285d Iustin Pop
    , oVerbose
54 0427285d Iustin Pop
    , oNoHeaders
55 0427285d Iustin Pop
    , oShowVer
56 0427285d Iustin Pop
    , oShowHelp
57 1b7a5835 Iustin Pop
    ]
58 1b7a5835 Iustin Pop
59 78694255 Iustin Pop
-- | Serialize a single node
60 78694255 Iustin Pop
serializeNode :: String -> Node.Node -> String
61 78694255 Iustin Pop
serializeNode csf node =
62 d4c453d2 Iustin Pop
    printf "%s|%.0f|%d|%d|%.0f|%d|%.0f|%c" (Node.name node ++ csf)
63 2060348b Iustin Pop
               (Node.tMem node) (Node.nMem node) (Node.fMem node)
64 2060348b Iustin Pop
               (Node.tDsk node) (Node.fDsk node) (Node.tCpu node)
65 d4c453d2 Iustin Pop
               (if Node.offline node then 'Y' else 'N')
66 78694255 Iustin Pop
67 1b7a5835 Iustin Pop
-- | Generate node file data from node objects
68 78694255 Iustin Pop
serializeNodes :: String -> Node.List -> String
69 78694255 Iustin Pop
serializeNodes csf =
70 78694255 Iustin Pop
    unlines . map (serializeNode csf) . Container.elems
71 78694255 Iustin Pop
72 78694255 Iustin Pop
-- | Serialize a single instance
73 78694255 Iustin Pop
serializeInstance :: String -> Node.List -> Instance.Instance -> String
74 78694255 Iustin Pop
serializeInstance csf nl inst =
75 78694255 Iustin Pop
    let
76 78694255 Iustin Pop
        iname = Instance.name inst ++ csf
77 2060348b Iustin Pop
        pnode = Container.nameOf nl (Instance.pNode inst) ++ csf
78 2060348b Iustin Pop
        sidx = Instance.sNode inst
79 d4c453d2 Iustin Pop
        snode = (if sidx == Node.noSecondary
80 d4c453d2 Iustin Pop
                    then ""
81 9f6dcdea Iustin Pop
                    else Container.nameOf nl sidx ++ csf)
82 78694255 Iustin Pop
    in
83 d4c453d2 Iustin Pop
      printf "%s|%d|%d|%d|%s|%s|%s"
84 78694255 Iustin Pop
             iname (Instance.mem inst) (Instance.dsk inst)
85 2060348b Iustin Pop
             (Instance.vcpus inst) (Instance.runSt inst)
86 78694255 Iustin Pop
             pnode snode
87 1b7a5835 Iustin Pop
88 1b7a5835 Iustin Pop
-- | Generate instance file data from instance objects
89 78694255 Iustin Pop
serializeInstances :: String -> Node.List -> Instance.List -> String
90 78694255 Iustin Pop
serializeInstances csf nl =
91 78694255 Iustin Pop
    unlines . map (serializeInstance csf nl) . Container.elems
92 1b7a5835 Iustin Pop
93 1b7a5835 Iustin Pop
-- | Return a one-line summary of cluster state
94 262a08a2 Iustin Pop
printCluster :: Node.List -> Instance.List
95 1b7a5835 Iustin Pop
             -> String
96 dbd6700b Iustin Pop
printCluster nl il =
97 1b7a5835 Iustin Pop
    let (bad_nodes, bad_instances) = Cluster.computeBadItems nl il
98 1b7a5835 Iustin Pop
        ccv = Cluster.compCV nl
99 1b7a5835 Iustin Pop
        nodes = Container.elems nl
100 dbd6700b Iustin Pop
        insts = Container.elems il
101 2060348b Iustin Pop
        t_ram = sum . map Node.tMem $ nodes
102 2060348b Iustin Pop
        t_dsk = sum . map Node.tDsk $ nodes
103 2060348b Iustin Pop
        f_ram = sum . map Node.fMem $ nodes
104 2060348b Iustin Pop
        f_dsk = sum . map Node.fDsk $ nodes
105 1b7a5835 Iustin Pop
    in
106 78694255 Iustin Pop
      printf "%5d %5d %5d %5d %6.0f %6d %6.0f %6d %.8f"
107 dbd6700b Iustin Pop
                 (length nodes) (length insts)
108 1b7a5835 Iustin Pop
                 (length bad_nodes) (length bad_instances)
109 78694255 Iustin Pop
                 t_ram f_ram
110 78694255 Iustin Pop
                 (t_dsk / 1024) (f_dsk `div` 1024)
111 1b7a5835 Iustin Pop
                 ccv
112 1b7a5835 Iustin Pop
113 1b7a5835 Iustin Pop
114 0944090a Iustin Pop
-- | Replace slashes with underscore for saving to filesystem
115 0944090a Iustin Pop
116 0944090a Iustin Pop
fixSlash :: String -> String
117 0944090a Iustin Pop
fixSlash = map (\x -> if x == '/' then '_' else x)
118 0944090a Iustin Pop
119 1b7a5835 Iustin Pop
-- | Main function.
120 1b7a5835 Iustin Pop
main :: IO ()
121 1b7a5835 Iustin Pop
main = do
122 1b7a5835 Iustin Pop
  cmd_args <- System.getArgs
123 0427285d Iustin Pop
  (opts, clusters) <- parseOpts cmd_args "hscan" options
124 1b7a5835 Iustin Pop
125 1b7a5835 Iustin Pop
  let odir = optOutPath opts
126 1b7a5835 Iustin Pop
      nlen = maximum . map length $ clusters
127 1b7a5835 Iustin Pop
128 0427285d Iustin Pop
  unless (optNoHeaders opts) $
129 1b7a5835 Iustin Pop
         printf "%-*s %5s %5s %5s %5s %6s %6s %6s %6s %10s\n" nlen
130 1b7a5835 Iustin Pop
                "Name" "Nodes" "Inst" "BNode" "BInst" "t_mem" "f_mem"
131 1b7a5835 Iustin Pop
                "t_disk" "f_disk" "Score"
132 1b7a5835 Iustin Pop
133 fd22ce8e Iustin Pop
  mapM_ (\ name ->
134 1b7a5835 Iustin Pop
            do
135 1b7a5835 Iustin Pop
              printf "%-*s " nlen name
136 1b7a5835 Iustin Pop
              hFlush stdout
137 040afc35 Iustin Pop
              input_data <- Rapi.loadData name
138 aa8d2e71 Iustin Pop
              let ldresult = input_data >>= Loader.mergeData []
139 fd22ce8e Iustin Pop
              (case ldresult of
140 fd22ce8e Iustin Pop
                 Bad err -> printf "\nError: failed to load data. \
141 fd22ce8e Iustin Pop
                                   \Details:\n%s\n" err
142 fd22ce8e Iustin Pop
                 Ok x -> do
143 8472a321 Iustin Pop
                   let (nl, il, csf) = x
144 dbd6700b Iustin Pop
                       (_, fix_nl) = Loader.checkData nl il
145 dbd6700b Iustin Pop
                   putStrLn $ printCluster fix_nl il
146 9f6dcdea Iustin Pop
                   when (optShowNodes opts) $
147 9f6dcdea Iustin Pop
                        putStr $ Cluster.printNodes fix_nl
148 78694255 Iustin Pop
                   let ndata = serializeNodes csf nl
149 78694255 Iustin Pop
                       idata = serializeInstances csf nl il
150 9f6dcdea Iustin Pop
                       oname = odir </> fixSlash name
151 fd22ce8e Iustin Pop
                   writeFile (oname <.> "nodes") ndata
152 fd22ce8e Iustin Pop
                   writeFile (oname <.> "instances") idata)
153 1b7a5835 Iustin Pop
       ) clusters