Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / ExtLoader.hs @ 669ea132

History | View | Annotate | Download (5 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 e8f89bb6 Iustin Pop
    ) where
35 e8f89bb6 Iustin Pop
36 e8f89bb6 Iustin Pop
import Data.Maybe (isJust, fromJust)
37 e8f89bb6 Iustin Pop
import Monad
38 e8f89bb6 Iustin Pop
import System.Posix.Env
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
-- | Parse the environment and return the node\/instance names.
58 e8f89bb6 Iustin Pop
--
59 e8f89bb6 Iustin Pop
-- This also hardcodes here the default node\/instance file names.
60 e8f89bb6 Iustin Pop
parseEnv :: () -> IO (String, String)
61 e8f89bb6 Iustin Pop
parseEnv () = do
62 e8f89bb6 Iustin Pop
  a <- getEnvDefault "HTOOLS_NODES" "nodes"
63 e8f89bb6 Iustin Pop
  b <- getEnvDefault "HTOOLS_INSTANCES" "instances"
64 e8f89bb6 Iustin Pop
  return (a, b)
65 e8f89bb6 Iustin Pop
66 e8f89bb6 Iustin Pop
-- | Error beautifier
67 e8f89bb6 Iustin Pop
wrapIO :: IO (Result a) -> IO (Result a)
68 1cf97474 Iustin Pop
wrapIO = flip catch (return . Bad . show)
69 e8f89bb6 Iustin Pop
70 aa8d2e71 Iustin Pop
parseUtilisation :: String -> Result (String, DynUtil)
71 aa8d2e71 Iustin Pop
parseUtilisation line =
72 aa8d2e71 Iustin Pop
    let columns = sepSplit ' ' line
73 aa8d2e71 Iustin Pop
    in case columns of
74 aa8d2e71 Iustin Pop
         [name, cpu, mem, dsk, net] -> do
75 aa8d2e71 Iustin Pop
                      rcpu <- tryRead name cpu
76 aa8d2e71 Iustin Pop
                      rmem <- tryRead name mem
77 aa8d2e71 Iustin Pop
                      rdsk <- tryRead name dsk
78 aa8d2e71 Iustin Pop
                      rnet <- tryRead name net
79 aa8d2e71 Iustin Pop
                      let du = DynUtil { cpuWeight = rcpu, memWeight = rmem
80 aa8d2e71 Iustin Pop
                                       , dskWeight = rdsk, netWeight = rnet }
81 aa8d2e71 Iustin Pop
                      return (name, du)
82 aa8d2e71 Iustin Pop
         _ -> Bad $ "Cannot parse line " ++ line
83 aa8d2e71 Iustin Pop
84 e8f89bb6 Iustin Pop
-- | External tool data loader from a variety of sources.
85 e8f89bb6 Iustin Pop
loadExternalData :: Options
86 94e05c32 Iustin Pop
                 -> IO (Node.List, Instance.List, [String], String)
87 e8f89bb6 Iustin Pop
loadExternalData opts = do
88 e8f89bb6 Iustin Pop
  (env_node, env_inst) <- parseEnv ()
89 e8f89bb6 Iustin Pop
  let nodef = if optNodeSet opts then optNodeFile opts
90 e8f89bb6 Iustin Pop
              else env_node
91 e8f89bb6 Iustin Pop
      instf = if optInstSet opts then optInstFile opts
92 e8f89bb6 Iustin Pop
              else env_inst
93 e8f89bb6 Iustin Pop
      mhost = optMaster opts
94 e8f89bb6 Iustin Pop
      lsock = optLuxi opts
95 e8f89bb6 Iustin Pop
      simdata = optNodeSim opts
96 e8f89bb6 Iustin Pop
      setRapi = mhost /= ""
97 e8f89bb6 Iustin Pop
      setLuxi = isJust lsock
98 e8f89bb6 Iustin Pop
      setSim = isJust simdata
99 e8f89bb6 Iustin Pop
      setFiles = optNodeSet opts || optInstSet opts
