Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Ssconf.hs @ fae980e5

History | View | Annotate | Download (4.5 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

    
3
{-| Implementation of the Ganeti Ssconf interface.
4

    
5
-}
6

    
7
{-
8

    
9
Copyright (C) 2012 Google Inc.
10

    
11
This program is free software; you can redistribute it and/or modify
12
it under the terms of the GNU General Public License as published by
13
the Free Software Foundation; either version 2 of the License, or
14
(at your option) any later version.
15

    
16
This program is distributed in the hope that it will be useful, but
17
WITHOUT ANY WARRANTY; without even the implied warranty of
18
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19
General Public License for more details.
20

    
21
You should have received a copy of the GNU General Public License
22
along with this program; if not, write to the Free Software
23
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
24
02110-1301, USA.
25

    
26
-}
27

    
28
module Ganeti.Ssconf
29
  ( SSKey(..)
30
  , sSKeyToRaw
31
  , sSKeyFromRaw
32
  , getPrimaryIPFamily
33
  ) where
34

    
35
import Ganeti.THH
36

    
37
import Control.Exception
38
import Control.Monad (liftM)
39
import Data.Char (isSpace)
40
import Data.Maybe (fromMaybe)
41
import Prelude hiding (catch)
42
import qualified Network.Socket as Socket
43
import System.FilePath ((</>))
44
import System.IO.Error (isDoesNotExistError)
45

    
46
import qualified Ganeti.Constants as C
47
import Ganeti.BasicTypes
48
import Ganeti.HTools.Utils
49

    
50
-- | Maximum ssconf file size we support.
51
maxFileSize :: Int
52
maxFileSize = 131072
53

    
54
$(declareSADT "SSKey"
55
  [ ("SSClusterName",          'C.ssClusterName)
56
  , ("SSClusterTags",          'C.ssClusterTags)
57
  , ("SSFileStorageDir",       'C.ssFileStorageDir)
58
  , ("SSSharedFileStorageDir", 'C.ssSharedFileStorageDir)
59
  , ("SSMasterCandidates",     'C.ssMasterCandidates)
60
  , ("SSMasterCandidatesIps",  'C.ssMasterCandidatesIps)
61
  , ("SSMasterIp",             'C.ssMasterIp)
62
  , ("SSMasterNetdev",         'C.ssMasterNetdev)
63
  , ("SSMasterNetmask",        'C.ssMasterNetmask)
64
  , ("SSMasterNode",           'C.ssMasterNode)
65
  , ("SSNodeList",             'C.ssNodeList)
66
  , ("SSNodePrimaryIps",       'C.ssNodePrimaryIps)
67
  , ("SSNodeSecondaryIps",     'C.ssNodeSecondaryIps)
68
  , ("SSOfflineNodes",         'C.ssOfflineNodes)
69
  , ("SSOnlineNodes",          'C.ssOnlineNodes)
70
  , ("SSPrimaryIpFamily",      'C.ssPrimaryIpFamily)
71
  , ("SSInstanceList",         'C.ssInstanceList)
72
  , ("SSReleaseVersion",       'C.ssReleaseVersion)
73
  , ("SSHypervisorList",       'C.ssHypervisorList)
74
  , ("SSMaintainNodeHealth",   'C.ssMaintainNodeHealth)
75
  , ("SSUidPool",              'C.ssUidPool)
76
  , ("SSNodegroups",           'C.ssNodegroups)
77
  ])
78

    
79
-- | Convert a ssconf key into a (full) file path.
80
keyToFilename :: Maybe FilePath     -- ^ Optional config path override
81
              -> SSKey              -- ^ ssconf key
82
              -> FilePath
83
keyToFilename optpath key = fromMaybe C.dataDir optpath </> sSKeyToRaw key
84

    
85
-- | Runs an IO action while transforming any error into 'Bad'
86
-- values. It also accepts an optional value to use in case the error
87
-- is just does not exist.
88
catchIOErrors :: Maybe a         -- ^ Optional default
89
              -> IO a            -- ^ Action to run
90
              -> IO (Result a)
91
catchIOErrors def action =
92
  catch (do
93
          result <- action
94
          return (Ok result)
95
        ) (\err -> let bad_result = Bad (show err)
96
                   in return $ if isDoesNotExistError err
97
                                 then maybe bad_result Ok def
98
                                 else bad_result)
99

    
100
-- | Read an ssconf file.
101
readSSConfFile :: Maybe FilePath            -- ^ Optional config path override
102
               -> Maybe String              -- ^ Optional default value
103
               -> SSKey                     -- ^ Desired ssconf key
104
               -> IO (Result String)
105
readSSConfFile optpath def key = do
106
  result <- catchIOErrors def . readFile . keyToFilename optpath $ key
107
  return (liftM (take maxFileSize) result)
108

    
109
-- | Strip space characthers (including newline). As this is
110
-- expensive, should only be run on small strings.
111
rstripSpace :: String -> String
112
rstripSpace = reverse . dropWhile isSpace . reverse
113

    
114
-- | Parses a string containing an IP family
115
parseIPFamily :: Int -> Result Socket.Family
116
parseIPFamily fam | fam == C.ip4Family = Ok Socket.AF_INET
117
                  | fam == C.ip6Family = Ok Socket.AF_INET6
118
                  | otherwise = Bad $ "Unknown af_family value: " ++ show fam
119

    
120
-- | Read the primary IP family.
121
getPrimaryIPFamily :: Maybe FilePath -> IO (Result Socket.Family)
122
getPrimaryIPFamily optpath = do
123
  result <- readSSConfFile optpath (Just (show C.ip4Family)) SSPrimaryIpFamily
124
  return (result >>= return . rstripSpace >>=
125
          tryRead "Parsing af_family" >>= parseIPFamily)