Statistics
| Branch: | Tag: | Revision:

root / hscan.hs @ 23f9ab76

History | View | Annotate | Download (5.1 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 e98fb766 Iustin Pop
import Data.Maybe (isJust, fromJust)
31 1b7a5835 Iustin Pop
import Monad
32 1b7a5835 Iustin Pop
import System
33 1b7a5835 Iustin Pop
import System.IO
34 1b7a5835 Iustin Pop
import System.FilePath
35 1b7a5835 Iustin Pop
import qualified System
36 1b7a5835 Iustin Pop
37 1b7a5835 Iustin Pop
import Text.Printf (printf)
38 1b7a5835 Iustin Pop
39 1b7a5835 Iustin Pop
import qualified Ganeti.HTools.Container as Container
40 1b7a5835 Iustin Pop
import qualified Ganeti.HTools.Cluster as Cluster
41 1b7a5835 Iustin Pop
import qualified Ganeti.HTools.Node as Node
42 1b7a5835 Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
43 040afc35 Iustin Pop
import qualified Ganeti.HTools.Rapi as Rapi
44 e4c5beaf Iustin Pop
import qualified Ganeti.HTools.Loader as Loader
45 1b7a5835 Iustin Pop
46 0427285d Iustin Pop
import Ganeti.HTools.CLI
47 0427285d Iustin Pop
import Ganeti.HTools.Types
48 1b7a5835 Iustin Pop
49 1b7a5835 Iustin Pop
-- | Options list and functions
50 0427285d Iustin Pop
options :: [OptType]
51 1b7a5835 Iustin Pop
options =
52 0427285d Iustin Pop
    [ oPrintNodes
53 0427285d Iustin Pop
    , oOutputDir
54 0427285d Iustin Pop
    , oVerbose
55 0427285d Iustin Pop
    , oNoHeaders
56 0427285d Iustin Pop
    , oShowVer
57 0427285d Iustin Pop
    , oShowHelp
58 1b7a5835 Iustin Pop
    ]
59 1b7a5835 Iustin Pop
60 78694255 Iustin Pop
-- | Serialize a single node
61 78694255 Iustin Pop
serializeNode :: String -> Node.Node -> String
62 78694255 Iustin Pop
serializeNode csf node =
63 d4c453d2 Iustin Pop
    printf "%s|%.0f|%d|%d|%.0f|%d|%.0f|%c" (Node.name node ++ csf)
64 2060348b Iustin Pop
               (Node.tMem node) (Node.nMem node) (Node.fMem node)
65 2060348b Iustin Pop
               (Node.tDsk node) (Node.fDsk node) (Node.tCpu node)
66 d4c453d2 Iustin Pop
               (if Node.offline node then 'Y' else 'N')
67 78694255 Iustin Pop
68 1b7a5835 Iustin Pop
-- | Generate node file data from node objects
69 78694255 Iustin Pop
serializeNodes :: String -> Node.List -> String
70 78694255 Iustin Pop
serializeNodes csf =
71 78694255 Iustin Pop
    unlines . map (serializeNode csf) . Container.elems
72 78694255 Iustin Pop
73 78694255 Iustin Pop
-- | Serialize a single instance
74 78694255 Iustin Pop
serializeInstance :: String -> Node.List -> Instance.Instance -> String
75 78694255 Iustin Pop
serializeInstance csf nl inst =
76 78694255 Iustin Pop
    let
77 78694255 Iustin Pop
        iname = Instance.name inst ++ csf
78 2060348b Iustin Pop
        pnode = Container.nameOf nl (Instance.pNode inst) ++ csf
79 2060348b Iustin Pop
        sidx = Instance.sNode inst
80 d4c453d2 Iustin Pop
        snode = (if sidx == Node.noSecondary
81 d4c453d2 Iustin Pop
                    then ""
82 9f6dcdea Iustin Pop
                    else Container.nameOf nl sidx ++ csf)
83 78694255 Iustin Pop
    in
84 17e7af2b Iustin Pop
      printf "%s|%d|%d|%d|%s|%s|%s|%s"
85 78694255 Iustin Pop
             iname (Instance.mem inst) (Instance.dsk inst)
86 2060348b Iustin Pop
             (Instance.vcpus inst) (Instance.runSt inst)
87 17e7af2b Iustin Pop
             pnode snode (intercalate "," (Instance.tags inst))
88 1b7a5835 Iustin Pop
89 1b7a5835 Iustin Pop
-- | Generate instance file data from instance objects
90 78694255 Iustin Pop
serializeInstances :: String -> Node.List -> Instance.List -> String
91 78694255 Iustin Pop
serializeInstances csf nl =
92 78694255 Iustin Pop
    unlines . map (serializeInstance csf nl) . Container.elems
93 1b7a5835 Iustin Pop
94 1b7a5835 Iustin Pop
-- | Return a one-line summary of cluster state
95 262a08a2 Iustin Pop
printCluster :: Node.List -> Instance.List
96 1b7a5835 Iustin Pop
             -> String
97 dbd6700b Iustin Pop
printCluster nl il =
98 1b7a5835 Iustin Pop
    let (bad_nodes, bad_instances) = Cluster.computeBadItems nl il
99 1b7a5835 Iustin Pop
        ccv = Cluster.compCV nl
100 1b7a5835 Iustin Pop
        nodes = Container.elems nl
101 dbd6700b Iustin Pop
        insts = Container.elems il
102 2060348b Iustin Pop
        t_ram = sum . map Node.tMem $ nodes
103 2060348b Iustin Pop
        t_dsk = sum . map Node.tDsk $ nodes
104 2060348b Iustin Pop
        f_ram = sum . map Node.fMem $ nodes
105 2060348b Iustin Pop
        f_dsk = sum . map Node.fDsk $ nodes
106 1b7a5835 Iustin Pop
    in
107 78694255 Iustin Pop
      printf "%5d %5d %5d %5d %6.0f %6d %6.0f %6d %.8f"
108 dbd6700b Iustin Pop
                 (length nodes) (length insts)
109 1b7a5835 Iustin Pop
                 (length bad_nodes) (length bad_instances)
110 78694255 Iustin Pop
                 t_ram f_ram
111 78694255 Iustin Pop
                 (t_dsk / 1024) (f_dsk `div` 1024)
112 1b7a5835 Iustin Pop
                 ccv
113 1b7a5835 Iustin Pop
114 1b7a5835 Iustin Pop
115 0944090a Iustin Pop
-- | Replace slashes with underscore for saving to filesystem
116 0944090a Iustin Pop
117 0944090a Iustin Pop
fixSlash :: String -> String
118 0944090a Iustin Pop
fixSlash = map (\x -> if x == '/' then '_' else x)
119 0944090a Iustin Pop
120 1b7a5835 Iustin Pop
-- | Main function.
121 1b7a5835 Iustin Pop
main :: IO ()
122 1b7a5835 Iustin Pop
main = do
123 1b7a5835 Iustin Pop
  cmd_args <- System.getArgs
124 0427285d Iustin Pop
  (opts, clusters) <- parseOpts cmd_args "hscan" options
125 1b7a5835 Iustin Pop
126 1b7a5835 Iustin Pop
  let odir = optOutPath opts
127 1b7a5835 Iustin Pop
      nlen = maximum . map length $ clusters
128 e98fb766 Iustin Pop
      shownodes = optShowNodes opts
129 1b7a5835 Iustin Pop
130 0427285d Iustin Pop
  unless (optNoHeaders opts) $
131 1b7a5835 Iustin Pop
         printf "%-*s %5s %5s %5s %5s %6s %6s %6s %6s %10s\n" nlen
132 1b7a5835 Iustin Pop
                "Name" "Nodes" "Inst" "BNode" "BInst" "t_mem" "f_mem"
133 1b7a5835 Iustin Pop
                "t_disk" "f_disk" "Score"
134 1b7a5835 Iustin Pop
135 fd22ce8e Iustin Pop
  mapM_ (\ name ->
136 1b7a5835 Iustin Pop
            do
137 1b7a5835 Iustin Pop
              printf "%-*s " nlen name
138 1b7a5835 Iustin Pop
              hFlush stdout
139 040afc35 Iustin Pop
              input_data <- Rapi.loadData name
140 0f15cc76 Iustin Pop
              let ldresult = input_data >>= Loader.mergeData [] []
141 fd22ce8e Iustin Pop
              (case ldresult of
142 fd22ce8e Iustin Pop
                 Bad err -> printf "\nError: failed to load data. \
143 fd22ce8e Iustin Pop
                                   \Details:\n%s\n" err
144 fd22ce8e Iustin Pop
                 Ok x -> do
145 94e05c32 Iustin Pop
                   let (nl, il, _, csf) = x
146 dbd6700b Iustin Pop
                       (_, fix_nl) = Loader.checkData nl il
147 dbd6700b Iustin Pop
                   putStrLn $ printCluster fix_nl il
148 e98fb766 Iustin Pop
                   when (isJust shownodes) $
149 e98fb766 Iustin Pop
                        putStr $ Cluster.printNodes fix_nl (fromJust shownodes)
150 78694255 Iustin Pop
                   let ndata = serializeNodes csf nl
151 78694255 Iustin Pop
                       idata = serializeInstances csf nl il
152 9f6dcdea Iustin Pop
                       oname = odir </> fixSlash name
153 66ea8434 Iustin Pop
                       adata = ndata ++ ['\n'] ++ idata
154 66ea8434 Iustin Pop
                   writeFile (oname <.> "data") adata)
155 66ea8434 Iustin Pop
        ) clusters