Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / ExtLoader.hs @ aa8d2e71

History | View | Annotate | Download (4.8 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.Posix.Env
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
-- | Parse the environment and return the node\/instance names.
58
--
59
-- This also hardcodes here the default node\/instance file names.
60
parseEnv :: () -> IO (String, String)
61
parseEnv () = do
62
  a <- getEnvDefault "HTOOLS_NODES" "nodes"
63
  b <- getEnvDefault "HTOOLS_INSTANCES" "instances"
64
  return (a, b)
65

    
66
-- | Error beautifier
67
wrapIO :: IO (Result a) -> IO (Result a)
68
wrapIO = flip catch (return . Bad . show)
69

    
70
parseUtilisation :: String -> Result (String, DynUtil)
71
parseUtilisation line =
72
    let columns = sepSplit ' ' line
73
    in case columns of
74
         [name, cpu, mem, dsk, net] -> do
75
                      rcpu <- tryRead name cpu
76
                      rmem <- tryRead name mem
77
                      rdsk <- tryRead name dsk
78
                      rnet <- tryRead name net
79
                      let du = DynUtil { cpuWeight = rcpu, memWeight = rmem
80
                                       , dskWeight = rdsk, netWeight = rnet }
81
                      return (name, du)
82
         _ -> Bad $ "Cannot parse line " ++ line
83

    
84
-- | External tool data loader from a variety of sources.
85
loadExternalData :: Options
86
                 -> IO (Node.List, Instance.List, String)
87
loadExternalData opts = do
88
  (env_node, env_inst) <- parseEnv ()
89
  let nodef = if optNodeSet opts then optNodeFile opts
90
              else env_node
91
      instf = if optInstSet opts then optInstFile opts
92
              else env_inst
93
      mhost = optMaster opts
94
      lsock = optLuxi opts
95
      simdata = optNodeSim opts
96
      setRapi = mhost /= ""
97
      setLuxi = isJust lsock
98
      setSim = isJust simdata
99
      setFiles = optNodeSet opts || optInstSet opts
100
      allSet = filter id [setRapi, setLuxi, setFiles]
101
  when (length allSet > 1) $
102
       do
103
         hPutStrLn stderr ("Error: Only one of the rapi, luxi, and data" ++
104
                           " files options should be given.")
105
         exitWith $ ExitFailure 1
106

    
107
  util_contents <- (case optDynuFile opts of
108
                      Just path -> readFile path
109
                      Nothing -> return "")
110
  let util_data = mapM parseUtilisation $ lines util_contents
111
  util_data' <- (case util_data of
112
                   Ok x -> return x
113
                   Bad y -> do
114
                     hPutStrLn stderr ("Error: can't parse utilisation" ++
115
                                       " data: " ++ show y)
116
                     exitWith $ ExitFailure 1)
117
  input_data <-
118
      case () of
119
        _ | setRapi ->
120
#ifdef NO_CURL
121
              return $ Bad "RAPI/curl backend disabled at compile time"
122
#else
123
              wrapIO $ Rapi.loadData mhost
124
#endif
125
          | setLuxi -> wrapIO $ Luxi.loadData $ fromJust lsock
126
          | setSim -> Simu.loadData $ fromJust simdata
127
          | otherwise -> wrapIO $ Text.loadData nodef instf
128

    
129
  let ldresult = input_data >>= Loader.mergeData util_data'
130
  (loaded_nl, il, csf) <-
131
      (case ldresult of
132
         Ok x -> return x
133
         Bad s -> do
134
           hPrintf stderr "Error: failed to load data. Details:\n%s\n" s
135
           exitWith $ ExitFailure 1
136
      )
137
  let (fix_msgs, fixed_nl) = Loader.checkData loaded_nl il
138

    
139
  unless (null fix_msgs || optVerbose opts == 0) $ do
140
         hPutStrLn stderr "Warning: cluster has inconsistent data:"
141
         hPutStrLn stderr . unlines . map (printf "  - %s") $ fix_msgs
142

    
143
  return (fixed_nl, il, csf)