Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / ExtLoader.hs @ 57587760

History | View | Annotate | Download (4.5 kB)

1
{-# LANGUAGE CPP #-}
2

    
3
{-| External data loader
4

    
5
This module holds the external data loading, and thus is the only one
6
depending (via the specialized Text\/Rapi\/Luxi modules) on the actual
7
libraries implementing the low-level protocols.
8

    
9
-}
10

    
11
{-
12

    
13
Copyright (C) 2009 Google Inc.
14

    
15
This program is free software; you can redistribute it and/or modify
16
it under the terms of the GNU General Public License as published by
17
the Free Software Foundation; either version 2 of the License, or
18
(at your option) any later version.
19

    
20
This program is distributed in the hope that it will be useful, but
21
WITHOUT ANY WARRANTY; without even the implied warranty of
22
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
23
General Public License for more details.
24

    
25
You should have received a copy of the GNU General Public License
26
along with this program; if not, write to the Free Software
27
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
28
02110-1301, USA.
29

    
30
-}
31

    
32
module Ganeti.HTools.ExtLoader
33
    ( loadExternalData
34
    ) where
35

    
36
import Data.Maybe (isJust, fromJust)
37
import Monad
38
import System.IO
39
import System
40
import Text.Printf (printf, hPrintf)
41

    
42
import qualified Ganeti.HTools.Luxi as Luxi
43
#ifndef NO_CURL
44
import qualified Ganeti.HTools.Rapi as Rapi
45
#endif
46
import qualified Ganeti.HTools.Simu as Simu
47
import qualified Ganeti.HTools.Text as Text
48
import qualified Ganeti.HTools.Loader as Loader
49
import qualified Ganeti.HTools.Instance as Instance
50
import qualified Ganeti.HTools.Node as Node
51

    
52
import Ganeti.HTools.Types
53
import Ganeti.HTools.CLI
54
import Ganeti.HTools.Utils (sepSplit, tryRead)
55

    
56
-- | Error beautifier
57
wrapIO :: IO (Result a) -> IO (Result a)
58
wrapIO = flip catch (return . Bad . show)
59

    
60
parseUtilisation :: String -> Result (String, DynUtil)
61
parseUtilisation line =
62
    let columns = sepSplit ' ' line
63
    in case columns of
64
         [name, cpu, mem, dsk, net] -> do
65
                      rcpu <- tryRead name cpu
66
                      rmem <- tryRead name mem
67
                      rdsk <- tryRead name dsk
68
                      rnet <- tryRead name net
69
                      let du = DynUtil { cpuWeight = rcpu, memWeight = rmem
70
                                       , dskWeight = rdsk, netWeight = rnet }
71
                      return (name, du)
72
         _ -> Bad $ "Cannot parse line " ++ line
73

    
74
-- | External tool data loader from a variety of sources.
75
loadExternalData :: Options
76
                 -> IO (Node.List, Instance.List, [String], String)
77
loadExternalData opts = do
78
  let mhost = optMaster opts
79
      lsock = optLuxi opts
80
      tfile = optDataFile opts
81
      simdata = optNodeSim opts
82
      setRapi = mhost /= ""
83
      setLuxi = isJust lsock
84
      setSim = isJust simdata
85
      setFile = isJust tfile
86
      allSet = filter id [setRapi, setLuxi, setFile]
87
      exTags = case optExTags opts of
88
                 Nothing -> []
89
                 Just etl -> map (++ ":") etl
90

    
91
  when (length allSet > 1) $
92
       do
93
         hPutStrLn stderr ("Error: Only one of the rapi, luxi, and data" ++
94
                           " files options should be given.")
95
         exitWith $ ExitFailure 1
96

    
97
  util_contents <- (case optDynuFile opts of
98
                      Just path -> readFile path
99
                      Nothing -> return "")
100
  let util_data = mapM parseUtilisation $ lines util_contents
101
  util_data' <- (case util_data of
102
                   Ok x -> return x
103
                   Bad y -> do
104
                     hPutStrLn stderr ("Error: can't parse utilisation" ++
105
                                       " data: " ++ show y)
106
                     exitWith $ ExitFailure 1)
107
  input_data <-
108
      case () of
109
        _ | setRapi ->
110
#ifdef NO_CURL
111
              return $ Bad "RAPI/curl backend disabled at compile time"
112
#else
113
              wrapIO $ Rapi.loadData mhost
114
#endif
115
          | setLuxi -> wrapIO $ Luxi.loadData $ fromJust lsock
116
          | setSim -> Simu.loadData $ fromJust simdata
117
          | setFile -> wrapIO $ Text.loadData $ fromJust tfile
118
          | otherwise -> return $ Bad "No backend selected! Exiting."
119

    
120
  let ldresult = input_data >>= Loader.mergeData util_data' exTags
121
  (loaded_nl, il, tags, csf) <-
122
      (case ldresult of
123
         Ok x -> return x
124
         Bad s -> do
125
           hPrintf stderr "Error: failed to load data. Details:\n%s\n" s
126
           exitWith $ ExitFailure 1
127
      )
128
  let (fix_msgs, fixed_nl) = Loader.checkData loaded_nl il
129

    
130
  unless (null fix_msgs || optVerbose opts == 0) $ do
131
         hPutStrLn stderr "Warning: cluster has inconsistent data:"
132
         hPutStrLn stderr . unlines . map (printf "  - %s") $ fix_msgs
133

    
134
  return (fixed_nl, il, tags, csf)