Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Ssconf.hs @ 256e28c4

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
  , keyToFilename
34
  , sSFilePrefix
35
  ) where
36

    
37
import Ganeti.THH
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 Ganeti.Constants as C
47
import qualified Ganeti.Path as Path
48
import Ganeti.BasicTypes
49
import Ganeti.Utils
50

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

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

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

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

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

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

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

    
124
-- | Read the primary IP family.
125
getPrimaryIPFamily :: Maybe FilePath -> IO (Result Socket.Family)
126
getPrimaryIPFamily optpath = do
127
  result <- readSSConfFile optpath (Just (show C.ip4Family)) SSPrimaryIpFamily
128
  return (liftM rStripSpace result >>=
129
          tryRead "Parsing af_family" >>= parseIPFamily)