100 e8f89bb6 Iustin Pop
      allSet = filter id [setRapi, setLuxi, setFiles]
101 0f15cc76 Iustin Pop
      exTags = case optExTags opts of
102 0f15cc76 Iustin Pop
                 Nothing -> []
103 0f15cc76 Iustin Pop
                 Just etl -> map (++ ":") etl
104 0f15cc76 Iustin Pop
105 e8f89bb6 Iustin Pop
  when (length allSet > 1) $
106 e8f89bb6 Iustin Pop
       do
107 45ab6a8d Iustin Pop
         hPutStrLn stderr ("Error: Only one of the rapi, luxi, and data" ++
108 45ab6a8d Iustin Pop
                           " files options should be given.")
109 e8f89bb6 Iustin Pop
         exitWith $ ExitFailure 1
110 e8f89bb6 Iustin Pop
111 aa8d2e71 Iustin Pop
  util_contents <- (case optDynuFile opts of
112 aa8d2e71 Iustin Pop
                      Just path -> readFile path
113 aa8d2e71 Iustin Pop
                      Nothing -> return "")
114 aa8d2e71 Iustin Pop
  let util_data = mapM parseUtilisation $ lines util_contents
115 aa8d2e71 Iustin Pop
  util_data' <- (case util_data of
116 aa8d2e71 Iustin Pop
                   Ok x -> return x
117 aa8d2e71 Iustin Pop
                   Bad y -> do
118 aa8d2e71 Iustin Pop
                     hPutStrLn stderr ("Error: can't parse utilisation" ++
119 aa8d2e71 Iustin Pop
                                       " data: " ++ show y)
120 aa8d2e71 Iustin Pop
                     exitWith $ ExitFailure 1)
121 e8f89bb6 Iustin Pop
  input_data <-
122 e8f89bb6 Iustin Pop
      case () of
123 45ab6a8d Iustin Pop
        _ | setRapi ->
124 45ab6a8d Iustin Pop
#ifdef NO_CURL
125 45ab6a8d Iustin Pop
              return $ Bad "RAPI/curl backend disabled at compile time"
126 45ab6a8d Iustin Pop
#else
127 45ab6a8d Iustin Pop
              wrapIO $ Rapi.loadData mhost
128 45ab6a8d Iustin Pop
#endif
129 e8f89bb6 Iustin Pop
          | setLuxi -> wrapIO $ Luxi.loadData $ fromJust lsock
130 e8f89bb6 Iustin Pop
          | setSim -> Simu.loadData $ fromJust simdata
131 e8f89bb6 Iustin Pop
          | otherwise -> wrapIO $ Text.loadData nodef instf
132 e8f89bb6 Iustin Pop
133 0f15cc76 Iustin Pop
  let ldresult = input_data >>= Loader.mergeData util_data' exTags
134 94e05c32 Iustin Pop
  (loaded_nl, il, tags, csf) <-
135 e8f89bb6 Iustin Pop
      (case ldresult of
136 e8f89bb6 Iustin Pop
         Ok x -> return x
137 e8f89bb6 Iustin Pop
         Bad s -> do
138 e8f89bb6 Iustin Pop
           hPrintf stderr "Error: failed to load data. Details:\n%s\n" s
139 e8f89bb6 Iustin Pop
           exitWith $ ExitFailure 1
140 e8f89bb6 Iustin Pop
      )
141 e8f89bb6 Iustin Pop
  let (fix_msgs, fixed_nl) = Loader.checkData loaded_nl il
142 e8f89bb6 Iustin Pop
143 e8f89bb6 Iustin Pop
  unless (null fix_msgs || optVerbose opts == 0) $ do
144 e8f89bb6 Iustin Pop
         hPutStrLn stderr "Warning: cluster has inconsistent data:"
145 e8f89bb6 Iustin Pop
         hPutStrLn stderr . unlines . map (printf "  - %s") $ fix_msgs
146 e8f89bb6 Iustin Pop
147 94e05c32 Iustin Pop
  return (fixed_nl, il, tags, csf)