Add 'Read' instances for most objects
[ganeti-local] / Ganeti / HTools / ExtLoader.hs
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, 2010 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     , commonSuffix
35     , maybeSaveData
36     ) where
37
38 import Data.Maybe (isJust, fromJust)
39 import Monad
40 import System.FilePath
41 import System.IO
42 import System
43 import Text.Printf (printf, hPrintf)
44
45 import qualified Ganeti.HTools.Luxi as Luxi
46 #ifndef NO_CURL
47 import qualified Ganeti.HTools.Rapi as Rapi
48 #endif
49 import qualified Ganeti.HTools.Simu as Simu
50 import qualified Ganeti.HTools.Text as Text
51 import Ganeti.HTools.Loader (mergeData, checkData, ClusterData(..)
52                             , commonSuffix)
53
54 import Ganeti.HTools.Types
55 import Ganeti.HTools.CLI
56 import Ganeti.HTools.Utils (sepSplit, tryRead)
57
58 -- | Error beautifier
59 wrapIO :: IO (Result a) -> IO (Result a)
60 wrapIO = flip catch (return . Bad . show)
61
62 parseUtilisation :: String -> Result (String, DynUtil)
63 parseUtilisation line =
64     let columns = sepSplit ' ' line
65     in case columns of
66          [name, cpu, mem, dsk, net] -> do
67                       rcpu <- tryRead name cpu
68                       rmem <- tryRead name mem
69                       rdsk <- tryRead name dsk
70                       rnet <- tryRead name net
71                       let du = DynUtil { cpuWeight = rcpu, memWeight = rmem
72                                        , dskWeight = rdsk, netWeight = rnet }
73                       return (name, du)
74          _ -> Bad $ "Cannot parse line " ++ line
75
76 -- | External tool data loader from a variety of sources.
77 loadExternalData :: Options
78                  -> IO ClusterData
79 loadExternalData opts = do
80   let mhost = optMaster opts
81       lsock = optLuxi opts
82       tfile = optDataFile opts
83       simdata = optNodeSim opts
84       setRapi = mhost /= ""
85       setLuxi = isJust lsock
86       setSim = (not . null) simdata
87       setFile = isJust tfile
88       allSet = filter id [setRapi, setLuxi, setFile]
89       exTags = case optExTags opts of
90                  Nothing -> []
91                  Just etl -> map (++ ":") etl
92       exInsts = optExInst opts
93
94   when (length allSet > 1) $
95        do
96          hPutStrLn stderr ("Error: Only one of the rapi, luxi, and data" ++
97                            " files options should be given.")
98          exitWith $ ExitFailure 1
99
100   util_contents <- (case optDynuFile opts of
101                       Just path -> readFile path
102                       Nothing -> return "")
103   let util_data = mapM parseUtilisation $ lines util_contents
104   util_data' <- (case util_data of
105                    Ok x -> return x
106                    Bad y -> do
107                      hPutStrLn stderr ("Error: can't parse utilisation" ++
108                                        " data: " ++ show y)
109                      exitWith $ ExitFailure 1)
110   input_data <-
111       case () of
112         _ | setRapi ->
113 #ifdef NO_CURL
114               return $ Bad "RAPI/curl backend disabled at compile time"
115 #else
116               wrapIO $ Rapi.loadData mhost
117 #endif
118           | setLuxi -> wrapIO $ Luxi.loadData $ fromJust lsock
119           | setSim -> Simu.loadData simdata
120           | setFile -> wrapIO $ Text.loadData $ fromJust tfile
121           | otherwise -> return $ Bad "No backend selected! Exiting."
122
123   let ldresult = input_data >>= mergeData util_data' exTags exInsts
124   cdata <-
125       (case ldresult of
126          Ok x -> return x
127          Bad s -> do
128            hPrintf stderr "Error: failed to load data. Details:\n%s\n" s
129                :: IO ()
130            exitWith $ ExitFailure 1
131       )
132   let (fix_msgs, nl) = checkData (cdNodes cdata) (cdInstances cdata)
133
134   unless (null fix_msgs || optVerbose opts == 0) $ do
135          hPutStrLn stderr "Warning: cluster has inconsistent data:"
136          hPutStrLn stderr . unlines . map (printf "  - %s") $ fix_msgs
137
138   return cdata {cdNodes = nl}
139
140 -- | Function to save the cluster data to a file.
141 maybeSaveData :: Maybe FilePath -- ^ The file prefix to save to
142               -> String         -- ^ The suffix (extension) to add
143               -> String         -- ^ Informational message
144               -> ClusterData    -- ^ The cluster data
145               -> IO ()
146 maybeSaveData Nothing _ _ _ = return ()
147 maybeSaveData (Just path) ext msg cdata = do
148   let adata = Text.serializeCluster cdata
149       out_path = path <.> ext
150   writeFile out_path adata
151   hPrintf stderr "The cluster state %s has been written to file '%s'\n"
152           msg out_path