Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / ExtLoader.hs @ 0ca66853

History | View | Annotate | Download (4.6 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
    , Loader.commonSuffix
35
    ) where
36

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

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

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

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

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

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

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

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

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

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

    
137
  return (fixed_nl, il, tags)