Turn on, and fix, more warnings
[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 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 Control.Exception
37 import Data.Maybe (isJust, fromJust)
38 import Monad
39 import System.Posix.Env
40 import System.IO
41 import System
42 import Text.Printf (printf, hPrintf)
43
44 import qualified Ganeti.HTools.Luxi as Luxi
45 #ifndef NO_CURL
46 import qualified Ganeti.HTools.Rapi as Rapi
47 #endif
48 import qualified Ganeti.HTools.Simu as Simu
49 import qualified Ganeti.HTools.Text as Text
50 import qualified Ganeti.HTools.Loader as Loader
51 import qualified Ganeti.HTools.Instance as Instance
52 import qualified Ganeti.HTools.Node as Node
53
54 import Ganeti.HTools.Types
55 import Ganeti.HTools.CLI
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 = handle (return . Bad . show)
69
70 -- | External tool data loader from a variety of sources.
71 loadExternalData :: Options
72                  -> IO (Node.List, Instance.List, String)
73 loadExternalData opts = do
74   (env_node, env_inst) <- parseEnv ()
75   let nodef = if optNodeSet opts then optNodeFile opts
76               else env_node
77       instf = if optInstSet opts then optInstFile opts
78               else env_inst
79       mhost = optMaster opts
80       lsock = optLuxi opts
81       simdata = optNodeSim opts
82       setRapi = mhost /= ""
83       setLuxi = isJust lsock
84       setSim = isJust simdata
85       setFiles = optNodeSet opts || optInstSet opts
86       allSet = filter id [setRapi, setLuxi, setFiles]
87   when (length allSet > 1) $
88        do
89          hPutStrLn stderr ("Error: Only one of the rapi, luxi, and data" ++
90                            " files options should be given.")
91          exitWith $ ExitFailure 1
92
93   input_data <-
94       case () of
95         _ | setRapi ->
96 #ifdef NO_CURL
97               return $ Bad "RAPI/curl backend disabled at compile time"
98 #else
99               wrapIO $ Rapi.loadData mhost
100 #endif
101           | setLuxi -> wrapIO $ Luxi.loadData $ fromJust lsock
102           | setSim -> Simu.loadData $ fromJust simdata
103           | otherwise -> wrapIO $ Text.loadData nodef instf
104
105   let ldresult = input_data >>= Loader.mergeData
106   (loaded_nl, il, csf) <-
107       (case ldresult of
108          Ok x -> return x
109          Bad s -> do
110            hPrintf stderr "Error: failed to load data. Details:\n%s\n" s
111            exitWith $ ExitFailure 1
112       )
113   let (fix_msgs, fixed_nl) = Loader.checkData loaded_nl il
114
115   unless (null fix_msgs || optVerbose opts == 0) $ do
116          hPutStrLn stderr "Warning: cluster has inconsistent data:"
117          hPutStrLn stderr . unlines . map (printf "  - %s") $ fix_msgs
118
119   return (fixed_nl, il, csf)