Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / ExtLoader.hs @ 2e5eb96a

History | View | Annotate | Download (5 kB)

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