Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / ExtLoader.hs @ f5ed8632

History | View | Annotate | Download (4.6 kB)

1 45ab6a8d Iustin Pop
{-# LANGUAGE CPP #-}
2 45ab6a8d Iustin Pop
3 e8f89bb6 Iustin Pop
{-| External data loader
4 e8f89bb6 Iustin Pop
5 e8f89bb6 Iustin Pop
This module holds the external data loading, and thus is the only one
6 cf924b6d Iustin Pop
depending (via the specialized Text\/Rapi\/Luxi modules) on the actual
7 e8f89bb6 Iustin Pop
libraries implementing the low-level protocols.
8 e8f89bb6 Iustin Pop
9 e8f89bb6 Iustin Pop
-}
10 e8f89bb6 Iustin Pop
11 e8f89bb6 Iustin Pop
{-
12 e8f89bb6 Iustin Pop
13 e8f89bb6 Iustin Pop
Copyright (C) 2009 Google Inc.
14 e8f89bb6 Iustin Pop
15 e8f89bb6 Iustin Pop
This program is free software; you can redistribute it and/or modify
16 e8f89bb6 Iustin Pop
it under the terms of the GNU General Public License as published by
17 e8f89bb6 Iustin Pop
the Free Software Foundation; either version 2 of the License, or
18 e8f89bb6 Iustin Pop
(at your option) any later version.
19 e8f89bb6 Iustin Pop
20 e8f89bb6 Iustin Pop
This program is distributed in the hope that it will be useful, but
21 e8f89bb6 Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
22 e8f89bb6 Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
23 e8f89bb6 Iustin Pop
General Public License for more details.
24 e8f89bb6 Iustin Pop
25 e8f89bb6 Iustin Pop
You should have received a copy of the GNU General Public License
26 e8f89bb6 Iustin Pop
along with this program; if not, write to the Free Software
27 e8f89bb6 Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
28 e8f89bb6 Iustin Pop
02110-1301, USA.
29 e8f89bb6 Iustin Pop
30 e8f89bb6 Iustin Pop
-}
31 e8f89bb6 Iustin Pop
32 e8f89bb6 Iustin Pop
module Ganeti.HTools.ExtLoader
33 e8f89bb6 Iustin Pop
    ( loadExternalData
34 3e4480e0 Iustin Pop
    , Loader.commonSuffix
35 e8f89bb6 Iustin Pop
    ) where
36 e8f89bb6 Iustin Pop
37 e8f89bb6 Iustin Pop
import Data.Maybe (isJust, fromJust)
38 e8f89bb6 Iustin Pop
import Monad
39 e8f89bb6 Iustin Pop
import System.IO
40 e8f89bb6 Iustin Pop
import System
41 e8f89bb6 Iustin Pop
import Text.Printf (printf, hPrintf)
42 e8f89bb6 Iustin Pop
43 e8f89bb6 Iustin Pop
import qualified Ganeti.HTools.Luxi as Luxi
44 45ab6a8d Iustin Pop
#ifndef NO_CURL
45 e8f89bb6 Iustin Pop
import qualified Ganeti.HTools.Rapi as Rapi
46 45ab6a8d Iustin Pop
#endif
47 e8f89bb6 Iustin Pop
import qualified Ganeti.HTools.Simu as Simu
48 e8f89bb6 Iustin Pop
import qualified Ganeti.HTools.Text as Text
49 e8f89bb6 Iustin Pop
import qualified Ganeti.HTools.Loader as Loader
50 e8f89bb6 Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
51 e8f89bb6 Iustin Pop
import qualified Ganeti.HTools.Node as Node
52 e8f89bb6 Iustin Pop
53 e8f89bb6 Iustin Pop
import Ganeti.HTools.Types
54 e8f89bb6 Iustin Pop
import Ganeti.HTools.CLI
55 aa8d2e71 Iustin Pop
import Ganeti.HTools.Utils (sepSplit, tryRead)
56 e8f89bb6 Iustin Pop
57 e8f89bb6 Iustin Pop
-- | Error beautifier
58 e8f89bb6 Iustin Pop
wrapIO :: IO (Result a) -> IO (Result a)
59 1cf97474 Iustin Pop
wrapIO = flip catch (return . Bad . show)
60 e8f89bb6 Iustin Pop
61 aa8d2e71 Iustin Pop
parseUtilisation :: String -> Result (String, DynUtil)
62 aa8d2e71 Iustin Pop
parseUtilisation line =
63 aa8d2e71 Iustin Pop
    let columns = sepSplit ' ' line
64 aa8d2e71 Iustin Pop
    in case columns of
65 aa8d2e71 Iustin Pop
         [name, cpu, mem, dsk, net] -> do
66 aa8d2e71 Iustin Pop
                      rcpu <- tryRead name cpu
67 aa8d2e71 Iustin Pop
                      rmem <- tryRead name mem
68 aa8d2e71 Iustin Pop
                      rdsk <- tryRead name dsk
69 aa8d2e71 Iustin Pop
                      rnet <- tryRead name net
70 aa8d2e71 Iustin Pop
                      let du = DynUtil { cpuWeight = rcpu, memWeight = rmem
71 aa8d2e71 Iustin Pop
                                       , dskWeight = rdsk, netWeight = rnet }
72 aa8d2e71 Iustin Pop
                      return (name, du)
73 aa8d2e71 Iustin Pop
         _ -> Bad $ "Cannot parse line " ++ line
74 aa8d2e71 Iustin Pop
75 e8f89bb6 Iustin Pop
-- | External tool data loader from a variety of sources.
76 e8f89bb6 Iustin Pop
loadExternalData :: Options
77 3e4480e0 Iustin Pop
                 -> IO (Node.List, Instance.List, [String])
78 e8f89bb6 Iustin Pop
loadExternalData opts = do
79 16c2369c Iustin Pop
  let mhost = optMaster opts
80 e8f89bb6 Iustin Pop
      lsock = optLuxi opts
81 16c2369c Iustin Pop
      tfile = optDataFile opts
82 e8f89bb6 Iustin Pop
      simdata = optNodeSim opts
83 e8f89bb6 Iustin Pop
      setRapi = mhost /= ""
84 e8f89bb6 Iustin Pop
      setLuxi = isJust lsock
85 e8f89bb6 Iustin Pop
      setSim = isJust simdata
86 16c2369c Iustin Pop
      setFile = isJust tfile
87 16c2369c Iustin Pop
      allSet = filter id [setRapi, setLuxi, setFile]
88 0f15cc76 Iustin Pop
      exTags = case optExTags opts of
89 0f15cc76 Iustin Pop
                 Nothing -> []
90 0f15cc76 Iustin Pop
                 Just etl -> map (++ ":") etl
91 39f979b8 Iustin Pop
      exInsts = optExInst opts
92 0f15cc76 Iustin Pop
93 e8f89bb6 Iustin Pop
  when (length allSet > 1) $
94 e8f89bb6 Iustin Pop
       do
95 45ab6a8d Iustin Pop
         hPutStrLn stderr ("Error: Only one of the rapi, luxi, and data" ++
96 45ab6a8d Iustin Pop
                           " files options should be given.")
97 e8f89bb6 Iustin Pop
         exitWith $ ExitFailure 1
98 e8f89bb6 Iustin Pop
99 aa8d2e71 Iustin Pop
  util_contents <- (case optDynuFile opts of
100 aa8d2e71 Iustin Pop
                      Just path -> readFile path
101 aa8d2e71 Iustin Pop
                      Nothing -> return "")
102 aa8d2e71 Iustin Pop
  let util_data = mapM parseUtilisation $ lines util_contents
103 aa8d2e71 Iustin Pop
  util_data' <- (case util_data of
104 aa8d2e71 Iustin Pop
                   Ok x -> return x
105 aa8d2e71 Iustin Pop
                   Bad y -> do
106 aa8d2e71 Iustin Pop
                     hPutStrLn stderr ("Error: can't parse utilisation" ++
107 aa8d2e71 Iustin Pop
                                       " data: " ++ show y)
108 aa8d2e71 Iustin Pop
                     exitWith $ ExitFailure 1)
