Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Ssconf.hs @ 36691f08

History | View | Annotate | Download (4.5 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 aa3adf35 Iustin Pop
  ) where
34 aa3adf35 Iustin Pop
35 aa3adf35 Iustin Pop
import Ganeti.THH
36 aa3adf35 Iustin Pop
37 79ac58fa Iustin Pop
import Control.Exception
38 aa3adf35 Iustin Pop
import Control.Monad (liftM)
39 aa3adf35 Iustin Pop
import Data.Char (isSpace)
40 aa3adf35 Iustin Pop
import Data.Maybe (fromMaybe)
41 79ac58fa Iustin Pop
import Prelude hiding (catch)
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 aa3adf35 Iustin Pop
import qualified Ganeti.Constants as C
47 aa3adf35 Iustin Pop
import Ganeti.BasicTypes
48 aa3adf35 Iustin Pop
import Ganeti.HTools.Utils
49 aa3adf35 Iustin Pop
50 aa3adf35 Iustin Pop
-- | Maximum ssconf file size we support.
51 aa3adf35 Iustin Pop
maxFileSize :: Int
52 aa3adf35 Iustin Pop
maxFileSize = 131072
53 aa3adf35 Iustin Pop
54 aa3adf35 Iustin Pop
$(declareSADT "SSKey"
55 aa3adf35 Iustin Pop
  [ ("SSClusterName",          'C.ssClusterName)
56 aa3adf35 Iustin Pop
  , ("SSClusterTags",          'C.ssClusterTags)
57 aa3adf35 Iustin Pop
  , ("SSFileStorageDir",       'C.ssFileStorageDir)
58 aa3adf35 Iustin Pop
  , ("SSSharedFileStorageDir", 'C.ssSharedFileStorageDir)
59 aa3adf35 Iustin Pop
  , ("SSMasterCandidates",     'C.ssMasterCandidates)
60 aa3adf35 Iustin Pop
  , ("SSMasterCandidatesIps",  'C.ssMasterCandidatesIps)
61 aa3adf35 Iustin Pop
  , ("SSMasterIp",             'C.ssMasterIp)
62 aa3adf35 Iustin Pop
  , ("SSMasterNetdev",         'C.ssMasterNetdev)
63 aa3adf35 Iustin Pop
  , ("SSMasterNetmask",        'C.ssMasterNetmask)
64 aa3adf35 Iustin Pop
  , ("SSMasterNode",           'C.ssMasterNode)
65 aa3adf35 Iustin Pop
  , ("SSNodeList",             'C.ssNodeList)
66 aa3adf35 Iustin Pop
  , ("SSNodePrimaryIps",       'C.ssNodePrimaryIps)
67 aa3adf35 Iustin Pop
  , ("SSNodeSecondaryIps",     'C.ssNodeSecondaryIps)
68 aa3adf35 Iustin Pop
  , ("SSOfflineNodes",         'C.ssOfflineNodes)
69 aa3adf35 Iustin Pop
  , ("SSOnlineNodes",          'C.ssOnlineNodes)
70 aa3adf35 Iustin Pop
  , ("SSPrimaryIpFamily",      'C.ssPrimaryIpFamily)
71 aa3adf35 Iustin Pop
  , ("SSInstanceList",         'C.ssInstanceList)
72 aa3adf35 Iustin Pop
  , ("SSReleaseVersion",       'C.ssReleaseVersion)
73 aa3adf35 Iustin Pop
  , ("SSHypervisorList",       'C.ssHypervisorList)
74 aa3adf35 Iustin Pop
  , ("SSMaintainNodeHealth",   'C.ssMaintainNodeHealth)
75 aa3adf35 Iustin Pop
  , ("SSUidPool",              'C.ssUidPool)
76 aa3adf35 Iustin Pop
  , ("SSNodegroups",           'C.ssNodegroups)
77 aa3adf35 Iustin Pop
  ])
78 aa3adf35 Iustin Pop
79 aa3adf35 Iustin Pop
-- | Convert a ssconf key into a (full) file path.
80 aa3adf35 Iustin Pop
keyToFilename :: Maybe FilePath     -- ^ Optional config path override
81 aa3adf35 Iustin Pop
              -> SSKey              -- ^ ssconf key
82 aa3adf35 Iustin Pop
              -> FilePath
83 aa3adf35 Iustin Pop
keyToFilename optpath key = fromMaybe C.dataDir optpath </> sSKeyToRaw key
84 aa3adf35 Iustin Pop
85 aa3adf35 Iustin Pop
-- | Runs an IO action while transforming any error into 'Bad'
86 aa3adf35 Iustin Pop
-- values. It also accepts an optional value to use in case the error
87 aa3adf35 Iustin Pop
-- is just does not exist.
88 aa3adf35 Iustin Pop
catchIOErrors :: Maybe a         -- ^ Optional default
89 aa3adf35 Iustin Pop
              -> IO a            -- ^ Action to run
90 aa3adf35 Iustin Pop
              -> IO (Result a)
91 aa3adf35 Iustin Pop
catchIOErrors def action =
92 aa3adf35 Iustin Pop
  catch (do
93 aa3adf35 Iustin Pop
          result <- action
94 aa3adf35 Iustin Pop
          return (Ok result)
95 aa3adf35 Iustin Pop
        ) (\err -> let bad_result = Bad (show err)
96 aa3adf35 Iustin Pop
                   in return $ if isDoesNotExistError err
97 aa3adf35 Iustin Pop
                                 then maybe bad_result Ok def
98 aa3adf35 Iustin Pop
                                 else bad_result)
99 aa3adf35 Iustin Pop
100 aa3adf35 Iustin Pop
-- | Read an ssconf file.
101 aa3adf35 Iustin Pop
readSSConfFile :: Maybe FilePath            -- ^ Optional config path override
102 aa3adf35 Iustin Pop
               -> Maybe String              -- ^ Optional default value
103 aa3adf35 Iustin Pop
               -> SSKey                     -- ^ Desired ssconf key
104 aa3adf35 Iustin Pop
               -> IO (Result String)
105 aa3adf35 Iustin Pop
readSSConfFile optpath def key = do
106 aa3adf35 Iustin Pop
  result <- catchIOErrors def . readFile . keyToFilename optpath $ key
107 aa3adf35 Iustin Pop
  return (liftM (take maxFileSize) result)
108 aa3adf35 Iustin Pop
109 aa3adf35 Iustin Pop
-- | Strip space characthers (including newline). As this is
110 aa3adf35 Iustin Pop
-- expensive, should only be run on small strings.
111 aa3adf35 Iustin Pop
rstripSpace :: String -> String
112 aa3adf35 Iustin Pop
rstripSpace = reverse . dropWhile isSpace . reverse
113 aa3adf35 Iustin Pop
114 aa3adf35 Iustin Pop
-- | Parses a string containing an IP family
115 aa3adf35 Iustin Pop
parseIPFamily :: Int -> Result Socket.Family
116 aa3adf35 Iustin Pop
parseIPFamily fam | fam == C.ip4Family = Ok Socket.AF_INET
117 aa3adf35 Iustin Pop
                  | fam == C.ip6Family = Ok Socket.AF_INET6
118 aa3adf35 Iustin Pop
                  | otherwise = Bad $ "Unknown af_family value: " ++ show fam
119 aa3adf35 Iustin Pop
120 aa3adf35 Iustin Pop
-- | Read the primary IP family.
121 aa3adf35 Iustin Pop
getPrimaryIPFamily :: Maybe FilePath -> IO (Result Socket.Family)
122 aa3adf35 Iustin Pop
getPrimaryIPFamily optpath = do
123 aa3adf35 Iustin Pop
  result <- readSSConfFile optpath (Just (show C.ip4Family)) SSPrimaryIpFamily
124 aa3adf35 Iustin Pop
  return (result >>= return . rstripSpace >>=
125 aa3adf35 Iustin Pop
          tryRead "Parsing af_family" >>= parseIPFamily)