Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Ssconf.hs @ 96e3dfa7

History | View | Annotate | Download (5.1 kB)

1 aa3adf35 Iustin Pop
{-# LANGUAGE TemplateHaskell #-}
2 aa3adf35 Iustin Pop
3 aa3adf35 Iustin Pop
{-| Implementation of the Ganeti Ssconf interface.
4 aa3adf35 Iustin Pop
5 aa3adf35 Iustin Pop
-}
6 aa3adf35 Iustin Pop
7 aa3adf35 Iustin Pop
{-
8 aa3adf35 Iustin Pop
9 aa3adf35 Iustin Pop
Copyright (C) 2012 Google Inc.
10 aa3adf35 Iustin Pop
11 aa3adf35 Iustin Pop
This program is free software; you can redistribute it and/or modify
12 aa3adf35 Iustin Pop
it under the terms of the GNU General Public License as published by
13 aa3adf35 Iustin Pop
the Free Software Foundation; either version 2 of the License, or
14 aa3adf35 Iustin Pop
(at your option) any later version.
15 aa3adf35 Iustin Pop
16 aa3adf35 Iustin Pop
This program is distributed in the hope that it will be useful, but
17 aa3adf35 Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
18 aa3adf35 Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19 aa3adf35 Iustin Pop
General Public License for more details.
20 aa3adf35 Iustin Pop
21 aa3adf35 Iustin Pop
You should have received a copy of the GNU General Public License
22 aa3adf35 Iustin Pop
along with this program; if not, write to the Free Software
23 aa3adf35 Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
24 aa3adf35 Iustin Pop
02110-1301, USA.
25 aa3adf35 Iustin Pop
26 aa3adf35 Iustin Pop
-}
27 aa3adf35 Iustin Pop
28 aa3adf35 Iustin Pop
module Ganeti.Ssconf
29 aa3adf35 Iustin Pop
  ( SSKey(..)
30 aa3adf35 Iustin Pop
  , sSKeyToRaw
31 aa3adf35 Iustin Pop
  , sSKeyFromRaw
32 aa3adf35 Iustin Pop
  , getPrimaryIPFamily
33 d8e9131b Michele Tartara
  , getMasterCandidatesIps
34 670e954a Thomas Thrainer
  , getMasterNode
35 c5b4a186 Iustin Pop
  , keyToFilename
36 c5b4a186 Iustin Pop
  , sSFilePrefix
37 aa3adf35 Iustin Pop
  ) where
38 aa3adf35 Iustin Pop
39 79ac58fa Iustin Pop
import Control.Exception
40 aa3adf35 Iustin Pop
import Control.Monad (liftM)
41 aa3adf35 Iustin Pop
import Data.Maybe (fromMaybe)
42 aa3adf35 Iustin Pop
import qualified Network.Socket as Socket
43 aa3adf35 Iustin Pop
import System.FilePath ((</>))
44 79ac58fa Iustin Pop
import System.IO.Error (isDoesNotExistError)
45 aa3adf35 Iustin Pop
46 ccdcdc5f Jose A. Lopes
import qualified AutoConf
47 ccdcdc5f Jose A. Lopes
import Ganeti.BasicTypes
48 aa3adf35 Iustin Pop
import qualified Ganeti.Constants as C
49 9eeb0aa5 Michael Hanselmann
import qualified Ganeti.Path as Path
50 ccdcdc5f Jose A. Lopes
import Ganeti.THH
51 26d62e4c Iustin Pop
import Ganeti.Utils
52 aa3adf35 Iustin Pop
53 aa3adf35 Iustin Pop
-- | Maximum ssconf file size we support.
54 aa3adf35 Iustin Pop
maxFileSize :: Int
55 aa3adf35 Iustin Pop
maxFileSize = 131072
56 aa3adf35 Iustin Pop
57 c5b4a186 Iustin Pop
-- | ssconf file prefix, re-exported from Constants.
58 c5b4a186 Iustin Pop
sSFilePrefix :: FilePath
59 c5b4a186 Iustin Pop
sSFilePrefix = C.ssconfFileprefix
60 c5b4a186 Iustin Pop
61 aa3adf35 Iustin Pop
$(declareSADT "SSKey"
62 aa3adf35 Iustin Pop
  [ ("SSClusterName",          'C.ssClusterName)
63 aa3adf35 Iustin Pop
  , ("SSClusterTags",          'C.ssClusterTags)
64 aa3adf35 Iustin Pop
  , ("SSFileStorageDir",       'C.ssFileStorageDir)
65 aa3adf35 Iustin Pop
  , ("SSSharedFileStorageDir", 'C.ssSharedFileStorageDir)
66 aa3adf35 Iustin Pop
  , ("SSMasterCandidates",     'C.ssMasterCandidates)
67 aa3adf35 Iustin Pop
  , ("SSMasterCandidatesIps",  'C.ssMasterCandidatesIps)
68 aa3adf35 Iustin Pop
  , ("SSMasterIp",             'C.ssMasterIp)
69 aa3adf35 Iustin Pop
  , ("SSMasterNetdev",         'C.ssMasterNetdev)
70 aa3adf35 Iustin Pop
  , ("SSMasterNetmask",        'C.ssMasterNetmask)
71 aa3adf35 Iustin Pop
  , ("SSMasterNode",           'C.ssMasterNode)
72 aa3adf35 Iustin Pop
  , ("SSNodeList",             'C.ssNodeList)
73 aa3adf35 Iustin Pop
  , ("SSNodePrimaryIps",       'C.ssNodePrimaryIps)
74 aa3adf35 Iustin Pop
  , ("SSNodeSecondaryIps",     'C.ssNodeSecondaryIps)
75 aa3adf35 Iustin Pop
  , ("SSOfflineNodes",         'C.ssOfflineNodes)
76 aa3adf35 Iustin Pop
  , ("SSOnlineNodes",          'C.ssOnlineNodes)
77 aa3adf35 Iustin Pop
  , ("SSPrimaryIpFamily",      'C.ssPrimaryIpFamily)
78 aa3adf35 Iustin Pop
  , ("SSInstanceList",         'C.ssInstanceList)
79 aa3adf35 Iustin Pop
  , ("SSReleaseVersion",       'C.ssReleaseVersion)
80 aa3adf35 Iustin Pop
  , ("SSHypervisorList",       'C.ssHypervisorList)
81 aa3adf35 Iustin Pop
  , ("SSMaintainNodeHealth",   'C.ssMaintainNodeHealth)
82 aa3adf35 Iustin Pop
  , ("SSUidPool",              'C.ssUidPool)
83 aa3adf35 Iustin Pop
  , ("SSNodegroups",           'C.ssNodegroups)
84 aa3adf35 Iustin Pop
  ])
85 aa3adf35 Iustin Pop
86 aa3adf35 Iustin Pop
-- | Convert a ssconf key into a (full) file path.
87 37904802 Iustin Pop
keyToFilename :: FilePath     -- ^ Config path root
88 37904802 Iustin Pop
              -> SSKey        -- ^ Ssconf key
89 37904802 Iustin Pop
              -> FilePath     -- ^ Full file name
90 67e4fcf4 Iustin Pop
keyToFilename cfgpath key =
91 37904802 Iustin Pop
  cfgpath </> sSFilePrefix ++ sSKeyToRaw key
92 aa3adf35 Iustin Pop
93 aa3adf35 Iustin Pop
-- | Runs an IO action while transforming any error into 'Bad'
94 aa3adf35 Iustin Pop
-- values. It also accepts an optional value to use in case the error
95 aa3adf35 Iustin Pop
-- is just does not exist.
96 aa3adf35 Iustin Pop
catchIOErrors :: Maybe a         -- ^ Optional default
97 aa3adf35 Iustin Pop
              -> IO a            -- ^ Action to run
98 aa3adf35 Iustin Pop
              -> IO (Result a)
99 aa3adf35 Iustin Pop
catchIOErrors def action =
100 1251817b Iustin Pop
  Control.Exception.catch
101 1251817b Iustin Pop
        (do
102 aa3adf35 Iustin Pop
          result <- action
103 aa3adf35 Iustin Pop
          return (Ok result)
104 aa3adf35 Iustin Pop
        ) (\err -> let bad_result = Bad (show err)
105 aa3adf35 Iustin Pop
                   in return $ if isDoesNotExistError err
106 aa3adf35 Iustin Pop
                                 then maybe bad_result Ok def
107 aa3adf35 Iustin Pop
                                 else bad_result)
108 aa3adf35 Iustin Pop
109 aa3adf35 Iustin Pop
-- | Read an ssconf file.
110 aa3adf35 Iustin Pop
readSSConfFile :: Maybe FilePath            -- ^ Optional config path override
111 aa3adf35 Iustin Pop
               -> Maybe String              -- ^ Optional default value
112 aa3adf35 Iustin Pop
               -> SSKey                     -- ^ Desired ssconf key
113 aa3adf35 Iustin Pop
               -> IO (Result String)
114 aa3adf35 Iustin Pop
readSSConfFile optpath def key = do
115 29a30533 Iustin Pop
  dpath <- Path.dataDir
116 37904802 Iustin Pop
  result <- catchIOErrors def . readFile .
117 29a30533 Iustin Pop
            keyToFilename (fromMaybe dpath optpath) $ key
118 aa3adf35 Iustin Pop
  return (liftM (take maxFileSize) result)
119 aa3adf35 Iustin Pop
120 aa3adf35 Iustin Pop
-- | Parses a string containing an IP family
121 aa3adf35 Iustin Pop
parseIPFamily :: Int -> Result Socket.Family
122 ccdcdc5f Jose A. Lopes
parseIPFamily fam | fam == AutoConf.pyAfInet4 = Ok Socket.AF_INET
123 ccdcdc5f Jose A. Lopes
                  | fam == AutoConf.pyAfInet6 = Ok Socket.AF_INET6
124 aa3adf35 Iustin Pop
                  | otherwise = Bad $ "Unknown af_family value: " ++ show fam
125 aa3adf35 Iustin Pop
126 aa3adf35 Iustin Pop
-- | Read the primary IP family.
127 aa3adf35 Iustin Pop
getPrimaryIPFamily :: Maybe FilePath -> IO (Result Socket.Family)
128 aa3adf35 Iustin Pop
getPrimaryIPFamily optpath = do
129 ccdcdc5f Jose A. Lopes
  result <- readSSConfFile optpath
130 ccdcdc5f Jose A. Lopes
                           (Just (show AutoConf.pyAfInet4))
131 ccdcdc5f Jose A. Lopes
                           SSPrimaryIpFamily
132 256e28c4 Iustin Pop
  return (liftM rStripSpace result >>=
133 aa3adf35 Iustin Pop
          tryRead "Parsing af_family" >>= parseIPFamily)
134 d8e9131b Michele Tartara
135 d8e9131b Michele Tartara
-- | Read the list of IP addresses of the master candidates of the cluster.
136 d8e9131b Michele Tartara
getMasterCandidatesIps :: Maybe FilePath -> IO (Result [String])
137 d8e9131b Michele Tartara
getMasterCandidatesIps optPath = do
138 d8e9131b Michele Tartara
  result <- readSSConfFile optPath Nothing SSMasterCandidatesIps
139 d8e9131b Michele Tartara
  return $ liftM lines result
140 670e954a Thomas Thrainer
141 670e954a Thomas Thrainer
-- | Read the name of the master node.
142 670e954a Thomas Thrainer
getMasterNode :: Maybe FilePath -> IO (Result String)
143 670e954a Thomas Thrainer
getMasterNode optPath = do
144 670e954a Thomas Thrainer
  result <- readSSConfFile optPath Nothing SSMasterNode
145 670e954a Thomas Thrainer
  return (liftM rStripSpace result)