Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Ssconf.hs @ c92b4671

History | View | Annotate | Download (5.2 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
  , getMasterCandidatesIps
34
  , getMasterNode
35
  , keyToFilename
36
  , sSFilePrefix
37
  ) where
38

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

    
46
import qualified AutoConf
47
import Ganeti.BasicTypes
48
import qualified Ganeti.Constants as C
49
import qualified Ganeti.Path as Path
50
import Ganeti.THH
51
import Ganeti.Utils
52

    
53
-- | Maximum ssconf file size we support.
54
maxFileSize :: Int
55
maxFileSize = 131072
56

    
57
-- | ssconf file prefix, re-exported from Constants.
58
sSFilePrefix :: FilePath
59
sSFilePrefix = C.ssconfFileprefix
60

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

    
87
-- | Convert a ssconf key into a (full) file path.
88
keyToFilename :: FilePath     -- ^ Config path root
89
              -> SSKey        -- ^ Ssconf key
90
              -> FilePath     -- ^ Full file name
91
keyToFilename cfgpath key =
92
  cfgpath </> sSFilePrefix ++ sSKeyToRaw key
93

    
94
-- | Runs an IO action while transforming any error into 'Bad'
95
-- values. It also accepts an optional value to use in case the error
96
-- is just does not exist.
97
catchIOErrors :: Maybe a         -- ^ Optional default
98
              -> IO a            -- ^ Action to run
99
              -> IO (Result a)
100
catchIOErrors def action =
101
  Control.Exception.catch
102
        (do
103
          result <- action
104
          return (Ok result)
105
        ) (\err -> let bad_result = Bad (show err)
106
                   in return $ if isDoesNotExistError err
107
                                 then maybe bad_result Ok def
108
                                 else bad_result)
109

    
110
-- | Read an ssconf file.
111
readSSConfFile :: Maybe FilePath            -- ^ Optional config path override
112
               -> Maybe String              -- ^ Optional default value
113
               -> SSKey                     -- ^ Desired ssconf key
114
               -> IO (Result String)
115
readSSConfFile optpath def key = do
116
  dpath <- Path.dataDir
117
  result <- catchIOErrors def . readFile .
118
            keyToFilename (fromMaybe dpath optpath) $ key
119
  return (liftM (take maxFileSize) result)
120

    
121
-- | Parses a string containing an IP family
122
parseIPFamily :: Int -> Result Socket.Family
123
parseIPFamily fam | fam == AutoConf.pyAfInet4 = Ok Socket.AF_INET
124
                  | fam == AutoConf.pyAfInet6 = Ok Socket.AF_INET6
125
                  | otherwise = Bad $ "Unknown af_family value: " ++ show fam
126

    
127
-- | Read the primary IP family.
128
getPrimaryIPFamily :: Maybe FilePath -> IO (Result Socket.Family)
129
getPrimaryIPFamily optpath = do
130
  result <- readSSConfFile optpath
131
                           (Just (show AutoConf.pyAfInet4))
132
                           SSPrimaryIpFamily
133
  return (liftM rStripSpace result >>=
134
          tryRead "Parsing af_family" >>= parseIPFamily)
135

    
136
-- | Read the list of IP addresses of the master candidates of the cluster.
137
getMasterCandidatesIps :: Maybe FilePath -> IO (Result [String])
138
getMasterCandidatesIps optPath = do
139
  result <- readSSConfFile optPath Nothing SSMasterCandidatesIps
140
  return $ liftM lines result
141

    
142
-- | Read the name of the master node.
143
getMasterNode :: Maybe FilePath -> IO (Result String)
144
getMasterNode optPath = do
145
  result <- readSSConfFile optPath Nothing SSMasterNode
146
  return (liftM rStripSpace result)