109 e8f89bb6 Iustin Pop
  input_data <-
110 e8f89bb6 Iustin Pop
      case () of
111 45ab6a8d Iustin Pop
        _ | setRapi ->
112 45ab6a8d Iustin Pop
#ifdef NO_CURL
113 45ab6a8d Iustin Pop
              return $ Bad "RAPI/curl backend disabled at compile time"
114 45ab6a8d Iustin Pop
#else
115 45ab6a8d Iustin Pop
              wrapIO $ Rapi.loadData mhost
116 45ab6a8d Iustin Pop
#endif
117 e8f89bb6 Iustin Pop
          | setLuxi -> wrapIO $ Luxi.loadData $ fromJust lsock
118 e8f89bb6 Iustin Pop
          | setSim -> Simu.loadData $ fromJust simdata
119 16c2369c Iustin Pop
          | setFile -> wrapIO $ Text.loadData $ fromJust tfile
120 16c2369c Iustin Pop
          | otherwise -> return $ Bad "No backend selected! Exiting."
121 e8f89bb6 Iustin Pop
122 39f979b8 Iustin Pop
  let ldresult = input_data >>= Loader.mergeData util_data' exTags exInsts
123 3e4480e0 Iustin Pop
  (loaded_nl, il, tags) <-
124 e8f89bb6 Iustin Pop
      (case ldresult of
125 e8f89bb6 Iustin Pop
         Ok x -> return x
126 e8f89bb6 Iustin Pop
         Bad s -> do
127 e8f89bb6 Iustin Pop
           hPrintf stderr "Error: failed to load data. Details:\n%s\n" s
128 c939b58e Iustin Pop
               :: IO ()
129 e8f89bb6 Iustin Pop
           exitWith $ ExitFailure 1
130 e8f89bb6 Iustin Pop
      )
131 e8f89bb6 Iustin Pop
  let (fix_msgs, fixed_nl) = Loader.checkData loaded_nl il
132 e8f89bb6 Iustin Pop
133 e8f89bb6 Iustin Pop
  unless (null fix_msgs || optVerbose opts == 0) $ do
134 e8f89bb6 Iustin Pop
         hPutStrLn stderr "Warning: cluster has inconsistent data:"
135 e8f89bb6 Iustin Pop
         hPutStrLn stderr . unlines . map (printf "  - %s") $ fix_msgs
136 e8f89bb6 Iustin Pop
137 3e4480e0 Iustin Pop
  return (fixed_nl, il, tags)